| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Mu.GRpc.Server
Description
This module allows you to server a Mu Server
as a WAI Application using gRPC as transport layer.
The simples way is to use runGRpcApp, all other
variants provide more control over the settings.
Synopsis
- data GRpcMessageProtocol
- msgProtoBuf :: Proxy 'MsgProtoBuf
- msgAvro :: Proxy 'MsgAvro
- runGRpcApp :: (KnownName name, GRpcServiceHandlers ('Package ('Just name) services) protocol ServerErrorIO chn services handlers) => Proxy protocol -> Port -> ServerT chn () ('Package ('Just name) services) ServerErrorIO handlers -> IO ()
- runGRpcAppTrans :: (KnownName name, GRpcServiceHandlers ('Package ('Just name) services) protocol m chn services handlers) => Proxy protocol -> Port -> (forall a. m a -> ServerErrorIO a) -> ServerT chn () ('Package ('Just name) services) m handlers -> IO ()
- runGRpcAppSettings :: (KnownName name, GRpcServiceHandlers ('Package ('Just name) services) protocol m chn services handlers) => Proxy protocol -> Settings -> (forall a. m a -> ServerErrorIO a) -> ServerT chn () ('Package ('Just name) services) m handlers -> IO ()
- data Settings
- runGRpcAppTLS :: (KnownName name, GRpcServiceHandlers ('Package ('Just name) services) protocol m chn services handlers) => Proxy protocol -> TLSSettings -> Settings -> (forall a. m a -> ServerErrorIO a) -> ServerT chn () ('Package ('Just name) services) m handlers -> IO ()
- data TLSSettings
- gRpcApp :: (KnownName name, GRpcServiceHandlers ('Package ('Just name) services) protocol ServerErrorIO chn services handlers) => Proxy protocol -> ServerT chn () ('Package ('Just name) services) ServerErrorIO handlers -> Application
- gRpcAppTrans :: (KnownName name, GRpcServiceHandlers ('Package ('Just name) services) protocol m chn services handlers) => Proxy protocol -> (forall a. m a -> ServerErrorIO a) -> ServerT chn () ('Package ('Just name) services) m handlers -> Application
- raiseErrors :: MonadIO m => ServerErrorIO a -> m a
- liftServerConduit :: MonadIO m => ConduitT a b ServerErrorIO r -> ConduitT a b m r
Supported messaging formats
data GRpcMessageProtocol #
Constructors
| MsgProtoBuf | |
| MsgAvro |
Instances
| Eq GRpcMessageProtocol | |
Defined in Mu.GRpc.Bridge Methods (==) :: GRpcMessageProtocol -> GRpcMessageProtocol -> Bool # (/=) :: GRpcMessageProtocol -> GRpcMessageProtocol -> Bool # | |
| Show GRpcMessageProtocol | |
Defined in Mu.GRpc.Bridge Methods showsPrec :: Int -> GRpcMessageProtocol -> ShowS # show :: GRpcMessageProtocol -> String # showList :: [GRpcMessageProtocol] -> ShowS # | |
msgProtoBuf :: Proxy 'MsgProtoBuf #
Run a Server directly
runGRpcApp :: (KnownName name, GRpcServiceHandlers ('Package ('Just name) services) protocol ServerErrorIO chn services handlers) => Proxy protocol -> Port -> ServerT chn () ('Package ('Just name) services) ServerErrorIO handlers -> IO () Source #
Run a Mu Server on the given port.
runGRpcAppTrans :: (KnownName name, GRpcServiceHandlers ('Package ('Just name) services) protocol m chn services handlers) => Proxy protocol -> Port -> (forall a. m a -> ServerErrorIO a) -> ServerT chn () ('Package ('Just name) services) m handlers -> IO () Source #
Run a Mu Server on the given port.
runGRpcAppSettings :: (KnownName name, GRpcServiceHandlers ('Package ('Just name) services) protocol m chn services handlers) => Proxy protocol -> Settings -> (forall a. m a -> ServerErrorIO a) -> ServerT chn () ('Package ('Just name) services) m handlers -> IO () Source #
Various Warp server settings. This is purposely kept as an abstract data
type so that new settings can be added without breaking backwards
compatibility. In order to create a Settings value, use defaultSettings
and the various 'set' functions to modify individual fields. For example:
setTimeout 20 defaultSettings
runGRpcAppTLS :: (KnownName name, GRpcServiceHandlers ('Package ('Just name) services) protocol m chn services handlers) => Proxy protocol -> TLSSettings -> Settings -> (forall a. m a -> ServerErrorIO a) -> ServerT chn () ('Package ('Just name) services) m handlers -> IO () Source #
Run a Mu Server using the given TLSSettings and Settings.
Go to WarpTLS to declare TLSSettings
and to Warp to declare Settings.
data TLSSettings #
Settings for WarpTLS.
Convert a Server into a WAI application
gRpcApp :: (KnownName name, GRpcServiceHandlers ('Package ('Just name) services) protocol ServerErrorIO chn services handlers) => Proxy protocol -> ServerT chn () ('Package ('Just name) services) ServerErrorIO handlers -> Application Source #
Turn a Mu Server into a WAI Application.
These Applications can be later combined using,
for example, wai-routes, or you can add middleware
from wai-extra, among others.
gRpcAppTrans :: (KnownName name, GRpcServiceHandlers ('Package ('Just name) services) protocol m chn services handlers) => Proxy protocol -> (forall a. m a -> ServerErrorIO a) -> ServerT chn () ('Package ('Just name) services) m handlers -> Application Source #
Turn a Mu Server into a WAI Application.
These Applications can be later combined using,
for example, wai-routes, or you can add middleware
from wai-extra, among others.
Raise errors as exceptions in IO
raiseErrors :: MonadIO m => ServerErrorIO a -> m a Source #
Raises errors from ServerErrorIO as exceptions
in a monad which supports IO.
This function is useful to interoperate with other
libraries which cannot handle the additional error
layer. In particular, with Conduit, as witnessed
by liftServerConduit.