{-# options_haddock prune #-}
module Polysemy.Conc.Effect.Monitor where
import Polysemy.Time (NanoSeconds)
import Polysemy.Conc.Effect.Scoped (Scoped, scoped)
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
/= :: Restart -> Restart -> Bool
$c/= :: Restart -> Restart -> Bool
== :: Restart -> Restart -> Bool
$c== :: 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
showList :: [Restart] -> ShowS
$cshowList :: [Restart] -> ShowS
show :: Restart -> String
$cshow :: Restart -> String
showsPrec :: Int -> Restart -> ShowS
$cshowsPrec :: Int -> 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
newtype MonitorResource a =
MonitorResource { forall a. MonitorResource a -> a
unMonitorResource :: a }
type ScopedMonitor (resource :: Type) (action :: Type) =
Scoped (MonitorResource resource) (Monitor action)
type RestartingMonitor (resource :: Type) =
ScopedMonitor resource Restart
data MonitorCheck r =
MonitorCheck {
forall (r :: [(* -> *) -> * -> *]). MonitorCheck r -> NanoSeconds
interval :: NanoSeconds,
forall (r :: [(* -> *) -> * -> *]).
MonitorCheck r -> MVar () -> Sem r ()
check :: MVar () -> Sem r ()
}
withMonitor ::
∀ resource action r .
Member (ScopedMonitor resource action) r =>
InterpreterFor (Monitor action) r
withMonitor :: forall resource action (r :: [(* -> *) -> * -> *]).
Member (ScopedMonitor resource action) r =>
InterpreterFor (Monitor action) r
withMonitor =
forall resource (effect :: (* -> *) -> * -> *)
(r :: [(* -> *) -> * -> *]).
Member (Scoped resource effect) r =>
InterpreterFor effect r
scoped @(MonitorResource resource)
restart ::
∀ resource r .
Member (ScopedMonitor resource Restart) r =>
InterpreterFor (Monitor Restart) r
restart :: forall resource (r :: [(* -> *) -> * -> *]).
Member (ScopedMonitor resource Restart) r =>
InterpreterFor (Monitor Restart) r
restart =
forall resource action (r :: [(* -> *) -> * -> *]).
Member (ScopedMonitor resource action) r =>
InterpreterFor (Monitor action) r
withMonitor @resource