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

Safe HaskellNone
LanguageHaskell2010

Control.Eff.Concurrent.Api.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 seperate module, since the child-id can be reused when a child exits.

Since: 0.23.0

Synopsis

Documentation

data Sup childId spawnResult Source #

Api type for supervisor processes.

The supervisor process contains a SpawnFun from which it can spawn new child processes.

The supervisor maps an identifier value of type childId to a ProcessId and a spawnResult type.

This spawnResult is likely a tuple of Server process ids that allow type-safe interaction with the process.

Also, this serves as handle or reference for interacting with a supervisor process.

A value of this type is returned by startSupervisor

Since: 0.23.0

Instances
Show i => Show (Api (Sup i o) (Synchronous r)) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Supervisor

Methods

showsPrec :: Int -> Api (Sup i o) (Synchronous r) -> ShowS #

show :: Api (Sup i o) (Synchronous r) -> String #

showList :: [Api (Sup i o) (Synchronous r)] -> ShowS #

NFData i => NFData (Api (Sup i o) (Synchronous r)) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Supervisor

Methods

rnf :: Api (Sup i o) (Synchronous r) -> () #

Eq (Sup childId spawnResult) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Supervisor

Methods

(==) :: Sup childId spawnResult -> Sup childId spawnResult -> Bool #

(/=) :: Sup childId spawnResult -> Sup childId spawnResult -> Bool #

Ord (Sup childId spawnResult) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Supervisor

Methods

compare :: Sup childId spawnResult -> Sup childId spawnResult -> Ordering #

(<) :: Sup childId spawnResult -> Sup childId spawnResult -> Bool #

(<=) :: Sup childId spawnResult -> Sup childId spawnResult -> Bool #

(>) :: Sup childId spawnResult -> Sup childId spawnResult -> Bool #

(>=) :: Sup childId spawnResult -> Sup childId spawnResult -> Bool #

max :: Sup childId spawnResult -> Sup childId spawnResult -> Sup childId spawnResult #

min :: Sup childId spawnResult -> Sup childId spawnResult -> Sup childId spawnResult #

(PrettyTypeShow (ToPretty childId), PrettyTypeShow (ToPretty spawnResult)) => Show (Sup childId spawnResult) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Supervisor

Methods

showsPrec :: Int -> Sup childId spawnResult -> ShowS #

show :: Sup childId spawnResult -> String #

showList :: [Sup childId spawnResult] -> ShowS #

NFData (Sup childId spawnResult) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Supervisor

Methods

rnf :: Sup childId spawnResult -> () #

type ToPretty (Sup i o :: Type) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Supervisor

type ToPretty (Sup i o :: Type) = ((PutStr "supervisor{" <++> ToPretty i) <+> PutStr "=>") <+> (ToPretty o <++> PutStr "}")
data Api (Sup i o) r Source #

The Api instance contains methods to start, stop and lookup a child process, as well as a diagnostic callback.

Since: 0.23.0

Instance details

Defined in Control.Eff.Concurrent.Api.Supervisor

data Api (Sup i o) r where

type SpawnFun i e o = i -> Eff e (o, ProcessId) Source #

A function that will initialize the child process.

The process-id returned from this function is kept private, but it is possible to return '(ProcessId, ProcessId)' for example.

The function is expected to return a value - usually a tuple of Server values for the different aspects of a process, such as sending API requests, managing observers and receiving other auxiliary API messages.

Since: 0.23.0

data SupConfig i e o Source #

Options that control the 'Sup i o' process.

This contains:

  • a SpawnFun
  • the Timeout after requesting a normal child exit before brutally killing the child.

Since: 0.23.0

Constructors

MkSupConfig (SpawnFun i e o) Timeout 

supConfigSpawnFun :: forall i e o i e o. Lens (SupConfig i e o) (SupConfig i e o) (SpawnFun i e o) (SpawnFun i e o) Source #

data SpawnErr i o Source #

Runtime-Errors occurring when spawning child-processes.

Since: 0.23.0

Constructors

