distributed-process-0.6.6: 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

newtype NodeId Source #

Node identifier

Constructors

NodeId 

Instances

Eq NodeId Source # 

Methods

(==) :: NodeId -> NodeId -> Bool #

(/=) :: NodeId -> NodeId -> Bool #

Data NodeId Source # 

Methods

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 :: (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 #

Ord NodeId Source # 
Show NodeId Source # 
Generic NodeId Source # 

Associated Types

type Rep NodeId :: * -> * #

Methods

from :: NodeId -> Rep NodeId x #

to :: Rep NodeId x -> NodeId #

Binary NodeId Source # 

Methods

put :: NodeId -> Put #

get :: Get NodeId #

putList :: [NodeId] -> Put #

NFData NodeId Source # 

Methods

rnf :: NodeId -> () #

Hashable NodeId Source # 

Methods

hashWithSalt :: Int -> NodeId -> Int #

hash :: NodeId -> Int #

type Rep NodeId Source # 
type Rep NodeId = D1 (MetaData "NodeId" "Control.Distributed.Process.Internal.Types" "distributed-process-0.6.6-C2Hr50TwUgZDi5s2rjWzWs" True) (C1 (MetaCons "NodeId" PrefixI True) (S1 (MetaSel (Just Symbol "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

Constructors

LocalProcessId 

Instances

Eq LocalProcessId Source # 
Data LocalProcessId Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LocalProcessId -> c LocalProcessId #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LocalProcessId #

toConstr :: LocalProcessId -> Constr #

dataTypeOf :: LocalProcessId -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c LocalProcessId) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LocalProcessId) #

gmapT :: (forall b. Data b => b -> b) -> LocalProcessId -> LocalProcessId #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LocalProcessId -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LocalProcessId -> r #

gmapQ :: (forall d. Data d => d -> u) -> LocalProcessId -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LocalProcessId -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LocalProcessId -> m LocalProcessId #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LocalProcessId -> m LocalProcessId #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LocalProcessId -> m LocalProcessId #

Ord LocalProcessId Source # 
Show LocalProcessId Source # 
Generic LocalProcessId Source # 

Associated Types

type Rep LocalProcessId :: * -> * #

Binary LocalProcessId Source # 
Hashable LocalProcessId Source # 
type Rep LocalProcessId Source # 
type Rep LocalProcessId = D1 (MetaData "LocalProcessId" "Control.Distributed.Process.Internal.Types" "distributed-process-0.6.6-C2Hr50TwUgZDi5s2rjWzWs" False) (C1 (MetaCons "LocalProcessId" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "lpidUnique") SourceUnpack SourceStrict DecidedStrict) (Rec0 Int32)) (S1 (MetaSel (Just Symbol "lpidCounter") SourceUnpack SourceStrict DecidedStrict) (Rec0 Int32))))

data ProcessId Source #

Process identifier

Constructors

ProcessId 

Fields

Instances

Eq ProcessId Source # 
Data ProcessId Source # 

Methods

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 :: (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 #

Ord ProcessId Source # 
Show ProcessId Source # 
Generic ProcessId Source # 

Associated Types

type Rep ProcessId :: * -> * #

Binary ProcessId Source # 
NFData ProcessId Source # 

Methods

rnf :: ProcessId -> () #

Hashable ProcessId Source # 
type Rep ProcessId Source # 
type Rep ProcessId = D1 (MetaData "ProcessId" "Control.Distributed.Process.Internal.Types" "distributed-process-0.6.6-C2Hr50TwUgZDi5s2rjWzWs" False) (C1 (MetaCons "ProcessId" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "processNodeId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 NodeId)) (S1 (MetaSel (Just Symbol "processLocalId") SourceUnpack SourceStrict DecidedStrict) (Rec0 LocalProcessId))))

data Identifier Source #

Union of all kinds of identifiers

Instances

Eq Identifier Source # 
Ord Identifier Source # 
Show Identifier Source # 
Generic Identifier Source # 

Associated Types

type Rep Identifier :: * -> * #

Binary Identifier Source # 
NFData Identifier Source # 

Methods

rnf :: Identifier -> () #

Hashable Identifier Source # 
type Rep Identifier Source # 
type Rep Identifier = D1 (MetaData "Identifier" "Control.Distributed.Process.Internal.Types" "distributed-process-0.6.6-C2Hr50TwUgZDi5s2rjWzWs" False) ((:+:) (C1 (MetaCons "NodeIdentifier" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 NodeId))) ((:+:) (C1 (MetaCons "ProcessIdentifier" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ProcessId))) (C1 (MetaCons "SendPortIdentifier" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SendPortId)))))

