Copyright | (c) Tim Watson 2012 - 2017 |
---|---|
License | BSD3 (see the file LICENSE) |
Maintainer | Tim Watson <watson.timothy@gmail.com> |
Stability | experimental |
Portability | non-portable (requires concurrency) |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
The Server Portion of the Managed Process API, as presented by the
GenProcess
monad. These functions are generally intended for internal
use, but the API is relatively stable and therefore they have been re-exported
here for general use. Note that if you modify a process' internal state
(especially that of the internal priority queue) then you are responsible for
any alteratoin that makes to the semantics of your processes behaviour.
See Control.Distributed.Process.ManagedProcess.Internal.GenProcess
Synopsis
- reply :: forall r s. Serializable r => r -> GenProcess s (ProcessReply r s)
- replyWith :: forall r s. Serializable r => r -> ProcessAction s -> GenProcess s (ProcessReply r s)
- noReply :: Serializable r => ProcessAction s -> GenProcess s (ProcessReply r s)
- continue :: GenProcess s (ProcessAction s)
- timeoutAfter :: Delay -> GenProcess s (ProcessAction s)
- hibernate :: TimeInterval -> GenProcess s (ProcessAction s)
- stop :: ExitReason -> GenProcess s (ProcessAction s)
- reject :: forall r s. String -> GenProcess s (ProcessReply r s)
- rejectWith :: forall r m s. Show r => r -> GenProcess s (ProcessReply m s)
- become :: forall s. ProcessDefinition s -> GenProcess s (ProcessAction s)
- haltNoReply :: forall s r. Serializable r => ExitReason -> GenProcess s (ProcessReply r s)
- lift :: Process a -> GenProcess s a
- recvLoop :: ProcessDefinition s -> s -> Delay -> Process ExitReason
- precvLoop :: PrioritisedProcessDefinition s -> s -> Delay -> Process ExitReason
- currentTimeout :: GenProcess s Delay
- systemTimeout :: GenProcess s Timer
- drainTimeout :: GenProcess s Delay
- processState :: GenProcess s s
- processDefinition :: GenProcess s (ProcessDefinition s)
- processFilters :: GenProcess s [DispatchFilter s]
- processUnhandledMsgPolicy :: GenProcess s UnhandledMessagePolicy
- processQueue :: GenProcess s [Message]
- gets :: forall s a. (ProcessState s -> a) -> GenProcess s a
- getAndModifyState :: (ProcessState s -> (ProcessState s, a)) -> GenProcess s a
- modifyState :: (ProcessState s -> ProcessState s) -> GenProcess s ()
- setUserTimeout :: Delay -> GenProcess s ()
- setProcessState :: s -> GenProcess s ()
- data GenProcess s a
- peek :: GenProcess s (Maybe Message)
- push :: forall s. Message -> GenProcess s ()
- enqueue :: forall s. Message -> GenProcess s ()
- dequeue :: GenProcess s (Maybe Message)
- addUserTimer :: Timer -> Message -> GenProcess s TimerKey
- removeUserTimer :: TimerKey -> GenProcess s ()
- eval :: forall s. GenProcess s (ProcessAction s) -> Action s
- act :: forall s. GenProcess s () -> Action s
- runAfter :: forall s m. Serializable m => TimeInterval -> m -> GenProcess s ()
- evalAfter :: forall s m. Serializable m => TimeInterval -> m -> s -> Action s
Server actions
reply :: forall r s. Serializable r => r -> GenProcess s (ProcessReply r s) Source #
Instructs the process to send a reply and continue running.
replyWith :: forall r s. Serializable r => r -> ProcessAction s -> GenProcess s (ProcessReply r s) Source #
Instructs the process to send a reply and evaluate the ProcessAction
.
noReply :: Serializable r => ProcessAction s -> GenProcess s (ProcessReply r s) Source #
Instructs the process to skip sending a reply and evaluate a ProcessAction
continue :: GenProcess s (ProcessAction s) Source #
Instructs the process to continue running and receiving messages.
timeoutAfter :: Delay -> GenProcess s (ProcessAction s) Source #
Instructs the process loop to wait for incoming messages until Delay
is exceeded. If no messages are handled during this period, the timeout
handler will be called. Note that this alters the process timeout permanently
such that the given Delay
will remain in use until changed.
Note that timeoutAfter NoDelay
will cause the timeout handler to execute
immediately if no messages are present in the process' mailbox.
hibernate :: TimeInterval -> GenProcess s (ProcessAction s) Source #
Instructs the process to hibernate for the given TimeInterval
. Note
that no messages will be removed from the mailbox until after hibernation has
ceased. This is equivalent to calling threadDelay
.
stop :: ExitReason -> GenProcess s (ProcessAction s) Source #
Instructs the process to terminate, giving the supplied reason. If a valid
shutdownHandler
is installed, it will be called with the ExitReason
returned from this call, along with the process state.
reject :: forall r s. String -> GenProcess s (ProcessReply r s) Source #
Reject the message we're currently handling.
rejectWith :: forall r m s. Show r => r -> GenProcess s (ProcessReply m s) Source #
Reject the message we're currently handling, giving an explicit reason.
become :: forall s. ProcessDefinition s -> GenProcess s (ProcessAction s) Source #
The server loop will execute against the supplied ProcessDefinition
, allowing
the process to change its behaviour (in terms of message handlers, exit handling,
termination, unhandled message policy, etc)
haltNoReply :: forall s r. Serializable r => ExitReason -> GenProcess s (ProcessReply r s) Source #
Halt process execution during a call handler, without paying any attention to the expected return type.
lift :: Process a -> GenProcess s a Source #
Lift an action in the Process
monad to GenProcess
.
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
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.
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.