This module is the core of Cloud Haskell. It provides processes, messages, monitoring, and configuration.
- data ProcessM a
- data NodeId
- data ProcessId
- type PeerInfo = Map String [NodeId]
- nullPid :: ProcessId
- getSelfPid :: ProcessM ProcessId
- getSelfNode :: ProcessM NodeId
- isPidLocal :: ProcessId -> ProcessM Bool
- expect :: Serializable a => ProcessM a
- data MatchM q a
- receive :: [MatchM q ()] -> ProcessM (Maybe q)
- receiveWait :: [MatchM q ()] -> ProcessM q
- receiveTimeout :: Int -> [MatchM q ()] -> ProcessM (Maybe q)
- match :: Serializable a => (a -> ProcessM q) -> MatchM q ()
- matchIf :: Serializable a => (a -> Bool) -> (a -> ProcessM q) -> MatchM q ()
- matchCond :: Serializable a => (a -> Maybe (ProcessM q)) -> MatchM q ()
- matchUnknown :: ProcessM q -> MatchM q ()
- matchUnknownThrow :: MatchM q ()
- matchProcessDown :: ProcessId -> ProcessM q -> MatchM q ()
- send :: Serializable a => ProcessId -> a -> ProcessM ()
- sendQuiet :: Serializable a => ProcessId -> a -> ProcessM TransmitStatus
- logS :: LogSphere -> LogLevel -> String -> ProcessM ()
- say :: String -> ProcessM ()
- type LogSphere = String
- data LogLevel
- = LoSay
- | LoFatal
- | LoCritical
- | LoImportant
- | LoStandard
- | LoInformation
- | LoTrivial
- data LogTarget
- data LogFilter
- data LogConfig = LogConfig {}
- setLogConfig :: LogConfig -> ProcessM ()
- getLogConfig :: ProcessM LogConfig
- setNodeLogConfig :: LogConfig -> ProcessM ()
- setRemoteNodeLogConfig :: NodeId -> LogConfig -> ProcessM ()
- defaultLogConfig :: LogConfig
- ptry :: Exception e => ProcessM a -> ProcessM (Either e a)
- ptimeout :: Int -> ProcessM a -> ProcessM (Maybe a)
- pbracket :: ProcessM a -> (a -> ProcessM b) -> (a -> ProcessM c) -> ProcessM c
- pfinally :: ProcessM a -> ProcessM b -> ProcessM a
- data UnknownMessageException = UnknownMessageException String
- data ServiceException = ServiceException String
- data TransmitException = TransmitException TransmitStatus
- data TransmitStatus
- nameSet :: String -> ProcessM ()
- nameQuery :: NodeId -> String -> ProcessM (Maybe ProcessId)
- nameQueryOrStart :: NodeId -> String -> Closure (ProcessM ()) -> ProcessM ProcessId
- spawnLocal :: ProcessM () -> ProcessM ProcessId
- spawnLocalAnd :: ProcessM () -> ProcessM () -> ProcessM ProcessId
- forkProcess :: ProcessM () -> ProcessM ProcessId
- spawn :: NodeId -> Closure (ProcessM ()) -> ProcessM ProcessId
- spawnAnd :: NodeId -> Closure (ProcessM ()) -> AmSpawnOptions -> ProcessM ProcessId
- spawnLink :: NodeId -> Closure (ProcessM ()) -> ProcessM ProcessId
- unpause :: ProcessId -> ProcessM ()
- data AmSpawnOptions = AmSpawnOptions {}
- defaultSpawnOptions :: AmSpawnOptions
- data MonitorAction
- = MaMonitor
- | MaLink
- | MaLinkError
- data SignalReason
- = SrNormal
- | SrException String
- | SrNoPing
- | SrInvalid
- data ProcessMonitorException = ProcessMonitorException ProcessId SignalReason
- linkProcess :: ProcessId -> ProcessM ()
- monitorProcess :: ProcessId -> ProcessId -> MonitorAction -> ProcessM ()
- unmonitorProcess :: ProcessId -> ProcessId -> MonitorAction -> ProcessM ()
- withMonitor :: ProcessId -> ProcessM a -> ProcessM a
- pingNode :: NodeId -> ProcessM Bool
- callRemote :: Serializable a => NodeId -> Closure (ProcessM a) -> ProcessM a
- callRemotePure :: Serializable a => NodeId -> Closure a -> ProcessM a
- callRemoteIO :: Serializable a => NodeId -> Closure (IO a) -> ProcessM a
- terminate :: ProcessM a
- readConfig :: Bool -> Maybe FilePath -> IO Config
- emptyConfig :: Config
- data Config = Config {
- cfgRole :: !String
- cfgHostName :: !HostName
- cfgListenPort :: !PortId
- cfgLocalRegistryListenPort :: !PortId
- cfgPeerDiscoveryPort :: !PortId
- cfgNetworkMagic :: !String
- cfgKnownHosts :: ![String]
- cfgRoundtripTimeout :: !Int
- cfgMaxOutgoing :: !Int
- cfgPromiseFlushDelay :: !Int
- cfgPromisePrefix :: !String
- cfgArgs :: [String]
- getConfig :: ProcessM Config
- getCfgArgs :: ProcessM [String]
- initNode :: Config -> Lookup -> IO (MVar Node)
- roleDispatch :: MVar Node -> (String -> ProcessM ()) -> IO ()
- setDaemonic :: ProcessM ()
- waitForThreads :: MVar Node -> IO ()
- performFinalization :: MVar Node -> IO ()
- forkAndListenAndDeliver :: MVar Node -> Config -> IO ()
- runLocalProcess :: MVar Node -> ProcessM () -> IO ProcessId
- makeClosure :: (Typeable a, Serializable v) => String -> v -> ProcessM (Closure a)
- invokeClosure :: Typeable a => Closure a -> ProcessM (Maybe a)
- evaluateClosure :: Typeable b => Closure a -> ProcessM (Maybe (Payload -> b))
- getQueueLength :: ProcessM Int
- nodeFromPid :: ProcessId -> NodeId
- localFromPid :: ProcessId -> LocalProcessId
- hostFromNid :: NodeId -> HostName
- type PortId = Int
- type LocalProcessId = Int
- localRegistryHello :: ProcessM ()
- localRegistryRegisterNode :: ProcessM ()
- localRegistryQueryNodes :: NodeId -> ProcessM (Maybe PeerInfo)
- localRegistryUnregisterNode :: ProcessM ()
- sendSimple :: Serializable a => ProcessId -> a -> PayloadDisposition -> ProcessM TransmitStatus
- makeNodeFromHost :: String -> PortId -> NodeId
- getNewMessageLocal :: Node -> LocalProcessId -> STM (Maybe Message)
- getProcess :: ProcessM Process
- data Message
- data Process
- prNodeRef :: Process -> MVar Node
- roundtripResponse :: (Serializable a, Serializable b) => (a -> ProcessM (b, q)) -> MatchM q ()
- roundtripResponseAsync :: (Serializable a, Serializable b) => (a -> (b -> ProcessM ()) -> ProcessM q) -> Bool -> MatchM q ()
- roundtripQuery :: (Serializable a, Serializable b) => PayloadDisposition -> ProcessId -> a -> ProcessM (Either TransmitStatus b)
- roundtripQueryMulti :: (Serializable a, Serializable b) => PayloadDisposition -> [ProcessId] -> a -> ProcessM [Either TransmitStatus b]
- makePayloadClosure :: Closure a -> Maybe (Closure Payload)
- getLookup :: ProcessM Lookup
- diffTime :: UTCTime -> UTCTime -> Int
- roundtripQueryImpl :: (Serializable a, Serializable b) => Int -> PayloadDisposition -> ProcessId -> a -> (b -> c) -> [MatchM (Either TransmitStatus c) ()] -> ProcessM (Either TransmitStatus c)
- roundtripQueryUnsafe :: (Serializable a, Serializable b) => PayloadDisposition -> ProcessId -> a -> ProcessM (Either TransmitStatus b)
- data PayloadDisposition
- suppressTransmitException :: ProcessM a -> ProcessM (Maybe a)
- data Node
- getMessagePayload :: Serializable a => Message -> Maybe a
- getMessageType :: Message -> String
- startSpawnerService :: ProcessM ()
- startLoggingService :: ProcessM ()
- startProcessMonitorService :: ProcessM ()
- startLocalRegistry :: Config -> Bool -> IO TransmitStatus
- startFinalizerService :: ProcessM () -> ProcessM ()
- startNodeMonitorService :: ProcessM ()
- startProcessRegistryService :: ProcessM ()
- standaloneLocalRegistry :: String -> IO ()
The Process monad
The monad ProcessM is the core of the process layer. Functions
in the ProcessM monad may participate in messaging and create
additional concurrent processes. You can create
a ProcessM context from an IO
context with the remoteInit
function.
Identifies a node somewhere on the network. These
can be queried from getPeers
. See also getSelfNode
Identifies a process somewhere on the network. These
are produced by the spawn
family of functions and
consumed by send
. When a process ends, its process ID
ceases to be valid. See also getSelfPid
type PeerInfo = Map String [NodeId]Source
Created by Remote.Peer.getPeers
, this maps
each role to a list of nodes that have that role.
It can be examined directly or queried with
findPeerByRole
.
getSelfPid :: ProcessM ProcessIdSource
Returns the process ID of the current process.
getSelfNode :: ProcessM NodeIdSource
Returns the node ID of the node that the current process is running on.
isPidLocal :: ProcessId -> ProcessM BoolSource
Returns true if the given process ID is associated with the current node. Does not examine if the process is currently running.
Message receiving
expect :: Serializable a => ProcessM aSource
A simple way to receive messages.
This will return the first message received
of the specified type; if no such message
is available, the function will block.
Unlike the receive
family of functions,
this function does not allow the notion
of choice in message extraction.
receive :: [MatchM q ()] -> ProcessM (Maybe q)Source
Examines the message queue of the current process, matching each message against each of the
provided message pattern clauses (typically provided by a function from the match
family). If
a message matches, the corresponding handler is invoked and its result is returned. If no
message matches, Nothing is returned.
receiveWait :: [MatchM q ()] -> ProcessM qSource
Examines the message queue of the current process, matching each message against each of the
provided message pattern clauses (typically provided by a function from the match
family). If
a message matches, the corresponding handler is invoked and its result is returned. If no
message matches, the function blocks until a matching message is received.
receiveTimeout :: Int -> [MatchM q ()] -> ProcessM (Maybe q)Source
Examines the message queue of the current process, matching each message against each of the
provided message pattern clauses (typically provided by a function from the match
family). If
a message matches, the corresponding handler is invoked and its result is returned. If no
message matches, the function blocks until a matching message is received, or until the
specified time in microseconds has elapsed, at which point it will return Nothing.
If the specified time is 0, this function is equivalent to receive
.
match :: Serializable a => (a -> ProcessM q) -> MatchM q ()Source
Used to specify a message pattern in receiveWait
and related functions.
Only messages containing data of type a, where a is the argument to the user-provided
function in the first parameter of match
, will be removed from the queue, at which point
the user-provided function will be invoked.
matchUnknown :: ProcessM q -> MatchM q ()Source
A catch-all variant of match
that invokes user-provided code and
will extact any message from the queue. This is useful for matching
against messages that are not recognized. Since message matching patterns
are evaluated in order, this function, if used, should be the last element
in the list of matchers given to receiveWait
and similar functions.
matchUnknownThrow :: MatchM q ()Source
A variant of matchUnknown
that throws a UnknownMessageException
if the process receives a message that isn't extracted by another message matcher.
Equivalent to:
matchUnknown (throw (UnknownMessageException "..."))
matchProcessDown :: ProcessId -> ProcessM q -> MatchM q ()Source
A specialized version of match
(for use with receive
, receiveWait
and friends) for catching process down
messages. This way processes can avoid waiting forever for a response from another process that has crashed.
Intended to be used within a withMonitor
block, e.g.:
withMonitor apid $ do send apid QueryMsg receiveWait [ match (\AnswerMsg -> return "ok"), matchProcessDown apid (return "aborted") ]
Message sending
send :: Serializable a => ProcessId -> a -> ProcessM ()Source
Sends a message to the given process. If the
process isn't running or can't be accessed,
this function will throw a TransmitException
.
The message must implement the Serializable
interface.
sendQuiet :: Serializable a => ProcessId -> a -> ProcessM TransmitStatusSource
Like send
, but in case of error returns a value rather than throw
an exception.
Logging functions
logS :: LogSphere -> LogLevel -> String -> ProcessM ()Source
Generates a log entry, using the process's current logging configuration.
-
LogSphere
indicates the subsystem generating this message. SYS in the case of componentes of the framework. -
LogLevel
indicates the importance of the message. - The third parameter is the log message.
Both of the first two parameters may be used to filter log output.
say :: String -> ProcessM ()Source
Uses the logging facility to produce non-filterable, programmatic output. Shouldn't be used for informational logging, but rather for application-level output.
Specifies the subsystem or region that is responsible for
generating a given log entry. This is useful in conjunction
with LogFilter
to limit displayed log output to the
particular area of your program that you are currently debugging.
The SYS, TSK, and SAY spheres are used by the framework
for messages relating to the Process layer, the Task layer,
and the say
function.
The remainder of values are free for use at the application level.
Specifies the importance of a particular log entry. Can also be used to filter log output.
LoSay | Non-suppressible application-level emission |
LoFatal | |
LoCritical | |
LoImportant | |
LoStandard | The default log level |
LoInformation | |
LoTrivial |
A preference as to what is done with log messages
Specifies which log messages will be output. All log messages of importance below the current log level or not among the criterea given here will be suppressed. This type lets you limit displayed log messages to certain components.
Expresses a current configuration of the logging
subsystem, which determines which log messages to
be output and where to send them when they are.
Both processes and nodes have log configurations,
set with setLogConfig
and setNodeLogConfig
respectively. The node log configuration is
used for all processes that have not explicitly
set their log configuration. Otherwise, the
process log configuration takes priority.
setLogConfig :: LogConfig -> ProcessM ()Source
Set the process's log configuration. This overrides any node-level log configuration
getLogConfig :: ProcessM LogConfigSource
Gets the currently active log configuration for the current process; if the current process doesn't have a log configuration set, the process's log configuration will be returned
setNodeLogConfig :: LogConfig -> ProcessM ()Source
Sets the node's log configuration
setRemoteNodeLogConfig :: NodeId -> LogConfig -> ProcessM ()Source
Sets the log configuration of a remote node. May throw TransmitException
defaultLogConfig :: LogConfigSource
The default log configuration represents a starting point for setting your own configuration. It is:
logLevel = LoStandard logTarget = LtStdout logFilter = LfAll
Exception handling
data UnknownMessageException Source
Thrown by matchUnknownThrow
in response to a message
of a wrong type being received by a process
data ServiceException Source
Thrown by Remote.Process system services in response to some problem
data TransmitException Source
Thrown by various network-related functions when communication with a host has failed
data TransmitStatus Source
Process naming
nameSet :: String -> ProcessM ()Source
Assigns a name to the current process. The name is local to the
node. On each node, each process may have only one name, and each
name may be given to only one node. If this function is called
more than once by the same process, or called more than once
with the name on a single node, it will throw a ServiceException
.
The PID of a named process can be queried later with nameQuery
. When the
named process ends, its name will again become available.
One reason to use named processes is to create node-local state.
This example lets each node have its own favorite color, which can
be changed and queried.
nodeFavoriteColor :: ProcessM () nodeFavoriteColor = do nameSet "favorite_color" loop Blue where loop color = receiveWait [ match (\newcolor -> return newcolor), match (\pid -> send pid color >> return color) ] >>= loop setFavoriteColor :: NodeId -> Color -> ProcessM () setFavoriteColor nid color = do (Just pid) <- nameQuery nid "favorite_color" send pid color getFavoriteColor :: NodeId -> ProcessM Color getFavoriteColor nid = do (Just pid) <- nameQuery nid "favorite_color" mypid <- getSelfPid send pid mypid expect
nameQuery :: NodeId -> String -> ProcessM (Maybe ProcessId)Source
Query the PID of a named process on a particular node. If no process of that name exists, or if that process has ended, this function returns Nothing.
nameQueryOrStart :: NodeId -> String -> Closure (ProcessM ()) -> ProcessM ProcessIdSource
Similar to nameQuery
but if the named process doesn't exist,
it will be started from the given closure. If the process is
already running, the closure will be ignored.
Process spawning and monitoring
spawnLocalAnd :: ProcessM () -> ProcessM () -> ProcessM ProcessIdSource
Start executing a process on the current node. This is a variation of spawnLocal
which accepts two blocks of user-defined code. The first block
is the main body of the code to run concurrently. The second block is a prefix
which is run in the new process, prior to the main body, but its completion
is guaranteed before spawnAnd returns. Thus, the prefix code is useful for
initializing the new process synchronously.
forkProcess :: ProcessM () -> ProcessM ProcessIdSource
A synonym for spawnLocal
spawn :: NodeId -> Closure (ProcessM ()) -> ProcessM ProcessIdSource
Start a process running the code, given as a closure, on the specified node.
If successful, returns the process ID of the new process. If unsuccessful,
throw a TransmitException
.
spawnAnd :: NodeId -> Closure (ProcessM ()) -> AmSpawnOptions -> ProcessM ProcessIdSource
A variant of spawn
that allows greater control over how the remote process is started.
spawnLink :: NodeId -> Closure (ProcessM ()) -> ProcessM ProcessIdSource
A variant of spawn
that starts the remote process with
bidirectoinal monitoring, as in linkProcess
unpause :: ProcessId -> ProcessM ()Source
If a remote process has been started in a paused state with spawnAnd
,
it will be running but inactive until unpaused. Use this function to unpause
such a function. It has no effect on processes that are not paused or that
have already been unpaused.
data AmSpawnOptions Source
AmSpawnOptions | |
|
data MonitorAction Source
The different kinds of monitoring available between processes.
MaMonitor | MaMonitor means that the monitor process will be sent a ProcessMonitorException message when the monitee terminates for any reason. |
MaLink | MaLink means that the monitor process will receive an asynchronous exception of type ProcessMonitorException when the monitee terminates for any reason |
MaLinkError | MaLinkError means that the monitor process will receive an asynchronous exception of type ProcessMonitorException when the monitee terminates abnormally |
data SignalReason Source
Part of the notification system of process monitoring, indicating why the monitor is being notified.
SrNormal | the monitee terminated normally |
SrException String | the monitee terminated with an uncaught exception, which is given as a string |
SrNoPing | the monitee is believed to have ended or be inaccessible, as the node on which its running is not responding to pings. This may indicate a network bisection or that the remote node has crashed. |
SrInvalid | SrInvalid: the monitee was not running at the time of the attempt to establish monitoring |
data ProcessMonitorException Source
The main form of notification to a monitoring process that a monitored process has terminated.
This data structure can be delivered to the monitor either as a message (if the monitor is
of type MaMonitor
) or as an asynchronous exception (if the monitor is of type MaLink
or MaLinkError
).
It contains the PID of the monitored process and the reason for its nofication.
linkProcess :: ProcessId -> ProcessM ()Source
Establishes bidirectional abnormal termination monitoring between the current
process and another. Monitoring established with linkProcess
is bidirectional and signals only in the event of abnormal termination.
In other words, linkProcess a
is equivalent to:
monitorProcess mypid a MaLinkError monitorProcess a mypid MaLinkError
monitorProcess :: ProcessId -> ProcessId -> MonitorAction -> ProcessM ()Source
Establishes unidirectional processing of another process. The format is:
monitorProcess monitor monitee action
Here,
- monitor is the process that will be notified if the monitee goes down
- monitee is the process that will be monitored
- action determines how the monitor will be notified
Monitoring will remain in place until one of the processes ends or until
unmonitorProcess
is called. Calls to monitorProcess
are cumulative,
such that calling monitorProcess
3 three times on the same pair of processes
will ensure that monitoring will stay in place until unmonitorProcess
is called
three times on the same pair of processes.
If the monitee is not currently running, the monitor will be signalled immediately.
See also MonitorAction
.
unmonitorProcess :: ProcessId -> ProcessId -> MonitorAction -> ProcessM ()Source
Removes monitoring established by monitorProcess
. Note that the type of
monitoring, given in the third parameter, must match in order for monitoring
to be removed. If monitoring has not already been established between these
two processes, this function takes not action.
withMonitor :: ProcessId -> ProcessM a -> ProcessM aSource
Establishes temporary monitoring of another process. The process to be monitored is given in the
first parameter, and the code to run in the second. If the given process goes down while the code
in the second parameter is running, a process down message will be sent to the current process,
which can be handled by matchProcessDown
.
pingNode :: NodeId -> ProcessM BoolSource
Sends a small message to the specified node to determine if it's alive. If the node cannot be reached or does not respond within a time frame, the function will return False.
callRemote :: Serializable a => NodeId -> Closure (ProcessM a) -> ProcessM aSource
Invokes a function on a remote node. The function must be given by a closure. This function will block until the called function completes or the connection is broken.
callRemotePure :: Serializable a => NodeId -> Closure a -> ProcessM aSource
callRemoteIO :: Serializable a => NodeId -> Closure (IO a) -> ProcessM aSource
Config file
readConfig :: Bool -> Maybe FilePath -> IO ConfigSource
Reads in configuration data from external sources, specifically from the command line arguments
and a configuration file.
The first parameter to this function determines whether command-line arguments are consulted.
If the second parameter is not Nothing
then it should be the name of the configuration file;
an exception will be thrown if the specified file does not exist.
Usually, this function shouldn't be called directly, but rather from Remote.Init.remoteInit
,
which also takes into account environment variables.
Options set by command-line parameters have the highest precedence,
followed by options read from a configuration file; if a configuration option is not explicitly
specified anywhere, a reasonable default is used. The configuration file has a format, wherein
one configuration option is specified on each line; the first token on each line is the name
of the configuration option, followed by whitespace, followed by its value. Lines beginning with #
are comments. Thus:
# This is a sample configuration file cfgHostName host3 cfgKnownHosts host1 host2 host3 host4
Options may be specified on the command line similarly. Note that command-line arguments containing spaces must be quoted.
./MyProgram -cfgHostName=host3 -cfgKnownHosts='host1 host2 host3 host4'
The Config structure encapsulates the user-settable configuration options for each node.
This settings are usually read in from a configuration file or from the executable's
command line; in either case, see Remote.Init.remoteInit
and readConfig
Config | |
|
getCfgArgs :: ProcessM [String]Source
Returns command-line arguments provided to the executable, excluding any command line arguments that were processed by the framework.
Initialization
initNode :: Config -> Lookup -> IO (MVar Node)Source
Creates a new Node
object, given the specified configuration (usually created by readConfig
) and
function metadata table (usually create by Remote.Call.registerCalls
). You probably want to use
Remote.Init.remoteInit
instead of this lower-level function.
waitForThreads :: MVar Node -> IO ()Source
Blocks until all non-daemonic processes of the given node have ended. Usually called on the main thread of a program.
forkAndListenAndDeliver :: MVar Node -> Config -> IO ()Source
Starts a message-receive loop on the given node. You probably don't want to call this function yourself.
Closures
makeClosure :: (Typeable a, Serializable v) => String -> v -> ProcessM (Closure a)Source
Debugging aids
nodeFromPid :: ProcessId -> NodeIdSource
hostFromNid :: NodeId -> HostNameSource
Various internals, not for general use
type LocalProcessId = IntSource
localRegistryHello :: ProcessM ()Source
Contacts the local node registry and attempts to verify that it is alive. If the local node registry cannot be contacted, an exception will be thrown.
localRegistryRegisterNode :: ProcessM ()Source
Contacts the local node registry and attempts to register current node.
You probably don't want to call this function yourself, as it's done for you in Remote.Init.remoteInit
localRegistryUnregisterNode :: ProcessM ()Source
Contacts the local node registry and attempts to unregister current node.
You probably don't want to call this function yourself, as it's done for you in Remote.Init.remoteInit
sendSimple :: Serializable a => ProcessId -> a -> PayloadDisposition -> ProcessM TransmitStatusSource
makeNodeFromHost :: String -> PortId -> NodeIdSource
getNewMessageLocal :: Node -> LocalProcessId -> STM (Maybe Message)Source
roundtripResponse :: (Serializable a, Serializable b) => (a -> ProcessM (b, q)) -> MatchM q ()Source
roundtripResponseAsync :: (Serializable a, Serializable b) => (a -> (b -> ProcessM ()) -> ProcessM q) -> Bool -> MatchM q ()Source
roundtripQuery :: (Serializable a, Serializable b) => PayloadDisposition -> ProcessId -> a -> ProcessM (Either TransmitStatus b)Source
roundtripQueryMulti :: (Serializable a, Serializable b) => PayloadDisposition -> [ProcessId] -> a -> ProcessM [Either TransmitStatus b]Source
roundtripQueryImpl :: (Serializable a, Serializable b) => Int -> PayloadDisposition -> ProcessId -> a -> (b -> c) -> [MatchM (Either TransmitStatus c) ()] -> ProcessM (Either TransmitStatus c)Source
roundtripQueryUnsafe :: (Serializable a, Serializable b) => PayloadDisposition -> ProcessId -> a -> ProcessM (Either TransmitStatus b)Source
data PayloadDisposition Source
suppressTransmitException :: ProcessM a -> ProcessM (Maybe a)Source
getMessagePayload :: Serializable a => Message -> Maybe aSource
System service processes, not for general use
startLocalRegistry :: Config -> Bool -> IO TransmitStatusSource
standaloneLocalRegistry :: String -> IO ()Source
Every host on which a node is running also needs a node registry, which arbitrates those nodes can responds to peer queries. If no registry is running, one will be automatically started when the framework is started, but the registry can be started independently, also. This function does that.