extensible-effects-concurrent-0.32.0: Message passing concurrency as extensible-effect

Safe HaskellNone
LanguageHaskell2010

Control.Eff.Concurrent.Protocol.Broker

Description

A process broker spawns and monitors child processes.

The child processes are mapped to symbolic identifier values: Child-IDs.

This is the barest, most minimal version of a broker. Children can be started, but not restarted.

Children can efficiently be looked-up by an id-value, and when the broker is shutdown, all children will be shutdown these are actually all the features of this broker implementation.

Also, this minimalist broker only knows how to spawn a single kind of child process.

When a broker spawns a new child process, it expects the child process to return a ProcessId. The broker will monitor the child process.

This is in stark contrast to how Erlang/OTP handles things; In the OTP Supervisor, the child has to link to the parent. This allows the child spec to be more flexible in that no pid has to be passed from the child start function to the broker process, and also, a child may break free from the broker by unlinking.

Now while this seems nice at first, this might actually cause surprising results, since it is usually expected that stopping a broker also stops the children, or that a child exit shows up in the logging originating from the former broker.

The approach here is to allow any child to link to the broker to realize when the broker was violently killed, and otherwise give the child no chance to unlink itself from its broker.

This module is far simpler than the Erlang/OTP counter part, of a simple_one_for_one supervisor.

The future of this broker might not be a-lot more than it currently is. The ability to restart processes might be implemented outside of this broker module.

One way to do that is to implement the restart logic in a separate module, since the child-id can be reused when a child exits.

Since: 0.23.0

Synopsis

Documentation

startLink :: forall p e. (HasCallStack, IoLogging (Processes e), TangibleBroker p, Server (Broker p) (Processes e)) => StartArgument (Broker p) -> Eff (Processes e) (Endpoint (Broker p)) Source #

Start and link a new broker process with the given SpawnFununction.

To spawn new child processes use spawnChild.

Since: 0.23.0

statefulChild :: forall p e. (HasCallStack, IoLogging e, TangibleBroker (Stateful p), Server (Broker (Stateful p)) e) => Timeout -> (ChildId p -> StartArgument p) -> StartArgument (Broker (Stateful p)) Source #

A smart constructor for MkBrokerConfig that makes it easy to start a Server instance.

The user needs to instantiate ChildId p.

Since: 0.30.0

stopBroker :: (HasCallStack, HasProcesses e q, Member Logs e, Lifted IO e, TangibleBroker p) => Endpoint (Broker p) -> Eff e () Source #

Stop the broker and shutdown all processes.

Block until the broker has finished.

Since: 0.23.0

isBrokerAlive :: forall p q0 e. (HasCallStack, Member Logs e, Typeable p, HasProcesses e q0) => Endpoint (Broker p) -> Eff e Bool Source #

Check if a broker process is still alive.

Since: 0.23.0

monitorBroker :: forall p q0 e. (HasCallStack, Member Logs e, HasProcesses e q0, TangibleBroker p) => Endpoint (Broker p) -> Eff e MonitorReference Source #

Monitor a broker process.

Since: 0.23.0

getDiagnosticInfo :: forall p e q0. (HasCallStack, HasProcesses e q0, TangibleBroker p) => Endpoint (Broker p) -> Eff e Text Source #

Return a Text describing the current state of the broker.

Since: 0.23.0

spawnChild :: forall p q0 e. (HasCallStack, Member Logs e, HasProcesses e q0, TangibleBroker p, Typeable (ServerPdu p)) => Endpoint (Broker p) -> ChildId p -> Eff e (Either (SpawnErr p) (Endpoint (ServerPdu p))) Source #

Start and monitor a new child process using the SpawnFun passed to startLink.

Since: 0.23.0

spawnOrLookup :: forall p q0 e. (HasCallStack, Member Logs e, HasProcesses e q0, TangibleBroker p, Typeable (ServerPdu p)) => Endpoint (Broker p) -> ChildId p -> Eff e (Endpoint (ServerPdu p)) Source #

Start and monitor a new child process using the SpawnFun passed to startLink.

Call spawnChild and unpack the Either result, ignoring the AlreadyStarted error.

Since: 0.29.2

lookupChild :: forall p e q0. (HasCallStack, Member Logs e, HasProcesses e q0, TangibleBroker p, Typeable (ServerPdu p)) => Endpoint (Broker p) -> ChildId p -> Eff e (Maybe (Endpoint (ServerPdu p))) Source #

Lookup the given child-id and return the output value of the SpawnFun if the client process exists.

Since: 0.23.0

