capataz-0.0.0.1: OTP-like supervision trees in Haskell

Safe HaskellNone
LanguageHaskell2010

Control.Concurrent.Capataz

Contents

Description

Public API for the capataz library

Capataz is a library that brings an OTP-like supervisor API to the Haskell concurrency toolset.

Synopsis

Types

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.Internal.Capataz.Types" "capataz-0.0.0.1-2u6yKqsDEDkHwgXFG9usGn" False) ((:+:) * (C1 * (MetaCons "OnCompletion" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "OnFailure" PrefixI False) (U1 *)) (C1 * (MetaCons "OnTermination" PrefixI False) (U1 *))))

data WorkerOptions Source #

Utility record used to specify options to a Worker instance

Constructors

WorkerOptions 

Fields

data WorkerRestartStrategy Source #

Specifies how a Worker should restart on failure. Default is Transient

Constructors

Permanent

Worker thread is always restarted

Transient

Worker thread is restarted only if it failed

Temporary

Worker thread is never restarted

data WorkerSpec Source #

WorkerSpec is a representation of the WorkerOptions record that embeds the IO () sub-routine of the worker thread. This record is used when we want to bound worker threads to a Capataz instance

Constructors

WorkerSpec 

Fields

Instances

Generic WorkerSpec Source # 

Associated Types

type Rep WorkerSpec :: * -> * #

type Rep WorkerSpec Source # 

data WorkerTerminationOrder Source #

Specifies how order in which workers should be terminated by a Capataz in case of restart or shutdown; default is OldestFirst

Constructors

NewestFirst

Terminate worker threads from most recent to oldest

OldestFirst

Terminate worker threads from oldest to most recent

Instances

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

Methods

rnf :: WorkerTerminationOrder -> () #

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

data WorkerTerminationPolicy Source #

Defines how a Worker termination should be handled, default WorkerTerminationPolicy is 3 seconds

Constructors

Infinity

Waits until infinity for the worker to terminate

BrutalTermination

Worker is terminated wihtout a chance to call its callback

TimeoutMillis !Int

Allows n milliseconds for worker termination callback to be executed, otherwise "BrutalTermination occurs"

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.Internal.Capataz.Types" "capataz-0.0.0.1-2u6yKqsDEDkHwgXFG9usGn" 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 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.

Constructors

Capataz 

Fields

data CapatazEvent Source #

Event passed to the "notifyEvent" callback sub-routine, this events can be used to monitor the capataz system and understanding what is doing. This provides high levels of telemetry for the Capataz instance, so is mainly used for logging, monitoring and testing purposes.

Constructors

InvalidCapatazStatusReached 

Fields

CapatazStatusChanged 
WorkerTerminated 

Fields

WorkerStarted 

Fields

WorkerRestarted 

Fields

WorkerCompleted 

Fields

WorkerFailed 

Fields

WorkerCallbackExecuted 

Fields

WorkersTerminationStarted 

Fields

WorkersTerminationFinished 

Fields

CapatazFailed 

Fields

CapatazTerminated 

Fields

CapatazShutdownInvoked 

Fields

data CapatazOptions Source #

Utility record used to specify options to a Capataz instance

Constructors

CapatazOptions 

Fields

data CapatazRestartStrategy Source #

Specifies how a Capataz should restart a failing worker. Default is OneForOne

Constructors

AllForOne

Terminate all workers threads when one fails and restart them all

OneForOne

Only restart worker thread that failed

Instances

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

Methods

rnf :: CapatazRestartStrategy -> () #

type Rep CapatazRestartStrategy Source # 
type Rep CapatazRestartStrategy = D1 * (MetaData "CapatazRestartStrategy" "Control.Concurrent.Internal.Capataz.Types" "capataz-0.0.0.1-2u6yKqsDEDkHwgXFG9usGn" False) ((:+:) * (C1 * (MetaCons "AllForOne" PrefixI False) (U1 *)) (C1 * (MetaCons "OneForOne" PrefixI False) (U1 *)))

data CapatazStatus Source #

Internal state machine record that indicates the state of a Capataz

Constructors

Initializing

This state is set when Worker is created and it spawn static worker threads

Running

This state is set when the Capataz thread is listenting to both ControlAction and MonitorEvent messages

Halting

This state is set when the Capataz thread is terminating it's assigned worker

Halted

The Capataz thread is done

Instances

Eq CapatazStatus Source # 
Show CapatazStatus Source # 
Generic CapatazStatus Source # 

Associated Types

type Rep CapatazStatus :: * -> * #

NFData CapatazStatus Source # 

Methods

rnf :: CapatazStatus -> () #

type Rep CapatazStatus Source # 
type Rep CapatazStatus = D1 * (MetaData "CapatazStatus" "Control.Concurrent.Internal.Capataz.Types" "capataz-0.0.0.1-2u6yKqsDEDkHwgXFG9usGn" 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 *))))

defWorkerOptions :: WorkerOptions Source #

Default options to easily create worker instances: * name defaults to "default-worker" * has a Transient worker restart strategy * has a termination policy of three (3) seconds

defWorkerSpec :: WorkerSpec Source #

Default spec to easily create worker instances: * IO () sub-routine simply returns unit * name defaults to "default-worker" * has a Transient worker restart strategy * has a termination policy of three (3) seconds

defCapatazOptions :: CapatazOptions Source #

Default options to easily create capataz instances: * name defaults to "default-capataz" * intensity error tolerance is set to 1 error every 5 seconds * has a "OneForOne " capataz restart strategy * has a termination order of OldestFirst

Core functionality

forkWorker Source #

Arguments

:: WorkerOptions

Worker options (restart, name, callbacks, etc)

-> IO ()

IO sub-routine that will be executed on worker thread

-> Capataz

Capataz instance that supervises the worker

-> IO WorkerId

An identifier that can be used to terminate the Worker

Creates a worker green thread "IO ()" sub-routine, and depending in options defined in the WorkerOptions record, it will restart the Worker sub-routine in case of failures

forkCapataz :: CapatazOptions -> IO Capataz Source #

Creates a Capataz record, which represents a supervision thread which monitors failure on worker threads defined in the CapatazOptions or worker threads that are created dynamically using "forkWorker".

terminateWorker :: Text -> WorkerId -> Capataz -> IO () Source #

Stops the execution of a worker green thread being supervised by the given Capataz instance, if the WorkerId does not belong to the Capataz, the operation does not perform any side-effect.

Note: If your worker has a Permanent worker restart strategy, the worker thread will be restarted again; so use a Transient restart strategy instead.

Utility functions

capatazToAsync :: Capataz -> Async () Source #

Utility function to transform a Capataz into an Async ()

Teardown (re-exported)

teardown :: ITeardown teardown => teardown -> IO TeardownResult #

Executes teardown sub-routine returning a TeardownResult