http2-client-grpc-0.5.0.3: Implement gRPC-over-HTTP2 clients.

Safe HaskellNone
LanguageHaskell2010

Network.GRPC.Client

Contents

Description

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

Building blocks.

data RPC s (m :: Symbol) #

A proxy type for giving static information about RPCs.

Constructors

RPC 

newtype RPCCall s (m :: Symbol) a Source #

Newtype helper used to uniformize all type of streaming modes when passing arguments to the open call.

type Authority = HeaderValue #

The HTTP2-Authority portion of an URL (e.g., "dicioccio.fr:7777").

newtype Timeout #

Timeout in seconds.

Constructors

Timeout Int 

open Source #

Arguments

:: (Service s, HasMethod s m) 
=> 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 s m a

The actual RPC handler.

-> IO (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

singleRequest Source #

Arguments

:: (Service s, HasMethod s m) 
=> RPC s m

RPC to call.

-> MethodInput s m

RPC's input.

-> RPCCall s m (RawReply (MethodOutput s m)) 

gRPC call for an unary request.

streamReply Source #

Arguments

:: (Service s, HasMethod s m, MethodStreamingType s m ~ ServerStreaming) 
=> RPC s m

RPC to call.

-> a

An initial state.

-> MethodInput s m

The input.

-> (a -> HeaderList -> MethodOutput s m -> IO a)

A state-passing handler that is called with the message read.

-> RPCCall s m (a, HeaderList, HeaderList) 

gRPC call for Server Streaming.

streamRequest Source #

Arguments

:: (Service s, HasMethod s m, MethodStreamingType s m ~ ClientStreaming) 
=> RPC s m

RPC to call.

-> a

An initial state.

-> (a -> IO (a, Either StreamDone (CompressMode, MethodInput s m)))

A state-passing action to retrieve the next message to send to the server.

-> RPCCall s m (a, RawReply (MethodOutput s m)) 

gRPC call for Client Streaming.

steppedBiDiStream Source #

Arguments

:: (Service s, HasMethod s m, MethodStreamingType s m ~ BiDiStreaming) 
=> RPC s m

RPC to call.

-> a

An initial state.

-> RunBiDiStep s m a

The program.

-> RPCCall s m 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.

generalHandler Source #

Arguments

:: (Service s, HasMethod s m) 
=> RPC s m

RPC to call.

-> a

An initial state for the incoming loop.

-> (a -> IncomingEvent s m a -> IO a)

A state-passing function for the incoming loop.

-> b

An initial state for the outgoing loop.

-> (b -> IO (b, OutgoingEvent s m b))

A state-passing function for the outgoing loop.

-> RPCCall s m (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 #

Constructors

StreamDone 

data BiDiStep s m a Source #

Constructors

Abort

Finalize and return the current state.

SendInput !CompressMode !(MethodInput s m)

Sends a single message.

WaitOutput (HandleMessageStep s m a) (HandleTrailersStep a)

Wait for information from the server, handlers can modify the state.

type RunBiDiStep s m a = a -> IO (a, BiDiStep s m a) Source #

State-based function.

type HandleMessageStep s m a = HeaderList -> a -> MethodOutput s m -> IO a Source #

Handler for received message.

type HandleTrailersStep a = HeaderList -> a -> HeaderList -> IO a Source #

Handler for received trailers.

data IncomingEvent s m a Source #

An event for the incoming loop of generalHandler.

Constructors

Headers HeaderList

The server sent some initial metadata with the headers.

RecvMessage (MethodOutput s m)

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 s m b Source #

An event for the outgoing loop of generalHandler.

Constructors

Finalize

The client is done with the RPC (the loop stops).

SendMessage CompressMode (MethodInput s m)

The client sends a message to the server.

Errors.

data InvalidState Source #

Exception raised when a ServerStreaming RPC results in an invalid state machine.

Constructors

InvalidState String 

data InvalidParse Source #

Exception raised when a BiDiStreaming RPC results in an invalid parse.

Constructors

InvalidParse String 

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.

uncompressed :: Compression #

Do not compress.

Re-exports.

type HeaderList = [Header] #

Header list.