callById :: forall destination protocol result e q0. (HasCallStack, Member Logs e, HasProcesses e q0, Lifted IO e, Lifted IO q0, TangibleBroker protocol, TangiblePdu destination (Synchronous result), TangiblePdu protocol (Synchronous result), Embeds (ServerPdu destination) protocol, Ord (ChildId destination), Tangible (ChildId destination), Typeable (ServerPdu destination), Tangible result, NFData (Pdu protocol (Synchronous result)), NFData (Pdu (ServerPdu destination) (Synchronous result)), Show (Pdu (ServerPdu destination) (Synchronous result))) => Endpoint (Broker destination) -> ChildId destination -> Pdu protocol (Synchronous result) -> Timeout -> Eff e result Source #

castById :: forall destination protocol e q0. (HasCallStack, Member Logs e, HasProcesses e q0, TangibleBroker protocol, TangiblePdu destination Asynchronous, TangiblePdu protocol Asynchronous) => Endpoint (Broker destination) -> ChildId destination -> Pdu protocol Asynchronous -> Eff e () Source #

stopChild :: forall p e q0. (HasCallStack, Member Logs e, HasProcesses e q0, TangibleBroker p) => Endpoint (Broker p) -> ChildId p -> Eff e Bool Source #

Stop a child process, and block until the child has exited.

Return True if a process with that ID was found, False if no process with the given ID was running.

Since: 0.23.0

data ChildNotFound child where Source #

Constructors

ChildNotFound :: ChildId child -> Endpoint (Broker child) -> ChildNotFound child 
Instances
(Show (ChildId child), Typeable child) => Show (ChildNotFound child) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Broker

Methods

showsPrec :: Int -> ChildNotFound child -> ShowS #

show :: ChildNotFound child -> String #

showList :: [ChildNotFound child] -> ShowS #

NFData (ChildId c) => NFData (ChildNotFound c) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Broker

Methods

rnf :: ChildNotFound c -> () #

data Broker (p :: Type) Source #

The index type of Server supervisors.

A Broker p manages the life cycle of the processes, running the Server p methods of that specific type.

The broker maps an identifier value of type ChildId p to an Endpoint p.

Since: 0.24.0

Instances
Typeable p => HasPdu (Broker p) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Broker

Associated Types

type EmbeddedPduList (Broker p) :: [Type] Source #

data Pdu (Broker p) reply :: Type Source #

Typeable p => HasPduPrism (Broker p) (ObserverRegistry (ChildEvent p)) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Broker

Methods

embeddedPdu :: Prism' (Pdu (Broker p) result) (Pdu (ObserverRegistry (ChildEvent p)) result) Source #

embedPdu :: Pdu (ObserverRegistry (ChildEvent p)) result -> Pdu (Broker p) result Source #

fromPdu :: Pdu (Broker p) result -> Maybe (Pdu (ObserverRegistry (ChildEvent p)) result) Source #

(IoLogging q, TangibleBroker p, Tangible (ChildId p), Typeable (ServerPdu p), Server p (Processes q), HasProcesses (ServerEffects p (Processes q)) q) => Server (Broker p) (Processes q) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Broker

Associated Types

data StartArgument (Broker p) :: Type Source #

type Protocol (Broker p) :: Type Source #

data Model (Broker p) :: Type Source #

type Settings (Broker p) :: Type Source #

