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

Safe HaskellNone
LanguageHaskell98

Control.Distributed.Process.Management.Internal.Types

Synopsis

Documentation

newtype MxAgentId Source #

A newtype wrapper for an agent id (which is a string).

Constructors

MxAgentId 

Fields

data MxTableId Source #

Instances

Generic MxTableId Source # 

Associated Types

type Rep MxTableId :: * -> * #

Binary MxTableId Source # 
type Rep MxTableId Source # 
type Rep MxTableId = D1 (MetaData "MxTableId" "Control.Distributed.Process.Management.Internal.Types" "distributed-process-0.6.6-C2Hr50TwUgZDi5s2rjWzWs" False) ((:+:) (C1 (MetaCons "MxForAgent" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 MxAgentId))) (C1 (MetaCons "MxForPid" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ProcessId))))

data MxAgentState s Source #

Instances

newtype MxAgent s a Source #

Monad for management agents.

Constructors

MxAgent 

Instances

Monad (MxAgent s) Source # 

Methods

(>>=) :: MxAgent s a -> (a -> MxAgent s b) -> MxAgent s b #

(>>) :: MxAgent s a -> MxAgent s b -> MxAgent s b #

return :: a -> MxAgent s a #

fail :: String -> MxAgent s a #

Functor (MxAgent s) Source # 

Methods

fmap :: (a -> b) -> MxAgent s a -> MxAgent s b #

(<$) :: a -> MxAgent s b -> MxAgent s a #

Applicative (MxAgent s) Source # 

Methods

pure :: a -> MxAgent s a #

(<*>) :: MxAgent s (a -> b) -> MxAgent s a -> MxAgent s b #

(*>) :: MxAgent s a -> MxAgent s b -> MxAgent s b #

(<*) :: MxAgent s a -> MxAgent s b -> MxAgent s a #

MonadIO (MxAgent s) Source # 

Methods

liftIO :: IO a -> MxAgent s a #

MonadState (MxAgentState s) (MxAgent s) Source # 

Methods

get :: MxAgent s (MxAgentState s) #

put :: MxAgentState s -> MxAgent s () #

state :: (MxAgentState s -> (a, MxAgentState s)) -> MxAgent s a #

data MxAction Source #

Represents the actions a management agent can take when evaluating an event sink.

data MxAgentStart Source #

Instances

Generic MxAgentStart Source # 

Associated Types

type Rep MxAgentStart :: * -> * #

Binary MxAgentStart Source # 
type Rep MxAgentStart Source # 
type Rep MxAgentStart = D1 (MetaData "MxAgentStart" "Control.Distributed.Process.Management.Internal.Types" "distributed-process-0.6.6-C2Hr50TwUgZDi5s2rjWzWs" False) (C1 (MetaCons "MxAgentStart" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "mxAgentTableChan") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SendPort ProcessId))) (S1 (MetaSel (Just Symbol "mxAgentIdStart") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MxAgentId))))

type Fork = Process () -> IO ProcessId Source #

Gross though it is, this synonym represents a function used to forking new processes, which has to be passed as a HOF when calling mxAgentController, since there's no other way to avoid a circular dependency with Node.hs

type MxSink s = Message -> MxAgent s (Maybe MxAction) Source #

Type of a management agent's event sink.

data MxEvent Source #

This is the default management event, fired for various internal events around the NT connection and Process lifecycle. All published events that conform to this type, are eligible for tracing - i.e., they will be delivered to the trace controller.

Constructors

MxSpawned ProcessId

fired whenever a local process is spawned

MxRegistered ProcessId String

fired whenever a process/name is registered (locally)

MxUnRegistered ProcessId String

fired whenever a process/name is unregistered (locally)

MxProcessDied ProcessId DiedReason

fired whenever a process dies

MxNodeDied NodeId DiedReason

fired whenever a node dies (i.e., the connection is broken/disconnected)

MxSent ProcessId ProcessId Message

fired whenever a message is sent from a local process

MxReceived ProcessId Message

fired whenever a message is received by a local process

MxConnected ConnectionId EndPointAddress

fired when a network-transport connection is first established

MxDisconnected ConnectionId EndPointAddress

fired when a network-transport connection is broken/disconnected

MxUser Message

a user defined trace event

MxLog String

a logging event - used for debugging purposes only

MxTraceTakeover ProcessId

notifies a trace listener that all subsequent traces will be sent to pid

MxTraceDisable

notifies a trace listener that it has been disabled/removed

Instances

Show MxEvent Source # 
Generic MxEvent Source # 

Associated Types

type Rep MxEvent :: * -> * #

Methods

from :: MxEvent -> Rep MxEvent x #

to :: Rep MxEvent x -> MxEvent #

Binary MxEvent Source # 

Methods

put :: MxEvent -> Put #

get :: Get MxEvent #

putList :: [MxEvent] -> Put #

Addressable MxEvent Source # 
type Rep MxEvent Source # 
type Rep MxEvent = D1 (MetaData "MxEvent" "Control.Distributed.Process.Management.Internal.Types" "distributed-process-0.6.6-C2Hr50TwUgZDi5s2rjWzWs" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "MxSpawned" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ProcessId))) ((:+:) (C1 (MetaCons "MxRegistered" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ProcessId)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))) (C1 (MetaCons "MxUnRegistered" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ProcessId)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))))) ((:+:) (C1 (MetaCons "MxProcessDied" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ProcessId)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DiedReason)))) ((:+:) (C1 (MetaCons "MxNodeDied" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NodeId)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DiedReason)))) (C1 (MetaCons "MxSent" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ProcessId)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ProcessId)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Message)))))))) ((:+:) ((:+:) (C1 (MetaCons "MxReceived" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ProcessId)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Message)))) ((:+:) (C1 (MetaCons "MxConnected" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ConnectionId)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EndPointAddress)))) (C1 (MetaCons "MxDisconnected" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ConnectionId)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EndPointAddress)))))) ((:+:) ((:+:) (C1 (MetaCons "MxUser" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Message))) (C1 (MetaCons "MxLog" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))) ((:+:) (C1 (MetaCons "MxTraceTakeover" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ProcessId))) (C1 (MetaCons "MxTraceDisable" PrefixI False) U1)))))

class Addressable a where Source #

The class of things that we might be able to resolve to a ProcessId (or not).

Minimal complete definition

resolveToPid