| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Network.GRPC.Server.Handlers
Synopsis
- type UnaryHandler s m = Request -> MethodInput s m -> IO (MethodOutput s m)
 - type ServerStreamHandler s m a = Request -> MethodInput s m -> IO (a, ServerStream s m a)
 - newtype ServerStream s m a = ServerStream {
- serverStreamNext :: a -> IO (Maybe (a, MethodOutput s m))
 
 - type ClientStreamHandler s m a = Request -> IO (a, ClientStream s m a)
 - data ClientStream s m a = ClientStream {
- clientStreamHandler :: a -> MethodInput s m -> IO a
 - clientStreamFinalizer :: a -> IO (MethodOutput s m)
 
 - unary :: (Service s, HasMethod s m) => RPC s m -> UnaryHandler s m -> ServiceHandler
 - serverStream :: (Service s, HasMethod s m, MethodStreamingType s m ~ ServerStreaming) => RPC s m -> ServerStreamHandler s m a -> ServiceHandler
 - clientStream :: (Service s, HasMethod s m, MethodStreamingType s m ~ ClientStreaming) => RPC s m -> ClientStreamHandler s m a -> ServiceHandler
 - handleUnary :: (Service s, HasMethod s m) => RPC s m -> UnaryHandler s m -> WaiHandler
 - handleServerStream :: (Service s, HasMethod s m) => RPC s m -> ServerStreamHandler s m a -> WaiHandler
 - handleClientStream :: (Service s, HasMethod s m) => RPC s m -> ClientStreamHandler s m a -> WaiHandler
 - handleRequestChunksLoop :: Message a => Decoder (Either String a) -> (ByteString -> a -> IO ()) -> IO () -> IO ByteString -> IO ()
 - errorOnLeftOver :: (a -> IO b) -> ByteString -> a -> IO b
 
Documentation
type UnaryHandler s m = Request -> MethodInput s m -> IO (MethodOutput s m) Source #
Handy type to refer to Handler for unary RPCs handler.
type ServerStreamHandler s m a = Request -> MethodInput s m -> IO (a, ServerStream s m a) Source #
Handy type for 'server-streaming' RPCs.
We expect an implementation to:
 - read the input request
 - return an initial state and an state-passing action that the server code will call to fetch the output to send to the client (or close an a Nothing)
 See ServerStream for the type which embodies these requirements.
newtype ServerStream s m a Source #
Constructors
| ServerStream | |
Fields 
  | |
type ClientStreamHandler s m a = Request -> IO (a, ClientStream s m a) Source #
Handy type for 'client-streaming' RPCs.
We expect an implementation to:
 - acknowledge a the new client stream by returning an initial state and two functions:
 - a state-passing handler for new client message
 - a state-aware handler for answering the client when it is ending its stream
 See ClientStream for the type which embodies these requirements.
data ClientStream s m a Source #
Constructors
| ClientStream | |
Fields 
  | |
unary :: (Service s, HasMethod s m) => RPC s m -> UnaryHandler s m -> ServiceHandler Source #
Construct a handler for handling a unary RPC.
serverStream :: (Service s, HasMethod s m, MethodStreamingType s m ~ ServerStreaming) => RPC s m -> ServerStreamHandler s m a -> ServiceHandler Source #
Construct a handler for handling a server-streaming RPC.
clientStream :: (Service s, HasMethod s m, MethodStreamingType s m ~ ClientStreaming) => RPC s m -> ClientStreamHandler s m a -> ServiceHandler Source #
Construct a handler for handling a client-streaming RPC.
handleUnary :: (Service s, HasMethod s m) => RPC s m -> UnaryHandler s m -> WaiHandler Source #
Handle unary RPCs.
handleServerStream :: (Service s, HasMethod s m) => RPC s m -> ServerStreamHandler s m a -> WaiHandler Source #
Handle Server-Streaming RPCs.
handleClientStream :: (Service s, HasMethod s m) => RPC s m -> ClientStreamHandler s m a -> WaiHandler Source #
Handle Client-Streaming RPCs.
handleRequestChunksLoop Source #
Arguments
| :: Message a | |
| => Decoder (Either String a) | Message decoder.  | 
| -> (ByteString -> a -> IO ()) | Handler for a single message. The ByteString corresponds to leftover data.  | 
| -> IO () | Handler for handling end-of-streams.  | 
| -> IO ByteString | Action to retrieve the next chunk.  | 
| -> IO () | 
Helpers to consume input in chunks.
errorOnLeftOver :: (a -> IO b) -> ByteString -> a -> IO b Source #
Combinator around message handler to error on left overs.
This combinator ensures that, unless for client stream, an unparsed piece of data with a correctly-read message is treated as an error.