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

Safe HaskellNone
LanguageHaskell98

Control.Distributed.Process.ManagedProcess.Internal.GenProcess

Description

This is the Process implementation of a managed process

Synopsis

Documentation

recvLoop :: ProcessDefinition s -> s -> Delay -> Process ExitReason Source #

Managed process loop.

Evaluating this function will cause the caller to enter a server loop, constantly reading messages from its mailbox (and/or other supplied control planes) and passing these to handler functions in the supplied process definition. Only when it is determined that the server process should terminate - either by the handlers deciding to stop the process, or by an unhandled exit signal or other form of failure condition (e.g. synchronous or asynchronous exceptions).

precvLoop :: PrioritisedProcessDefinition s -> s -> Delay -> Process ExitReason Source #

Prioritised process loop.

Evaluating this function will cause the caller to enter a server loop, constantly reading messages from its mailbox (and/or other supplied control planes) and passing these to handler functions in the supplied process definition. Only when it is determined that the server process should terminate - either by the handlers deciding to stop the process, or by an unhandled exit signal or other form of failure condition (e.g. synchronous or asynchronous exceptions).

ensureIOManagerIsRunning before evaluating this loop...

currentTimeout :: GenProcess s Delay Source #

The current (user supplied) timeout.

systemTimeout :: GenProcess s Timer Source #

The Timer for the system timeout. See drainTimeout.

drainTimeout :: GenProcess s Delay Source #

The Delay for the drainTimeout.

processState :: GenProcess s s Source #

Evaluates to the user defined state for the currently executing server loop.

processDefinition :: GenProcess s (ProcessDefinition s) Source #

The ProcessDefinition for the current loop.

processFilters :: GenProcess s [DispatchFilter s] Source #

The list of filters for the current loop.

processUnhandledMsgPolicy :: GenProcess s UnhandledMessagePolicy Source #

Evaluates to the UnhandledMessagePolicy for the current loop.

processQueue :: GenProcess s [Message] Source #

Returns a read only view on the internal priority queue.

gets :: forall s a. (ProcessState s -> a) -> GenProcess s a Source #

Evaluate the given function over the ProcessState s for the caller, and return the result.

getAndModifyState :: (ProcessState s -> (ProcessState s, a)) -> GenProcess s a Source #

Modify our state and return a value (potentially from it).

modifyState :: (ProcessState s -> ProcessState s) -> GenProcess s () Source #

Modify our state.

setUserTimeout :: Delay -> GenProcess s () Source #

Set the user timeout applied whilst a prioritised process loop is in a blocking receive.

setProcessState :: s -> GenProcess s () Source #

Set the current process state.

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 #

peek :: GenProcess s (Maybe Message) Source #

Peek at the next available message in the internal priority queue, without removing it.

push :: forall s. Message -> GenProcess s () Source #

Push a message to the head of the internal priority queue.

enqueue :: forall s. Message -> GenProcess s () Source #

Enqueue a message to the back of the internal priority queue.

dequeue :: GenProcess s (Maybe Message) Source #

Dequeue a message from the internal priority queue.

addUserTimer :: Timer -> Message -> GenProcess s TimerKey Source #

Add a user timer, bound to the given datum.

removeUserTimer :: TimerKey -> GenProcess s () Source #

Remove a user timer, for the given key.

eval :: forall s. GenProcess s (ProcessAction s) -> Action s Source #

Evaluate an expression in the GenProcess monad.

act :: forall s. GenProcess s () -> Action s Source #

Warning: This interface is intended for internal use only

Produce an Action s that, if it is the result of a handler, will cause the server loop to evaluate the supplied expression. This is given in the GenProcess monad, which is intended for internal use only.

runAfter :: forall s m. Serializable m => TimeInterval -> m -> GenProcess s () Source #

Warning: This interface is intended for internal use only

Starts a timer and adds it as a user timeout.

evalAfter :: forall s m. Serializable m => TimeInterval -> m -> s -> Action s Source #

Evaluate any matching info handler with the supplied datum after waiting for at least TimeInterval. The process state (for the resulting Action s) is also given and the process loop will go on as per Server.continue.

Informally, evaluating this expression (such that the Action is given as the result of a handler or filter) will ensure that the supplied message (datum) is availble for processing no sooner than TimeInterval.

Currently, this expression creates an Action that triggers immediate evaluation in the process loop before continuing with the given state. The process loop stores a user timeout for the given time interval, which is trigerred like a wait/drain timeout. This implementation is subject to change.