{-# options_haddock prune #-}
module Polysemy.Conc.Effect.Monitor where
import Polysemy.Time (NanoSeconds)
data Restart =
Restart
deriving stock (Restart -> Restart -> Bool
(Restart -> Restart -> Bool)
-> (Restart -> Restart -> Bool) -> Eq Restart
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Restart -> Restart -> Bool
== :: Restart -> Restart -> Bool
$c/= :: Restart -> Restart -> Bool
/= :: Restart -> Restart -> Bool
Eq, Int -> Restart -> ShowS
[Restart] -> ShowS
Restart -> String
(Int -> Restart -> ShowS)
-> (Restart -> String) -> ([Restart] -> ShowS) -> Show Restart
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Restart -> ShowS
showsPrec :: Int -> Restart -> ShowS
$cshow :: Restart -> String
show :: Restart -> String
$cshowList :: [Restart] -> ShowS
showList :: [Restart] -> ShowS
Show)
data Monitor (action :: Type) :: Effect where
Monitor :: m a -> Monitor action m a
makeSem_ ''Monitor
monitor ::
∀ action r a .
Member (Monitor action) r =>
Sem r a ->
Sem r a
type ScopedMonitor (action :: Type) =
Scoped_ (Monitor action)
type RestartingMonitor =
ScopedMonitor Restart
data MonitorCheck r =
MonitorCheck {
forall (r :: EffectRow). MonitorCheck r -> NanoSeconds
interval :: NanoSeconds,
forall (r :: EffectRow). MonitorCheck r -> Sem r Bool
check :: Sem r Bool
}
hoistMonitorCheck ::
(∀ x . Sem r x -> Sem r' x) ->
MonitorCheck r ->
MonitorCheck r'
hoistMonitorCheck :: forall (r :: EffectRow) (r' :: EffectRow).
(forall x. Sem r x -> Sem r' x)
-> MonitorCheck r -> MonitorCheck r'
hoistMonitorCheck forall x. Sem r x -> Sem r' x
f MonitorCheck {Sem r Bool
NanoSeconds
$sel:interval:MonitorCheck :: forall (r :: EffectRow). MonitorCheck r -> NanoSeconds
$sel:check:MonitorCheck :: forall (r :: EffectRow). MonitorCheck r -> Sem r Bool
interval :: NanoSeconds
check :: Sem r Bool
..} =
MonitorCheck {$sel:check:MonitorCheck :: Sem r' Bool
check = Sem r Bool -> Sem r' Bool
forall x. Sem r x -> Sem r' x
f Sem r Bool
check, NanoSeconds
$sel:interval:MonitorCheck :: NanoSeconds
interval :: NanoSeconds
..}
withMonitor ::
∀ action r .
Member (ScopedMonitor action) r =>
InterpreterFor (Monitor action) r
withMonitor :: forall action (r :: EffectRow).
Member (ScopedMonitor action) r =>
InterpreterFor (Monitor action) r
withMonitor =
Sem (Monitor action : r) a -> Sem r a
InterpreterFor (Monitor action) r
forall (effect :: Effect) (r :: EffectRow).
Member (Scoped_ effect) r =>
InterpreterFor effect r
scoped_
restart ::
Member (ScopedMonitor Restart) r =>
InterpreterFor (Monitor Restart) r
restart :: forall (r :: EffectRow).
Member (ScopedMonitor Restart) r =>
InterpreterFor (Monitor Restart) r
restart =
Sem (Monitor Restart : r) a -> Sem r a
InterpreterFor (Monitor Restart) r
forall action (r :: EffectRow).
Member (ScopedMonitor action) r =>
InterpreterFor (Monitor action) r
withMonitor