capataz-0.1.0.1: OTP-like supervision trees in Haskell

Safe HaskellNone
LanguageHaskell2010

Control.Concurrent.Capataz.Internal.Types

Description

This module contains all the types used across all the other modules

Synopsis

Documentation

data CapatazEvent Source #

Event delivered to the "notifyEvent" callback sub-routine; these events can be used to monitor the capataz system and track what is doing, providing high levels of telemetry for all supervisors and workers of a capataz system, ergo, should be used for logging, monitoring and testing purposes.

Constructors

InvalidSupervisorStatusReached 
SupervisorStatusChanged 
ProcessTerminated 
ProcessStarted 
ProcessRestarted 
ProcessCompleted 
ProcessFailed 
ProcessCallbackExecuted 
ProcessTerminationStarted 
ProcessTerminationFinished 
CapatazFailed 
CapatazTerminated 

Instances

Show CapatazEvent Source # 
Generic CapatazEvent Source # 

Associated Types

type Rep CapatazEvent :: * -> * #

type Rep CapatazEvent Source # 
type Rep CapatazEvent = D1 * (MetaData "CapatazEvent" "Control.Concurrent.Capataz.Internal.Types" "capataz-0.1.0.1-BMUnXiQkbJaLDuTJjK4mTQ" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "InvalidSupervisorStatusReached" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "supervisorId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * SupervisorId)) ((:*:) * (S1 * (MetaSel (Just Symbol "supervisorName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * SupervisorName)) (S1 * (MetaSel (Just Symbol "eventTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * UTCTime))))) ((:+:) * (C1 * (MetaCons "SupervisorStatusChanged" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "supervisorId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * SupervisorId)) (S1 * (MetaSel (Just Symbol "supervisorName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * SupervisorName))) ((:*:) * (S1 * (MetaSel (Just Symbol "prevSupervisorStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * SupervisorStatus)) ((:*:) * (S1 * (MetaSel (Just Symbol "newSupervisorStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * SupervisorStatus)) (S1 * (MetaSel (Just Symbol "eventTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * UTCTime)))))) (C1 * (MetaCons "ProcessTerminated" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "supervisorId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * SupervisorId)) (S1 * (MetaSel (Just Symbol "supervisorName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * SupervisorName))) ((:*:) * (S1 * (MetaSel (Just Symbol "processThreadId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ProcessThreadId)) (S1 * (MetaSel (Just Symbol "processId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ProcessId)))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "processName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ProcessName)) (S1 * (MetaSel (Just Symbol "processType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ProcessType))) ((:*:) * (S1 * (MetaSel (Just Symbol "terminationReason") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "eventTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * UTCTime)))))))) ((:+:) * (C1 * (MetaCons "ProcessStarted" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "supervisorId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * SupervisorId)) ((:*:) * (S1 * (MetaSel (Just Symbol "supervisorName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * SupervisorName)) (S1 * (MetaSel (Just Symbol "processThreadId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ProcessThreadId)))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "processId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ProcessId)) (S1 * (MetaSel (Just Symbol "processName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ProcessName))) ((:*:) * (S1 * (MetaSel (Just Symbol "processType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ProcessType)) (S1 * (MetaSel (Just Symbol "eventTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * UTCTime)))))) ((:+:) * (C1 * (MetaCons "ProcessRestarted" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "supervisorId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * SupervisorId)) (S1 * (MetaSel (Just Symbol "supervisorName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * SupervisorName))) ((:*:) * (S1 * (MetaSel (Just Symbol "processThreadId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ProcessThreadId)) (S1 * (MetaSel (Just Symbol "processId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ProcessId)))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "processName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ProcessName)) (S1 * (MetaSel (Just Symbol "processType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ProcessType))) ((:*:) * (S1 * (MetaSel (Just Symbol "processRestartCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "eventTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * UTCTime)))))) (C1 * (MetaCons "ProcessCompleted" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "supervisorId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * SupervisorId)) ((:*:) * (S1 * (MetaSel (Just Symbol "supervisorName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * SupervisorName)) (S1 * (MetaSel (Just Symbol "processThreadId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ProcessThreadId)))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "processId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ProcessId)) (S1 * (MetaSel (Just Symbol "processName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ProcessName))) ((:*:) * (S1 * (MetaSel (Just Symbol "processType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ProcessType)) (S1 * (MetaSel (Just Symbol "eventTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * UTCTime))))))))) ((:+:) * ((:+:) * (C1 * (MetaCons "ProcessFailed" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "supervisorName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * SupervisorName)) (S1 * (MetaSel (Just Symbol "supervisorId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * SupervisorId))) ((:*:) * (S1 * (MetaSel (Just Symbol "processThreadId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ProcessThreadId)) (S1 * (MetaSel (Just Symbol "processId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ProcessId)))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "processName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ProcessName)) (S1 * (MetaSel (Just Symbol "processType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ProcessType))) ((:*:) * (S1 * (MetaSel (Just Symbol "processError") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * SomeException)) (S1 * (MetaSel (Just Symbol "eventTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * UTCTime)))))) ((:+:) * (C1 * (MetaCons "ProcessCallbackExecuted" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "supervisorId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * SupervisorId)) (S1 * (MetaSel (Just Symbol "supervisorName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * SupervisorName))) ((:*:) * (S1 * (MetaSel (Just Symbol "processThreadId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ProcessThreadId)) (S1 * (MetaSel (Just Symbol "processId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ProcessId)))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "processName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ProcessName)) (S1 * (MetaSel (Just Symbol "processType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ProcessType))) ((:*:) * (S1 * (MetaSel (Just Symbol "processCallbackError") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe SomeException))) ((:*:) * (S1 * (MetaSel (Just Symbol "processCallbackType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * CallbackType)) (S1 * (MetaSel (Just Symbol "eventTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * UTCTime))))))) (C1 * (MetaCons "ProcessTerminationStarted" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "supervisorName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * SupervisorName)) (S1 * (MetaSel (Just Symbol "supervisorId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * SupervisorId))) ((:*:) * (S1 * (MetaSel (Just Symbol "terminationReason") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "eventTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * UTCTime))))))) ((:+:) * (C1 * (MetaCons "ProcessTerminationFinished" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "supervisorName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * SupervisorName)) (S1 * (MetaSel (Just Symbol "supervisorId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * SupervisorId))) ((:*:) * (S1 * (MetaSel (Just Symbol "terminationReason") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "eventTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * UTCTime))))) ((:+:) * (C1 * (MetaCons "CapatazFailed" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "supervisorId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * SupervisorId)) (S1 * (MetaSel (Just Symbol "supervisorName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * SupervisorName))) ((:*:) * (S1 * (MetaSel (Just Symbol "supervisorError") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * SomeException)) (S1 * (MetaSel (Just Symbol "eventTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * UTCTime))))) (C1 * (MetaCons "CapatazTerminated" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "supervisorName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * SupervisorName)) ((:*:) * (S1 * (MetaSel (Just Symbol "supervisorId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * SupervisorId)) (S1 * (MetaSel (Just Symbol "eventTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * UTCTime)))))))))

