Safe Haskell | None |
---|---|
Language | Haskell98 |
Types used throughout the ManagedProcess framework
- data InitResult s
- = InitOk s Delay
- | InitStop String
- | InitIgnore
- data GenProcess s a
- runProcess :: State s -> GenProcess s a -> Process (a, State s)
- lift :: Process a -> GenProcess s a
- liftIO :: IO a -> GenProcess s a
- data ProcessState s = ProcessState {
- timeoutSpec :: RecvTimeoutPolicy
- procDef :: ProcessDefinition s
- procPrio :: [DispatchPriority s]
- procFilters :: [DispatchFilter s]
- usrTimeout :: Delay
- sysTimeout :: Timer
- usrTimers :: TimerMap
- internalQ :: Queue
- procState :: s
- type State s = IORef (ProcessState s)
- type Queue = PriorityQ Int Message
- type Limit = Maybe Int
- data Condition s m
- data ProcessAction s
- = ProcessSkip
- | ProcessActivity (GenProcess s ())
- | ProcessExpression (GenProcess s (ProcessAction s))
- | ProcessContinue s
- | ProcessTimeout Delay s
- | ProcessHibernate TimeInterval s
- | ProcessStop ExitReason
- | ProcessStopping s ExitReason
- | ProcessBecome (ProcessDefinition s) s
- data ProcessReply r s
- = ProcessReply r (ProcessAction s)
- | ProcessReject String (ProcessAction s)
- | NoReply (ProcessAction s)
- type Action s = Process (ProcessAction s)
- type Reply b s = Process (ProcessReply b s)
- type ActionHandler s a = s -> a -> Action s
- type CallHandler s a b = s -> a -> Reply b s
- type CastHandler s a = ActionHandler s a
- type StatelessHandler s a = a -> s -> Action s
- type DeferredCallHandler s a b = CallRef b -> CallHandler s a b
- type StatelessCallHandler s a b = CallRef b -> a -> Reply b s
- type InfoHandler s a = ActionHandler s a
- type ChannelHandler s a b = SendPort b -> ActionHandler s a
- type StatelessChannelHandler s a b = SendPort b -> StatelessHandler s a
- type InitHandler a s = a -> Process (InitResult s)
- type ShutdownHandler s = ExitState s -> ExitReason -> Process ()
- data ExitState s
- = CleanShutdown s
- | LastKnown s
- isCleanShutdown :: ExitState s -> Bool
- exitState :: ExitState s -> s
- type TimeoutHandler s = ActionHandler s Delay
- data UnhandledMessagePolicy
- = Terminate
- | DeadLetter ProcessId
- | Log
- | Drop
- data ProcessDefinition s = ProcessDefinition {}
- newtype Priority a = Priority {}
- data DispatchPriority s
- = PrioritiseCall { }
- | PrioritiseCast { }
- | PrioritiseInfo { }
- data DispatchFilter s
- = (Serializable a, Serializable b) => FilterApi { }
- | Serializable a => FilterAny { }
- | FilterRaw { }
- | FilterState {
- stateFilter :: s -> Process (Maybe (Filter s))
- data Filter s
- = FilterOk s
- | FilterSafe s
- | Show m => FilterReject m s
- | FilterSkip s
- | FilterStop s ExitReason
- data PrioritisedProcessDefinition s = PrioritisedProcessDefinition {
- processDef :: ProcessDefinition s
- priorities :: [DispatchPriority s]
- filters :: [DispatchFilter s]
- recvTimeout :: RecvTimeoutPolicy
- data RecvTimeoutPolicy
- newtype ControlChannel m = ControlChannel {
- unControl :: (SendPort (Message m ()), ReceivePort (Message m ()))
- newControlChan :: Serializable m => Process (ControlChannel m)
- newtype ControlPort m = ControlPort {}
- channelControlPort :: ControlChannel m -> ControlPort m
- data Dispatcher s
- = (Serializable a, Serializable b) => Dispatch {
- dispatch :: s -> Message a b -> Process (ProcessAction s)
- | (Serializable a, Serializable b) => DispatchIf {
- dispatch :: s -> Message a b -> Process (ProcessAction s)
- dispatchIf :: s -> Message a b -> Bool
- = (Serializable a, Serializable b) => Dispatch {
- data ExternDispatcher s
- = (Serializable a, Serializable b) => DispatchCC {
- channel :: ReceivePort (Message a b)
- dispatchChan :: s -> Message a b -> Process (ProcessAction s)
- | Serializable a => DispatchSTM {
- stmAction :: STM a
- dispatchStm :: s -> a -> Process (ProcessAction s)
- matchStm :: Match Message
- matchAnyStm :: forall m. (Message -> m) -> Match m
- = (Serializable a, Serializable b) => DispatchCC {
- data DeferredDispatcher s = DeferredDispatcher {
- dispatchInfo :: s -> Message -> Process (Maybe (ProcessAction s))
- data ExitSignalDispatcher s = ExitSignalDispatcher {
- dispatchExit :: s -> ProcessId -> Message -> Process (Maybe (ProcessAction s))
- class MessageMatcher d where
- class ExternMatcher d where
- data Message a b
- = CastMessage a
- | CallMessage a (CallRef b)
- | ChanMessage a (SendPort b)
- data CallResponse a = CallResponse a CallId
- type CallId = MonitorRef
- newtype CallRef a = CallRef {}
- data CallRejected = CallRejected String CallId
- makeRef :: Recipient -> CallId -> CallRef a
- caller :: forall a b. Message a b -> Maybe Recipient
- rejectToCaller :: forall a b. Message a b -> String -> Process ()
- recipient :: CallRef a -> Recipient
- tag :: CallRef a -> CallId
- initCall :: forall s a b. (Addressable s, Serializable a, Serializable b) => s -> a -> Process (CallRef b)
- unsafeInitCall :: forall s a b. (Addressable s, NFSerializable a, NFSerializable b) => s -> a -> Process (CallRef b)
- waitResponse :: forall b. Serializable b => Maybe TimeInterval -> CallRef b -> Process (Maybe (Either ExitReason b))
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.
Monad (GenProcess s) Source # | |
Functor (GenProcess s) Source # | |
MonadFix (GenProcess s) Source # | |
Applicative (GenProcess s) Source # | |
MonadIO (GenProcess s) Source # | |
MonadThrow (GenProcess s) Source # | |
MonadCatch (GenProcess s) Source # | |
MonadMask (GenProcess s) Source # | |
MonadState (State s) (GenProcess s) Source # | |
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.
ProcessState | |
|
MonadState (State s) (GenProcess s) Source # | |
type State s = IORef (ProcessState s) Source #
Prioritised process state, held as an IORef
.
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.
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.
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 |
ProcessStopping s ExitReason | stop the process with |
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.
ProcessReply r (ProcessAction s) | |
ProcessReject String (ProcessAction s) | |
NoReply (ProcessAction s) |
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
Informs a shutdown handler of whether it is running due to a clean shutdown, or in response to an unhandled exception.
CleanShutdown s | given when an ordered shutdown is underway |
LastKnown s |
isCleanShutdown :: ExitState s -> Bool Source #
True
if the ExitState
is CleanShutdown
, otherwise False
.
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.
Terminate | stop immediately, giving |
DeadLetter ProcessId | forward the message to the given recipient |
Log | log messages, then behave identically to |
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.
ProcessDefinition | |
|
data DispatchPriority s Source #
Dispatcher for prioritised handlers
data DispatchFilter s Source #
Provides dispatch from a variety of inputs to a typed filter handler.
(Serializable a, Serializable b) => FilterApi | |
Serializable a => FilterAny | |
FilterRaw | |
FilterState | |
|
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.
FilterOk s | |
FilterSafe s | |
Show m => FilterReject m s | |
FilterSkip s | |
FilterStop s ExitReason |
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.
ControlChannel | |
|
newControlChan :: Serializable m => Process (ControlChannel m) Source #
Creates a new ControlChannel
.
newtype ControlPort m Source #
The writable end of a ControlChannel
.
Eq (ControlPort m) Source # | |
Show (ControlPort m) Source # | |
Serializable m => Binary (ControlPort m) Source # | |
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.
(Serializable a, Serializable b) => Dispatch | |
| |
(Serializable a, Serializable b) => DispatchIf | |
|
data ExternDispatcher s Source #
Provides dispatch for channels and STM actions
(Serializable a, Serializable b) => DispatchCC | |
| |
Serializable a => DispatchSTM | |
|
data DeferredDispatcher s Source #
Provides dispatch for any input, returns Nothing
for unhandled messages.
DeferredDispatcher | |
|
data ExitSignalDispatcher s Source #
Provides dispatch for any exit signal - returns Nothing
for unhandled exceptions
ExitSignalDispatcher | |
|
class MessageMatcher d where Source #
Defines the means of dispatching inbound messages to a handler
matchDispatch :: UnhandledMessagePolicy -> s -> d s -> Match (ProcessAction s) Source #
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.
matchExtern :: UnhandledMessagePolicy -> s -> d s -> Match Message Source #
matchMapExtern :: forall m s. UnhandledMessagePolicy -> s -> (Message -> m) -> d s -> Match m Source #
Message
type used internally by the call, cast, and rpcChan APIs.
CastMessage a | |
CallMessage a (CallRef b) | |
ChanMessage a (SendPort b) |
data CallResponse a Source #
Response type for the call API
Eq a => Eq (CallResponse a) Source # | |
Show a => Show (CallResponse a) Source # | |
Generic (CallResponse a) Source # | |
Serializable a => Binary (CallResponse a) Source # | |
NFSerializable a => NFData (CallResponse a) Source # | |
type Rep (CallResponse a) Source # | |
type CallId = MonitorRef Source #
wrapper for a MonitorRef
Wraps a consumer of the call API
data CallRejected Source #
Sent to a consumer of the call API when a server filter expression explicitly rejects an incoming call message.
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.
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.