| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
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
- 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))
- data Watchdog (child :: Type)
- 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 ()
- 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 ()
- 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))
- data CrashRate = CrashesPerSeconds {}
- crashCount :: Lens' CrashRate CrashCount
- crashTimeSpan :: Lens' CrashRate CrashTimeSpan
- crashesPerSeconds :: CrashCount -> CrashTimeSpan -> CrashRate
- type CrashCount = Int
- type CrashTimeSpan = Int
- data ChildWatch child = MkChildWatch {}
- parent :: Lens' (ChildWatch child) (Endpoint (Broker child))
- crashes :: Lens' (ChildWatch child) (Set (CrashReport (ChildId child)))
- data ExonerationTimer a = MkExonerationTimer !a !TimerReference
- data CrashReport a = MkCrashReport {}
- crashTime :: Lens' (CrashReport a) UTCTime
- crashReason :: Lens' (CrashReport a) (Interrupt NoRecovery)
- exonerationTimerReference :: Lens' (CrashReport a) TimerReference
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
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 #
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
Constructors
| CrashesPerSeconds | |
Fields | |
Instances
| Eq CrashRate Source # | |
| Ord CrashRate Source # | |
Defined in Control.Eff.Concurrent.Protocol.Watchdog | |
| Show CrashRate Source # | |
| Default CrashRate Source # | The default is three crashes in 30 seconds. Since: 0.30.0 |
Defined in Control.Eff.Concurrent.Protocol.Watchdog | |
| NFData CrashRate Source # | |
Defined in Control.Eff.Concurrent.Protocol.Watchdog | |
crashCount :: Lens' CrashRate CrashCount Source #
A lens for _crashCount.
Since: 0.30.0
crashTimeSpan :: Lens' CrashRate CrashTimeSpan Source #
A lens for _crashTimeSpan.
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 # | |
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 # | |
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
Constructors
| MkExonerationTimer !a !TimerReference |
Instances
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
| |
Instances
| Eq (CrashReport a) Source # | |
Defined in Control.Eff.Concurrent.Protocol.Watchdog Methods (==) :: CrashReport a -> CrashReport a -> Bool # (/=) :: CrashReport a -> CrashReport a -> Bool # | |
| Ord (CrashReport a) Source # | |
Defined in Control.Eff.Concurrent.Protocol.Watchdog Methods compare :: CrashReport a -> CrashReport a -> Ordering # (<) :: CrashReport a -> CrashReport a -> Bool # (<=) :: CrashReport a -> CrashReport a -> Bool # (>) :: CrashReport a -> CrashReport a -> Bool # (>=) :: CrashReport a -> CrashReport a -> Bool # max :: CrashReport a -> CrashReport a -> CrashReport a # min :: CrashReport a -> CrashReport a -> CrashReport a # | |
| (Show a, Typeable a) => Show (CrashReport a) Source # | |
Defined in Control.Eff.Concurrent.Protocol.Watchdog Methods showsPrec :: Int -> CrashReport a -> ShowS # show :: CrashReport a -> String # showList :: [CrashReport a] -> ShowS # | |
| NFData (CrashReport a) Source # | |
Defined in Control.Eff.Concurrent.Protocol.Watchdog Methods rnf :: CrashReport a -> () # | |
crashTime :: Lens' (CrashReport a) UTCTime Source #
Lens for _crashTime
Since: 0.30.0
crashReason :: Lens' (CrashReport a) (Interrupt NoRecovery) Source #
Lens for _crashReason
Since: 0.30.0
exonerationTimerReference :: Lens' (CrashReport a) TimerReference Source #
Lens for _exonerationTimerReference
Since: 0.30.0