data WorkerTerminationPolicy Source #

Defines how a Worker process termination should be handled by its supervisor.

Constructors

Infinity

Supervisor waits until infinity for the worker termination callback to finish execution.

BrutalTermination

Supervisor terminates worker process without a chance to call its termination callback.

TimeoutMillis !Int

Supervisor allows a number of milliseconds for worker termination callback complete, if not completed by specified milliseconds the termination is cancelled via a BrutalTermination signal.

Instances

Eq WorkerTerminationPolicy Source # 
Ord WorkerTerminationPolicy Source # 
Show WorkerTerminationPolicy Source # 
Generic WorkerTerminationPolicy Source # 
Default WorkerTerminationPolicy Source # 
NFData WorkerTerminationPolicy Source # 

Methods

rnf :: WorkerTerminationPolicy -> () #

type Rep WorkerTerminationPolicy Source # 
type Rep WorkerTerminationPolicy = D1 * (MetaData "WorkerTerminationPolicy" "Control.Concurrent.Capataz.Internal.Types" "capataz-0.1.0.1-BMUnXiQkbJaLDuTJjK4mTQ" False) ((:+:) * (C1 * (MetaCons "Infinity" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "BrutalTermination" PrefixI False) (U1 *)) (C1 * (MetaCons "TimeoutMillis" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int)))))

data ProcessRestartAction Source #

