distributed-process-client-server-0.2.5.1: The Cloud Haskell Application Platform

Safe HaskellNone
LanguageHaskell98

Control.Distributed.Process.ManagedProcess.Internal.Types

Contents

Description

Types used throughout the ManagedProcess framework

Synopsis

Exported data types

data InitResult s Source #

Return type for and InitHandler expression.

data GenProcess s a Source #

StateT based monad for prioritised process loops.

Instances

Monad (GenProcess s) Source # 

Methods

(>>=) :: GenProcess s a -> (a -> GenProcess s b) -> GenProcess s b #

(>>) :: GenProcess s a -> GenProcess s b -> GenProcess s b #

return :: a -> GenProcess s a #

fail :: String -> GenProcess s a #

Functor (GenProcess s) Source # 

Methods

fmap :: (a -> b) -> GenProcess s a -> GenProcess s b #

(<$) :: a -> GenProcess s b -> GenProcess s a #

MonadFix (GenProcess s) Source # 

Methods

mfix :: (a -> GenProcess s a) -> GenProcess s a #

Applicative (GenProcess s) Source # 

Methods

pure :: a -> GenProcess s a #

(<*>) :: GenProcess s (a -> b) -> GenProcess s a -> GenProcess s b #

liftA2 :: (a -> b -> c) -> GenProcess s a -> GenProcess s b -> GenProcess s c #

(*>) :: GenProcess s a -> GenProcess s b -> GenProcess s b #

(<*) :: GenProcess s a -> GenProcess s b -> GenProcess s a #

MonadIO (GenProcess s) Source # 

Methods

liftIO :: IO a -> GenProcess s a #

MonadThrow (GenProcess s) Source # 

Methods

throwM :: Exception e => e -> GenProcess s a #

MonadCatch (GenProcess s) Source # 

Methods

catch :: Exception e => GenProcess s a -> (e -> GenProcess s a) -> GenProcess s a #

MonadMask (GenProcess s) Source # 

Methods

mask :: ((forall a. GenProcess s a -> GenProcess s a) -> GenProcess s b) -> GenProcess s b #

uninterruptibleMask :: ((forall a. GenProcess s a -> GenProcess s a) -> GenProcess s b) -> GenProcess s b #

generalBracket :: GenProcess s a -> (a -> ExitCase b -> GenProcess s c) -> (a -> GenProcess s b) -> GenProcess s (b, c) #

MonadState (State s) (GenProcess s) Source # 

Methods

get :: GenProcess s (State s) #

put :: State s -> GenProcess s () #

state :: (State s -> (a, State s)) -> GenProcess s a #

runProcess :: State s -> GenProcess s a -> Process (a, State s) Source #

Run an action in the GenProcess monad.

lift :: Process a -> GenProcess s a Source #

Lift an action in the Process monad to GenProcess.

liftIO :: IO a -> GenProcess s a Source #

Lift an IO action directly into GenProcess, liftIO = lift . Process.LiftIO.

data ProcessState s Source #

Internal state of a prioritised process loop.

Instances

MonadState (State s) (GenProcess s) Source # 

Methods

get :: GenProcess s (State s) #

put :: State s -> GenProcess s () #

state :: (State s -> (a, State s)) -> GenProcess s a #

type State s = IORef (ProcessState s) Source #

Prioritised process state, held as an IORef.

type Queue = PriorityQ Int Message Source #

Internal priority queue, used by prioritised processes.

type Limit = Maybe Int Source #

Represent a max-backlog from RecvTimeoutPolicy

data Condition s m Source #

Wraps a predicate that is used to determine whether or not a handler is valid based on some combination of the current process state, the type and/or value of the input message or both.

Constructors

Condition (s -> m -> Bool)

predicated on the process state and the message

State (s -> Bool)

predicated on the process state only

Input (m -> Bool)

predicated on the input message only

data ProcessAction s Source #

The action taken by a process after a handler has run and its updated state. See "Control.Distributed.Process.ManagedProcess.Server.continue" "Control.Distributed.Process.ManagedProcess.Server.timeoutAfter" "Control.Distributed.Process.ManagedProcess.Server.hibernate" "Control.Distributed.Process.ManagedProcess.Server.stop" "Control.Distributed.Process.ManagedProcess.Server.stopWith"

