| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Network.GRPC.Server
Synopsis
- runGrpc :: TLSSettings -> Settings -> [ServiceHandler] -> [Compression] -> IO ()
 - type UnaryHandler s m = Request -> MethodInput s m -> IO (MethodOutput s m)
 - type ServerStreamHandler s m a = Request -> MethodInput s m -> IO (a, ServerStream s m a)
 - newtype ServerStream s m a = ServerStream {
- serverStreamNext :: a -> IO (Maybe (a, MethodOutput s m))
 
 - type ClientStreamHandler s m a = Request -> IO (a, ClientStream s m a)
 - data ClientStream s m a = ClientStream {
- clientStreamHandler :: a -> MethodInput s m -> IO a
 - clientStreamFinalizer :: a -> IO (MethodOutput s m)
 
 - data ServiceHandler
 - unary :: (Service s, HasMethod s m) => RPC s m -> UnaryHandler s m -> ServiceHandler
 - serverStream :: (Service s, HasMethod s m, MethodStreamingType s m ~ ServerStreaming) => RPC s m -> ServerStreamHandler s m a -> ServiceHandler
 - clientStream :: (Service s, HasMethod s m, MethodStreamingType s m ~ ClientStreaming) => RPC s m -> ClientStreamHandler s m a -> 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 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 
  | |
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.
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.