Safe Haskell | None |
---|---|
Language | Haskell98 |
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 Tracer = Tracer {}
- data MxEventBus
- data LocalNodeState = LocalNodeState {}
- data LocalProcess = LocalProcess {
- processQueue :: !(CQueue Message)
- processWeakQ :: !(Weak (CQueue Message))
- processId :: !ProcessId
- processState :: !(StrictMVar LocalProcessState)
- processThread :: !ThreadId
- processNode :: !LocalNode
- data LocalProcessState = LocalProcessState {}
- 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 { }
- | forall a . Serializable a => UnencodedMessage {
- messageFingerprint :: !Fingerprint
- messagePayload :: !a
- 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 {}
- 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
- data DiedReason
- 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
- data ProcessInfo = ProcessInfo {
- infoNode :: NodeId
- infoRegisteredNames :: [String]
- infoMessageQueueLength :: Maybe Int
- infoMonitors :: [(ProcessId, MonitorRef)]
- infoLinks :: [ProcessId]
- data ProcessInfoNone = ProcessInfoNone DiedReason
- data NodeStats = NodeStats {}
- 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
- | LocalSend !ProcessId !Message
- | LocalPortSend !SendPortId !Message
- | Kill !ProcessId !String
- | Exit !ProcessId !Message
- | GetInfo !ProcessId
- | SigShutdown
- | GetNodeStats !NodeId
- localProcesses :: Accessor LocalNodeState (Map LocalProcessId LocalProcess)
- localPidCounter :: Accessor LocalNodeState Int32
- localPidUnique :: Accessor LocalNodeState Int32
- localConnections :: Accessor LocalNodeState (Map (Identifier, Identifier) (Connection, ImplicitReconnect))
- localProcessWithId :: LocalProcessId -> Accessor LocalNodeState (Maybe LocalProcess)
- localConnectionBetween :: Identifier -> Identifier -> Accessor LocalNodeState (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
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
LocalProcessId | |
|
Process identifier
ProcessId | |
|
data Identifier Source
Union of all kinds of identifiers
nodeOf :: Identifier -> NodeId Source
nullProcessId :: NodeId -> ProcessId Source
Local nodes and processes
Local nodes
LocalNode | |
|
Provides access to the trace controller
data MxEventBus Source
Local system management event bus state
MxEventBusInitialising | |
MxEventBus | |
|
data LocalNodeState Source
Local node state
LocalNodeState | |
|
data LocalProcess Source
Processes running on our local node
LocalProcess | |
|
data LocalProcessState Source
Local process state
The Cloud Haskell Process
type
runLocalProcess :: LocalProcess -> Process a -> IO a Source
Deconstructor for Process
(not exported to the public API)
data ImplicitReconnect Source
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.
SendPortId | |
|
data TypedChannel Source
forall a . Serializable a => TypedChannel (Weak (TQueue a)) |
The send send of a typed channel (serializable)
SendPort | |
|
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.
ReceivePort | |
|
Messages
Messages consist of their typeRep fingerprint and their encoding
EncodedMessage | |
forall a . Serializable a => UnencodedMessage | |
|
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
MonitorRef | |
|
data ProcessMonitorNotification Source
Message sent by process monitors
data NodeMonitorNotification Source
Message sent by node monitors
data PortMonitorNotification Source
Message sent by channel (port) monitors
data ProcessExitException Source
Internal exception thrown indirectly by exit
data ProcessLinkException Source
Exceptions thrown when a linked process dies
data NodeLinkException Source
Exception thrown when a linked node dies
data PortLinkException Source
Exception thrown when a linked channel (port) dies
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
data DiedReason Source
Why did a process die?
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 |
newtype DidUnmonitor Source
(Asynchronous) reply from unmonitor
newtype DidUnlinkProcess Source
(Asynchronous) reply from unlink
newtype DidUnlinkNode Source
(Asynchronous) reply from unlinkNode
newtype DidUnlinkPort Source
(Asynchronous) reply from unlinkPort
SpawnRef
are used to return pids of spawned processes
(Asynchronius) reply from spawn
data WhereIsReply Source
(Asynchronous) reply from whereis
data RegisterReply Source
(Asynchronous) reply from register
and unregister
data ProcessInfo Source
Provide information about a running process
ProcessInfo | |
|
data ProcessInfoNone Source
Node controller internal data types
Messages to the node controller
data ProcessSignal Source
Signals to the node controller (see NCMsg
)
Accessors
localConnections :: Accessor LocalNodeState (Map (Identifier, Identifier) (Connection, ImplicitReconnect)) Source
localConnectionBetween :: Identifier -> Identifier -> Accessor LocalNodeState (Maybe (Connection, ImplicitReconnect)) Source