distributed-process-0.5.2: Cloud Haskell: Erlang-style concurrency in Haskell

Safe HaskellNone
LanguageHaskell98

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.

Synopsis

Node and process identifiers

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 

data ProcessId Source

Process identifier

Constructors

ProcessId 

Fields

processNodeId :: !NodeId

The ID of the node the process is running on

processLocalId :: !LocalProcessId

Node-local identifier for the process

Local nodes and processes

data LocalNode Source

Local nodes

Constructors

LocalNode 

Fields

localNodeId :: !NodeId

NodeId of the node

localEndPoint :: !EndPoint

The network endpoint associated with this node

localState :: !(StrictMVar LocalNodeState)

Local node state

localCtrlChan :: !(Chan NCMsg)

Channel for the node controller

localEventBus :: !MxEventBus

Internal management event bus

remoteTable :: !RemoteTable

Runtime lookup table for supporting closures TODO: this should be part of the CH state, not the local endpoint state

data Tracer Source

Provides access to the trace controller

Constructors

Tracer 

Fields

tracerPid :: !ProcessId

Process id for the currently active trace handler

weakQ :: !(Weak (CQueue Message))

Weak reference to the tracer controller's mailbox

data MxEventBus Source

Local system management event bus state

Constructors

MxEventBusInitialising 
MxEventBus 

Fields

agent :: !ProcessId

Process id of the management agent controller process

tracer :: !Tracer

Configuration for the local trace controller

evbuss :: !(Weak (CQueue Message))

Weak reference to the management agent controller's mailbox

mxNew :: !(((TChan Message, TChan Message) -> Process ()) -> IO ProcessId)

API for adding management agents to a running node

data LocalNodeState Source

Local node state

Constructors

LocalNodeState 

Fields

_localProcesses :: !(Map LocalProcessId LocalProcess)

Processes running on this node

_localPidCounter :: !Int32

Counter to assign PIDs

_localPidUnique :: !Int32

The unique value used to create PIDs (so that processes on restarted nodes have new PIDs)

_localConnections :: !(Map (Identifier, Identifier) (Connection, ImplicitReconnect))

Outgoing connections

runLocalProcess :: LocalProcess -> Process a -> IO a Source

Deconstructor for Process (not exported to the public API)

Typed channels

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

sendPortProcessId :: !ProcessId

The ID of the process that will receive messages sent on this port

sendPortLocalId :: !LocalSendPortId

Process-local ID of the channel

data TypedChannel Source

Constructors

forall a . Serializable a => TypedChannel (Weak (TQueue a)) 

newtype SendPort a Source

The send send of a typed channel (serializable)

Constructors

SendPort 

Fields

sendPortId :: SendPortId

The (unique) ID of this send port

Instances

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

receiveSTM :: STM a
 

Messages

data Message Source

Messages consist of their typeRep fingerprint and their encoding

isEncoded :: Message -> Bool Source

internal use only.

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

monitorRefIdent :: !Identifier

ID of the entity to be monitored

monitorRefCounter :: !Int32

Unique to distinguish multiple monitor requests by the same process

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?

Constructors

DiedNormal

Normal termination

DiedException !String

The process exited with an exception (provided as String because Exception does not implement Binary)

DiedDisconnect

We got disconnected from the process node

DiedNodeDown

The process node died

DiedUnknownId

Invalid (processnodechannel) identifier

newtype DidUnmonitor Source

(Asynchronous) reply from unmonitor

Constructors

DidUnmonitor MonitorRef 

newtype DidUnlinkProcess Source

(Asynchronous) reply from unlink

newtype DidUnlinkNode Source

(Asynchronous) reply from unlinkNode

Constructors

DidUnlinkNode NodeId 

newtype DidUnlinkPort Source

(Asynchronous) reply from unlinkPort

newtype SpawnRef Source

SpawnRef are used to return pids of spawned processes

Constructors

SpawnRef Int32 

data DidSpawn Source

(Asynchronius) reply from spawn

data WhereIsReply Source

(Asynchronous) reply from whereis

data RegisterReply Source

(Asynchronous) reply from register and unregister

Constructors

RegisterReply String Bool 

Node controller internal data types

data NCMsg Source

Messages to the node controller

Instances

Accessors

Utilities

forever' :: Monad m => m a -> m b Source