time-warp-1.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.MonadDialog

Contents

Description

This module defines Dialog monad, which is add-on over Transfer and allows to send/receive whole messages, where serialization strategy could be defined in arbitrary way.

For Dialog, send function is trivial; listen function infinitelly captures messages from input stream, processing them in separate thread then.

Mainly, following structure of message is currently supported: [header, name, content] where name uniquely defines type of message.

Given message could be deserealized as sum of header and raw data; then user can just send the message further, or deserialize and process message's content.

Synopsis

MonadDialog

Dialog

newtype Dialog p m a Source #

Default implementation of MonadDialog. Keeps packing type in context, allowing to use the same serialization strategy all over the code without extra boilerplate.

Constructors

Dialog 

Instances

MonadTransfer s m => MonadDialog s p (Dialog p m) Source # 
MonadState s m => MonadState s (Dialog p m) Source # 

Methods

get :: Dialog p m s #

put :: s -> Dialog p m () #

state :: (s -> (a, s)) -> Dialog p m a #

MonadBase IO m => MonadBase IO (Dialog p m) Source # 

Methods

liftBase :: IO α -> Dialog p m α #

MonadBaseControl IO m => MonadBaseControl IO (Dialog p m) Source # 

Associated Types

type StM (Dialog p m :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase (Dialog p m) IO -> IO a) -> Dialog p m a #

restoreM :: StM (Dialog p m) a -> Dialog p m a #

MonadTransfer s m => MonadTransfer s (Dialog p m) Source # 
MonadTrans (Dialog p) Source # 

Methods

lift :: Monad m => m a -> Dialog p m a #

MonadTransControl (Dialog p) Source # 

Associated Types

type StT (Dialog p :: (* -> *) -> * -> *) a :: * #

Methods

liftWith :: Monad m => (Run (Dialog p) -> m a) -> Dialog p m a #

restoreT :: Monad m => m (StT (Dialog p) a) -> Dialog p m a #

Monad m => Monad (Dialog p m) Source # 

Methods

(>>=) :: Dialog p m a -> (a -> Dialog p m b) -> Dialog p m b #

(>>) :: Dialog p m a -> Dialog p m b -> Dialog p m b #

return :: a -> Dialog p m a #

fail :: String -> Dialog p m a #

Functor m => Functor (Dialog p m) Source # 

Methods

fmap :: (a -> b) -> Dialog p m a -> Dialog p m b #

(<$) :: a -> Dialog p m b -> Dialog p m a #

Applicative m => Applicative (Dialog p m) Source # 

Methods

pure :: a -> Dialog p m a #

(<*>) :: Dialog p m (a -> b) -> Dialog p m a -> Dialog p m b #

(*>) :: Dialog p m a -> Dialog p m b -> Dialog p m b #

(<*) :: Dialog p m a -> Dialog p m b -> Dialog p m a #

MonadIO m => MonadIO (Dialog p m) Source # 

Methods

liftIO :: IO a -> Dialog p m a #

MonadThrow m => MonadThrow (Dialog p m) Source # 

Methods

throwM :: Exception e => e -> Dialog p m a #

MonadCatch m => MonadCatch (Dialog p m) Source # 

Methods

catch :: Exception e => Dialog p m a -> (e -> Dialog p m a) -> Dialog p m a #

MonadMask m => MonadMask (Dialog p m) Source # 

Methods

mask :: ((forall a. Dialog p m a -> Dialog p m a) -> Dialog p m b) -> Dialog p m b #

uninterruptibleMask :: ((forall a. Dialog p m a -> Dialog p m a) -> Dialog p m b) -> Dialog p m b #

CanLog m => CanLog (Dialog p m) Source # 

Methods

dispatchMessage :: LoggerName -> Severity -> Text -> Dialog p m () #

(HasLoggerName m, Monad m) => HasLoggerName (Dialog p m) Source # 
Monad m => WrappedM (Dialog p m) Source # 

Associated Types

type UnwrappedM (Dialog p m :: * -> *) :: * -> * #

Methods

_WrappedM :: (Profunctor p, Functor f) => p (UnwrappedM (Dialog p m) a) (f (UnwrappedM (Dialog p m) a)) -> p (Dialog p m a) (f (Dialog p m a)) #

packM :: Dialog p m a -> UnwrappedM (Dialog p m) a #

unpackM :: UnwrappedM (Dialog p m) a -> Dialog p m a #