(Typeable p, Show (ChildId p)) => Show (Pdu (Broker p) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Broker

Methods

showsPrec :: Int -> Pdu (Broker p) r -> ShowS #

show :: Pdu (Broker p) r -> String #

showList :: [Pdu (Broker p) r] -> ShowS #

NFData (ChildId p) => NFData (Pdu (Broker p) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Broker

Methods

rnf :: Pdu (Broker p) r -> () #

type EmbeddedPduList (Broker p) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Broker

data Pdu (Broker p) r Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Broker

data Pdu (Broker p) r where
data StartArgument (Broker p) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Broker

type Protocol (Broker p) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Broker

type Protocol (Broker p) = Broker p
data Model (Broker p) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Broker

type Settings (Broker p) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Broker

type Settings (Broker p) = ()
type ToPretty (Broker p :: Type) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Broker

type ToPretty (Broker p :: Type) = "broker" <:> ToPretty p

data family Pdu protocol (reply :: Synchronicity) Source #

The protocol data unit type for the given protocol.

Instances
(Show (Pdu a1 r), Show (Pdu a2 r)) => Show (Pdu (a1, a2) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

showsPrec :: Int -> Pdu (a1, a2) r -> ShowS #

show :: Pdu (a1, a2) r -> String #

showList :: [Pdu (a1, a2) r] -> ShowS #

(Show (Pdu a1 r), Show (Pdu a2 r), Show (Pdu a3 r)) => Show (Pdu (a1, a2, a3) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

showsPrec :: Int -> Pdu (a1, a2, a3) r -> ShowS #

show :: Pdu (a1, a2, a3) r -> String #

showList :: [Pdu (a1, a2, a3) r] -> ShowS #

(Show (Pdu a1 r), Show (Pdu a2 r), Show (Pdu a3 r), Show (Pdu a4 r)) => Show (Pdu (a1, a2, a3, a4) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

showsPrec :: Int -> Pdu (a1, a2, a3, a4) r -> ShowS #

show :: Pdu (a1, a2, a3, a4) r -> String #

showList :: [Pdu (a1, a2, a3, a4) r] -> ShowS #

(Show (Pdu a1 r), Show (Pdu a2 r), Show (Pdu a3 r), Show (Pdu a4 r), Show (Pdu a5 r)) => Show (Pdu (a1, a2, a3, a4, a5) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

showsPrec :: Int -> Pdu (a1, a2, a3, a4, a5) r -> ShowS #

show :: Pdu (a1, a2, a3, a4, a5) r -> String #

showList :: [Pdu (a1, a2, a3, a4, a5) r] -> ShowS #

Typeable event => Show (Pdu (ObserverRegistry event) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

showsPrec :: Int -> Pdu (ObserverRegistry event) r -> ShowS #

show :: Pdu (ObserverRegistry event) r -> String #

showList :: [Pdu (ObserverRegistry event) r] -> ShowS #

Show event => Show (Pdu (Observer event) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

showsPrec :: Int -> Pdu (Observer event) r -> ShowS #

show :: Pdu (Observer event) r -> String #

showList :: [Pdu (Observer event) r] -> ShowS #

(Typeable p, Show (ChildId p)) => Show (Pdu (Broker p) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Broker

Methods

showsPrec :: Int -> Pdu (Broker p) r -> ShowS #

show :: Pdu (Broker p) r -> String #

showList :: [Pdu (Broker p) r] -> ShowS #

(Show (ChildId child), Typeable child, Typeable (ServerPdu child)) => Show (Pdu (Watchdog child) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Watchdog

Methods

showsPrec :: Int -> Pdu (Watchdog child) r -> ShowS #

show :: Pdu (Watchdog child) r -> String #

showList :: [Pdu (Watchdog child) r] -> ShowS #

(NFData (Pdu a1 r), NFData (Pdu a2 r)) => NFData (Pdu (a1, a2) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

rnf :: Pdu (a1, a2) r -> () #

(NFData (Pdu a1 r), NFData (Pdu a2 r), NFData (Pdu a3 r)) => NFData (Pdu (a1, a2, a3) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

rnf :: Pdu (a1, a2, a3) r -> () #

(NFData (Pdu a1 r), NFData (Pdu a2 r), NFData (Pdu a3 r), NFData (Pdu a4 r)) => NFData (Pdu (a1, a2, a3, a4) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

rnf :: Pdu (a1, a2, a3, a4) r -> () #

(Typeable r, NFData (Pdu a1 r), NFData (Pdu a2 r), NFData (Pdu a3 r), NFData (Pdu a4 r), NFData (Pdu a5 r)) => NFData (Pdu (a1, a2, a3, a4, a5) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

rnf :: Pdu (a1, a2, a3, a4, a5) r -> () #

NFData (Pdu (ObserverRegistry event) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

rnf :: Pdu (ObserverRegistry event) r -> () #

NFData event => NFData (Pdu (Observer event) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

rnf :: Pdu (Observer event) r -> () #

NFData (ChildId p) => NFData (Pdu (Broker p) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Broker

Methods

rnf :: Pdu (Broker p) r -> () #

NFData (ChildId child) => NFData (Pdu (Watchdog child) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Watchdog

Methods

rnf :: Pdu (Watchdog child) r -> () #

data Pdu (ObserverRegistry event) r Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

data Pdu (Broker p) r Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Broker

data Pdu (Broker p) r where
data Pdu (Watchdog child) r Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Watchdog

data Pdu (Watchdog child) r where
type ToPretty (Pdu x y :: Type) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

type ToPretty (Pdu x y :: Type) = PrettySurrounded (PutStr "<") (PutStr ">") (("protocol" <:> ToPretty x) <+> ToPretty y)
data Pdu (a1, a2) r Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

data Pdu (a1, a2) r
data Pdu (Observer event) r Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

data Pdu (Observer event) r where
data Pdu (a1, a2, a3) r Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

data Pdu (a1, a2, a3) r
data Pdu (a1, a2, a3, a4) r Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

data Pdu (a1, a2, a3, a4) r
data Pdu (a1, a2, a3, a4, a5) r Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

data Pdu (a1, a2, a3, a4, a5) r

type family ChildId p Source #

The type of value used to index running Server processes managed by a Broker.

Note, that the type you provide must be Tangible.

Since: 0.24.0

Instances
type ChildId (Stateful p) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Broker

type ChildId (Stateful p) = ChildId p

data family StartArgument a Source #

The value that defines what is required to initiate a Server loop.

data SpawnErr p Source #

Runtime-Errors occurring when spawning child-processes.

Since: 0.23.0

Constructors

AlreadyStarted (ChildId p) (Endpoint (ServerPdu p)) 
Instances
Eq (ChildId p) => Eq (SpawnErr p) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Broker

Methods

(==) :: SpawnErr p -> SpawnErr p -> Bool #

(/=) :: SpawnErr p -> SpawnErr p -> Bool #

Ord (ChildId p) => Ord (SpawnErr p) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Broker

Methods

compare :: SpawnErr p -> SpawnErr p -> Ordering #

(<) :: SpawnErr p -> SpawnErr p -> Bool #

(<=) :: SpawnErr p -> SpawnErr p -> Bool #

(>) :: SpawnErr p -> SpawnErr p -> Bool #

(>=) :: SpawnErr p -> SpawnErr p -> Bool #

max :: SpawnErr p -> SpawnErr p -> SpawnErr p #

min :: SpawnErr p -> SpawnErr p -> SpawnErr p #

(Typeable (ServerPdu p), Show (ChildId p)) => Show (SpawnErr p) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Broker

Methods

showsPrec :: Int -> SpawnErr p -> ShowS #

show :: SpawnErr p -> String #

showList :: [SpawnErr p] -> ShowS #

Generic (SpawnErr p) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Broker

Associated Types

type Rep (SpawnErr p) :: Type -> Type #

Methods

from :: SpawnErr p -> Rep (SpawnErr p) x #

to :: Rep (SpawnErr p) x -> SpawnErr p #

NFData (ChildId p) => NFData (SpawnErr p) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Broker

Methods

rnf :: SpawnErr p -> () #

type Rep (SpawnErr p) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Broker

type Rep (SpawnErr p) = D1 (MetaData "SpawnErr" "Control.Eff.Concurrent.Protocol.Broker" "extensible-effects-concurrent-0.32.0-GimAdtHOovq4dulPgeQPe9" False) (C1 (MetaCons "AlreadyStarted" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ChildId p)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Endpoint (ServerPdu p)))))

data ChildEvent p where Source #

The event type to indicate that a child was started or stopped.

The need for this type originated for the watchdog functionality introduced in 0.30.0. The watch dog shall restart a crashed child, and in order to do so, it must somehow monitor the child. Since no order is specified in which processes get the ProcessDown events, a watchdog cannot monitor a child and restart it immediately, because it might have received the process down event before the broker. So instead the watchdog can simply use the broker events, and monitor only the broker process.

Since: 0.30.0

Constructors

OnChildSpawned :: Endpoint (Broker p) -> ChildId p -> Endpoint (ServerPdu p) -> ChildEvent p 
OnChildDown :: Endpoint (Broker p) -> ChildId p -> Endpoint (ServerPdu p) -> Interrupt NoRecovery -> ChildEvent p 
OnBrokerShuttingDown 

Fields

Instances
(Typeable p, Typeable (ServerPdu p), Show (ChildId p)) => Show (ChildEvent p) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Broker

Generic (ChildEvent p) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Broker

Associated Types

type Rep (ChildEvent p) :: Type -> Type #

Methods

from :: ChildEvent p -> Rep (ChildEvent p) x #

to :: Rep (ChildEvent p) x -> ChildEvent p #

NFData (ChildId p) => NFData (ChildEvent p) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Broker

Methods

rnf :: ChildEvent p -> () #

Typeable p => HasPduPrism (Broker p) (ObserverRegistry (ChildEvent p)) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Broker

Methods

embeddedPdu :: Prism' (Pdu (Broker p) result) (Pdu (ObserverRegistry (ChildEvent p)) result) Source #

embedPdu :: Pdu (ObserverRegistry (ChildEvent p)) result -> Pdu (Broker p) result Source #

fromPdu :: Pdu (Broker p) result -> Maybe (Pdu (ObserverRegistry (ChildEvent p)) result) Source #

Typeable child => HasPduPrism (Watchdog child) (Observer (ChildEvent child)) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Watchdog

Methods

embeddedPdu :: Prism' (Pdu (Watchdog child) result) (Pdu (Observer (ChildEvent child)) result) Source #

embedPdu :: Pdu (Observer (ChildEvent child)) result -> Pdu (Watchdog child) result Source #

fromPdu :: Pdu (Watchdog child) result -> Maybe (Pdu (Observer (ChildEvent child)) result) Source #

type Rep (ChildEvent p) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Broker