AlreadyStarted i o 
Instances
(Eq i, Eq o) => Eq (SpawnErr i o) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Supervisor

Methods

(==) :: SpawnErr i o -> SpawnErr i o -> Bool #

(/=) :: SpawnErr i o -> SpawnErr i o -> Bool #

(Ord i, Ord o) => Ord (SpawnErr i o) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Supervisor

Methods

compare :: SpawnErr i o -> SpawnErr i o -> Ordering #

(<) :: SpawnErr i o -> SpawnErr i o -> Bool #

(<=) :: SpawnErr i o -> SpawnErr i o -> Bool #

(>) :: SpawnErr i o -> SpawnErr i o -> Bool #

(>=) :: SpawnErr i o -> SpawnErr i o -> Bool #

max :: SpawnErr i o -> SpawnErr i o -> SpawnErr i o #

min :: SpawnErr i o -> SpawnErr i o -> SpawnErr i o #

(Show i, Show o) => Show (SpawnErr i o) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Supervisor

Methods

showsPrec :: Int -> SpawnErr i o -> ShowS #

show :: SpawnErr i o -> String #

showList :: [SpawnErr i o] -> ShowS #

Generic (SpawnErr i o) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Supervisor

Associated Types

type Rep (SpawnErr i o) :: Type -> Type #

Methods

from :: SpawnErr i o -> Rep (SpawnErr i o) x #

to :: Rep (SpawnErr i o) x -> SpawnErr i o #

(NFData i, NFData o) => NFData (SpawnErr i o) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Supervisor

Methods

rnf :: SpawnErr i o -> () #

type Rep (SpawnErr i o) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Supervisor

type Rep (SpawnErr i o) = D1 (MetaData "SpawnErr" "Control.Eff.Concurrent.Api.Supervisor" "extensible-effects-concurrent-0.23.0-7MuK5Qv52654cloU1vX0" False) (C1 (MetaCons "AlreadyStarted" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 i) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 o)))

startSupervisor :: forall i e o. (HasCallStack, Member Logs e, Lifted IO e, Ord i, Tangible i, Tangible o) => SupConfig i (InterruptableProcess e) o -> Eff (InterruptableProcess e) (Sup i o) 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, Member Interrupts e, SetMember Process (Process q0) e, Member Logs e, Lifted IO e, Ord i, Tangible i, Tangible o) => Sup i o -> Eff e () Source #

Stop the supervisor and shutdown all processes.

Block until the supervisor has finished.

Since: 0.23.0

isSupervisorAlive :: (HasCallStack, Member Interrupts e, Member Logs e, Typeable i, Typeable o, NFData i, NFData o, Show i, Show o, SetMember Process (Process q0) e) => Sup i o -> Eff e Bool Source #

Check if a supervisor process is still alive.

Since: 0.23.0

monitorSupervisor :: (HasCallStack, Member Interrupts e, Member Logs e, Typeable i, Typeable o, NFData i, NFData o, Show i, Show o, SetMember Process (Process q0) e) => Sup i o -> Eff e MonitorReference Source #

Monitor a supervisor process.

Since: 0.23.0

getDiagnosticInfo :: (Ord i, Tangible i, Tangible o, Typeable e, HasCallStack, Member Interrupts e, SetMember Process (Process q0) e) => Sup i o -> Eff e Text Source #

Return a Text describing the current state of the supervisor.

Since: 0.23.0

spawnChild :: (HasCallStack, Member Interrupts e, Member Logs e, Ord i, Tangible i, Tangible o, SetMember Process (Process q0) e) => Sup i o -> i -> Eff e (Either (SpawnErr i o) o) Source #

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

Since: 0.23.0

lookupChild :: (HasCallStack, Member Interrupts e, Member Logs e, Ord i, Tangible i, Tangible o, SetMember Process (Process q0) e) => Sup i o -> i -> Eff e (Maybe o) Source #

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

Since: 0.23.0

stopChild :: (HasCallStack, Member Interrupts e, Member Logs e, Ord i, Tangible i, Tangible o, SetMember Process (Process q0) e) => Sup i o -> i -> 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