Internal helper record that assesses if a Supervisor error intensity has been breached.

Constructors

ResetRestartCount

Indicates a Supervisor to restart a failed process _and_ reset the restart count given this Supervisor's intensity period timeout has passed.

IncreaseRestartCount

Indicates a Supervisor to restart the failed process _and_ increase the restart count (normal operation) of the supervised process.

HaltSupervisor

Indicates a Supervisor stop executing given the error intensity has been breached.

Instances

data ProcessTerminationOrder Source #

Specifies the order in which supervised process should be terminated by a Supervisor in case of a restart or shutdown.

Constructors

NewestFirst

Supervisor terminates supervised process from most recent to oldest.

OldestFirst

Supervisor terminates supervised process from oldest to most recent.

Instances

Eq ProcessTerminationOrder Source # 
Ord ProcessTerminationOrder Source # 
Show ProcessTerminationOrder Source # 
Generic ProcessTerminationOrder Source # 
Default ProcessTerminationOrder Source # 
NFData ProcessTerminationOrder Source # 

Methods

rnf :: ProcessTerminationOrder -> () #

type Rep ProcessTerminationOrder Source # 
type Rep ProcessTerminationOrder = D1 * (MetaData "ProcessTerminationOrder" "Control.Concurrent.Capataz.Internal.Types" "capataz-0.1.0.1-BMUnXiQkbJaLDuTJjK4mTQ" False) ((:+:) * (C1 * (MetaCons "NewestFirst" PrefixI False) (U1 *)) (C1 * (MetaCons "OldestFirst" PrefixI False) (U1 *)))

data SupervisorRestartStrategy Source #

Specifies how a Supervisor restarts a failing process.

Constructors

AllForOne

Supervisor terminates all sibling supervised processes that didn't fail, and then restarts all of them together. This strategy serves best when all processes depend upon each other.

OneForOne

Supervisor only restarts the supervised process that failed.

Instances

Eq SupervisorRestartStrategy Source # 
Ord SupervisorRestartStrategy Source # 
Show SupervisorRestartStrategy Source # 
Generic SupervisorRestartStrategy Source # 
Default SupervisorRestartStrategy Source # 
NFData SupervisorRestartStrategy Source # 
type Rep SupervisorRestartStrategy Source # 
type Rep SupervisorRestartStrategy = D1 * (MetaData "SupervisorRestartStrategy" "Control.Concurrent.Capataz.Internal.Types" "capataz-0.1.0.1-BMUnXiQkbJaLDuTJjK4mTQ" False) ((:+:) * (C1 * (MetaCons "AllForOne" PrefixI False) (U1 *)) (C1 * (MetaCons "OneForOne" PrefixI False) (U1 *)))

data CapatazOptions Source #

Allows to:

  • Specify options for The root supervisor of a capataz system.
  • Provie a "notifyEvent" callback to monitor or log a capataz system.

data WorkerRestartStrategy Source #

Specifies how a Supervisor deals with the lifecycle of worker process in case of completion without errors and failure.

Constructors

Permanent

Supervisor will always restart a worker process, in both completion and failure scenarios.

Transient

Supervisor will only restart worker process if it has a failure in execution.

Temporary

Supervisor will never restart a worker, even on failure.

data WorkerOptions Source #

Specifies all options that can be used to create a Worker Process. You may create a record of this type via the smart constructor "buildWorkerOptions".

Constructors

WorkerOptions 

Fields

Instances

data Worker Source #

Record that contains the Async record (thread reference) of a worker

Constructors

Worker 

Fields

data SupervisorOptions Source #

Constructors

SupervisorOptions 

Fields

data ControlAction Source #

Internal record that represents an action being sent from threads using the Capataz public API.

Instances

Generic ControlAction Source # 

Associated Types

type Rep ControlAction :: * -> * #