Also see "Control.Distributed.Process.Management.Priority.act" and "Control.Distributed.Process.ManagedProcess.Priority.runAfter".

And other actions. This type should not be used directly.

Constructors

ProcessSkip 
ProcessActivity (GenProcess s ())

run the given activity

ProcessExpression (GenProcess s (ProcessAction s))

evaluate an expression

ProcessContinue s

continue with (possibly new) state

ProcessTimeout Delay s

timeout if no messages are received

ProcessHibernate TimeInterval s

hibernate for delay

ProcessStop ExitReason

stop the process, giving ExitReason

ProcessStopping s ExitReason

stop the process with ExitReason, with updated state

ProcessBecome (ProcessDefinition s) s

changes the current process definition

data ProcessReply r s Source #

Returned from handlers for the synchronous call protocol, encapsulates the reply data and the action to take after sending the reply. A handler can return NoReply if they wish to ignore the call.

type Action s = Process (ProcessAction s) Source #

An action (server state transition) in the Process monad

type Reply b s = Process (ProcessReply b s) Source #

An action (server state transition) causing a reply to a caller, in the Process monad

type ActionHandler s a = s -> a -> Action s Source #

An expression used to handle a message

type CallHandler s a b = s -> a -> Reply b s Source #

An expression used to handle a message and providing a reply

type CastHandler s a = ActionHandler s a Source #

An expression used to handle a cast message

type StatelessHandler s a = a -> s -> Action s Source #

An expression used to ignore server state during handling

type DeferredCallHandler s a b = CallRef b -> CallHandler s a b Source #

An expression used to handle a call message where the reply is deferred via the CallRef

type StatelessCallHandler s a b = CallRef b -> a -> Reply b s Source #

An expression used to handle a call message ignoring server state

type InfoHandler s a = ActionHandler s a Source #

An expression used to handle an info message

type ChannelHandler s a b = SendPort b -> ActionHandler s a Source #

An expression used to handle a channel message

type StatelessChannelHandler s a b = SendPort b -> StatelessHandler s a Source #

An expression used to handle a channel message in a stateless process

type InitHandler a s = a -> Process (InitResult s) Source #

An expression used to initialise a process with its state

type ShutdownHandler s = ExitState s -> ExitReason -> Process () Source #

An expression used to handle process termination

data ExitState s Source #

Informs a shutdown handler of whether it is running due to a clean shutdown, or in response to an unhandled exception.

Constructors

CleanShutdown s

given when an ordered shutdown is underway

LastKnown s 

isCleanShutdown :: ExitState s -> Bool Source #

True if the ExitState is CleanShutdown, otherwise False.

exitState :: ExitState s -> s Source #

Evaluates to the s state datum in the given ExitState.

type TimeoutHandler s = ActionHandler s Delay Source #

An expression used to handle process timeouts

data UnhandledMessagePolicy Source #

Policy for handling unexpected messages, i.e., messages which are not sent using the call or cast APIs, and which are not handled by any of the handleInfo handlers.

Constructors

Terminate

stop immediately, giving ExitOther UnhandledInput as the reason

DeadLetter ProcessId

forward the message to the given recipient

Log

log messages, then behave identically to Drop

Drop

dequeue and then drop/ignore the message

data ProcessDefinition s Source #

Stores the functions that determine runtime behaviour in response to incoming messages and a policy for responding to unhandled messages.

Constructors

ProcessDefinition 

Fields

newtype Priority a Source #

Priority of a message, encoded as an Int

Constructors

Priority 

Fields

data DispatchPriority s Source #

Dispatcher for prioritised handlers

data DispatchFilter s Source #

Provides dispatch from a variety of inputs to a typed filter handler.

Constructors

(Serializable a, Serializable b) => FilterApi 

Fields

Serializable a => FilterAny 

Fields

FilterRaw 

Fields

FilterState 

Fields

data Filter s Source #

Given as the result of evaluating a DispatchFilter. This type is intended for internal use. For an API for working with filters, see Control.Distributed.Process.ManagedProcess.Priority.

data PrioritisedProcessDefinition s Source #

A ProcessDefinition decorated with DispatchPriority for certain input domains.

data RecvTimeoutPolicy Source #

