module Control.Concurrent.Ticker
( newTicker
, withTicker
, newCPUTimeTicker
) where
import Control.Monad (forever)
import Control.Concurrent (threadDelay)
import Control.Concurrent.Async (async, cancel)
import Control.Concurrent.Chan (Chan, newChan, writeChan)
import Control.Exception.Safe (bracket)
import Control.Monad (forM_)
import System.CPUTime (getCPUTime)
newTicker
:: Int
-> IO (Chan (), IO ())
newTicker microSec = do
chan <- newChan
thread <- async $ forever $ do
threadDelay microSec
writeChan chan ()
return (chan, cancel thread)
withTicker
:: Int
-> (Chan () -> IO a)
-> IO a
withTicker microSec action = bracket
(newTicker microSec)
(\(_, cancelTicker) -> cancelTicker)
(\(chan, _) -> action chan)
newCPUTimeTicker :: Int -> IO (Chan (), IO ())
newCPUTimeTicker microSec = do
chan <- newChan
initialTick <- getCPUTime
let picoSec = (toInteger microSec) * 10^6
thread <- async $ go chan $ iterate (+picoSec) initialTick
return (chan, cancel thread)
where
go :: Chan () -> [Integer] -> IO ()
go chan checkTicks = do
threadDelay $ 10^3
now <- getCPUTime
let (target, rest) = span (<now) checkTicks
forM_ target $ \_ -> writeChan chan ()
go chan rest