type Rep ControlAction Source # 
type Rep ControlAction = D1 * (MetaData "ControlAction" "Control.Concurrent.Capataz.Internal.Types" "capataz-0.1.0.1-BMUnXiQkbJaLDuTJjK4mTQ" False) ((:+:) * (C1 * (MetaCons "ForkWorker" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "workerOptions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * WorkerOptions)) (S1 * (MetaSel (Just Symbol "returnWorkerId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (WorkerId -> IO ()))))) ((:+:) * (C1 * (MetaCons "ForkSupervisor" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "supervisorOptions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * SupervisorOptions)) (S1 * (MetaSel (Just Symbol "returnSupervisor") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Supervisor -> IO ()))))) (C1 * (MetaCons "TerminateProcess" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "processId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ProcessId)) ((:*:) * (S1 * (MetaSel (Just Symbol "processTerminationReason") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "notifyProcessTermination") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Bool -> IO ()))))))))

data CapatazSignal Source #

Internal exception thrown to the Capataz loop to indicate termination of execution

Instances

Show CapatazSignal Source # 
Generic CapatazSignal Source # 

Associated Types

type Rep CapatazSignal :: * -> * #

Exception CapatazSignal Source # 
NFData CapatazSignal Source # 

Methods

rnf :: CapatazSignal -> () #

type Rep CapatazSignal Source # 
type Rep CapatazSignal = D1 * (MetaData "CapatazSignal" "Control.Concurrent.Capataz.Internal.Types" "capataz-0.1.0.1-BMUnXiQkbJaLDuTJjK4mTQ" False) ((:+:) * ((:+:) * (C1 * (MetaCons "CapatazFailure" PrefixI False) (U1 *)) (C1 * (MetaCons "RestartProcessException" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "TerminateProcessException" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "processId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ProcessId)) (S1 * (MetaSel (Just Symbol "processTerminationReason") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)))) (C1 * (MetaCons "BrutallyTerminateProcessException" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "processId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ProcessId)) (S1 * (MetaSel (Just Symbol "processTerminationReason") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))))))

data CapatazError Source #

Internal exception triggered when a Worker violates error intensity specification

data CallbackType Source #

Internal record that indicates what type of callback function is being invoked; this is used for telemetry purposes

Instances

Eq CallbackType Source # 
Show CallbackType Source # 
Generic CallbackType Source # 

Associated Types

type Rep CallbackType :: * -> * #

type Rep CallbackType Source # 
type Rep CallbackType = D1 * (MetaData "CallbackType" "Control.Concurrent.Capataz.Internal.Types" "capataz-0.1.0.1-BMUnXiQkbJaLDuTJjK4mTQ" False) ((:+:) * (C1 * (MetaCons "OnCompletion" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "OnFailure" PrefixI False) (U1 *)) (C1 * (MetaCons "OnTermination" PrefixI False) (U1 *))))

data ProcessError Source #

Internal exception triggered when a callback of a Worker fails

data SupervisorStatus Source #

Internal record used as a state machine, indicating the state of a supervisor process

Constructors

Initializing

This state is set when the process is created and it starts spawning its static process list.

Running

This state is set when the supervisor process starts listenting to both ControlAction and MonitorEvent messages.

Halting

This state is set when the supervisor process is terminating it's assigned worker

Halted

This state is set when the supervisor process is finished

Instances

Eq SupervisorStatus Source # 
Show SupervisorStatus Source # 
Generic SupervisorStatus Source # 
NFData SupervisorStatus Source # 

Methods

rnf :: SupervisorStatus -> () #

