module Control.Concurrent.Async.Timer.Internal where
import qualified Control.Concurrent.Async as Async
import Control.Exception.Safe
import Control.Monad (void)
import Control.Monad.IO.Unlift
import UnliftIO.Async
import UnliftIO.Concurrent
import UnliftIO.STM
data Timer = Timer { timerMVar :: MVar ()
, timerControl :: TBQueue TimerCommand }
data TimerCommand = TimerReset deriving (Show, Eq)
data TimerConf = TimerConf { _timerConfInitDelay :: Int
, _timerConfInterval :: Int }
millisleep :: MonadIO m => Int -> m ()
millisleep dt = threadDelay (dt * 10 ^ 3)
defaultConf :: TimerConf
defaultConf = TimerConf { _timerConfInitDelay = 0
, _timerConfInterval = 1000 }
setInitDelay :: Int -> TimerConf -> TimerConf
setInitDelay n conf = conf { _timerConfInitDelay = n }
setInterval :: Int -> TimerConf -> TimerConf
setInterval n conf = conf { _timerConfInterval = n }
timerLoop
:: MonadUnliftIO m
=> Int
-> Int
-> Timer
-> m ()
timerLoop initDelay intervalDelay timer = go initDelay
where go delay = do
race (millisleep delay) readCmd >>= \ case
Left () -> do
wakeUp
go intervalDelay
Right cmd ->
case cmd of
TimerReset ->
go intervalDelay
wakeUp = putMVar (timerMVar timer) ()
readCmd = atomically $ readTBQueue (timerControl timer)
wait
:: MonadUnliftIO m
=> Timer
-> m ()
wait = void . takeMVar . timerMVar
reset
:: MonadUnliftIO m
=> Timer
-> m ()
reset timer =
atomically $ writeTBQueue (timerControl timer) TimerReset
withAsyncTimer
:: (MonadUnliftIO m, MonadMask m)
=> TimerConf
-> (Timer -> m b)
-> m b
withAsyncTimer conf io = do
mVar <- newEmptyMVar
controlChannel <- atomically $ newTBQueue 1
let timer = Timer { timerMVar = mVar
, timerControl = controlChannel }
initDelay = _timerConfInitDelay conf
intervalDelay = _timerConfInterval conf
withAsync (timerLoop initDelay intervalDelay timer) $ \ asyncTimer -> do
liftIO $ Async.link asyncTimer
io timer