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

Safe HaskellNone
LanguageHaskell2010

Control.Eff.Concurrent.Protocol.Supervisor

Description

A process supervisor 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 supervisor. Children can be started, but not restarted.

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

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

When a supervisor spawns a new child process, it expects the child process to return a ProcessId. The supervisor 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 supervisor process, and also, a child may break free from the supervisor by unlinking.

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

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

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

The future of this supervisor might not be a-lot more than it currently is. The ability to restart processes might be implemented outside of this supervisor 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

startSupervisor :: forall p e. (HasCallStack, LogIo (Processes e), TangibleSup p, Server (Sup p) (Processes e)) => StartArgument (Sup p) (Processes e) -> Eff (Processes e) (Endpoint (Sup p)) Source #

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

To spawn new child processes use spawnChild.

Since: 0.23.0

stopSupervisor :: (HasCallStack, HasProcesses e q, Member Logs e, Lifted IO e, TangibleSup p) => Endpoint (Sup p) -> Eff e () Source #

Stop the supervisor and shutdown all processes.

Block until the supervisor has finished.

Since: 0.23.0

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

Check if a supervisor process is still alive.

Since: 0.23.0

monitorSupervisor :: forall p q0 e. (HasCallStack, Member Logs e, HasProcesses e q0, TangibleSup p) => Endpoint (Sup p) -> Eff e MonitorReference Source #

Monitor a supervisor process.

Since: 0.23.0

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

Return a Text describing the current state of the supervisor.

Since: 0.23.0

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

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

Since: 0.23.0

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

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

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, TangibleSup p, Typeable (ServerPdu p)) => Endpoint (Sup 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

stopChild :: forall p e q0. (HasCallStack, Member Logs e, HasProcesses e q0, TangibleSup p) => Endpoint (Sup 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 Sup (p :: Type) Source #

The index type of Server supervisors.

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

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

Since: 0.24.0

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

Defined in Control.Eff.Concurrent.Protocol.Supervisor

Associated Types

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

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

(LogIo q, TangibleSup p, Tangible (ChildId p), Typeable (ServerPdu p), Server p (Processes q), HasProcesses (ServerEffects p (Processes q)) q) => Server (Sup p) (Processes q) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Supervisor

Associated Types

data StartArgument (Sup p) (Processes q) :: Type Source #

type Protocol (Sup p) :: Type Source #

type Model (Sup p) :: Type Source #

type Settings (Sup p) :: Type Source #

Show (ChildId p) => Show (Pdu (Sup p) (Synchronous r)) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Supervisor

Methods

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

show :: Pdu (Sup p) (Synchronous r) -> String #

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

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

Defined in Control.Eff.Concurrent.Protocol.Supervisor

Methods

rnf :: Pdu (Sup p) (Synchronous r) -> () #

type EmbeddedPduList (Sup p) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Supervisor

type EmbeddedPduList (Sup p) = ([] :: [Type])
data Pdu (Sup p) r Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Supervisor

data Pdu (Sup p) r where
type Protocol (Sup p) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Supervisor

type Protocol (Sup p) = Sup p
type Model (Sup p) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Supervisor

type Model (Sup p)
type Settings (Sup p) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Supervisor

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

Defined in Control.Eff.Concurrent.Protocol.Supervisor

type ToPretty (Sup p :: Type) = "supervisor" <:> ToPretty p
data StartArgument (Sup p) (Processes q) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Supervisor

type family ChildId p Source #

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

Note, that the type you provide must be Tangible.

Since: 0.24.0

data family StartArgument a q 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.Supervisor

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.Supervisor

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.Supervisor

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.Supervisor

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.Supervisor

Methods

rnf :: SpawnErr p -> () #

type Rep (SpawnErr p) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Supervisor

type Rep (SpawnErr p) = D1 (MetaData "SpawnErr" "Control.Eff.Concurrent.Protocol.Supervisor" "extensible-effects-concurrent-0.29.2-LYViqZFOIQHPuntx6ss9S" 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)))))