time-warp-0.1.1.2: Distributed systems execution emulation

Copyright(c) Serokell, 2016
LicenseGPL-3 (see the file LICENSE)
MaintainerSerokell <hi@serokell.io>
Stabilityexperimental
PortabilityPOSIX, GHC
Safe HaskellNone
LanguageHaskell2010

Control.TimeWarp.Rpc.MonadRpc

Contents

Description

This module contains MonadRpc typeclass which abstracts over RPC communication.

Synopsis

Documentation

type Port = Int Source #

Port number.

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

execClient, serve

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.

class RpcType t Source #

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 # 

Methods

rpcc :: String -> [Object] -> Client o

(RpcType t, MessagePack p) => RpcType (p -> t) Source # 

Methods

rpcc :: String -> [Object] -> p -> t

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).

data Method m Source #

Keeps method definition.

Constructors

Method 

Fields

data Client a where Source #

Keeps function name and arguments.

Constructors

Client :: MessagePack a => String -> [Object] -> Client a 

Instances

MessagePack o => RpcType (Client o) Source # 

Methods

rpcc :: String -> [Object] -> Client o

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 

Methods

lift :: Monad m => m a -> ServerT m a #

(Functor m, MonadThrow m, MessagePack o) => MethodType m (ServerT m o) 

Methods

toBody :: ServerT m o -> [Object] -> m Object

Monad m => Monad (ServerT m) 

Methods

(>>=) :: ServerT m a -> (a -> ServerT m b) -> ServerT m b #

(>>) :: ServerT m a -> ServerT m b -> ServerT m b #

return :: a -> ServerT m a #

fail :: String -> ServerT m a #

Functor m => Functor (ServerT m) 

Methods

fmap :: (a -> b) -> ServerT m a -> ServerT m b #

(<$) :: a -> ServerT m b -> ServerT m a #

Applicative m => Applicative (ServerT m) 

Methods

pure :: a -> ServerT m a #

(<*>) :: ServerT m (a -> b) -> ServerT m a -> ServerT m b #

(*>) :: ServerT m a -> ServerT m b -> ServerT m b #

(<*) :: ServerT m a -> ServerT m b -> ServerT m a #

MonadIO m => MonadIO (ServerT m) 

Methods

liftIO :: IO a -> ServerT m a #

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) 

Methods

toBody :: ServerT m o -> [Object] -> m Object

(MonadThrow m, MessagePack o, MethodType m r) => MethodType m (o -> r) 

Methods

toBody :: (o -> r) -> [Object] -> m Object

Orphan instances