Safe Haskell | None |
---|---|
Language | Haskell2010 |
A module adding support for gRPC over HTTP2.
This module provides helpers to encode gRPC queries on top of HTTP2 client.
The helpers we provide for streaming RPCs (streamReply
, streamRequest
,
steppedBiDiStream
) are a subset of what gRPC allows: the gRPC definition
of streaming RPCs offers a large amount of valid behaviors regarding timing
of headers, trailers, and end of streams.
The limitations of these functions should be clear from the type signatures.
But in general, the design is to only allow synchronous state machines. Such
state-machines cannot immediately react to server-sent messages but must
wait for the client code to poll for some server-sent information. In
short, these handlers prevents programs from observing intermediary steps
which may be valid applications by gRPC standards. Simply put, it is not
possibly to simultaneously wait for some information from the server and
send some information.
For instance, in a client-streaming RPC, the server is allowed to send
trailers at any time, even before receiving any input message. The
streamRequest
functions disallows reading trailers until the client code
is done sending requests.
A result from this design choice is to offer a simple programming surface
for the most common use cases. Further, these simple state-machines require
little runtime overhead.
A more general handler generalHandler
is provided which runs two thread in
parallel. This handler allows to send an receive messages concurrently using
one loop each, which allows to circumvent the limitations of the above
handlers (but at a cost: complexity and threading overhead). It also means
that a sending action may be stuck indefinitely on flow-control and cannot
be cancelled without killing the RPC
thread. You see where we are going:
the more elaborate the semantics, the more a programmer has to think.
Though, all hope of expressing wacky application semantics is not lost: it
is always possible to write its own RPC
function. Writing one's own RPC
function allows to leverage the specific semantics of the RPC call to save
some overhead (much like the three above streaming helpers assume a simple
behavior from the server). Hence, it is generally a good idea to take
inspiration from the existing RPC functions and learn how to write one.
Synopsis
- data RPCCall r a = RPCCall {
- rpcFromCall :: r
- runRPC :: Http2Client -> Http2Stream -> IncomingFlowControl -> OutgoingFlowControl -> Encoding -> Decoding -> ClientIO a
- type CIHeaderList = [(CI ByteString, ByteString)]
- type Authority = HeaderValue
- newtype Timeout = Timeout Int
- open :: IsRPC r => Http2Client -> Authority -> HeaderList -> Timeout -> Encoding -> Decoding -> RPCCall r a -> ClientIO (Either TooMuchConcurrency a)
- type RawReply a = Either ErrorCode (CIHeaderList, Maybe CIHeaderList, Either String a)
- singleRequest :: (GRPCInput r i, GRPCOutput r o) => r -> i -> RPCCall r (RawReply o)
- streamReply :: (GRPCInput r i, GRPCOutput r o) => r -> a -> i -> (a -> HeaderList -> o -> ClientIO a) -> RPCCall r (a, HeaderList, HeaderList)
- streamRequest :: (GRPCInput r i, GRPCOutput r o) => r -> a -> (a -> ClientIO (a, Either StreamDone (CompressMode, i))) -> RPCCall r (a, RawReply o)
- steppedBiDiStream :: (GRPCInput r i, GRPCOutput r o) => r -> a -> RunBiDiStep i o a -> RPCCall r a
- generalHandler :: (GRPCInput r i, GRPCOutput r o) => r -> a -> (a -> IncomingEvent o a -> ClientIO a) -> b -> (b -> ClientIO (b, OutgoingEvent i b)) -> RPCCall r (a, b)
- data CompressMode
- data StreamDone = StreamDone
- data BiDiStep i o a
- = Abort
- | SendInput !CompressMode !i
- | WaitOutput (HandleMessageStep i o a) (HandleTrailersStep a)
- type RunBiDiStep s meth a = a -> ClientIO (a, BiDiStep s meth a)
- type HandleMessageStep i o a = HeaderList -> a -> o -> ClientIO a
- type HandleTrailersStep a = HeaderList -> a -> HeaderList -> ClientIO a
- data IncomingEvent o a
- data OutgoingEvent i b
- newtype InvalidState = InvalidState String
- newtype StreamReplyDecodingError = StreamReplyDecodingError String
- data UnallowedPushPromiseReceived = UnallowedPushPromiseReceived
- newtype InvalidParse = InvalidParse String
- data Compression
- gzip :: Compression
- uncompressed :: Compression
- type HeaderList = [Header]
Building blocks.
Newtype helper used to uniformize all type of streaming modes when
passing arguments to the open
call.
RPCCall | |
|
type CIHeaderList = [(CI ByteString, ByteString)] Source #
type Authority = HeaderValue #
The HTTP2-Authority portion of an URL (e.g., "dicioccio.fr:7777").
:: IsRPC r | |
=> Http2Client | A connected HTTP2 client. |
-> Authority | The HTTP2-Authority portion of the URL (e.g., "dicioccio.fr:7777"). |
-> HeaderList | A set of HTTP2 headers (e.g., for adding authentication headers). |
-> Timeout | Timeout in seconds. |
-> Encoding | Compression used for encoding. |
-> Decoding | Compression allowed for decoding |
-> RPCCall r a | The actual RPC handler. |
-> ClientIO (Either TooMuchConcurrency a) |
Main handler to perform gRPC calls to a service.
type RawReply a = Either ErrorCode (CIHeaderList, Maybe CIHeaderList, Either String a) Source #
A reply.
This reply object contains a lot of information because a single gRPC call returns a lot of data. A future version of the library will have a proper data structure with properly named-fields on the reply object.
For now, remember: - 1st item: initial HTTP2 response - 2nd item: second (trailers) HTTP2 response - 3rd item: proper gRPC answer
Helpers
:: (GRPCInput r i, GRPCOutput r o) | |
=> r | RPC to call. |
-> i | RPC's input. |
-> RPCCall r (RawReply o) |
gRPC call for an unary request.
:: (GRPCInput r i, GRPCOutput r o) | |
=> r | RPC to call. |
-> a | An initial state. |
-> i | The input. |
-> (a -> HeaderList -> o -> ClientIO a) | A state-passing handler that is called with the message read. |
-> RPCCall r (a, HeaderList, HeaderList) |
gRPC call for Server Streaming.
:: (GRPCInput r i, GRPCOutput r o) | |
=> r | RPC to call. |
-> a | An initial state. |
-> (a -> ClientIO (a, Either StreamDone (CompressMode, i))) | A state-passing action to retrieve the next message to send to the server. |
-> RPCCall r (a, RawReply o) |
gRPC call for Client Streaming.
:: (GRPCInput r i, GRPCOutput r o) | |
=> r | RPC to call. |
-> a | An initial state. |
-> RunBiDiStep i o a | The program. |
-> RPCCall r a |
gRPC call for a stepped bidirectional stream.
This helper limited.
See BiDiStep
and RunBiDiStep
to understand the type of programs one can
write with this function.
:: (GRPCInput r i, GRPCOutput r o) | |
=> r | RPC to call. |
-> a | An initial state for the incoming loop. |
-> (a -> IncomingEvent o a -> ClientIO a) | A state-passing function for the incoming loop. |
-> b | An initial state for the outgoing loop. |
-> (b -> ClientIO (b, OutgoingEvent i b)) | A state-passing function for the outgoing loop. |
-> RPCCall r (a, b) |
General RPC handler for decorrelating the handling of received headers/trailers from the sending of messages.
There is no constraints on the stream-arity of the RPC. It requires a bit of viligence to avoid breaking the gRPC semantics but this one is easy to pay attention to.
This handler runs two loops concurrently
:
One loop accepts and chunks messages from the HTTP2 stream, then return events
and stops on Trailers or Invalid. The other loop waits for messages to send to
the server or finalize and returns.
data StreamDone Source #
Abort | Finalize and return the current state. |
SendInput !CompressMode !i | Sends a single message. |
WaitOutput (HandleMessageStep i o a) (HandleTrailersStep a) | Wait for information from the server, handlers can modify the state. |
type RunBiDiStep s meth a = a -> ClientIO (a, BiDiStep s meth a) Source #
State-based function.
type HandleMessageStep i o a = HeaderList -> a -> o -> ClientIO a Source #
Handler for received message.
type HandleTrailersStep a = HeaderList -> a -> HeaderList -> ClientIO a Source #
Handler for received trailers.
data IncomingEvent o a Source #
An event for the incoming loop of generalHandler
.
Headers HeaderList | The server sent some initial metadata with the headers. |
RecvMessage o | The server send a message. |
Trailers HeaderList | The server send final metadata (the loop stops). |
Invalid SomeException | Something went wrong (the loop stops). |
data OutgoingEvent i b Source #
An event for the outgoing loop of generalHandler
.
Finalize | The client is done with the RPC (the loop stops). |
SendMessage CompressMode i | The client sends a message to the server. |
Errors.
newtype InvalidState Source #
Exception raised when a ServerStreaming RPC results in an invalid state machine.
Instances
Show InvalidState Source # | |
Defined in Network.GRPC.Client showsPrec :: Int -> InvalidState -> ShowS # show :: InvalidState -> String # showList :: [InvalidState] -> ShowS # | |
Exception InvalidState Source # | |
Defined in Network.GRPC.Client |
newtype StreamReplyDecodingError Source #
Exception raised when a ServerStreaming RPC results in a decoding error.
Instances
Show StreamReplyDecodingError Source # | |
Defined in Network.GRPC.Client showsPrec :: Int -> StreamReplyDecodingError -> ShowS # show :: StreamReplyDecodingError -> String # showList :: [StreamReplyDecodingError] -> ShowS # | |
Exception StreamReplyDecodingError Source # | |
data UnallowedPushPromiseReceived Source #
gRPC disables HTTP2 push-promises.
If a server attempts to send push-promises, this exception will be raised.
Instances
newtype InvalidParse Source #
Exception raised when a BiDiStreaming RPC results in an invalid parse.
Instances
Show InvalidParse Source # | |
Defined in Network.GRPC.Client showsPrec :: Int -> InvalidParse -> ShowS # show :: InvalidParse -> String # showList :: [InvalidParse] -> ShowS # | |
Exception InvalidParse Source # | |
Defined in Network.GRPC.Client |
Compression of individual messages.
data Compression #
Opaque type for handling compression.
So far, only "pure" compression algorithms are supported.
TODO: suport IO-based compression implementations once we move from Builder
.
gzip :: Compression #
Use gzip as compression.
Do not compress.
Re-exports.
type HeaderList = [Header] #
Header list.