distributed-process-0.7.6: Cloud Haskell: Erlang-style concurrency in Haskell
Safe HaskellNone
LanguageHaskell2010

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 MxAgentState s Source #

Constructors

MxAgentState 

Instances

Instances details
MonadState (MxAgentState s) (MxAgent s) Source # 
Instance details

Defined in Control.Distributed.Process.Management.Internal.Types

Methods

get :: MxAgent s (MxAgentState s) #

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

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

newtype MxAgent s a Source #

Monad for management agents.

Constructors

MxAgent 

Instances

Instances details
MonadFix (MxAgent s) Source # 
Instance details

Defined in Control.Distributed.Process.Management.Internal.Types

Methods

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

MonadIO (MxAgent s) Source # 
Instance details

Defined in Control.Distributed.Process.Management.Internal.Types

Methods

liftIO :: IO a -> MxAgent s a #

Applicative (MxAgent s) Source # 
Instance details

Defined in Control.Distributed.Process.Management.Internal.Types

Methods

pure :: a -> MxAgent s a #

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

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

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

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

Functor (MxAgent s) Source # 
Instance details

Defined in Control.Distributed.Process.Management.Internal.Types

Methods

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

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

Monad (MxAgent s) Source # 
Instance details

Defined in Control.Distributed.Process.Management.Internal.Types

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 #

MonadState (MxAgentState s) (MxAgent s) Source # 
Instance details

Defined in Control.Distributed.Process.Management.Internal.Types

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.

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

MxSentToName String ProcessId Message

fired whenever a named send occurs

MxSentToPort ProcessId SendPortId Message

fired whenever a sendChan occurs

MxReceived ProcessId Message

fired whenever a message is received by a local process

MxReceivedPort SendPortId Message

fired whenever a message is received via a typed channel

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

Instances details
Generic MxEvent Source # 
Instance details

Defined in Control.Distributed.Process.Management.Internal.Types

Associated Types

type Rep MxEvent 
Instance details

Defined in Control.Distributed.Process.Management.Internal.Types

type Rep MxEvent = D1 ('MetaData "MxEvent" "Control.Distributed.Process.Management.Internal.Types" "distributed-process-0.7.6-F5sZSqR3Cb09RBogyeswiz" 'False) ((((C1 ('MetaCons "MxSpawned" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ProcessId)) :+: C1 ('MetaCons "MxRegistered" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ProcessId) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: (C1 ('MetaCons "MxUnRegistered" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ProcessId) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "MxProcessDied" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ProcessId) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DiedReason)))) :+: ((C1 ('MetaCons "MxNodeDied" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 NodeId) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DiedReason)) :+: C1 ('MetaCons "MxSent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ProcessId) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ProcessId) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Message)))) :+: (C1 ('MetaCons "MxSentToName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ProcessId) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Message))) :+: C1 ('MetaCons "MxSentToPort" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ProcessId) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SendPortId) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Message)))))) :+: (((C1 ('MetaCons "MxReceived" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ProcessId) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Message)) :+: C1 ('MetaCons "MxReceivedPort" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SendPortId) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Message))) :+: (C1 ('MetaCons "MxConnected" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ConnectionId) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EndPointAddress)) :+: C1 ('MetaCons "MxDisconnected" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ConnectionId) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EndPointAddress)))) :+: ((C1 ('MetaCons "MxUser" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Message)) :+: C1 ('MetaCons "MxLog" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: (C1 ('MetaCons "MxTraceTakeover" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ProcessId)) :+: C1 ('MetaCons "MxTraceDisable" 'PrefixI 'False) (U1 :: Type -> Type)))))

Methods

from :: MxEvent -> Rep MxEvent x #

to :: Rep MxEvent x -> MxEvent #

Show MxEvent Source # 
Instance details

Defined in Control.Distributed.Process.Management.Internal.Types

Binary MxEvent Source # 
Instance details

Defined in Control.Distributed.Process.Management.Internal.Types

Methods

put :: MxEvent -> Put #

get :: Get MxEvent #

putList :: [MxEvent] -> Put #

Addressable MxEvent Source # 
Instance details

Defined in Control.Distributed.Process.Management.Internal.Types

type Rep MxEvent Source # 
Instance details

Defined in Control.Distributed.Process.Management.Internal.Types

type Rep MxEvent = D1 ('MetaData "MxEvent" "Control.Distributed.Process.Management.Internal.Types" "distributed-process-0.7.6-F5sZSqR3Cb09RBogyeswiz" 'False) ((((C1 ('MetaCons "MxSpawned" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ProcessId)) :+: C1 ('MetaCons "MxRegistered" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ProcessId) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: (C1 ('MetaCons "MxUnRegistered" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ProcessId) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "MxProcessDied" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ProcessId) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DiedReason)))) :+: ((C1 ('MetaCons "MxNodeDied" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 NodeId) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DiedReason)) :+: C1 ('MetaCons "MxSent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ProcessId) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ProcessId) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Message)))) :+: (C1 ('MetaCons "MxSentToName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ProcessId) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Message))) :+: C1 ('MetaCons "MxSentToPort" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ProcessId) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SendPortId) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Message)))))) :+: (((C1 ('MetaCons "MxReceived" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ProcessId) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Message)) :+: C1 ('MetaCons "MxReceivedPort" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SendPortId) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Message))) :+: (C1 ('MetaCons "MxConnected" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ConnectionId) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EndPointAddress)) :+: C1 ('MetaCons "MxDisconnected" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ConnectionId) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EndPointAddress)))) :+: ((C1 ('MetaCons "MxUser" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Message)) :+: C1 ('MetaCons "MxLog" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: (C1 ('MetaCons "MxTraceTakeover" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ProcessId)) :+: C1 ('MetaCons "MxTraceDisable" 'PrefixI 'False) (U1 :: Type -> Type)))))

class Addressable a where Source #

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