MonadTimed m => MonadTimed (Dialog p m) Source # 

Methods

virtualTime :: Dialog p m Microsecond Source #

currentTime :: Dialog p m Microsecond Source #

wait :: RelativeToNow -> Dialog p m () Source #

fork :: Dialog p m () -> Dialog p m (ThreadId (Dialog p m)) Source #

myThreadId :: Dialog p m (ThreadId (Dialog p m)) Source #

throwTo :: Exception e => ThreadId (Dialog p m) -> e -> Dialog p m () Source #

timeout :: TimeUnit t => t -> Dialog p m a -> Dialog p m a Source #

forkSlave :: Dialog p m () -> Dialog p m (ThreadId (Dialog p m)) Source #

type StT (Dialog p) a Source # 
type StT (Dialog p) a = StT (ReaderT * p) a
type UnwrappedM (Dialog p m) Source # 
type ThreadId (Dialog p m) Source # 
type ThreadId (Dialog p m) = ThreadId m
type StM (Dialog p m) a Source # 
type StM (Dialog p m) a = ComposeSt (Dialog p) m a

runDialog :: p -> Dialog p m a -> m a Source #

Runs given Dialog.

ForkStrategy

data ForkStrategy s Source #

Constructors

ForkStrategy 

Fields

Communication methods

Functions differ by suffix, meanings are following:

  • No suffix - operates with plain message (TODO: weaken Packable constraints)
  • H - operates with message with header
  • R - operates with message in raw form with header

send :: (Packable p (WithHeaderData () (ContentData r)), MonadDialog s p m, MonadThrow m) => NetworkAddress -> r -> m () Source #

Send plain message

sendH :: (Packable p (WithHeaderData h (ContentData r)), MonadDialog s p m, MonadThrow m) => NetworkAddress -> h -> r -> m () Source #

Send message with header

sendR :: (Packable p (WithHeaderData h RawData), MonadDialog s p m, MonadThrow m) => NetworkAddress -> h -> RawData -> m () Source #

Send message given in raw form

listen :: (Unpackable p (WithHeaderData () RawData), Unpackable p NameData, MonadListener s m, MonadDialog s p m) => Binding -> [Listener s p m] -> m (m ()) Source #

Starts server with given set of listeners.

listenH :: (Unpackable p (WithHeaderData h RawData), Unpackable p NameData, MonadListener s m, MonadDialog s p m) => Binding -> [ListenerH s p h m] -> m (m ()) Source #

Starts server with given set of listeners, which allow to read both header and content of received message.

listenR :: (Unpackable p (WithHeaderData h RawData), Unpackable p NameData, MonadListener s m, MonadDialog s p m) => Binding -> [ListenerH s p h m] -> ListenerR s h m -> m (m ()) Source #

Starts server with given raw listener and set of typed listeners. First, raw listener is applied, it allows to read header and content in raw form of received message. If raw listener returned True, then processing continues with given typed listeners in the way defined in listenH.

reply :: (Packable p (WithHeaderData () (ContentData r)), MonadDialog s p m, MonadResponse s m, MonadThrow m) => r -> m () Source #

Sends message to peer node.

replyH :: (Packable p (WithHeaderData h (ContentData r)), MonadDialog s p m, MonadResponse s m, MonadThrow m) => h -> r -> m () Source #

Sends message with given header to peer node.

replyR :: (Packable p (WithHeaderData h RawData), MonadDialog s p m, MonadResponse s m, MonadThrow m) => h -> RawData -> m () Source #

Sends message with given header and message content in raw form to peer node.

Listeners

data Listener s p m Source #

Creates plain listener which accepts message.

Constructors

(Unpackable p (ContentData r), Message r) => Listener (r -> ResponseT s m ()) 

data ListenerH s p h m Source #

Creates listener which accepts header and message.

Constructors

(Unpackable p (ContentData r), Message r) => ListenerH ((h, r) -> ResponseT s m ()) 

type ListenerR s h m = (h, RawData) -> ResponseT s m Bool Source #

Creates listener which accepts header and raw data. Returns, whether message souhld then be deserialized and passed to typed listener.

getListenerName :: Listener s p m -> MessageName Source #

Gets name of message type, acceptable by this listener.

getListenerNameH :: ListenerH s p h m -> MessageName Source #

Gets name of message type, acceptable by this listener.

Misc