module Control.Concurrent.Async.Timer.Internal
( Timer(..)
, TimerConf(..)
, TimerException(..)
, defaultTimerConf
, timerThread
, timerConfSetInitDelay
, timerConfSetInterval
, timerWait
) where
import Control.Concurrent.Lifted
import Control.Exception.Safe
import Control.Monad
import Control.Monad.Base
import Control.Monad.Trans.Control
data TimerException = TimerEnd deriving (Typeable, Show)
instance Exception TimerException
newtype Timer = Timer { timerMVar :: MVar () }
data TimerConf = TimerConf { _timerConfInitDelay :: Int
, _timerConfInterval :: Int }
timerHandler :: Monad m => Handler m ()
timerHandler = Handler $ \case
TimerEnd -> return ()
millisleep :: MonadBase IO m => Int -> m ()
millisleep dt = threadDelay (fromIntegral dt * 10 ^ 3)
defaultTimerConf :: TimerConf
defaultTimerConf = TimerConf { _timerConfInitDelay = 0
, _timerConfInterval = 1000 }
timerConfSetInitDelay :: Int -> TimerConf -> TimerConf
timerConfSetInitDelay n conf = conf { _timerConfInitDelay = n }
timerConfSetInterval :: Int -> TimerConf -> TimerConf
timerConfSetInterval n conf = conf { _timerConfInterval = n }
timerThread :: (MonadBaseControl IO m, MonadCatch m) => Int -> Int -> MVar () -> m ()
timerThread initDelay intervalDelay syncMVar =
catches (timerLoop initDelay intervalDelay syncMVar) [timerHandler]
timerLoop :: (MonadBaseControl IO m) => Int -> Int -> MVar () -> m ()
timerLoop initDelay intervalDelay syncMVar = do
millisleep initDelay
forever $ putMVar syncMVar () >> millisleep intervalDelay
timerWait :: MonadBaseControl IO m => Timer -> m ()
timerWait = void . takeMVar . timerMVar