Local nodes and processes

data LocalNode Source #

Local nodes

Constructors

LocalNode 

Fields

data ValidLocalNodeState Source #

Constructors

ValidLocalNodeState 

Fields

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.

data Tracer Source #

Provides access to the trace controller

Constructors

Tracer 

Fields

data MxEventBus Source #

Local system management event bus state

Constructors

MxEventBusInitialising 
MxEventBus 

Fields

newtype Process a Source #

The Cloud Haskell Process type

Constructors

Process 

Instances

Monad Process Source # 

Methods

(>>=) :: Process a -> (a -> Process b) -> Process b #

(>>) :: Process a -> Process b -> Process b #

return :: a -> Process a #

fail :: String -> Process a #

Functor Process Source # 

Methods

fmap :: (a -> b) -> Process a -> Process b #

(<$) :: a -> Process b -> Process a #

MonadFix Process Source # 

Methods

mfix :: (a -> Process a) -> Process a #

Applicative Process Source # 

Methods

pure :: a -> Process a #

(<*>) :: Process (a -> b) -> Process a -> Process b #

(*>) :: Process a -> Process b -> Process b #

(<*) :: Process a -> Process b -> Process a #

MonadIO Process Source # 

Methods

liftIO :: IO a -> Process a #

MonadThrow Process Source # 

Methods

throwM :: Exception e => e -> Process a #

MonadCatch Process Source # 

Methods

catch :: Exception e => Process a -> (e -> Process a) -> Process a #

MonadMask Process Source # 

Methods

mask :: ((forall a. Process a -> Process a) -> Process b) -> Process b #

uninterruptibleMask :: ((forall a. Process a -> Process a) -> Process b) -> Process b #

MonadReader LocalProcess Process Source # 
Serializable b => MkTDict (Process b) Source # 

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

Instances

newtype SendPort a Source #

The send send of a typed channel (serializable)

Constructors

SendPort 

Fields

Instances

Eq (SendPort a) Source # 

Methods

(==) :: SendPort a -> SendPort a -> Bool #

(/=) :: SendPort a -> SendPort a -> Bool #

Ord (SendPort a) Source # 

Methods

compare :: SendPort a -> SendPort a -> Ordering #

(<) :: SendPort a -> SendPort a -> Bool #

(<=) :: SendPort a -> SendPort a -> Bool #

(>) :: SendPort a -> SendPort a -> Bool #

(>=) :: SendPort a -> SendPort a -> Bool #

max :: SendPort a -> SendPort a -> SendPort a #

min :: SendPort a -> SendPort a -> SendPort a #

Show (SendPort a) Source # 

Methods

showsPrec :: Int -> SendPort a -> ShowS #

show :: SendPort a -> String #

showList :: [SendPort a] -> ShowS #

Generic (SendPort a) Source # 

Associated Types

type Rep (SendPort a) :: * -> * #

Methods

from :: SendPort a -> Rep (SendPort a) x #

to :: Rep (SendPort a) x -> SendPort a #

Serializable a => Binary (SendPort a) Source # 

Methods

put :: SendPort a -> Put #

get :: Get (SendPort a) #

putList :: [SendPort a] -> Put #

NFData a => NFData (SendPort a) Source # 

Methods

rnf :: SendPort a -> () #

Hashable a => Hashable (SendPort a) Source # 

Methods

hashWithSalt :: Int -> SendPort a -> Int #

hash :: SendPort a -> Int #

type Rep (SendPort a) Source # 
type Rep (SendPort a) = D1 (MetaData "SendPort" "Control.Distributed.Process.Internal.Types" "distributed-process-0.6.6-C2Hr50TwUgZDi5s2rjWzWs" True) (C1 (MetaCons "SendPort" PrefixI True) (S1 (MetaSel (Just Symbol "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.

Constructors

ReceivePort 

Fields

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

Instances

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.

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 RegisterReply Source #

(Asynchronous) reply from register and unregister

Node controller internal data types

data NCMsg Source #

Messages to the node controller

Instances

Accessors

Utilities

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