Safe Haskell | None |
---|
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
- data LocalNode = LocalNode {}
- data LocalNodeState = LocalNodeState {}
- data LocalProcess = LocalProcess {}
- data LocalProcessState = LocalProcessState {}
- newtype Process a = Process {
- unProcess :: ReaderT LocalProcess (MessageT IO) a
- procMsg :: MessageT IO a -> Process a
- type LocalSendPortId = Int32
- data SendPortId = SendPortId {}
- data TypedChannel = forall a . Serializable a => TypedChannel (TChan a)
- newtype SendPort a = SendPort {}
- data ReceivePort a
- = ReceivePortSingle (TChan a)
- | ReceivePortBiased [ReceivePort a]
- | ReceivePortRR (TVar [ReceivePort a])
- data StaticLabel
- = UserStatic String
- | ClosureReturn
- | ClosureSend
- | ClosureExpect
- | ClosureApply
- | ClosureConst
- | ClosureUnit
- | CpId
- | CpComp
- | CpFirst
- | CpSwap
- | CpCopy
- | CpLeft
- | CpMirror
- | CpUntag
- | CpApply
- newtype Static a = Static StaticLabel
- data Closure a = Closure (Static (ByteString -> a)) ByteString
- data RemoteTable = RemoteTable {}
- data SerializableDict a where
- SerializableDict :: Serializable a => SerializableDict a
- data RuntimeSerializableSupport = RuntimeSerializableSupport {}
- data Message = Message {}
- createMessage :: 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 ProcessLinkException = ProcessLinkException ProcessId DiedReason
- data NodeLinkException = NodeLinkException NodeId DiedReason
- data PortLinkException = PortLinkException SendPortId DiedReason
- 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 NCMsg = NCMsg {}
- data ProcessSignal
- = Link Identifier
- | Unlink Identifier
- | Monitor MonitorRef
- | Unmonitor MonitorRef
- | Died Identifier DiedReason
- | Spawn (Closure (Process ())) SpawnRef
- | WhereIs String
- | Register String (Maybe ProcessId)
- | NamedSend String Message
- newtype MessageT m a = MessageT {
- unMessageT :: StateT MessageState m a
- data MessageState = MessageState {}
- localProcesses :: Accessor LocalNodeState (Map LocalProcessId LocalProcess)
- localPidCounter :: Accessor LocalNodeState Int32
- localPidUnique :: Accessor LocalNodeState Int32
- localProcessWithId :: LocalProcessId -> Accessor LocalNodeState (Maybe LocalProcess)
- monitorCounter :: Accessor LocalProcessState Int32
- spawnCounter :: Accessor LocalProcessState Int32
- channelCounter :: Accessor LocalProcessState LocalSendPortId
- typedChannels :: Accessor LocalProcessState (Map LocalSendPortId TypedChannel)
- typedChannelWithId :: LocalSendPortId -> Accessor LocalProcessState (Maybe TypedChannel)
- remoteTableLabels :: Accessor RemoteTable (Map String Dynamic)
- remoteTableDicts :: Accessor RemoteTable (Map TypeRep RuntimeSerializableSupport)
- remoteTableLabel :: String -> Accessor RemoteTable (Maybe Dynamic)
- remoteTableDict :: TypeRep -> Accessor RemoteTable (Maybe RuntimeSerializableSupport)
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
|
Process identifier
Constructors
ProcessId | |
Fields
|
nodeOf :: Identifier -> NodeIdSource
Local nodes and processes
Local nodes
Constructors
LocalNode | |
Fields
|
data LocalProcess Source
Processes running on our local node
Constructors
LocalProcess | |
Fields |
Instances
The Cloud Haskell Process
type
Typed channels
type LocalSendPortId = Int32Source
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
data TypedChannel Source
Constructors
forall a . Serializable a => TypedChannel (TChan a) |
The send send of a typed channel (serializable)
Constructors
SendPort | |
Fields
|
data ReceivePort a Source
The receive end of a typed channel (not serializable)
Constructors
ReceivePortSingle (TChan a) | A single receive port |
ReceivePortBiased [ReceivePort a] | A left-biased combination of receive ports |
ReceivePortRR (TVar [ReceivePort a]) | A round-robin combination of receive ports |
Closures
data StaticLabel Source
Constructors
UserStatic String | |
ClosureReturn | |
ClosureSend | |
ClosureExpect | |
ClosureApply | |
ClosureConst | |
ClosureUnit | |
CpId | |
CpComp | |
CpFirst | |
CpSwap | |
CpCopy | |
CpLeft | |
CpMirror | |
CpUntag | |
CpApply |
Instances
A static value is one that is bound at top-level.
Constructors
Static StaticLabel |
A closure is a static value and an encoded environment
Constructors
Closure (Static (ByteString -> a)) ByteString |
data RemoteTable Source
Used to fake static
(see paper)
Constructors
RemoteTable | |
Fields
|
data SerializableDict a whereSource
Reification of Serializable
(see Control.Distributed.Process.Closure)
Constructors
SerializableDict :: Serializable a => SerializableDict a |
Instances
data RuntimeSerializableSupport Source
Runtime support for implementing polymorphic functions with a Serializable qualifier (sendClosure, returnClosure, ..).
We don't attempt to keep this minimal, but instead just add functions as
convenient. This will be replaced anyway once static
has been implemented.
Messages
Messages consist of their typeRep fingerprint and their encoding
Constructors
Message | |
Fields |
createMessage :: Serializable a => a -> MessageSource
Turn any serialiable term into a message
messageToPayload :: Message -> [ByteString]Source
Serialize a message
payloadToMessage :: [ByteString] -> MessageSource
Deserialize a message
Node controller user-visible data types
data MonitorRef Source
MonitorRef is opaque for regular Cloud Haskell processes
Constructors
MonitorRef | |
Fields
|
Instances
data ProcessMonitorNotification Source
Message sent by process monitors
Constructors
ProcessMonitorNotification MonitorRef ProcessId DiedReason |
data NodeMonitorNotification Source
Message sent by node monitors
Constructors
NodeMonitorNotification MonitorRef NodeId DiedReason |
data PortMonitorNotification Source
Message sent by channel (port) monitors
Constructors
PortMonitorNotification MonitorRef SendPortId DiedReason |
data ProcessLinkException Source
Exceptions thrown when a linked process dies
Constructors
ProcessLinkException ProcessId DiedReason |
data NodeLinkException Source
Exception thrown when a linked node dies
Constructors
NodeLinkException NodeId DiedReason |
data PortLinkException Source
Exception thrown when a linked channel (port) dies
Constructors
PortLinkException SendPortId DiedReason |
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
newtype DidUnmonitor Source
(Asynchronous) reply from unmonitor
Constructors
DidUnmonitor MonitorRef |
Instances
newtype DidUnlinkProcess Source
(Asynchronous) reply from unlink
Constructors
DidUnlinkProcess ProcessId |
Instances
newtype DidUnlinkNode Source
(Asynchronous) reply from unlinkNode
Constructors
DidUnlinkNode NodeId |
Instances
newtype DidUnlinkPort Source
(Asynchronous) reply from unlinkPort
Constructors
DidUnlinkPort SendPortId |
Instances
SpawnRef
are used to return pids of spawned processes
(Asynchronius) reply from spawn
data WhereIsReply Source
(Asynchronous) reply from whereis
Constructors
WhereIsReply String (Maybe ProcessId) |
Instances
Node controller internal data types
Messages to the node controller
Constructors
NCMsg | |
Fields |
data ProcessSignal Source
Signals to the node controller (see NCMsg
)
Constructors
Instances
MessageT monad
Constructors
MessageT | |
Fields
|
data MessageState Source
Constructors
MessageState | |
Fields |
Instances
Monad m => MonadState MessageState (MessageT m) |