For a PrioritisedProcessDefinition, this policy determines for how long the receive loop should continue draining the process' mailbox before processing its received mail (in priority order).

If a prioritised managed process is receiving a lot of messages (into its real mailbox), the server might never get around to actually processing its inputs. This (mandatory) policy provides a guarantee that eventually (i.e., after a specified number of received messages or time interval), the server will stop removing messages from its mailbox and process those it has already received.

newtype ControlChannel m Source #

Provides a means for servers to listen on a separate, typed control channel, thereby segregating the channel from their regular (and potentially busy) mailbox.

Constructors

ControlChannel 

Fields

newtype ControlPort m Source #

The writable end of a ControlChannel.

Constructors

ControlPort 

Fields

channelControlPort :: ControlChannel m -> ControlPort m Source #

Obtain an opaque expression for communicating with a ControlChannel.

data Dispatcher s Source #

Provides dispatch from cast and call messages to a typed handler.

Constructors

(Serializable a, Serializable b) => Dispatch 

Fields

(Serializable a, Serializable b) => DispatchIf 

Fields

data DeferredDispatcher s Source #

Provides dispatch for any input, returns Nothing for unhandled messages.

Constructors

DeferredDispatcher 

data ExitSignalDispatcher s Source #

Provides dispatch for any exit signal - returns Nothing for unhandled exceptions

class MessageMatcher d where Source #

Defines the means of dispatching inbound messages to a handler

Minimal complete definition

matchDispatch

class ExternMatcher d where Source #

Defines the means of dispatching messages from external channels (e.g. those defined in terms of ControlChannel, and STM actions) to a handler.

Minimal complete definition

matchExtern, matchMapExtern

Methods

matchExtern :: UnhandledMessagePolicy -> s -> d s -> Match Message Source #

matchMapExtern :: forall m s. UnhandledMessagePolicy -> s -> (Message -> m) -> d s -> Match m Source #

data Message a b Source #

Message type used internally by the call, cast, and rpcChan APIs.

Constructors

CastMessage a 
CallMessage a (CallRef b) 
ChanMessage a (SendPort b) 

Instances

(Eq a, Eq b) => Eq (Message a b) Source # 

Methods

(==) :: Message a b -> Message a b -> Bool #

(/=) :: Message a b -> Message a b -> Bool #

(Show a, Show b) => Show (Message a b) Source # 

Methods

showsPrec :: Int -> Message a b -> ShowS #

show :: Message a b -> String #

showList :: [Message a b] -> ShowS #

Generic (Message a b) Source # 

Associated Types

type Rep (Message a b) :: * -> * #

Methods

from :: Message a b -> Rep (Message a b) x #

to :: Rep (Message a b) x -> Message a b #

(Serializable a, Serializable b) => Binary (Message a b) Source # 

Methods

put :: Message a b -> Put #

get :: Get (Message a b) #

putList :: [Message a b] -> Put #

(NFSerializable a, NFSerializable b) => NFData (Message a b) Source # 

Methods

rnf :: Message a b -> () #

type Rep (Message a b) Source # 
type Rep (Message a b) = D1 * (MetaData "Message" "Control.Distributed.Process.ManagedProcess.Internal.Types" "distributed-process-client-server-0.2.5.1-BTofhwwXL5R2qkWyoacqPv" False) ((:+:) * (C1 * (MetaCons "CastMessage" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a))) ((:+:) * (C1 * (MetaCons "CallMessage" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (CallRef b))))) (C1 * (MetaCons "ChanMessage" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (SendPort b)))))))

data CallResponse a Source #

Response type for the call API

Constructors

CallResponse a CallId 

Instances

Eq a => Eq (CallResponse a) Source # 
Show a => Show (CallResponse a) Source # 
Generic (CallResponse a) Source # 

Associated Types

type Rep (CallResponse a) :: * -> * #

Methods

from :: CallResponse a -> Rep (CallResponse a) x #

to :: Rep (CallResponse a) x -> CallResponse a #

Serializable a => Binary (CallResponse a) Source # 

Methods

put :: CallResponse a -> Put #

get :: Get (CallResponse a) #

putList :: [CallResponse a] -> Put #

NFSerializable a => NFData (CallResponse a) Source # 

Methods

rnf :: CallResponse a -> () #

