Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data Method m
- class Monad m => MethodType m f where
- data MethodDocs = MethodDocs {
- methodArgs :: [MethodVal]
- methodRetv :: MethodVal
- data MethodVal = MethodVal {}
- newtype ServerT m a = ServerT {
- runServerT :: m a
- type Server = ServerT IO
- method :: MethodType m f => Text -> MethodDocs -> f -> Method m
- methodName :: Method m -> Text
- methodDocs :: Method m -> MethodDocs
- serve :: (MonadBaseControl IO m, MonadIO m, MonadCatch m, MonadUnliftIO m) => Int -> [Method m] -> m ()
- runServer :: (MonadBaseControl IO m, MonadIO m, MonadCatch m, MonadUnliftIO m) => Int -> [Method m] -> m ()
RPC method types
class Monad m => MethodType m f where Source #
Instances
(Functor m, MonadThrow m, MessagePack o) => MethodType m (ServerT m o) Source # | |
(MonadThrow m, MessagePack o, MethodType m r) => MethodType m (o -> r) Source # | |
data MethodDocs Source #
MessagePack RPC method
MethodDocs | |
|
Instances
Eq MethodDocs Source # | |
Defined in Network.MessagePack.Types.Server (==) :: MethodDocs -> MethodDocs -> Bool # (/=) :: MethodDocs -> MethodDocs -> Bool # | |
Read MethodDocs Source # | |
Defined in Network.MessagePack.Types.Server readsPrec :: Int -> ReadS MethodDocs # readList :: ReadS [MethodDocs] # readPrec :: ReadPrec MethodDocs # readListPrec :: ReadPrec [MethodDocs] # | |
Show MethodDocs Source # | |
Defined in Network.MessagePack.Types.Server showsPrec :: Int -> MethodDocs -> ShowS # show :: MethodDocs -> String # showList :: [MethodDocs] -> ShowS # |
ServerT | |
|
Instances
MonadTrans ServerT Source # | |
Defined in Network.MessagePack.Server.Basic | |
(Functor m, MonadThrow m, MessagePack o) => MethodType m (ServerT m o) Source # | |
Monad m => Monad (ServerT m) Source # | |
Functor m => Functor (ServerT m) Source # | |
MonadFail m => MonadFail (ServerT m) Source # | |
Defined in Network.MessagePack.Server.Basic | |
Applicative m => Applicative (ServerT m) Source # | |
Defined in Network.MessagePack.Server.Basic | |
MonadIO m => MonadIO (ServerT m) Source # | |
Defined in Network.MessagePack.Server.Basic |
Build a method
:: MethodType m f | |
=> Text | Method name |
-> MethodDocs | |
-> f | Method body |
-> Method m |
Build a method
methodName :: Method m -> Text Source #
methodDocs :: Method m -> MethodDocs Source #
Start RPC server
:: (MonadBaseControl IO m, MonadIO m, MonadCatch m, MonadUnliftIO m) | |
=> Int | Port number |
-> [Method m] | list of methods |
-> m () |
Start RPC server with a set of RPC methods.
:: (MonadBaseControl IO m, MonadIO m, MonadCatch m, MonadUnliftIO m) | |
=> Int | Port number |
-> [Method m] | list of methods |
-> m () |
Start RPC server with a set of RPC methods.