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

Safe HaskellNone
LanguageHaskell2010

Control.Eff.Concurrent.Protocol.Watchdog

Description

Monitor a process and act when it is unresponsive.

Behaviour of the watchdog:

When a child crashes: * if the allowed maximum number crashes per time span has been reached for the process, ** cancel all other timers ** don't start the child again ** if this is a permanent watchdog crash the watchdog * otherwise ** tell the broker to start the child ** record a crash and start a timer to remove the record later ** monitor the child

When a child crash timer elapses: * remove the crash record

Since: 0.30.0

Synopsis

Documentation

startLink :: forall child e q. (HasCallStack, Typeable child, FilteredLogging (Processes q), Member Logs q, HasProcesses e q, Tangible (ChildId child), Ord (ChildId child), HasPdu (ServerPdu child), Lifted IO q) => CrashRate -> Eff e (Endpoint (Watchdog child)) Source #

Start and link a new watchdog process.

The watchdog process will register itself to the ChildEvents and restart crashed children.

Since: 0.30.0

data Watchdog (child :: Type) Source #

The phantom for watchdog processes, that watch the given type of servers

This type is used for the Server and HasPdu instances.

Since: 0.30.0

Instances
(Show (ChildId child), Typeable (ChildId child), Typeable child) => Show (Model (Watchdog child)) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Watchdog

Methods

showsPrec :: Int -> Model (Watchdog child) -> ShowS #

show :: Model (Watchdog child) -> String #

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

Default (Model (Watchdog child)) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Watchdog

Methods

def :: Model (Watchdog child) #

Typeable child => HasPdu (Watchdog child) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Watchdog

Associated Types

type EmbeddedPduList (Watchdog child) :: [Type] Source #

data Pdu (Watchdog child) reply :: Type Source #

(Typeable child, HasPdu (ServerPdu child), Tangible (ChildId child), Ord (ChildId child), Eq (ChildId child), Lifted IO e, Member Logs e) => Server (Watchdog child) (Processes e) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Watchdog

Associated Types

data StartArgument (Watchdog child) :: Type Source #

type Protocol (Watchdog child) :: Type Source #

data Model (Watchdog child) :: Type Source #

type Settings (Watchdog child) :: Type 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 #

(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 (ChildId child) => NFData (Pdu (Watchdog child) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Watchdog

Methods

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

type EmbeddedPduList (Watchdog child) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Watchdog

type EmbeddedPduList (Watchdog child) = Observer (ChildEvent child) ': ([] :: [Type])
data Pdu (Watchdog child) r Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Watchdog

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

Defined in Control.Eff.Concurrent.Protocol.Watchdog

type Protocol (Watchdog child) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Watchdog

type Protocol (Watchdog child) = Watchdog child
data Model (Watchdog child) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Watchdog

data Model (Watchdog child) = WatchdogModel {}
type Settings (Watchdog child) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Watchdog

type Settings (Watchdog child) = ()

attachTemporary :: forall child q e. (HasCallStack, FilteredLogging e, Typeable child, HasPdu (ServerPdu child), Tangible (ChildId child), Ord (ChildId child), HasProcesses e q) => Endpoint (Watchdog child) -> Endpoint (Broker child) -> Eff e () Source #

Restart children of the given broker.

When the broker exits, ignore the children of that broker.

Since: 0.30.0

attachPermanent :: forall child q e. (HasCallStack, FilteredLogging e, Typeable child, HasPdu (ServerPdu child), Tangible (ChildId child), Ord (ChildId child), HasProcesses e q) => Endpoint (Watchdog child) -> Endpoint (Broker child) -> Eff e () Source #

Restart children of the given broker.

When the broker exits, the watchdog process will exit, too.

Since: 0.30.0

getCrashReports :: forall child q e. (HasCallStack, FilteredLogging e, Typeable child, HasPdu (ServerPdu child), Tangible (ChildId child), Ord (ChildId child), HasProcesses e q, Lifted IO q, Lifted IO e, Member Logs e) => Endpoint (Watchdog child) -> Eff e (Map (ChildId child) (ChildWatch child)) Source #

Return a list of CrashReports.

Useful for diagnostics

Since: 0.30.0

data CrashRate Source #

The limit of crashes (see CrashCount) per time span (see CrashTimeSpan) that justifies restarting child processes.

Used as parameter for startLink.

Use crashesPerSeconds to construct a value.

This governs how long the ExonerationTimer runs before cleaning up a CrashReport in a ChildWatch.

Since: 0.30.0

crashesPerSeconds :: CrashCount -> CrashTimeSpan -> CrashRate Source #

A smart constructor for CrashRate.

The first parameter is the number of crashes allowed per number of seconds (second parameter) until the watchdog should give up restarting a child.

Since: 0.30.0

type CrashCount = Int Source #

Number of crashes in CrashRate.

Since: 0.30.0

type CrashTimeSpan = Int Source #

Time span in which crashes are counted in CrashRate.

Since: 0.30.0

data ChildWatch child Source #

An internal data structure that keeps the CrashReports of a child of an attached Broker monitored by a Watchdog.

See attachPermanent and attachTemporary, ExonerationTimer, CrashRate.

Since: 0.30.0

Constructors

MkChildWatch 

Fields

Instances
(Typeable child, Typeable (ChildId child), Show (ChildId child)) => Show (ChildWatch child) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Watchdog

Methods

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

show :: ChildWatch child -> String #

showList :: [ChildWatch child] -> ShowS #

NFData (ChildWatch child) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Watchdog

Methods

rnf :: ChildWatch child -> () #

parent :: Lens' (ChildWatch child) (Endpoint (Broker child)) Source #

A lens for _parent.

Since: 0.30.0

crashes :: Lens' (ChildWatch child) (Set (CrashReport (ChildId child))) Source #

A lens for _crashes

Since: 0.30.0

data ExonerationTimer a Source #

The timer started based on the CrashRate _crashTimeSpan when a CrashReport is recorded.

After this timer elapses, the Watchdog server will remove the CrashReport from the ChildWatch of that child.

Since: 0.30.0

data CrashReport a Source #

An internal data structure that records a single crash of a child of an attached Broker.

See attachPermanent and attachTemporary.

Since: 0.30.0

Constructors

MkCrashReport 

Fields

crashTime :: Lens' (CrashReport a) UTCTime Source #

Lens for _crashTime

Since: 0.30.0