type Rep SupervisorStatus Source # 
type Rep SupervisorStatus = D1 * (MetaData "SupervisorStatus" "Control.Concurrent.Capataz.Internal.Types" "capataz-0.1.0.1-BMUnXiQkbJaLDuTJjK4mTQ" False) ((:+:) * ((:+:) * (C1 * (MetaCons "Initializing" PrefixI False) (U1 *)) (C1 * (MetaCons "Running" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Halting" PrefixI False) (U1 *)) (C1 * (MetaCons "Halted" PrefixI False) (U1 *))))

data SupervisorMessage Source #

Internal message delivered to a supervisor process that can either be a call from public API or an event from its monitored worker process.

Constructors

ControlAction !ControlAction

Represents a request from done to the supervisor thread from another thread using the public API

MonitorEvent !MonitorEvent

Represents an event (failure, completion, etc) from a monitored worker process to the supervisor

Instances

Generic SupervisorMessage Source # 
type Rep SupervisorMessage Source # 
type Rep SupervisorMessage = D1 * (MetaData "SupervisorMessage" "Control.Concurrent.Capataz.Internal.Types" "capataz-0.1.0.1-BMUnXiQkbJaLDuTJjK4mTQ" False) ((:+:) * (C1 * (MetaCons "ControlAction" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ControlAction))) (C1 * (MetaCons "MonitorEvent" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * MonitorEvent))))

data Process Source #

Internal Type to manage both Worker and Supervisor processes

data ProcessSpec Source #

Record used to specify how to build a runtime Process in a static supervision tree; to create values of this type, you must use:

  • "workerSpec" or "workerSpecWithDefaults" to build a worker process
  • "supervisorSpec" or "supervisorSpecWithDefaults" to build a supervisor process

data Capataz Source #

Record that contains the environment of a capataz monitor, this is used as the main record to create workers and to stop the supervisor thread.

data ParentSupervisorEnv Source #

Internal utility record used to hold part of the runtime information of a supervisor that acts as a parent of another supervisor.

defCapatazOptions Source #

Arguments

:: Text 
-> (CapatazOptions -> CapatazOptions)

Function to modify root supervisor

-> CapatazOptions 

Builds a CapatazOptions record with defaults on how to create a capataz root supervisor, these defaults are:

This function is intended to be used in combination with "forkCapataz".

supervisorSpec Source #

Arguments

:: SupervisorName

Name used for telemetry purposes

-> (SupervisorOptions -> SupervisorOptions)

Function to modify default supervisor options

-> ProcessSpec 

Builds a ProcessSpec record for a supervisor process with defaults from "supervisorSpecWithDefaults". This function allows overrides of these defaults using lenses.

This function is used when building a supervisor branch in a static supervision trees.

supervisorSpecWithDefaults Source #

Arguments

:: SupervisorName

Name used for telemetry purposes

-> ProcessSpec 

Builds a ProcessSpec record for a supervisor process with defaults from "buildSupervisorOptionsWithDefaults".

This function is used when building a supervisor branch in a static supervision trees.

workerSpec Source #

Arguments

:: WorkerName

Name used for telemetry purposes

-> IO ()

IO sub-routine to be supervised

-> (WorkerOptions -> WorkerOptions)

Function to modify default worker options

-> ProcessSpec 

Builds a ProcessSpec record for a worker process with defaults from "workerSpecWithDefaults". This function allows overrides of these defaults using lenses.

This function is used when building a worker in a static supervision tree.

workerSpecWithDefaults Source #

Arguments

:: WorkerName

Name used for telemetry purposes

-> IO ()

IO sub-routine to be supervised

-> ProcessSpec 

Builds a ProcessSpec record for a worker process with defaults from "buildSupervisorOptionsWithDefaults".

This function is used when building a worker in a static supervision tree.

buildSupervisorOptions Source #

Arguments

:: SupervisorName

Name used for telemetry purposes

-> (SupervisorOptions -> SupervisorOptions)

Function to modify default supervisor options

-> SupervisorOptions 

Builds a SupervisorOptions record with defaults from "buildSupervisorOptionsWithDefaults". This function allows overrides of these defaults using lenses.

This function is intended to be used in combination with "forkSupervisor".

buildSupervisorOptionsWithDefaults Source #

Arguments

:: SupervisorName

Name used for telemetry purposes

-> SupervisorOptions 

Builds a SupervisorOptions record with defaults to create a supervisor process, these defaults are:

This function is intended to be used in combination with "forkSupervisor".

buildWorkerOptions Source #

Arguments

:: WorkerName

Name used for telemetry purposes

-> IO ()

IO sub-routine to be supervised

-> (WorkerOptions -> WorkerOptions)

Function to modify default worker options

-> WorkerOptions 

Builds a WorkerOptions record, keeps the defaults from "buildWorkerOptionsWithDefaults" but allows overrides using lenses.

This function is intended to be used in combination with "forkWorker". See the ... example in the examples directory for a demonstration.

buildWorkerOptionsWithDefaults Source #

Arguments

:: WorkerName

Name used for telemetry purposes

-> IO ()

IO sub-routine to be supervised

-> WorkerOptions 

Builds a WorkerOptions record with defaults to create a worker process, the defaults are:

This function is intended to be used in combination with "forkWorker", for creating a worker in an static supervision tree, use "workerSpecWithDefaults" instead. See the ... example for a demonstration.