| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Network.GRPC.Server.Handlers.Trans
Synopsis
- type UnaryHandler m i o = Request -> i -> m o
- type ServerStreamHandler m i o a = Request -> i -> m (a, ServerStream m o a)
- newtype ServerStream m o a = ServerStream {
- serverStreamNext :: a -> m (Maybe (a, o))
- type ClientStreamHandler m i o a = Request -> m (a, ClientStream m i o a)
- data ClientStream m i o a = ClientStream {
- clientStreamHandler :: a -> i -> m a
- clientStreamFinalizer :: a -> m o
- type BiDiStreamHandler m i o a = Request -> m (a, BiDiStream m i o a)
- data BiDiStep m i o a
- = Abort
- | WaitInput !(a -> i -> m a) !(a -> m a)
- | WriteOutput !a o
- newtype BiDiStream m i o a = BiDiStream {
- bidirNextStep :: a -> m (BiDiStep m i o a)
- unary :: (MonadIO m, GRPCInput r i, GRPCOutput r o) => (forall x. m x -> IO x) -> r -> UnaryHandler m i o -> ServiceHandler
- serverStream :: (MonadIO m, GRPCInput r i, GRPCOutput r o) => (forall x. m x -> IO x) -> r -> ServerStreamHandler m i o a -> ServiceHandler
- clientStream :: (MonadIO m, GRPCInput r i, GRPCOutput r o) => (forall x. m x -> IO x) -> r -> ClientStreamHandler m i o a -> ServiceHandler
- bidiStream :: (MonadIO m, GRPCInput r i, GRPCOutput r o) => (forall x. m x -> IO x) -> r -> BiDiStreamHandler m i o a -> ServiceHandler
- generalStream :: (MonadIO m, GRPCInput r i, GRPCOutput r o) => (forall x. m x -> IO x) -> r -> GeneralStreamHandler m i o a b -> ServiceHandler
- handleUnary :: (MonadIO m, GRPCInput r i, GRPCOutput r o) => (forall x. m x -> IO x) -> r -> UnaryHandler m i o -> WaiHandler
- handleServerStream :: (MonadIO m, GRPCInput r i, GRPCOutput r o) => (forall x. m x -> IO x) -> r -> ServerStreamHandler m i o a -> WaiHandler
- handleClientStream :: forall m r i o a. (MonadIO m, GRPCInput r i, GRPCOutput r o) => (forall x. m x -> IO x) -> r -> ClientStreamHandler m i o a -> WaiHandler
- handleBiDiStream :: forall m r i o a. (MonadIO m, GRPCInput r i, GRPCOutput r o) => (forall x. m x -> IO x) -> r -> BiDiStreamHandler m i o a -> WaiHandler
- type GeneralStreamHandler m i o a b = Request -> m (a, IncomingStream m i a, b, OutgoingStream m o b)
- data IncomingStream m i a = IncomingStream {
- incomingStreamHandler :: a -> i -> m a
- incomingStreamFinalizer :: a -> m ()
- newtype OutgoingStream m o a = OutgoingStream {
- outgoingStreamNext :: a -> m (Maybe (a, o))
- handleGeneralStream :: forall m r i o a b. (MonadIO m, GRPCInput r i, GRPCOutput r o) => (forall x. m x -> IO x) -> r -> GeneralStreamHandler m i o a b -> WaiHandler
- handleRequestChunksLoop :: MonadIO m => Decoder (Either String a) -> (ByteString -> a -> m b) -> m b -> IO ByteString -> m b
- errorOnLeftOver :: MonadIO m => (a -> m b) -> ByteString -> a -> m b
Documentation
type UnaryHandler m i o = Request -> i -> m o Source #
Handy type to refer to Handler for unary RPCs handler.
type ServerStreamHandler m i o a = Request -> i -> m (a, ServerStream m o 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 m o a Source #
Constructors
| ServerStream | |
Fields
| |
type ClientStreamHandler m i o a = Request -> m (a, ClientStream m i o 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 m i o a Source #
Constructors
| ClientStream | |
Fields
| |
type BiDiStreamHandler m i o a = Request -> m (a, BiDiStream m i o a) Source #
Handy type for 'bidirectional-streaming' RPCs.
We expect an implementation to: - acknowlege a new bidirection stream by returning an initial state and one functions: - a state-passing function that returns a single action step The action may be to - stop immediately - wait and handle some input with a callback and a finalizer (if the client closes the stream on its side) that may change the state - return a value and a new state
There is no way to stop locally (that would mean sending HTTP2 trailers) and keep receiving messages from the client.
data BiDiStep m i o a Source #
Constructors
| Abort | |
| WaitInput !(a -> i -> m a) !(a -> m a) | |
| WriteOutput !a o |
newtype BiDiStream m i o a Source #
Constructors
| BiDiStream | |
Fields
| |
unary :: (MonadIO m, GRPCInput r i, GRPCOutput r o) => (forall x. m x -> IO x) -> r -> UnaryHandler m i o -> ServiceHandler Source #
Construct a handler for handling a unary RPC.
serverStream :: (MonadIO m, GRPCInput r i, GRPCOutput r o) => (forall x. m x -> IO x) -> r -> ServerStreamHandler m i o a -> ServiceHandler Source #
Construct a handler for handling a server-streaming RPC.
clientStream :: (MonadIO m, GRPCInput r i, GRPCOutput r o) => (forall x. m x -> IO x) -> r -> ClientStreamHandler m i o a -> ServiceHandler Source #
Construct a handler for handling a client-streaming RPC.
bidiStream :: (MonadIO m, GRPCInput r i, GRPCOutput r o) => (forall x. m x -> IO x) -> r -> BiDiStreamHandler m i o a -> ServiceHandler Source #
Construct a handler for handling a bidirectional-streaming RPC.
generalStream :: (MonadIO m, GRPCInput r i, GRPCOutput r o) => (forall x. m x -> IO x) -> r -> GeneralStreamHandler m i o a b -> ServiceHandler Source #
Construct a handler for handling a bidirectional-streaming RPC.
handleUnary :: (MonadIO m, GRPCInput r i, GRPCOutput r o) => (forall x. m x -> IO x) -> r -> UnaryHandler m i o -> WaiHandler Source #
Handle unary RPCs.
handleServerStream :: (MonadIO m, GRPCInput r i, GRPCOutput r o) => (forall x. m x -> IO x) -> r -> ServerStreamHandler m i o a -> WaiHandler Source #
Handle Server-Streaming RPCs.
handleClientStream :: forall m r i o a. (MonadIO m, GRPCInput r i, GRPCOutput r o) => (forall x. m x -> IO x) -> r -> ClientStreamHandler m i o a -> WaiHandler Source #
Handle Client-Streaming RPCs.
handleBiDiStream :: forall m r i o a. (MonadIO m, GRPCInput r i, GRPCOutput r o) => (forall x. m x -> IO x) -> r -> BiDiStreamHandler m i o a -> WaiHandler Source #
Handle Bidirectional-Streaming RPCs.
type GeneralStreamHandler m i o a b = Request -> m (a, IncomingStream m i a, b, OutgoingStream m o b) Source #
A GeneralStreamHandler combining server and client asynchronous streams.
data IncomingStream m i a Source #
Pair of handlers for reacting to incoming messages.
Constructors
| IncomingStream | |
Fields
| |
newtype OutgoingStream m o a Source #
Handler to decide on the next message (if any) to return.
Constructors
| OutgoingStream | |
Fields
| |
handleGeneralStream :: forall m r i o a b. (MonadIO m, GRPCInput r i, GRPCOutput r o) => (forall x. m x -> IO x) -> r -> GeneralStreamHandler m i o a b -> WaiHandler Source #
Handler for the somewhat general case where two threads behave concurrently: - one reads messages from the client - one returns messages to the client
handleRequestChunksLoop Source #
Arguments
| :: MonadIO m | |
| => Decoder (Either String a) | Message decoder. |
| -> (ByteString -> a -> m b) | Handler for a single message. The ByteString corresponds to leftover data. |
| -> m b | Handler for handling end-of-streams. |
| -> IO ByteString | Action to retrieve the next chunk. |
| -> m b |
Helpers to consume input in chunks.
errorOnLeftOver :: MonadIO m => (a -> m b) -> ByteString -> a -> m 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.