Safe Haskell | None |
---|---|
Language | Haskell2010 |
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)
- type BiDiStreamHandler s m a = Request -> IO (a, BiDiStream s m a)
- data BiDiStep s m a
- = Abort
- | WaitInput !(a -> MethodInput s m -> IO a) !(a -> IO a)
- | WriteOutput !a (MethodOutput s m)
- data BiDiStream s m a = BiDiStream {
- bidirNextStep :: a -> IO (BiDiStep s m a)
- 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
- bidiStream :: (Service s, HasMethod s m, MethodStreamingType s m ~ BiDiStreaming) => RPC s m -> BiDiStreamHandler s m a -> ServiceHandler
- generalStream :: (Service s, HasMethod s m) => RPC s m -> GeneralStreamHandler s m a b -> 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
- handleBiDiStream :: (Service s, HasMethod s m) => RPC s m -> BiDiStreamHandler s m a -> WaiHandler
- type GeneralStreamHandler s m a b = Request -> IO (a, IncomingStream s m a, b, OutgoingStream s m b)
- data IncomingStream s m a = IncomingStream {
- incomingStreamHandler :: a -> MethodInput s m -> IO a
- incomingStreamFinalizer :: a -> IO ()
- data OutgoingStream s m a = OutgoingStream {
- outgoingStreamNext :: a -> IO (Maybe (a, MethodOutput s m))
- handleGeneralStream :: (Service s, HasMethod s m) => RPC s m -> GeneralStreamHandler s m a b -> WaiHandler
- handleRequestChunksLoop :: Message a => Decoder (Either String a) -> (ByteString -> a -> IO b) -> IO b -> IO ByteString -> IO b
- 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 #
ServerStream | |
|
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 #
ClientStream | |
|
type BiDiStreamHandler s m a = Request -> IO (a, BiDiStream s m 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.
Abort | |
WaitInput !(a -> MethodInput s m -> IO a) !(a -> IO a) | |
WriteOutput !a (MethodOutput s m) |
data BiDiStream s m a Source #
BiDiStream | |
|
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.
bidiStream :: (Service s, HasMethod s m, MethodStreamingType s m ~ BiDiStreaming) => RPC s m -> BiDiStreamHandler s m a -> ServiceHandler Source #
Construct a handler for handling a bidirectional-streaming RPC.
generalStream :: (Service s, HasMethod s m) => RPC s m -> GeneralStreamHandler s m a b -> ServiceHandler Source #
Construct a handler for handling a bidirectional-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.
handleBiDiStream :: (Service s, HasMethod s m) => RPC s m -> BiDiStreamHandler s m a -> WaiHandler Source #
Handle Bidirectional-Streaming RPCs.
type GeneralStreamHandler s m a b = Request -> IO (a, IncomingStream s m a, b, OutgoingStream s m b) Source #
A GeneralStreamHandler combining server and client asynchronous streams.
data IncomingStream s m a Source #
Pair of handlers for reacting to incoming messages.
IncomingStream | |
|
data OutgoingStream s m a Source #
Handler to decide on the next message (if any) to return.
OutgoingStream | |
|
handleGeneralStream :: (Service s, HasMethod s m) => RPC s m -> GeneralStreamHandler s m 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 #
:: Message a | |
=> Decoder (Either String a) | Message decoder. |
-> (ByteString -> a -> IO b) | Handler for a single message. The ByteString corresponds to leftover data. |
-> IO b | Handler for handling end-of-streams. |
-> IO ByteString | Action to retrieve the next chunk. |
-> IO b |
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.