warp-grpc-0.1.0.3: A minimal gRPC server on top of Warp.

Safe HaskellNone
LanguageHaskell2010

Network.GRPC.Server

Contents

Synopsis

Documentation

runGrpc Source #

Arguments

:: TLSSettings

TLS settings for the HTTP2 server.

-> Settings

Warp settings.

-> [ServiceHandler]

List of ServiceHandler. Refer to grcpApp

-> [Compression]

Compression methods used.

-> IO () 

Helper to constructs and serve a gRPC over HTTP2 application.

You may want to use grpcApp for adding middlewares to your gRPC server.

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

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.

data BiDiStream s m a Source #

Constructors

BiDiStream 

Fields

data BiDiStep s m a Source #

Constructors

Abort 
WaitInput !(a -> MethodInput s m -> IO a) !(a -> IO a) 
WriteOutput !a (MethodOutput s m) 

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.

Constructors

IncomingStream 

Fields

data OutgoingStream s m a Source #

Handler to decide on the next message (if any) to return.

Constructors

OutgoingStream 

Fields

registration

data ServiceHandler Source #

Untyped gRPC Service handler.

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.

registration

throwIO :: Exception e => e -> IO a #

A variant of throw that can only be used within the IO monad.

Although throwIO has a type that is an instance of the type of throw, the two functions are subtly different:

throw e   `seq` x  ===> throw e
throwIO e `seq` x  ===> x

The first example will cause the exception e to be raised, whereas the second one won't. In fact, throwIO will only cause an exception to be raised when it is used within the IO monad. The throwIO variant should be used in preference to throw to raise an exception within the IO monad because it guarantees ordering with respect to other IO operations, whereas throw does not.

to work directly with WAI

grpcApp :: [Compression] -> [ServiceHandler] -> Application Source #

Build a WAI Application from a list of ServiceHandler.

Currently, gRPC calls are lookuped up by traversing the list of ServiceHandler. This lookup may be inefficient for large amount of servics.

grpcService :: [Compression] -> [ServiceHandler] -> Application -> Application Source #

Build a WAI Middleware from a list of ServiceHandler.

Currently, gRPC calls are lookuped up by traversing the list of ServiceHandler. This lookup may be inefficient for large amount of services.