type Rep (CallResponse a) Source # 
type Rep (CallResponse a) = D1 * (MetaData "CallResponse" "Control.Distributed.Process.ManagedProcess.Internal.Types" "distributed-process-client-server-0.2.5.1-BTofhwwXL5R2qkWyoacqPv" False) (C1 * (MetaCons "CallResponse" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CallId))))

type CallId = MonitorRef Source #

wrapper for a MonitorRef

newtype CallRef a Source #

Wraps a consumer of the call API

Constructors

CallRef 

Fields

Instances

Eq (CallRef a) Source # 

Methods

(==) :: CallRef a -> CallRef a -> Bool #

(/=) :: CallRef a -> CallRef a -> Bool #

Show (CallRef a) Source # 

Methods

showsPrec :: Int -> CallRef a -> ShowS #

show :: CallRef a -> String #

showList :: [CallRef a] -> ShowS #

Generic (CallRef a) Source # 

Associated Types

type Rep (CallRef a) :: * -> * #

Methods

from :: CallRef a -> Rep (CallRef a) x #

to :: Rep (CallRef a) x -> CallRef a #

Binary (CallRef a) Source # 

Methods

put :: CallRef a -> Put #

get :: Get (CallRef a) #

putList :: [CallRef a] -> Put #

NFData (CallRef a) Source # 

Methods

rnf :: CallRef a -> () #

Resolvable (CallRef a) Source # 
Routable (CallRef a) Source # 

Methods

sendTo :: (Serializable m, Resolvable (CallRef a)) => CallRef a -> m -> Process () #

unsafeSendTo :: (NFSerializable m, Resolvable (CallRef a)) => CallRef a -> m -> Process () #

type Rep (CallRef a) Source # 
type Rep (CallRef a) = D1 * (MetaData "CallRef" "Control.Distributed.Process.ManagedProcess.Internal.Types" "distributed-process-client-server-0.2.5.1-BTofhwwXL5R2qkWyoacqPv" True) (C1 * (MetaCons "CallRef" PrefixI True) (S1 * (MetaSel (Just Symbol "unCaller") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Recipient, CallId))))

data CallRejected Source #

Sent to a consumer of the call API when a server filter expression explicitly rejects an incoming call message.

Constructors

CallRejected String CallId 

Instances

Eq CallRejected Source # 
Show CallRejected Source # 
Generic CallRejected Source # 

Associated Types

type Rep CallRejected :: * -> * #

Binary CallRejected Source # 
NFData CallRejected Source # 

Methods

rnf :: CallRejected -> () #

type Rep CallRejected Source # 
type Rep CallRejected = D1 * (MetaData "CallRejected" "Control.Distributed.Process.ManagedProcess.Internal.Types" "distributed-process-client-server-0.2.5.1-BTofhwwXL5R2qkWyoacqPv" False) (C1 * (MetaCons "CallRejected" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CallId))))

makeRef :: Recipient -> CallId -> CallRef a Source #

Creates a CallRef for the given Recipient and CallId

caller :: forall a b. Message a b -> Maybe Recipient Source #

Retrieve the Recipient from a Message. If the supplied message is a cast or chan message will evaluate to Nothing, otherwise Just ref.

rejectToCaller :: forall a b. Message a b -> String -> Process () Source #

Reject a call message with the supplied string. Sends CallRejected to the recipient if the input is a CallMessage, otherwise has no side effects.

recipient :: CallRef a -> Recipient Source #

Retrieve the Recipient for a CallRef.

tag :: CallRef a -> CallId Source #

Retrieve the CallId for a CallRef.

initCall :: forall s a b. (Addressable s, Serializable a, Serializable b) => s -> a -> Process (CallRef b) Source #

The send part of the call client-server interaction. The resulting CallRef can be used to identify the corrolary response message (if one is sent by the server), and is unique to this call-reply pair.

unsafeInitCall :: forall s a b. (Addressable s, NFSerializable a, NFSerializable b) => s -> a -> Process (CallRef b) Source #

Version of initCall that utilises "unsafeSendTo".

waitResponse :: forall b. Serializable b => Maybe TimeInterval -> CallRef b -> Process (Maybe (Either ExitReason b)) Source #

Wait on the server's response after an "initCall" has been previously been sent.

This function does not trap asynchronous exceptions.