Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- 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 {}
- 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 {}
- 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 = Serializable a => TypedChannel (Weak (TQueue a))
- newtype SendPort a = SendPort {}
- newtype ReceivePort a = ReceivePort {
- receiveSTM :: STM a
- data Message
- = EncodedMessage { }
- | 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 !(Maybe ProcessId)
- 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 (Maybe ProcessId)
- data ProcessInfo = ProcessInfo {
- infoNode :: NodeId
- infoRegisteredNames :: [String]
- infoMessageQueueLength :: 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
- | 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
Instances
Data NodeId Source # | |||||
Defined in Control.Distributed.Process.Internal.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NodeId -> c NodeId # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NodeId # toConstr :: NodeId -> Constr # dataTypeOf :: NodeId -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NodeId) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NodeId) # gmapT :: (forall b. Data b => b -> b) -> NodeId -> NodeId # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NodeId -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NodeId -> r # gmapQ :: (forall d. Data d => d -> u) -> NodeId -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> NodeId -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> NodeId -> m NodeId # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NodeId -> m NodeId # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NodeId -> m NodeId # | |||||
Generic NodeId Source # | |||||
Defined in Control.Distributed.Process.Internal.Types
| |||||
Show NodeId Source # | |||||
Binary NodeId Source # | |||||
NFData NodeId Source # | |||||
Defined in Control.Distributed.Process.Internal.Types | |||||
Eq NodeId Source # | |||||
Ord NodeId Source # | |||||
Hashable NodeId Source # | |||||
Defined in Control.Distributed.Process.Internal.Types | |||||
type Rep NodeId Source # | |||||
Defined in Control.Distributed.Process.Internal.Types type Rep NodeId = D1 ('MetaData "NodeId" "Control.Distributed.Process.Internal.Types" "distributed-process-0.7.6-F5sZSqR3Cb09RBogyeswiz" 'True) (C1 ('MetaCons "NodeId" 'PrefixI 'True) (S1 ('MetaSel ('Just "nodeAddress") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EndPointAddress))) |
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 | |
|
Instances
Process identifier
ProcessId | |
|
Instances
Data ProcessId Source # | |||||
Defined in Control.Distributed.Process.Internal.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ProcessId -> c ProcessId # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ProcessId # toConstr :: ProcessId -> Constr # dataTypeOf :: ProcessId -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ProcessId) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ProcessId) # gmapT :: (forall b. Data b => b -> b) -> ProcessId -> ProcessId # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ProcessId -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ProcessId -> r # gmapQ :: (forall d. Data d => d -> u) -> ProcessId -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ProcessId -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ProcessId -> m ProcessId # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ProcessId -> m ProcessId # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ProcessId -> m ProcessId # | |||||
Generic ProcessId Source # | |||||
Defined in Control.Distributed.Process.Internal.Types
| |||||
Show ProcessId Source # | |||||
Binary ProcessId Source # | |||||
NFData ProcessId Source # | |||||
Defined in Control.Distributed.Process.Internal.Types | |||||
Eq ProcessId Source # | |||||
Ord ProcessId Source # | |||||
Defined in Control.Distributed.Process.Internal.Types | |||||
Hashable ProcessId Source # | |||||
Defined in Control.Distributed.Process.Internal.Types | |||||
type Rep ProcessId Source # | |||||
Defined in Control.Distributed.Process.Internal.Types type Rep ProcessId = D1 ('MetaData "ProcessId" "Control.Distributed.Process.Internal.Types" "distributed-process-0.7.6-F5sZSqR3Cb09RBogyeswiz" 'False) (C1 ('MetaCons "ProcessId" 'PrefixI 'True) (S1 ('MetaSel ('Just "processNodeId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NodeId) :*: S1 ('MetaSel ('Just "processLocalId") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 LocalProcessId))) |
data Identifier Source #
Union of all kinds of identifiers
Instances
Generic Identifier Source # | |||||
Defined in Control.Distributed.Process.Internal.Types
from :: Identifier -> Rep Identifier x # to :: Rep Identifier x -> Identifier # | |||||
Show Identifier Source # | |||||
Defined in Control.Distributed.Process.Internal.Types showsPrec :: Int -> Identifier -> ShowS # show :: Identifier -> String # showList :: [Identifier] -> ShowS # | |||||
Binary Identifier Source # | |||||
Defined in Control.Distributed.Process.Internal.Types | |||||
NFData Identifier Source # | |||||
Defined in Control.Distributed.Process.Internal.Types rnf :: Identifier -> () # | |||||
Eq Identifier Source # | |||||
Defined in Control.Distributed.Process.Internal.Types (==) :: Identifier -> Identifier -> Bool # (/=) :: Identifier -> Identifier -> Bool # | |||||
Ord Identifier Source # | |||||
Defined in Control.Distributed.Process.Internal.Types compare :: Identifier -> Identifier -> Ordering # (<) :: Identifier -> Identifier -> Bool # (<=) :: Identifier -> Identifier -> Bool # (>) :: Identifier -> Identifier -> Bool # (>=) :: Identifier -> Identifier -> Bool # max :: Identifier -> Identifier -> Identifier # min :: Identifier -> Identifier -> Identifier # | |||||
Hashable Identifier Source # | |||||
Defined in Control.Distributed.Process.Internal.Types hashWithSalt :: Int -> Identifier -> Int # hash :: Identifier -> Int # | |||||
type Rep Identifier Source # | |||||
Defined in Control.Distributed.Process.Internal.Types type Rep Identifier = D1 ('MetaData "Identifier" "Control.Distributed.Process.Internal.Types" "distributed-process-0.7.6-F5sZSqR3Cb09RBogyeswiz" 'False) (C1 ('MetaCons "NodeIdentifier" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NodeId)) :+: (C1 ('MetaCons "ProcessIdentifier" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ProcessId)) :+: C1 ('MetaCons "SendPortIdentifier" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SendPortId)))) |
nodeOf :: Identifier -> NodeId Source #
nullProcessId :: NodeId -> ProcessId Source #
Local nodes and processes
Local nodes
LocalNode | |
|
data ValidLocalNodeState Source #
ValidLocalNodeState | |
|
data NodeClosedException Source #
Thrown by some primitives when they notice the node has been closed.
Instances
Exception NodeClosedException Source # | |
Show NodeClosedException Source # | |
Defined in Control.Distributed.Process.Internal.Types showsPrec :: Int -> NodeClosedException -> ShowS # show :: NodeClosedException -> String # showList :: [NodeClosedException] -> ShowS # |
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
MxEventBusInitialising | |
MxEventBus | |
|
data LocalProcess Source #
Processes running on our local node
LocalProcess | |
|
Instances
MonadReader LocalProcess Process Source # | |
Defined in Control.Distributed.Process.Internal.Types ask :: Process LocalProcess # local :: (LocalProcess -> LocalProcess) -> Process a -> Process a # reader :: (LocalProcess -> a) -> Process a # |
data LocalProcessState Source #
Local process state
The Cloud Haskell Process
type
Instances
MonadFail Process Source # | |
Defined in Control.Distributed.Process.Internal.Types | |
MonadFix Process Source # | |
Defined in Control.Distributed.Process.Internal.Types | |
MonadIO Process Source # | |
Defined in Control.Distributed.Process.Internal.Types | |
Applicative Process Source # | |
Functor Process Source # | |
Monad Process Source # | |
MonadCatch Process Source # | |
Defined in Control.Distributed.Process.Internal.Types | |
MonadMask Process Source # | |
Defined in Control.Distributed.Process.Internal.Types mask :: HasCallStack => ((forall a. Process a -> Process a) -> Process b) -> Process b # uninterruptibleMask :: HasCallStack => ((forall a. Process a -> Process a) -> Process b) -> Process b # generalBracket :: HasCallStack => Process a -> (a -> ExitCase b -> Process c) -> (a -> Process b) -> Process (b, c) # | |
MonadThrow Process Source # | |
Defined in Control.Distributed.Process.Internal.Types throwM :: (HasCallStack, Exception e) => e -> Process a # | |
MonadReader LocalProcess Process Source # | |
Defined in Control.Distributed.Process.Internal.Types ask :: Process LocalProcess # local :: (LocalProcess -> LocalProcess) -> Process a -> Process a # reader :: (LocalProcess -> a) -> Process a # | |
Serializable b => MkTDict (Process b) Source # | |
runLocalProcess :: LocalProcess -> Process a -> IO a Source #
Deconstructor for Process
(not exported to the public API)
data ImplicitReconnect Source #
Instances
Show ImplicitReconnect Source # | |
Defined in Control.Distributed.Process.Internal.Types showsPrec :: Int -> ImplicitReconnect -> ShowS # show :: ImplicitReconnect -> String # showList :: [ImplicitReconnect] -> ShowS # | |
Eq ImplicitReconnect Source # | |
Defined in Control.Distributed.Process.Internal.Types (==) :: ImplicitReconnect -> ImplicitReconnect -> Bool # (/=) :: ImplicitReconnect -> ImplicitReconnect -> Bool # |
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 | |
|
Instances
Generic SendPortId Source # | |||||
Defined in Control.Distributed.Process.Internal.Types
from :: SendPortId -> Rep SendPortId x # to :: Rep SendPortId x -> SendPortId # | |||||
Show SendPortId Source # | |||||
Defined in Control.Distributed.Process.Internal.Types showsPrec :: Int -> SendPortId -> ShowS # show :: SendPortId -> String # showList :: [SendPortId] -> ShowS # | |||||
Binary SendPortId Source # | |||||
Defined in Control.Distributed.Process.Internal.Types | |||||
NFData SendPortId Source # | |||||
Defined in Control.Distributed.Process.Internal.Types rnf :: SendPortId -> () # | |||||
Eq SendPortId Source # | |||||
Defined in Control.Distributed.Process.Internal.Types (==) :: SendPortId -> SendPortId -> Bool # (/=) :: SendPortId -> SendPortId -> Bool # | |||||
Ord SendPortId Source # | |||||
Defined in Control.Distributed.Process.Internal.Types compare :: SendPortId -> SendPortId -> Ordering # (<) :: SendPortId -> SendPortId -> Bool # (<=) :: SendPortId -> SendPortId -> Bool # (>) :: SendPortId -> SendPortId -> Bool # (>=) :: SendPortId -> SendPortId -> Bool # max :: SendPortId -> SendPortId -> SendPortId # min :: SendPortId -> SendPortId -> SendPortId # | |||||
Hashable SendPortId Source # | |||||
Defined in Control.Distributed.Process.Internal.Types hashWithSalt :: Int -> SendPortId -> Int # hash :: SendPortId -> Int # | |||||
type Rep SendPortId Source # | |||||
Defined in Control.Distributed.Process.Internal.Types type Rep SendPortId = D1 ('MetaData "SendPortId" "Control.Distributed.Process.Internal.Types" "distributed-process-0.7.6-F5sZSqR3Cb09RBogyeswiz" 'False) (C1 ('MetaCons "SendPortId" 'PrefixI 'True) (S1 ('MetaSel ('Just "sendPortProcessId") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 ProcessId) :*: S1 ('MetaSel ('Just "sendPortLocalId") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 LocalSendPortId))) |
data TypedChannel Source #
Serializable a => TypedChannel (Weak (TQueue a)) |
The send send of a typed channel (serializable)
SendPort | |
|
Instances
Generic (SendPort a) Source # | |||||
Defined in Control.Distributed.Process.Internal.Types
| |||||
Show (SendPort a) Source # | |||||
Serializable a => Binary (SendPort a) Source # | |||||
NFData a => NFData (SendPort a) Source # | |||||
Defined in Control.Distributed.Process.Internal.Types | |||||
Eq (SendPort a) Source # | |||||
Ord (SendPort a) Source # | |||||
Defined in Control.Distributed.Process.Internal.Types | |||||
Hashable a => Hashable (SendPort a) Source # | |||||
Defined in Control.Distributed.Process.Internal.Types | |||||
type Rep (SendPort a) Source # | |||||
Defined in Control.Distributed.Process.Internal.Types type Rep (SendPort a) = D1 ('MetaData "SendPort" "Control.Distributed.Process.Internal.Types" "distributed-process-0.7.6-F5sZSqR3Cb09RBogyeswiz" 'True) (C1 ('MetaCons "SendPort" 'PrefixI 'True) (S1 ('MetaSel ('Just "sendPortId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SendPortId))) |
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 | |
|
Instances
Alternative ReceivePort Source # | |
Defined in Control.Distributed.Process.Internal.Types empty :: ReceivePort a # (<|>) :: ReceivePort a -> ReceivePort a -> ReceivePort a # some :: ReceivePort a -> ReceivePort [a] # many :: ReceivePort a -> ReceivePort [a] # | |
Applicative ReceivePort Source # | |
Defined in Control.Distributed.Process.Internal.Types pure :: a -> ReceivePort a # (<*>) :: ReceivePort (a -> b) -> ReceivePort a -> ReceivePort b # liftA2 :: (a -> b -> c) -> ReceivePort a -> ReceivePort b -> ReceivePort c # (*>) :: ReceivePort a -> ReceivePort b -> ReceivePort b # (<*) :: ReceivePort a -> ReceivePort b -> ReceivePort a # | |
Functor ReceivePort Source # | |
Defined in Control.Distributed.Process.Internal.Types fmap :: (a -> b) -> ReceivePort a -> ReceivePort b # (<$) :: a -> ReceivePort b -> ReceivePort a # | |
Monad ReceivePort Source # | |
Defined in Control.Distributed.Process.Internal.Types (>>=) :: ReceivePort a -> (a -> ReceivePort b) -> ReceivePort b # (>>) :: ReceivePort a -> ReceivePort b -> ReceivePort b # return :: a -> ReceivePort a # |
Messages
Messages consist of their typeRep fingerprint and their encoding
EncodedMessage | |
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 | |
|
Instances
Generic MonitorRef Source # | |||||
Defined in Control.Distributed.Process.Internal.Types
from :: MonitorRef -> Rep MonitorRef x # to :: Rep MonitorRef x -> MonitorRef # | |||||
Show MonitorRef Source # | |||||
Defined in Control.Distributed.Process.Internal.Types showsPrec :: Int -> MonitorRef -> ShowS # show :: MonitorRef -> String # showList :: [MonitorRef] -> ShowS # | |||||
Binary MonitorRef Source # | |||||
Defined in Control.Distributed.Process.Internal.Types | |||||
NFData MonitorRef Source # | |||||
Defined in Control.Distributed.Process.Internal.Types rnf :: MonitorRef -> () # | |||||
Eq MonitorRef Source # | |||||
Defined in Control.Distributed.Process.Internal.Types (==) :: MonitorRef -> MonitorRef -> Bool # (/=) :: MonitorRef -> MonitorRef -> Bool # | |||||
Ord MonitorRef Source # | |||||
Defined in Control.Distributed.Process.Internal.Types compare :: MonitorRef -> MonitorRef -> Ordering # (<) :: MonitorRef -> MonitorRef -> Bool # (<=) :: MonitorRef -> MonitorRef -> Bool # (>) :: MonitorRef -> MonitorRef -> Bool # (>=) :: MonitorRef -> MonitorRef -> Bool # max :: MonitorRef -> MonitorRef -> MonitorRef # min :: MonitorRef -> MonitorRef -> MonitorRef # | |||||
Hashable MonitorRef Source # | |||||
Defined in Control.Distributed.Process.Internal.Types hashWithSalt :: Int -> MonitorRef -> Int # hash :: MonitorRef -> Int # | |||||
type Rep MonitorRef Source # | |||||
Defined in Control.Distributed.Process.Internal.Types type Rep MonitorRef = D1 ('MetaData "MonitorRef" "Control.Distributed.Process.Internal.Types" "distributed-process-0.7.6-F5sZSqR3Cb09RBogyeswiz" 'False) (C1 ('MetaCons "MonitorRef" 'PrefixI 'True) (S1 ('MetaSel ('Just "monitorRefIdent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Identifier) :*: S1 ('MetaSel ('Just "monitorRefCounter") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int32))) |
data ProcessMonitorNotification Source #
Message sent by process monitors
Instances
Show ProcessMonitorNotification Source # | |
Defined in Control.Distributed.Process.Internal.Types showsPrec :: Int -> ProcessMonitorNotification -> ShowS # show :: ProcessMonitorNotification -> String # showList :: [ProcessMonitorNotification] -> ShowS # | |
Binary ProcessMonitorNotification Source # | |
Defined in Control.Distributed.Process.Internal.Types put :: ProcessMonitorNotification -> Put # get :: Get ProcessMonitorNotification # putList :: [ProcessMonitorNotification] -> Put # |
data NodeMonitorNotification Source #
Message sent by node monitors
Instances
Show NodeMonitorNotification Source # | |
Defined in Control.Distributed.Process.Internal.Types showsPrec :: Int -> NodeMonitorNotification -> ShowS # show :: NodeMonitorNotification -> String # showList :: [NodeMonitorNotification] -> ShowS # | |
Binary NodeMonitorNotification Source # | |
Defined in Control.Distributed.Process.Internal.Types put :: NodeMonitorNotification -> Put # get :: Get NodeMonitorNotification # putList :: [NodeMonitorNotification] -> Put # |
data PortMonitorNotification Source #
Message sent by channel (port) monitors
Instances
Show PortMonitorNotification Source # | |
Defined in Control.Distributed.Process.Internal.Types showsPrec :: Int -> PortMonitorNotification -> ShowS # show :: PortMonitorNotification -> String # showList :: [PortMonitorNotification] -> ShowS # | |
Binary PortMonitorNotification Source # | |
Defined in Control.Distributed.Process.Internal.Types put :: PortMonitorNotification -> Put # get :: Get PortMonitorNotification # putList :: [PortMonitorNotification] -> Put # |
data ProcessExitException Source #
Internal exception thrown indirectly by exit
Instances
Exception ProcessExitException Source # | |
Show ProcessExitException Source # | |
Defined in Control.Distributed.Process.Internal.Types showsPrec :: Int -> ProcessExitException -> ShowS # show :: ProcessExitException -> String # showList :: [ProcessExitException] -> ShowS # |
data ProcessLinkException Source #
Exceptions thrown when a linked process dies
Instances
Exception ProcessLinkException Source # | |
Show ProcessLinkException Source # | |
Defined in Control.Distributed.Process.Internal.Types showsPrec :: Int -> ProcessLinkException -> ShowS # show :: ProcessLinkException -> String # showList :: [ProcessLinkException] -> ShowS # |
data NodeLinkException Source #
Exception thrown when a linked node dies
Instances
Exception NodeLinkException Source # | |
Show NodeLinkException Source # | |
Defined in Control.Distributed.Process.Internal.Types showsPrec :: Int -> NodeLinkException -> ShowS # show :: NodeLinkException -> String # showList :: [NodeLinkException] -> ShowS # |
data PortLinkException Source #
Exception thrown when a linked channel (port) dies
Instances
Exception PortLinkException Source # | |
Show PortLinkException Source # | |
Defined in Control.Distributed.Process.Internal.Types showsPrec :: Int -> PortLinkException -> ShowS # show :: PortLinkException -> String # showList :: [PortLinkException] -> ShowS # |
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.
Instances
Exception ProcessRegistrationException Source # | |
Show ProcessRegistrationException Source # | |
Defined in Control.Distributed.Process.Internal.Types showsPrec :: Int -> ProcessRegistrationException -> ShowS # show :: ProcessRegistrationException -> String # showList :: [ProcessRegistrationException] -> ShowS # |
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 |
Instances
Show DiedReason Source # | |
Defined in Control.Distributed.Process.Internal.Types showsPrec :: Int -> DiedReason -> ShowS # show :: DiedReason -> String # showList :: [DiedReason] -> ShowS # | |
Binary DiedReason Source # | |
Defined in Control.Distributed.Process.Internal.Types | |
NFData DiedReason Source # | |
Defined in Control.Distributed.Process.Internal.Types rnf :: DiedReason -> () # | |
Eq DiedReason Source # | |
Defined in Control.Distributed.Process.Internal.Types (==) :: DiedReason -> DiedReason -> Bool # (/=) :: DiedReason -> DiedReason -> Bool # |
newtype DidUnmonitor Source #
(Asynchronous) reply from unmonitor
Instances
newtype DidUnlinkProcess Source #
(Asynchronous) reply from unlink
Instances
newtype DidUnlinkNode Source #
(Asynchronous) reply from unlinkNode
Instances
newtype DidUnlinkPort Source #
(Asynchronous) reply from unlinkPort
Instances
SpawnRef
are used to return pids of spawned processes
data WhereIsReply Source #
(Asynchronous) reply from whereis
Instances
Show WhereIsReply Source # | |
Defined in Control.Distributed.Process.Internal.Types showsPrec :: Int -> WhereIsReply -> ShowS # show :: WhereIsReply -> String # showList :: [WhereIsReply] -> ShowS # | |
Binary WhereIsReply Source # | |
Defined in Control.Distributed.Process.Internal.Types |
data RegisterReply Source #
(Asynchronous) reply from register
and unregister
Instances
Show RegisterReply Source # | |
Defined in Control.Distributed.Process.Internal.Types showsPrec :: Int -> RegisterReply -> ShowS # show :: RegisterReply -> String # showList :: [RegisterReply] -> ShowS # | |
Binary RegisterReply Source # | |
Defined in Control.Distributed.Process.Internal.Types |
data ProcessInfo Source #
Provide information about a running process
ProcessInfo | |
|
Instances
Show ProcessInfo Source # | |
Defined in Control.Distributed.Process.Internal.Types showsPrec :: Int -> ProcessInfo -> ShowS # show :: ProcessInfo -> String # showList :: [ProcessInfo] -> ShowS # | |
Binary ProcessInfo Source # | |
Defined in Control.Distributed.Process.Internal.Types | |
Eq ProcessInfo Source # | |
Defined in Control.Distributed.Process.Internal.Types (==) :: ProcessInfo -> ProcessInfo -> Bool # (/=) :: ProcessInfo -> ProcessInfo -> Bool # |
data ProcessInfoNone Source #
Instances
Show ProcessInfoNone Source # | |
Defined in Control.Distributed.Process.Internal.Types showsPrec :: Int -> ProcessInfoNone -> ShowS # show :: ProcessInfoNone -> String # showList :: [ProcessInfoNone] -> ShowS # | |
Binary ProcessInfoNone Source # | |
Defined in Control.Distributed.Process.Internal.Types |
Node controller internal data types
data ProcessSignal Source #
Signals to the node controller (see NCMsg
)
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 # | |
Defined in Control.Distributed.Process.Internal.Types showsPrec :: Int -> ProcessSignal -> ShowS # show :: ProcessSignal -> String # showList :: [ProcessSignal] -> ShowS # | |
Binary ProcessSignal Source # | |
Defined in Control.Distributed.Process.Internal.Types |
Accessors
localConnections :: Accessor ValidLocalNodeState (Map (Identifier, Identifier) (Connection, ImplicitReconnect)) Source #
localConnectionBetween :: Identifier -> Identifier -> Accessor ValidLocalNodeState (Maybe (Connection, ImplicitReconnect)) Source #