-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | A minimal gRPC server on top of Warp. -- -- Please see the README on Github at -- https://github.com/haskell-grpc-native/http2-grpc-haskell/blob/master/warp-grpc/README.md @package warp-grpc @version 0.4.0.1 module Network.GRPC.Server.Helpers -- | Helper to set the GRPCStatus on the trailers reply. modifyGRPCStatus :: IORef [(HeaderKey, HeaderValue)] -> Request -> GRPCStatus -> IO () module Network.GRPC.Server.Wai -- | A Wai Handler for a request. type WaiHandler = Decoding " Compression for the request inputs." -> Encoding " Compression for the request outputs." -> Request " Request object." -> (Builder -> IO ()) " Write a data chunk in the reply." -> IO () " Flush the output." -> IO () -- | Untyped gRPC Service handler. data ServiceHandler ServiceHandler :: ByteString -> WaiHandler -> ServiceHandler -- | Path to the Service to be handled. [grpcHandlerPath] :: ServiceHandler -> ByteString -- | Actual request handler. [grpcWaiHandler] :: ServiceHandler -> WaiHandler -- | 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. grpcApp :: [Compression] -> [ServiceHandler] -> Application -- | Aborts a GRPC handler with a given GRPCStatus. closeEarly :: MonadIO m => GRPCStatus -> m a -- | 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. grpcService :: [Compression] -> [ServiceHandler] -> Application -> Application -- | Looks-up header for encoding outgoing messages. requestAcceptEncodingNames :: Request -> [ByteString] -- | Looks-up the compression to use from a set of known algorithms. lookupEncoding :: Request -> [Compression] -> Maybe Encoding -- | Looks-up header for decoding incoming messages. requestDecodingName :: Request -> Maybe ByteString -- | Looks-up the compression to use for decoding messages. lookupDecoding :: Request -> [Compression] -> Maybe Decoding module Network.GRPC.Server.Handlers.Trans -- | Handy type to refer to Handler for unary RPCs handler. type UnaryHandler m i o = Request -> i -> m o -- | 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. type ServerStreamHandler m i o a = Request -> i -> m (a, ServerStream m o a) newtype ServerStream m o a ServerStream :: (a -> m (Maybe (a, o))) -> ServerStream m o a [serverStreamNext] :: ServerStream m o a -> a -> m (Maybe (a, o)) -- | 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. type ClientStreamHandler m i o a = Request -> m (a, ClientStream m i o a) data ClientStream m i o a ClientStream :: (a -> i -> m a) -> (a -> m o) -> ClientStream m i o a [clientStreamHandler] :: ClientStream m i o a -> a -> i -> m a [clientStreamFinalizer] :: ClientStream m i o a -> a -> m o -- | 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. type BiDiStreamHandler m i o a = Request -> m (a, BiDiStream m i o a) data BiDiStep m i o a Abort :: BiDiStep m i o a WaitInput :: !a -> i -> m a -> !a -> m a -> BiDiStep m i o a WriteOutput :: !a -> o -> BiDiStep m i o a newtype BiDiStream m i o a BiDiStream :: (a -> m (BiDiStep m i o a)) -> BiDiStream m i o a [bidirNextStep] :: BiDiStream m i o a -> a -> m (BiDiStep m i o a) -- | Construct a handler for handling a unary RPC. unary :: (MonadIO m, GRPCInput r i, GRPCOutput r o) => (forall x. m x -> IO x) -> r -> UnaryHandler m i o -> ServiceHandler -- | Construct a handler for handling a server-streaming RPC. serverStream :: (MonadIO m, GRPCInput r i, GRPCOutput r o) => (forall x. m x -> IO x) -> r -> ServerStreamHandler m i o a -> ServiceHandler -- | Construct a handler for handling a client-streaming RPC. clientStream :: (MonadIO m, GRPCInput r i, GRPCOutput r o) => (forall x. m x -> IO x) -> r -> ClientStreamHandler m i o a -> ServiceHandler -- | Construct a handler for handling a bidirectional-streaming RPC. bidiStream :: (MonadIO m, GRPCInput r i, GRPCOutput r o) => (forall x. m x -> IO x) -> r -> BiDiStreamHandler m i o a -> ServiceHandler -- | Construct a handler for handling a bidirectional-streaming RPC. generalStream :: (MonadIO m, GRPCInput r i, GRPCOutput r o) => (forall x. m x -> IO x) -> r -> GeneralStreamHandler m i o a b -> ServiceHandler -- | Handle unary RPCs. handleUnary :: (MonadIO m, GRPCInput r i, GRPCOutput r o) => (forall x. m x -> IO x) -> r -> UnaryHandler m i o -> WaiHandler -- | Handle Server-Streaming RPCs. handleServerStream :: (MonadIO m, GRPCInput r i, GRPCOutput r o) => (forall x. m x -> IO x) -> r -> ServerStreamHandler m i o a -> WaiHandler -- | Handle Client-Streaming RPCs. handleClientStream :: forall m r i o a. (MonadIO m, GRPCInput r i, GRPCOutput r o) => (forall x. m x -> IO x) -> r -> ClientStreamHandler m i o a -> WaiHandler -- | Handle Bidirectional-Streaming RPCs. handleBiDiStream :: forall m r i o a. (MonadIO m, GRPCInput r i, GRPCOutput r o) => (forall x. m x -> IO x) -> r -> BiDiStreamHandler m i o a -> WaiHandler -- | A GeneralStreamHandler combining server and client asynchronous -- streams. type GeneralStreamHandler m i o a b = Request -> m (a, IncomingStream m i a, b, OutgoingStream m o b) -- | Pair of handlers for reacting to incoming messages. data IncomingStream m i a IncomingStream :: (a -> i -> m a) -> (a -> m ()) -> IncomingStream m i a [incomingStreamHandler] :: IncomingStream m i a -> a -> i -> m a [incomingStreamFinalizer] :: IncomingStream m i a -> a -> m () -- | Handler to decide on the next message (if any) to return. newtype OutgoingStream m o a OutgoingStream :: (a -> m (Maybe (a, o))) -> OutgoingStream m o a [outgoingStreamNext] :: OutgoingStream m o a -> a -> m (Maybe (a, o)) -- | Handler for the somewhat general case where two threads behave -- concurrently: - one reads messages from the client - one returns -- messages to the client handleGeneralStream :: forall m r i o a b. (MonadIO m, GRPCInput r i, GRPCOutput r o) => (forall x. m x -> IO x) -> r -> GeneralStreamHandler m i o a b -> WaiHandler -- | Helpers to consume input in chunks. handleRequestChunksLoop :: MonadIO m => Decoder (Either String a) -> (ByteString -> a -> m b) -> m b -> IO ByteString -> m b -- | 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. errorOnLeftOver :: MonadIO m => (a -> m b) -> ByteString -> a -> m b module Network.GRPC.Server.Handlers.Unlift -- | Handy type to refer to Handler for unary RPCs handler. type UnaryHandler m i o = Request -> i -> m o unary :: (MonadUnliftIO m, GRPCInput r i, GRPCOutput r o) => r -> UnaryHandler m i o -> m ServiceHandler -- | 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. type ServerStreamHandler m i o a = Request -> i -> m (a, ServerStream m o a) newtype ServerStream m o a ServerStream :: (a -> m (Maybe (a, o))) -> ServerStream m o a [serverStreamNext] :: ServerStream m o a -> a -> m (Maybe (a, o)) serverStream :: (MonadUnliftIO m, GRPCInput r i, GRPCOutput r o) => r -> ServerStreamHandler m i o a -> m ServiceHandler -- | 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. type ClientStreamHandler m i o a = Request -> m (a, ClientStream m i o a) data ClientStream m i o a ClientStream :: (a -> i -> m a) -> (a -> m o) -> ClientStream m i o a [clientStreamHandler] :: ClientStream m i o a -> a -> i -> m a [clientStreamFinalizer] :: ClientStream m i o a -> a -> m o clientStream :: (MonadUnliftIO m, GRPCInput r i, GRPCOutput r o) => r -> ClientStreamHandler m i o a -> m ServiceHandler -- | 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. type BiDiStreamHandler m i o a = Request -> m (a, BiDiStream m i o a) data BiDiStep m i o a Abort :: BiDiStep m i o a WaitInput :: !a -> i -> m a -> !a -> m a -> BiDiStep m i o a WriteOutput :: !a -> o -> BiDiStep m i o a newtype BiDiStream m i o a BiDiStream :: (a -> m (BiDiStep m i o a)) -> BiDiStream m i o a [bidirNextStep] :: BiDiStream m i o a -> a -> m (BiDiStep m i o a) bidiStream :: (MonadUnliftIO m, GRPCInput r i, GRPCOutput r o) => r -> BiDiStreamHandler m i o a -> m ServiceHandler -- | A GeneralStreamHandler combining server and client asynchronous -- streams. type GeneralStreamHandler m i o a b = Request -> m (a, IncomingStream m i a, b, OutgoingStream m o b) -- | Pair of handlers for reacting to incoming messages. data IncomingStream m i a IncomingStream :: (a -> i -> m a) -> (a -> m ()) -> IncomingStream m i a [incomingStreamHandler] :: IncomingStream m i a -> a -> i -> m a [incomingStreamFinalizer] :: IncomingStream m i a -> a -> m () -- | Handler to decide on the next message (if any) to return. newtype OutgoingStream m o a OutgoingStream :: (a -> m (Maybe (a, o))) -> OutgoingStream m o a [outgoingStreamNext] :: OutgoingStream m o a -> a -> m (Maybe (a, o)) generalStream :: (MonadUnliftIO m, GRPCInput r i, GRPCOutput r o) => r -> GeneralStreamHandler m i o a b -> m ServiceHandler module Network.GRPC.Server.Handlers -- | Handy type to refer to Handler for unary RPCs handler. type UnaryHandler m i o = Request -> i -> m o unary :: (GRPCInput r i, GRPCOutput r o) => r -> UnaryHandler IO i o -> ServiceHandler -- | 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. type ServerStreamHandler m i o a = Request -> i -> m (a, ServerStream m o a) newtype ServerStream m o a ServerStream :: (a -> m (Maybe (a, o))) -> ServerStream m o a [serverStreamNext] :: ServerStream m o a -> a -> m (Maybe (a, o)) serverStream :: (GRPCInput r i, GRPCOutput r o) => r -> ServerStreamHandler IO i o a -> ServiceHandler -- | 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. type ClientStreamHandler m i o a = Request -> m (a, ClientStream m i o a) data ClientStream m i o a ClientStream :: (a -> i -> m a) -> (a -> m o) -> ClientStream m i o a [clientStreamHandler] :: ClientStream m i o a -> a -> i -> m a [clientStreamFinalizer] :: ClientStream m i o a -> a -> m o clientStream :: (GRPCInput r i, GRPCOutput r o) => r -> ClientStreamHandler IO i o a -> ServiceHandler -- | 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. type BiDiStreamHandler m i o a = Request -> m (a, BiDiStream m i o a) data BiDiStep m i o a Abort :: BiDiStep m i o a WaitInput :: !a -> i -> m a -> !a -> m a -> BiDiStep m i o a WriteOutput :: !a -> o -> BiDiStep m i o a newtype BiDiStream m i o a BiDiStream :: (a -> m (BiDiStep m i o a)) -> BiDiStream m i o a [bidirNextStep] :: BiDiStream m i o a -> a -> m (BiDiStep m i o a) bidiStream :: (GRPCInput r i, GRPCOutput r o) => r -> BiDiStreamHandler IO i o a -> ServiceHandler -- | A GeneralStreamHandler combining server and client asynchronous -- streams. type GeneralStreamHandler m i o a b = Request -> m (a, IncomingStream m i a, b, OutgoingStream m o b) -- | Pair of handlers for reacting to incoming messages. data IncomingStream m i a IncomingStream :: (a -> i -> m a) -> (a -> m ()) -> IncomingStream m i a [incomingStreamHandler] :: IncomingStream m i a -> a -> i -> m a [incomingStreamFinalizer] :: IncomingStream m i a -> a -> m () -- | Handler to decide on the next message (if any) to return. newtype OutgoingStream m o a OutgoingStream :: (a -> m (Maybe (a, o))) -> OutgoingStream m o a [outgoingStreamNext] :: OutgoingStream m o a -> a -> m (Maybe (a, o)) generalStream :: (GRPCInput r i, GRPCOutput r o) => r -> GeneralStreamHandler IO i o a b -> ServiceHandler module Network.GRPC.Server -- | Helper to constructs and serve a gRPC over HTTP2 application. -- -- You may want to use grpcApp for adding middlewares to your gRPC -- server. runGrpc :: TLSSettings -> Settings -> [ServiceHandler] -> [Compression] -> IO () -- | Handy type to refer to Handler for unary RPCs handler. type UnaryHandler m i o = Request -> i -> m o -- | 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. type ServerStreamHandler m i o a = Request -> i -> m (a, ServerStream m o a) newtype ServerStream m o a ServerStream :: (a -> m (Maybe (a, o))) -> ServerStream m o a [serverStreamNext] :: ServerStream m o a -> a -> m (Maybe (a, o)) -- | 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. type ClientStreamHandler m i o a = Request -> m (a, ClientStream m i o a) data ClientStream m i o a ClientStream :: (a -> i -> m a) -> (a -> m o) -> ClientStream m i o a [clientStreamHandler] :: ClientStream m i o a -> a -> i -> m a [clientStreamFinalizer] :: ClientStream m i o a -> a -> m o -- | 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. type BiDiStreamHandler m i o a = Request -> m (a, BiDiStream m i o a) newtype BiDiStream m i o a BiDiStream :: (a -> m (BiDiStep m i o a)) -> BiDiStream m i o a [bidirNextStep] :: BiDiStream m i o a -> a -> m (BiDiStep m i o a) data BiDiStep m i o a Abort :: BiDiStep m i o a WaitInput :: !a -> i -> m a -> !a -> m a -> BiDiStep m i o a WriteOutput :: !a -> o -> BiDiStep m i o a -- | A GeneralStreamHandler combining server and client asynchronous -- streams. type GeneralStreamHandler m i o a b = Request -> m (a, IncomingStream m i a, b, OutgoingStream m o b) -- | Pair of handlers for reacting to incoming messages. data IncomingStream m i a IncomingStream :: (a -> i -> m a) -> (a -> m ()) -> IncomingStream m i a [incomingStreamHandler] :: IncomingStream m i a -> a -> i -> m a [incomingStreamFinalizer] :: IncomingStream m i a -> a -> m () -- | Handler to decide on the next message (if any) to return. newtype OutgoingStream m o a OutgoingStream :: (a -> m (Maybe (a, o))) -> OutgoingStream m o a [outgoingStreamNext] :: OutgoingStream m o a -> a -> m (Maybe (a, o)) -- | Untyped gRPC Service handler. 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 -> GRPCStatus -- | 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. throwIO :: Exception e => e -> IO a type GRPCStatusMessage = HeaderValue data GRPCStatusCode OK :: GRPCStatusCode CANCELLED :: GRPCStatusCode UNKNOWN :: GRPCStatusCode INVALID_ARGUMENT :: GRPCStatusCode DEADLINE_EXCEEDED :: GRPCStatusCode NOT_FOUND :: GRPCStatusCode ALREADY_EXISTS :: GRPCStatusCode PERMISSION_DENIED :: GRPCStatusCode UNAUTHENTICATED :: GRPCStatusCode RESOURCE_EXHAUSTED :: GRPCStatusCode FAILED_PRECONDITION :: GRPCStatusCode ABORTED :: GRPCStatusCode OUT_OF_RANGE :: GRPCStatusCode UNIMPLEMENTED :: GRPCStatusCode INTERNAL :: GRPCStatusCode UNAVAILABLE :: GRPCStatusCode DATA_LOSS :: GRPCStatusCode -- | 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. grpcApp :: [Compression] -> [ServiceHandler] -> Application -- | 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. grpcService :: [Compression] -> [ServiceHandler] -> Application -> Application