Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data SupervisionCtx q
- data Supervisor q
- class QueueLike q where
- newQueueIO :: Natural -> IO (q a)
- readQueue :: q a -> STM a
- writeQueue :: q a -> a -> STM ()
- data Child_ q
- data DeadLetter
- type RestartAction = ThreadId -> IO ThreadId
- data SupervisionEvent
- = ChildBorn !ThreadId !UTCTime
- | ChildDied !ThreadId !SomeException !UTCTime
- | ChildRestarted !ThreadId !ThreadId !RetryStatus !UTCTime
- | ChildNotFound !ThreadId !UTCTime
- | StaleDeadLetterReceived !ThreadId !LetterEpoch !ChildEpoch !UTCTime
- | ChildRestartLimitReached !ThreadId !RetryStatus !UTCTime
- | ChildFinished !ThreadId !UTCTime
- data RestartStrategy = OneForOne
- data RestartResult
- = Restarted !ThreadId !ThreadId !RetryStatus !UTCTime
- | StaleDeadLetter !ThreadId !LetterEpoch !ChildEpoch !UTCTime
- | RestartFailed SupervisionEvent
- newSupervisor :: QueueLike q => RestartStrategy -> Natural -> IO (Supervisor q)
- fibonacciRetryPolicy :: RetryPolicyM IO
- shutdownSupervisor :: QueueLike q => Supervisor q -> IO ()
- eventStream :: QueueLike q => Supervisor q -> q SupervisionEvent
- activeChildren :: QueueLike q => Supervisor q -> IO Int
- forkSupervised :: QueueLike q => Supervisor q -> RetryPolicyM IO -> IO () -> IO ThreadId
- monitorWith :: QueueLike q => RetryPolicyM IO -> Supervisor q -> Supervisor q -> IO ThreadId
Documentation
data SupervisionCtx q Source #
data Supervisor q Source #
class QueueLike q where Source #
newQueueIO :: Natural -> IO (q a) Source #
readQueue :: q a -> STM a Source #
writeQueue :: q a -> a -> STM () Source #
data DeadLetter Source #
data SupervisionEvent Source #
ChildBorn !ThreadId !UTCTime | |
ChildDied !ThreadId !SomeException !UTCTime | |
ChildRestarted !ThreadId !ThreadId !RetryStatus !UTCTime | |
ChildNotFound !ThreadId !UTCTime | |
StaleDeadLetterReceived !ThreadId !LetterEpoch !ChildEpoch !UTCTime | |
ChildRestartLimitReached !ThreadId !RetryStatus !UTCTime | |
ChildFinished !ThreadId !UTCTime |
Instances
Show SupervisionEvent Source # | |
Defined in Control.Concurrent.Supervisor.Types showsPrec :: Int -> SupervisionEvent -> ShowS # show :: SupervisionEvent -> String # showList :: [SupervisionEvent] -> ShowS # |
data RestartStrategy Source #
Erlang inspired strategies. At the moment only the OneForOne
is
implemented.
Instances
Show RestartStrategy Source # | |
Defined in Control.Concurrent.Supervisor.Types showsPrec :: Int -> RestartStrategy -> ShowS # show :: RestartStrategy -> String # showList :: [RestartStrategy] -> ShowS # |
data RestartResult Source #
Restarted !ThreadId !ThreadId !RetryStatus !UTCTime | The supervised |
StaleDeadLetter !ThreadId !LetterEpoch !ChildEpoch !UTCTime | A stale |
RestartFailed SupervisionEvent | The restart failed for a reason decribed by a |
Instances
Show RestartResult Source # | |
Defined in Control.Concurrent.Supervisor.Types showsPrec :: Int -> RestartResult -> ShowS # show :: RestartResult -> String # showList :: [RestartResult] -> ShowS # |
Creating a new supervisor
In order to create a new supervisor, you need a SupervisorSpec
,
which can be acquired by a call to newSupervisor
:
newSupervisor :: QueueLike q => RestartStrategy -> Natural -> IO (Supervisor q) Source #
Restart Policies
fibonacciRetryPolicy :: RetryPolicyM IO Source #
Smart constructor which offers a default throttling based on fibonacci numbers.
Stopping a supervisor
shutdownSupervisor :: QueueLike q => Supervisor q -> IO () Source #
Shutdown the given supervisor. This will cause the supervised children to
be killed as well. To do so, we explore the children tree, killing workers as we go,
and recursively calling shutdownSupervisor
in case we hit a monitored Supervisor
.
Accessing Supervisor event log
eventStream :: QueueLike q => Supervisor q -> q SupervisionEvent Source #
Gives you access to the event this supervisor is generating, allowing you to react. It's using a bounded queue to explicitly avoid memory leaks in case you do not want to drain the queue to listen to incoming events.
activeChildren :: QueueLike q => Supervisor q -> IO Int Source #
Returns the number of active threads at a given moment in time.
Supervise a forked thread
:: QueueLike q | |
=> Supervisor q | The |
-> RetryPolicyM IO | The retry policy to use |
-> IO () | The computation to run |
-> IO ThreadId |
Fork a thread in a supervised mode.
Monitor another supervisor
:: QueueLike q | |
=> RetryPolicyM IO | The retry policy to use |
-> Supervisor q | The supervisor |
-> Supervisor q | The |
-> IO ThreadId |
Monitor another supervisor. To achieve these, we simulate a new DeadLetter
,
so that the first supervisor will effectively restart the monitored one.
Thanks to the fact that for the supervisor the restart means we just copy over
its internal state, it should be perfectly fine to do so.
Returns the ThreadId
of the monitored supervisor.