Safe Haskell | None |
---|---|
Language | Haskell98 |
Control.Distributed.Process.Internal.Types
Contents
Description
Types used throughout the Cloud Haskell framework
We collect all types used internally in a single module because many of these data types are mutually recursive and cannot be split across modules.
- newtype NodeId = NodeId {}
- data LocalProcessId = LocalProcessId {
- lpidUnique :: !Int32
- lpidCounter :: !Int32
- data ProcessId = ProcessId {}
- data Identifier
- nodeOf :: Identifier -> NodeId
- firstNonReservedProcessId :: Int32
- nullProcessId :: NodeId -> ProcessId
- data LocalNode = LocalNode {
- localNodeId :: !NodeId
- localEndPoint :: !EndPoint
- localState :: !(StrictMVar LocalNodeState)
- localCtrlChan :: !(Chan NCMsg)
- localEventBus :: !MxEventBus
- remoteTable :: !RemoteTable
- data LocalNodeState
- data ValidLocalNodeState = ValidLocalNodeState {
- _localProcesses :: !(Map LocalProcessId LocalProcess)
- _localPidCounter :: !Int32
- _localPidUnique :: !Int32
- _localConnections :: !(Map (Identifier, Identifier) (Connection, ImplicitReconnect))
- data NodeClosedException = NodeClosedException NodeId
- withValidLocalState :: LocalNode -> (ValidLocalNodeState -> IO r) -> IO r
- modifyValidLocalState :: LocalNode -> (ValidLocalNodeState -> IO (ValidLocalNodeState, a)) -> IO (Maybe a)
- modifyValidLocalState_ :: LocalNode -> (ValidLocalNodeState -> IO ValidLocalNodeState) -> IO ()
- data Tracer = Tracer {}
- data MxEventBus
- data LocalProcess = LocalProcess {
- processQueue :: !(CQueue Message)
- processWeakQ :: !(Weak (CQueue Message))
- processId :: !ProcessId
- processState :: !(StrictMVar LocalProcessState)
- processThread :: !ThreadId
- processNode :: !LocalNode
- data LocalProcessState = LocalProcessState {
- _monitorCounter :: !Int32
- _spawnCounter :: !Int32
- _channelCounter :: !Int32
- _typedChannels :: !(Map LocalSendPortId TypedChannel)
- newtype Process a = Process {
- unProcess :: ReaderT LocalProcess IO a
- runLocalProcess :: LocalProcess -> Process a -> IO a
- data ImplicitReconnect
- type LocalSendPortId = Int32
- data SendPortId = SendPortId {}
- data TypedChannel = forall a . Serializable a => TypedChannel (Weak (TQueue a))
- newtype SendPort a = SendPort {}
- newtype ReceivePort a = ReceivePort {
- receiveSTM :: STM a
- data Message
- = EncodedMessage {
- messageFingerprint :: !Fingerprint
- messageEncoding :: !ByteString
- | forall a . Serializable a => UnencodedMessage {
- messageFingerprint :: !Fingerprint
- messagePayload :: !a
- = EncodedMessage {
- isEncoded :: Message -> Bool
- createMessage :: Serializable a => a -> Message
- createUnencodedMessage :: Serializable a => a -> Message
- unsafeCreateUnencodedMessage :: Serializable a => a -> Message
- messageToPayload :: Message -> [ByteString]
- payloadToMessage :: [ByteString] -> Message
- data MonitorRef = MonitorRef {
- monitorRefIdent :: !Identifier
- monitorRefCounter :: !Int32
- data ProcessMonitorNotification = ProcessMonitorNotification !MonitorRef !ProcessId !DiedReason
- data NodeMonitorNotification = NodeMonitorNotification !MonitorRef !NodeId !DiedReason
- data PortMonitorNotification = PortMonitorNotification !MonitorRef !SendPortId !DiedReason
- data ProcessExitException = ProcessExitException !ProcessId !Message
- data ProcessLinkException = ProcessLinkException !ProcessId !DiedReason
- data NodeLinkException = NodeLinkException !NodeId !DiedReason
- data PortLinkException = PortLinkException !SendPortId !DiedReason
- data ProcessRegistrationException = ProcessRegistrationException !String !(Maybe ProcessId)
- data DiedReason
- = DiedNormal
- | DiedException !String
- | DiedDisconnect
- | DiedNodeDown
- | DiedUnknownId
- newtype DidUnmonitor = DidUnmonitor MonitorRef
- newtype DidUnlinkProcess = DidUnlinkProcess ProcessId
- newtype DidUnlinkNode = DidUnlinkNode NodeId
- newtype DidUnlinkPort = DidUnlinkPort SendPortId
- newtype SpawnRef = SpawnRef Int32
- data DidSpawn = DidSpawn SpawnRef ProcessId
- data WhereIsReply = WhereIsReply String (Maybe ProcessId)
- data RegisterReply = RegisterReply String Bool (Maybe ProcessId)
- data ProcessInfo = ProcessInfo {
- infoNode :: NodeId
- infoRegisteredNames :: [String]
- infoMessageQueueLength :: Int
- infoMonitors :: [(ProcessId, MonitorRef)]
- infoLinks :: [ProcessId]
- data ProcessInfoNone = ProcessInfoNone DiedReason
- data NodeStats = NodeStats {
- nodeStatsNode :: NodeId
- nodeStatsRegisteredNames :: Int
- nodeStatsMonitors :: Int
- nodeStatsLinks :: Int
- nodeStatsProcesses :: Int
- data NCMsg = NCMsg {}
- data ProcessSignal
- = Link !Identifier
- | Unlink !Identifier
- | Monitor !MonitorRef
- | Unmonitor !MonitorRef
- | Died Identifier !DiedReason
- | Spawn !(Closure (Process ())) !SpawnRef
- | WhereIs !String
- | Register !String !NodeId !(Maybe ProcessId) !Bool
- | NamedSend !String !Message
- | UnreliableSend !LocalProcessId !Message
- | LocalSend !ProcessId !Message
- | LocalPortSend !SendPortId !Message
- | Kill !ProcessId !String
- | Exit !ProcessId !Message
- | GetInfo !ProcessId
- | SigShutdown
- | GetNodeStats !NodeId
- localProcesses :: Accessor ValidLocalNodeState (Map LocalProcessId LocalProcess)
- localPidCounter :: Accessor ValidLocalNodeState Int32
- localPidUnique :: Accessor ValidLocalNodeState Int32
- localConnections :: Accessor ValidLocalNodeState (Map (Identifier, Identifier) (Connection, ImplicitReconnect))
- localProcessWithId :: LocalProcessId -> Accessor ValidLocalNodeState (Maybe LocalProcess)
- localConnectionBetween :: Identifier -> Identifier -> Accessor ValidLocalNodeState (Maybe (Connection, ImplicitReconnect))
- monitorCounter :: Accessor LocalProcessState Int32
- spawnCounter :: Accessor LocalProcessState Int32
- channelCounter :: Accessor LocalProcessState LocalSendPortId
- typedChannels :: Accessor LocalProcessState (Map LocalSendPortId TypedChannel)
- typedChannelWithId :: LocalSendPortId -> Accessor LocalProcessState (Maybe TypedChannel)
- forever' :: Monad m => m a -> m b
Node and process identifiers
Node identifier
Constructors
NodeId | |
Fields |
data LocalProcessId Source
A local process ID consists of a seed which distinguishes processes from different instances of the same local node and a counter
Constructors
LocalProcessId | |
Fields
|
Instances
Eq LocalProcessId Source | |
Data LocalProcessId Source | |
Ord LocalProcessId Source | |
Show LocalProcessId Source | |
Generic LocalProcessId Source | |
Hashable LocalProcessId Source | |
Binary LocalProcessId Source | |
type Rep LocalProcessId Source |
Process identifier
Constructors
ProcessId | |
Fields
|
data Identifier Source
Union of all kinds of identifiers
Constructors
NodeIdentifier !NodeId | |
ProcessIdentifier !ProcessId | |
SendPortIdentifier !SendPortId |
Instances
Eq Identifier Source | |
Ord Identifier Source | |
Show Identifier Source | |
Generic Identifier Source | |
Hashable Identifier Source | |
NFData Identifier Source | |
Binary Identifier Source | |
type Rep Identifier Source |
nodeOf :: Identifier -> NodeId Source
firstNonReservedProcessId :: Int32 Source
nullProcessId :: NodeId -> ProcessId Source
Local nodes and processes
Local nodes
Constructors
LocalNode | |
Fields
|
data LocalNodeState Source
Local node state
Constructors
LocalNodeValid !ValidLocalNodeState | |
LocalNodeClosed |
data ValidLocalNodeState Source
Constructors
ValidLocalNodeState | |
Fields
|
data NodeClosedException Source
Thrown by some primitives when they notice the node has been closed.
Constructors
NodeClosedException NodeId |
Instances
Show NodeClosedException Source | |
Exception NodeClosedException Source |
withValidLocalState :: LocalNode -> (ValidLocalNodeState -> IO r) -> IO r Source
Wrapper around withMVar
that checks that the local node is still in
a valid state.
modifyValidLocalState :: LocalNode -> (ValidLocalNodeState -> IO (ValidLocalNodeState, a)) -> IO (Maybe a) Source
Wrapper around modifyMVar
that checks that the local node is still in
a valid state.
modifyValidLocalState_ :: LocalNode -> (ValidLocalNodeState -> IO ValidLocalNodeState) -> IO () Source
Wrapper around modifyMVar_
that checks that the local node is still in
a valid state.
Provides access to the trace controller
data MxEventBus Source
Local system management event bus state
Constructors
MxEventBusInitialising | |
MxEventBus | |
Fields
|
data LocalProcess Source
Processes running on our local node
Constructors
LocalProcess | |
Fields
|
Instances
data LocalProcessState Source
Local process state
Constructors
LocalProcessState | |
Fields
|
The Cloud Haskell Process
type
Constructors
Process | |
Fields
|
runLocalProcess :: LocalProcess -> Process a -> IO a Source
Deconstructor for Process
(not exported to the public API)
Typed channels
type LocalSendPortId = Int32 Source
data SendPortId Source
A send port is identified by a SendPortId.
You cannot send directly to a SendPortId; instead, use newChan
to create a SendPort.
Constructors
SendPortId | |
Fields
|
Instances
Eq SendPortId Source | |
Ord SendPortId Source | |
Show SendPortId Source | |
Generic SendPortId Source | |
Hashable SendPortId Source | |
NFData SendPortId Source | |
Binary SendPortId Source | |
type Rep SendPortId Source |
data TypedChannel Source
Constructors
forall a . Serializable a => TypedChannel (Weak (TQueue a)) |
The send send of a typed channel (serializable)
Constructors
SendPort | |
Fields
|
newtype ReceivePort a Source
The receive end of a typed channel (not serializable)
Note that ReceivePort
implements Functor
, Applicative
, Alternative
and Monad
. This is especially useful when merging receive ports.
Constructors
ReceivePort | |
Fields
|
Instances
Monad ReceivePort Source | |
Functor ReceivePort Source | |
Applicative ReceivePort Source | |
Alternative ReceivePort Source |
Messages
Messages consist of their typeRep fingerprint and their encoding
Constructors
EncodedMessage | |
Fields
| |
forall a . Serializable a => UnencodedMessage | |
Fields
|
createMessage :: Serializable a => a -> Message Source
Turn any serialiable term into a message
createUnencodedMessage :: Serializable a => a -> Message Source
Turn any serializable term into an unencoded/local message
unsafeCreateUnencodedMessage :: Serializable a => a -> Message Source
Turn any serializable term into an unencodede/local message, without evalutaing it! This is a dangerous business.
messageToPayload :: Message -> [ByteString] Source
Serialize a message
payloadToMessage :: [ByteString] -> Message Source
Deserialize a message
Node controller user-visible data types
data MonitorRef Source
MonitorRef is opaque for regular Cloud Haskell processes
Constructors
MonitorRef | |
Fields
|
Instances
Eq MonitorRef Source | |
Ord MonitorRef Source | |
Show MonitorRef Source | |
Generic MonitorRef Source | |
Hashable MonitorRef Source | |
NFData MonitorRef Source | |
Binary MonitorRef Source | |
type Rep MonitorRef Source |
data ProcessMonitorNotification Source
Message sent by process monitors
Constructors
ProcessMonitorNotification !MonitorRef !ProcessId !DiedReason |
Instances
data NodeMonitorNotification Source
Message sent by node monitors
Constructors
NodeMonitorNotification !MonitorRef !NodeId !DiedReason |
Instances
Show NodeMonitorNotification Source | |
Binary NodeMonitorNotification Source |
data PortMonitorNotification Source
Message sent by channel (port) monitors
Constructors
PortMonitorNotification !MonitorRef !SendPortId !DiedReason |
Instances
Show PortMonitorNotification Source | |
Binary PortMonitorNotification Source |
data ProcessExitException Source
Internal exception thrown indirectly by exit
Constructors
ProcessExitException !ProcessId !Message |
Instances
Show ProcessExitException Source | |
Exception ProcessExitException Source |
data ProcessLinkException Source
Exceptions thrown when a linked process dies
Constructors
ProcessLinkException !ProcessId !DiedReason |
Instances
Show ProcessLinkException Source | |
Exception ProcessLinkException Source |
data NodeLinkException Source
Exception thrown when a linked node dies
Constructors
NodeLinkException !NodeId !DiedReason |
Instances
Show NodeLinkException Source | |
Exception NodeLinkException Source |
data PortLinkException Source
Exception thrown when a linked channel (port) dies
Constructors
PortLinkException !SendPortId !DiedReason |
Instances
Show PortLinkException Source | |
Exception PortLinkException Source |
data ProcessRegistrationException Source
Exception thrown when a process attempts to register a process under an already-registered name or to unregister a name that hasn't been registered. Returns the name and the identifier of the process that owns it, if any.
Constructors
ProcessRegistrationException !String !(Maybe ProcessId) |
Instances
Show ProcessRegistrationException Source | |
Exception ProcessRegistrationException Source |
data DiedReason Source
Why did a process die?
Constructors
DiedNormal | Normal termination |
DiedException !String | The process exited with an exception
(provided as |
DiedDisconnect | We got disconnected from the process node |
DiedNodeDown | The process node died |
DiedUnknownId | Invalid (processnodechannel) identifier |
Instances
Eq DiedReason Source | |
Show DiedReason Source | |
NFData DiedReason Source | |
Binary DiedReason Source |
newtype DidUnmonitor Source
(Asynchronous) reply from unmonitor
Constructors
DidUnmonitor MonitorRef |
Instances
Binary DidUnmonitor Source |
newtype DidUnlinkProcess Source
(Asynchronous) reply from unlink
Constructors
DidUnlinkProcess ProcessId |
Instances
Binary DidUnlinkProcess Source |
newtype DidUnlinkNode Source
(Asynchronous) reply from unlinkNode
Constructors
DidUnlinkNode NodeId |
Instances
Binary DidUnlinkNode Source |
newtype DidUnlinkPort Source
(Asynchronous) reply from unlinkPort
Constructors
DidUnlinkPort SendPortId |
Instances
Binary DidUnlinkPort Source |
(Asynchronius) reply from spawn
data WhereIsReply Source
(Asynchronous) reply from whereis
Constructors
WhereIsReply String (Maybe ProcessId) |
Instances
Show WhereIsReply Source | |
Binary WhereIsReply Source |
data RegisterReply Source
(Asynchronous) reply from register
and unregister
Constructors
RegisterReply String Bool (Maybe ProcessId) |
Instances
Show RegisterReply Source | |
Binary RegisterReply Source |
data ProcessInfo Source
Provide information about a running process
Constructors
ProcessInfo | |
Fields
|
Instances
Eq ProcessInfo Source | |
Show ProcessInfo Source | |
Binary ProcessInfo Source |
data ProcessInfoNone Source
Constructors
ProcessInfoNone DiedReason |
Instances
Show ProcessInfoNone Source | |
Binary ProcessInfoNone Source |
Constructors
NodeStats | |
Fields
|
Node controller internal data types
Messages to the node controller
Constructors
NCMsg | |
Fields |
data ProcessSignal Source
Signals to the node controller (see NCMsg
)
Constructors
Link !Identifier | |
Unlink !Identifier | |
Monitor !MonitorRef | |
Unmonitor !MonitorRef | |
Died Identifier !DiedReason | |
Spawn !(Closure (Process ())) !SpawnRef | |
WhereIs !String | |
Register !String !NodeId !(Maybe ProcessId) !Bool | |
NamedSend !String !Message | |
UnreliableSend !LocalProcessId !Message | |
LocalSend !ProcessId !Message | |
LocalPortSend !SendPortId !Message | |
Kill !ProcessId !String | |
Exit !ProcessId !Message | |
GetInfo !ProcessId | |
SigShutdown | |
GetNodeStats !NodeId |
Instances
Show ProcessSignal Source | |
Binary ProcessSignal Source |
Accessors
localPidCounter :: Accessor ValidLocalNodeState Int32 Source
localPidUnique :: Accessor ValidLocalNodeState Int32 Source
localConnections :: Accessor ValidLocalNodeState (Map (Identifier, Identifier) (Connection, ImplicitReconnect)) Source
localConnectionBetween :: Identifier -> Identifier -> Accessor ValidLocalNodeState (Maybe (Connection, ImplicitReconnect)) Source
monitorCounter :: Accessor LocalProcessState Int32 Source
spawnCounter :: Accessor LocalProcessState Int32 Source
typedChannelWithId :: LocalSendPortId -> Accessor LocalProcessState (Maybe TypedChannel) Source