{-# options_haddock prune #-}

-- |Description: Monitor Effect, Internal
module Polysemy.Conc.Effect.Monitor where

import Polysemy.Time (NanoSeconds)

-- |Marker type for the restarting action for 'Monitor'.
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)

-- |Mark a region as being subject to intervention by a monitoring program.
-- This can mean that a thread is repeatedly checking a condition and cancelling this region when it is unmet.
-- A use case could be checking whether a remote service is available, or whether the system was suspended and resumed.
-- This should be used in a 'Scoped_' context, like 'withMonitor'.
data Monitor (action :: Type) :: Effect where
  Monitor :: m a -> Monitor action m a

makeSem_ ''Monitor

-- |Mark a region as being subject to intervention by a monitoring program.
monitor ::
   action r a .
  Member (Monitor action) r =>
  Sem r a ->
  Sem r a

-- |Convenience alias for a 'Scoped_' 'Monitor'.
type ScopedMonitor (action :: Type) =
  Scoped_ (Monitor action)

-- |'Monitor' specialized to the 'Restart' action.
type RestartingMonitor =
  ScopedMonitor Restart

-- |Resources for a 'Scoped_' 'Monitor'.
data MonitorCheck r =
  MonitorCheck {
    forall (r :: EffectRow). MonitorCheck r -> NanoSeconds
interval :: NanoSeconds,
    forall (r :: EffectRow). MonitorCheck r -> MVar () -> Sem r ()
check :: MVar () -> Sem r ()
  }

-- | Transform the stack of the check in a 'MonitorCheck'.
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 {NanoSeconds
MVar () -> Sem r ()
check :: MVar () -> Sem r ()
interval :: NanoSeconds
$sel:check:MonitorCheck :: forall (r :: EffectRow). MonitorCheck r -> MVar () -> Sem r ()
$sel:interval:MonitorCheck :: forall (r :: EffectRow). MonitorCheck r -> NanoSeconds
..} =
  MonitorCheck :: forall (r :: EffectRow).
NanoSeconds -> (MVar () -> Sem r ()) -> MonitorCheck r
MonitorCheck {$sel:check:MonitorCheck :: MVar () -> Sem r' ()
check = Sem r () -> Sem r' ()
forall x. Sem r x -> Sem r' x
f (Sem r () -> Sem r' ())
-> (MVar () -> Sem r ()) -> MVar () -> Sem r' ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MVar () -> Sem r ()
check, NanoSeconds
interval :: NanoSeconds
$sel:interval:MonitorCheck :: NanoSeconds
..}

-- |Start a region that can contain monitor-intervention regions.
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
forall (effect :: Effect) (r :: EffectRow).
Member (Scoped_ effect) r =>
InterpreterFor effect r
scoped_

-- |Variant of 'withMonitor' that uses the 'Restart' strategy.
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
forall action (r :: EffectRow).
Member (ScopedMonitor action) r =>
InterpreterFor (Monitor action) r
withMonitor