| Copyright | (c) Serokell, 2016 |
|---|---|
| License | GPL-3 (see the file LICENSE) |
| Maintainer | Serokell <hi@serokell.io> |
| Stability | experimental |
| Portability | POSIX, GHC |
| Safe Haskell | None |
| Language | Haskell2010 |
Control.TimeWarp.Rpc.MonadRpc
Contents
Description
This module contains MonadRpc typeclass which abstracts over
RPC communication.
- type Port = Int
- type Host = ByteString
- type NetworkAddress = (Host, Port)
- class MonadThrow r => MonadRpc r where
- class RpcType t
- execClientTimeout :: (MonadTimed m, MonadRpc m, MessagePack a, TimeUnit t) => t -> NetworkAddress -> Client a -> m a
- data Method m = Method {
- methodName :: String
- methodBody :: [Object] -> m Object
- data Client a where
- Client :: MessagePack a => String -> [Object] -> Client a
- method :: MethodType m f => String -> f -> Method m
- call :: RpcType t => String -> t
- type Server = ServerT IO
- data ServerT m a :: (* -> *) -> * -> *
- class Monad m => MethodType m f
- data RpcError :: *
Documentation
type Host = ByteString Source #
Host address.
type NetworkAddress = (Host, Port) Source #
Full node address.
class MonadThrow r => MonadRpc r where Source #
Defines protocol of RPC layer.
Minimal complete definition
Methods
execClient :: MessagePack a => NetworkAddress -> Client a -> r a Source #
Executes remote method call.
serve :: Port -> [Method r] -> r () Source #
Starts RPC server with a set of RPC methods.
Collects function name and arguments (it's msgpack-rpc implementation is hidden, need our own).
Minimal complete definition
rpcc
Instances
| MessagePack o => RpcType (Client o) Source # | |
| (RpcType t, MessagePack p) => RpcType (p -> t) Source # | |
execClientTimeout :: (MonadTimed m, MonadRpc m, MessagePack a, TimeUnit t) => t -> NetworkAddress -> Client a -> m a Source #
Same as execClient, but allows to set up timeout for a call (see
timeout).
Keeps method definition.
Constructors
| Method | |
Fields
| |
Keeps function name and arguments.
Constructors
| Client :: MessagePack a => String -> [Object] -> Client a |
Instances
| MessagePack o => RpcType (Client o) Source # | |
method :: MethodType m f => String -> f -> Method m Source #
Creates method available for RPC-requests. It accepts method name (which would be refered by clients) and it's body.
call :: RpcType t => String -> t Source #
Creates a function call. It accepts function name and arguments.
data ServerT m a :: (* -> *) -> * -> * #
Instances
| MonadTrans ServerT | |
| (Functor m, MonadThrow m, MessagePack o) => MethodType m (ServerT m o) | |
| Monad m => Monad (ServerT m) | |
| Functor m => Functor (ServerT m) | |
| Applicative m => Applicative (ServerT m) | |
| MonadIO m => MonadIO (ServerT m) | |
class Monad m => MethodType m f #
Minimal complete definition
toBody
Instances
| MethodType MsgPackRpc f => MethodType MsgPackRpc (MsgPackRpc f) # | |
| (Functor m, MonadThrow m, MessagePack o) => MethodType m (ServerT m o) | |
| (MonadThrow m, MessagePack o, MethodType m r) => MethodType m (o -> r) | |
Constructors
| ServerError Object | |
| ResultTypeError String Object | |
| ProtocolError String |
Orphan instances
| Monad m => MethodType m Object Source # | |
| MonadThrow m => MonadThrow (ServerT m) Source # | |
| MonadCatch m => MonadCatch (ServerT m) Source # | |
| WithNamedLogger m => WithNamedLogger (ServerT m) Source # | |