Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type Request ix = (Int, Int, ix, [Object])
- type Response = (Int, Int, Object, Object)
- packRequest :: (Eq mth, MessagePack mth) => [mth] -> Request mth -> ByteString
- packResponse :: Response -> ByteString
- unpackRequest :: MessagePack ix => Object -> Either DecodeError (Request ix)
- unpackResponse :: Object -> Either DecodeError Response
- data MethodVal = MethodVal {}
- data MethodDocs = MethodDocs {
- methodArgs :: [MethodVal]
- methodRetv :: MethodVal
- class Monad m => MethodType m f where
- data Method m = Method {
- methodName :: Text
- methodDocs :: MethodDocs
- methodBody :: [Object] -> m Object
- method :: MethodType m f => Text -> MethodDocs -> f -> Method m
- data RpcError
- newtype ServerError = ServerError Text
- class RpcType r where
- call :: RpcType a => Text -> a
Documentation
packRequest :: (Eq mth, MessagePack mth) => [mth] -> Request mth -> ByteString Source #
packResponse :: Response -> ByteString Source #
unpackRequest :: MessagePack ix => Object -> Either DecodeError (Request ix) 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 # |
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 # | |
Method | |
|
:: MethodType m f | |
=> Text | Method name |
-> MethodDocs | |
-> f | Method body |
-> Method m |
Build a method
RPC error type
RemoteError Object | Server error |
ResultTypeError Text Object | Result type mismatch |
ProtocolError Text | Protocol error |
Instances
Eq RpcError Source # | |
Ord RpcError Source # | |
Defined in Network.MessagePack.Types.Error | |
Show RpcError Source # | |
Exception RpcError Source # | |
Defined in Network.MessagePack.Types.Error toException :: RpcError -> SomeException # fromException :: SomeException -> Maybe RpcError # displayException :: RpcError -> String # |
newtype ServerError Source #
Instances
Show ServerError Source # | |
Defined in Network.MessagePack.Types.Error showsPrec :: Int -> ServerError -> ShowS # show :: ServerError -> String # showList :: [ServerError] -> ShowS # | |
Exception ServerError Source # | |
Defined in Network.MessagePack.Types.Error |
class RpcType r where Source #
Instances
(MessagePack o, RpcType r) => RpcType (o -> r) Source # | |
(MonadIO m, MonadThrow m, MessagePack o) => RpcType (ClientT m o) Source # | |