| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Network.GRPC.Server
Synopsis
- runGrpc :: TLSSettings -> Settings -> [ServiceHandler] -> [Compression] -> IO ()
- 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)
- newtype BiDiStream m i o a = BiDiStream {
- bidirNextStep :: a -> m (BiDiStep m i o a)
- data BiDiStep m i o a
- = Abort
- | WaitInput !(a -> i -> m a) !(a -> m a)
- | WriteOutput !a o
- 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))
- data ServiceHandler
- unary :: (GRPCInput r i, GRPCOutput r o) => r -> UnaryHandler IO i o -> ServiceHandler
- serverStream :: (GRPCInput r i, GRPCOutput r o) => r -> ServerStreamHandler IO i o a -> ServiceHandler
- clientStream :: (GRPCInput r i, GRPCOutput r o) => r -> ClientStreamHandler IO i o a -> ServiceHandler
- bidiStream :: (GRPCInput r i, GRPCOutput r o) => r -> BiDiStreamHandler IO i o a -> ServiceHandler
- generalStream :: (GRPCInput r i, GRPCOutput r o) => r -> GeneralStreamHandler IO i o a b -> ServiceHandler
- data GRPCStatus = GRPCStatus !GRPCStatusCode !GRPCStatusMessage
- throwIO :: Exception e => e -> IO a
- type GRPCStatusMessage = HeaderValue
- data GRPCStatusCode
- grpcApp :: [Compression] -> [ServiceHandler] -> Application
- grpcService :: [Compression] -> [ServiceHandler] -> Application -> Application
Documentation
Arguments
| :: TLSSettings | TLS settings for the HTTP2 server. |
| -> Settings | Warp settings. |
| -> [ServiceHandler] | List of ServiceHandler. Refer to |
| -> [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 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.
newtype BiDiStream m i o a Source #
Constructors
| BiDiStream | |
Fields
| |
data BiDiStep m i o a Source #
Constructors
| Abort | |
| WaitInput !(a -> i -> m a) !(a -> m a) | |
| WriteOutput !a o |
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
| |
registration
data ServiceHandler Source #
Untyped gRPC Service handler.
unary :: (GRPCInput r i, GRPCOutput r o) => r -> UnaryHandler IO i o -> ServiceHandler Source #
serverStream :: (GRPCInput r i, GRPCOutput r o) => r -> ServerStreamHandler IO i o a -> ServiceHandler Source #
clientStream :: (GRPCInput r i, GRPCOutput r o) => r -> ClientStreamHandler IO i o a -> ServiceHandler Source #
bidiStream :: (GRPCInput r i, GRPCOutput r o) => r -> BiDiStreamHandler IO i o a -> ServiceHandler Source #
generalStream :: (GRPCInput r i, GRPCOutput r o) => r -> GeneralStreamHandler IO i o a b -> ServiceHandler Source #
registration
data GRPCStatus #
Constructors
| GRPCStatus !GRPCStatusCode !GRPCStatusMessage |
Instances
| Eq GRPCStatus | |
Defined in Network.GRPC.HTTP2.Types | |
| Ord GRPCStatus | |
Defined in Network.GRPC.HTTP2.Types Methods compare :: GRPCStatus -> GRPCStatus -> Ordering # (<) :: GRPCStatus -> GRPCStatus -> Bool # (<=) :: GRPCStatus -> GRPCStatus -> Bool # (>) :: GRPCStatus -> GRPCStatus -> Bool # (>=) :: GRPCStatus -> GRPCStatus -> Bool # max :: GRPCStatus -> GRPCStatus -> GRPCStatus # min :: GRPCStatus -> GRPCStatus -> GRPCStatus # | |
| Show GRPCStatus | |
Defined in Network.GRPC.HTTP2.Types Methods showsPrec :: Int -> GRPCStatus -> ShowS # show :: GRPCStatus -> String # showList :: [GRPCStatus] -> ShowS # | |
| Exception GRPCStatus | |
Defined in Network.GRPC.HTTP2.Types Methods toException :: GRPCStatus -> SomeException # fromException :: SomeException -> Maybe GRPCStatus # displayException :: GRPCStatus -> String # | |
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.
type GRPCStatusMessage = HeaderValue #
data GRPCStatusCode #
Constructors
Instances
| Eq GRPCStatusCode | |
Defined in Network.GRPC.HTTP2.Types Methods (==) :: GRPCStatusCode -> GRPCStatusCode -> Bool # (/=) :: GRPCStatusCode -> GRPCStatusCode -> Bool # | |
| Ord GRPCStatusCode | |
Defined in Network.GRPC.HTTP2.Types Methods compare :: GRPCStatusCode -> GRPCStatusCode -> Ordering # (<) :: GRPCStatusCode -> GRPCStatusCode -> Bool # (<=) :: GRPCStatusCode -> GRPCStatusCode -> Bool # (>) :: GRPCStatusCode -> GRPCStatusCode -> Bool # (>=) :: GRPCStatusCode -> GRPCStatusCode -> Bool # max :: GRPCStatusCode -> GRPCStatusCode -> GRPCStatusCode # min :: GRPCStatusCode -> GRPCStatusCode -> GRPCStatusCode # | |
| Show GRPCStatusCode | |
Defined in Network.GRPC.HTTP2.Types Methods showsPrec :: Int -> GRPCStatusCode -> ShowS # show :: GRPCStatusCode -> String # showList :: [GRPCStatusCode] -> ShowS # | |
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.