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 Prioritised Server portion of the Managed Process API.
Synopsis
- prioritiseCall :: forall s a b. (Serializable a, Serializable b) => (s -> a -> Priority b) -> DispatchPriority s
- prioritiseCall_ :: forall s a b. (Serializable a, Serializable b) => (a -> Priority b) -> DispatchPriority s
- prioritiseCast :: forall s a. Serializable a => (s -> a -> Priority ()) -> DispatchPriority s
- prioritiseCast_ :: forall s a. Serializable a => (a -> Priority ()) -> DispatchPriority s
- prioritiseInfo :: forall s a. Serializable a => (s -> a -> Priority ()) -> DispatchPriority s
- prioritiseInfo_ :: forall s a. Serializable a => (a -> Priority ()) -> DispatchPriority s
- setPriority :: Int -> Priority m
- check :: forall s. FilterHandler s -> DispatchFilter s
- raw :: forall s. (s -> Message -> Process Bool) -> (s -> Message -> Process (Maybe (Filter s))) -> FilterHandler s
- raw_ :: forall s. (Message -> Process Bool) -> (s -> Message -> Process (Maybe (Filter s))) -> FilterHandler s
- api :: forall s m b. (Serializable m, Serializable b) => (s -> m -> Process Bool) -> (s -> Message m b -> Process (Filter s)) -> FilterHandler s
- api_ :: forall m b s. (Serializable m, Serializable b) => (m -> Process Bool) -> (s -> Message m b -> Process (Filter s)) -> FilterHandler s
- info :: forall s m. Serializable m => (s -> m -> Process Bool) -> (s -> m -> Process (Filter s)) -> FilterHandler s
- info_ :: forall s m. Serializable m => (m -> Process Bool) -> (s -> m -> Process (Filter s)) -> FilterHandler s
- refuse :: forall s m. Serializable m => (m -> Bool) -> DispatchFilter s
- reject :: forall s m r. Show r => r -> s -> m -> Process (Filter s)
- rejectApi :: forall s m b r. (Show r, Serializable m, Serializable b) => r -> s -> Message m b -> Process (Filter s)
- store :: (s -> s) -> DispatchFilter s
- storeM :: forall s m. Serializable m => (s -> m -> Process s) -> DispatchFilter s
- crash :: forall s. s -> ExitReason -> Process (Filter s)
- ensure :: forall s. (s -> Bool) -> DispatchFilter s
- ensureM :: forall s m. Serializable m => (s -> m -> Process Bool) -> DispatchFilter s
- data Filter s
- data DispatchFilter s
- safe :: forall s m. Serializable m => (s -> m -> Bool) -> DispatchFilter s
- apiSafe :: forall s m b. (Serializable m, Serializable b) => (s -> m -> Maybe b -> Bool) -> DispatchFilter s
- safely :: forall s. (s -> Message -> Bool) -> DispatchFilter s
- data Message a b
- evalAfter :: forall s m. Serializable m => TimeInterval -> m -> s -> Action s
- currentTimeout :: GenProcess s Delay
- processState :: GenProcess s s
- processDefinition :: GenProcess s (ProcessDefinition s)
- processFilters :: GenProcess s [DispatchFilter s]
- processUnhandledMsgPolicy :: GenProcess s UnhandledMessagePolicy
- setUserTimeout :: Delay -> GenProcess s ()
- setProcessState :: s -> GenProcess s ()
- data GenProcess s a
- peek :: GenProcess s (Maybe Message)
- push :: forall s. Message -> GenProcess s ()
- addUserTimer :: Timer -> Message -> GenProcess s TimerKey
- act :: forall s. GenProcess s () -> Action s
- runAfter :: forall s m. Serializable m => TimeInterval -> m -> GenProcess s ()
Prioritising API Handlers
prioritiseCall :: forall s a b. (Serializable a, Serializable b) => (s -> a -> Priority b) -> DispatchPriority s Source #
Prioritise a call handler
prioritiseCall_ :: forall s a b. (Serializable a, Serializable b) => (a -> Priority b) -> DispatchPriority s Source #
Prioritise a call handler, ignoring the server's state
prioritiseCast :: forall s a. Serializable a => (s -> a -> Priority ()) -> DispatchPriority s Source #
Prioritise a cast handler
prioritiseCast_ :: forall s a. Serializable a => (a -> Priority ()) -> DispatchPriority s Source #
Prioritise a cast handler, ignoring the server's state
prioritiseInfo :: forall s a. Serializable a => (s -> a -> Priority ()) -> DispatchPriority s Source #
Prioritise an info handler
prioritiseInfo_ :: forall s a. Serializable a => (a -> Priority ()) -> DispatchPriority s Source #
Prioritise an info handler, ignoring the server's state
setPriority :: Int -> Priority m Source #
Sets an explicit priority from 1..100. Values > 100 are rounded to 100, and values < 1 are set to 0.
Creating Filters
check :: forall s. FilterHandler s -> DispatchFilter s Source #
Create a filter from a FilterHandler
.
raw :: forall s. (s -> Message -> Process Bool) -> (s -> Message -> Process (Maybe (Filter s))) -> FilterHandler s Source #
A raw filter (targetting raw messages).
raw_ :: forall s. (Message -> Process Bool) -> (s -> Message -> Process (Maybe (Filter s))) -> FilterHandler s Source #
A raw filter that ignores the server state in its condition expression.
api :: forall s m b. (Serializable m, Serializable b) => (s -> m -> Process Bool) -> (s -> Message m b -> Process (Filter s)) -> FilterHandler s Source #
An API filter (targetting call, cast, and chan messages).
api_ :: forall m b s. (Serializable m, Serializable b) => (m -> Process Bool) -> (s -> Message m b -> Process (Filter s)) -> FilterHandler s Source #
An API filter that ignores the server state in its condition expression.
info :: forall s m. Serializable m => (s -> m -> Process Bool) -> (s -> m -> Process (Filter s)) -> FilterHandler s Source #
An info filter (targetting info messages of a specific type)
info_ :: forall s m. Serializable m => (m -> Process Bool) -> (s -> m -> Process (Filter s)) -> FilterHandler s Source #
An info filter that ignores the server state in its condition expression.
refuse :: forall s m. Serializable m => (m -> Bool) -> DispatchFilter s Source #
Refuse messages for which the given expression evaluates to True
.
reject :: forall s m r. Show r => r -> s -> m -> Process (Filter s) Source #
Create a filter expression that will reject all messages of a specific type.
rejectApi :: forall s m b r. (Show r, Serializable m, Serializable b) => r -> s -> Message m b -> Process (Filter s) Source #
A version of reject
that deals with API messages (i.e. call, cast, etc)
and in the case of a call interaction, will reject the messages and reply to
the sender accordingly (with CallRejected
).
store :: (s -> s) -> DispatchFilter s Source #
Modify the server state every time a message is recieved.
storeM :: forall s m. Serializable m => (s -> m -> Process s) -> DispatchFilter s Source #
Motify the server state when messages of a certain type arrive...
crash :: forall s. s -> ExitReason -> Process (Filter s) Source #
Create a filter expression that will crash (i.e. stop) the server.
ensure :: forall s. (s -> Bool) -> DispatchFilter s Source #
Ensure that the server state is consistent with the given expression each
time a message arrives/is processed. If the expression evaluates to True
then the filter will evaluate to FilterOk, otherwise FilterStop (which
will cause the server loop to stop with ExitOther filterFail
).
ensureM :: forall s m. Serializable m => (s -> m -> Process Bool) -> DispatchFilter s Source #
As ensure
but runs in the Process
monad, and matches only inputs of type m
.
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 DispatchFilter s Source #
Provides dispatch from a variety of inputs to a typed filter handler.
safe :: forall s m. Serializable m => (s -> m -> Bool) -> DispatchFilter s Source #
Given a check expression, if it evaluates to True
for some input,
then do not dequeue the message until after any matching handlers have
successfully run, or the the unhandled message policy is chosen if none match.
Thus, if an exit signal (async exception) terminates execution of a handler, and we
have an installed exit handler which allows the process to continue running,
we will retry the input in question since it has not been fully dequeued prior
to the exit signal arriving.
apiSafe :: forall s m b. (Serializable m, Serializable b) => (s -> m -> Maybe b -> Bool) -> DispatchFilter s Source #
As safe
, but as applied to api messages (i.e. those originating from
call as cast client interactions).
safely :: forall s. (s -> Message -> Bool) -> DispatchFilter s Source #
As safe
, but matches on a raw message.
Message
type used internally by the call, cast, and rpcChan APIs.
Instances
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.
currentTimeout :: GenProcess s Delay Source #
The current (user supplied) timeout.
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.
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.
addUserTimer :: Timer -> Message -> GenProcess s TimerKey Source #
Add a user timer, bound to the given datum.
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.