module Control.Distributed.Process.Extras.Timer
(
TimerRef
, Tick(Tick)
, sleep
, sleepFor
, sendAfter
, runAfter
, exitAfter
, killAfter
, startTimer
, ticker
, periodically
, resetTimer
, cancelTimer
, flushTimer
) where
import Control.DeepSeq (NFData)
import Control.Distributed.Process hiding (send)
import Control.Distributed.Process.Serializable
import Control.Distributed.Process.Extras.UnsafePrimitives (send)
import Control.Distributed.Process.Extras.Internal.Types (NFSerializable)
import Control.Distributed.Process.Extras.Time
import Data.Binary
import Data.Typeable (Typeable)
import Prelude hiding (init)
import GHC.Generics
type TimerRef = ProcessId
data TimerConfig = Reset | Cancel
deriving (Typeable, Generic, Eq, Show)
instance Binary TimerConfig where
instance NFData TimerConfig where
data Tick = Tick
deriving (Typeable, Generic, Eq, Show)
instance Binary Tick where
instance NFData Tick where
data SleepingPill = SleepingPill
deriving (Typeable, Generic, Eq, Show)
instance Binary SleepingPill where
instance NFData SleepingPill where
sleep :: TimeInterval -> Process ()
sleep t =
let ms = asTimeout t in do
_ <- receiveTimeout ms [matchIf (\SleepingPill -> True)
(\_ -> return ())]
return ()
sleepFor :: Int -> TimeUnit -> Process ()
sleepFor i u = sleep (within i u)
sendAfter :: (NFSerializable a)
=> TimeInterval
-> ProcessId
-> a
-> Process TimerRef
sendAfter t pid msg = runAfter t proc
where proc = do { send pid msg }
runAfter :: TimeInterval -> Process () -> Process TimerRef
runAfter t p = spawnLocal $ runTimer t p True
exitAfter :: (Serializable a)
=> TimeInterval
-> ProcessId
-> a
-> Process TimerRef
exitAfter delay pid reason = runAfter delay $ exit pid reason
killAfter :: TimeInterval -> ProcessId -> String -> Process TimerRef
killAfter delay pid why = runAfter delay $ kill pid why
startTimer :: (NFSerializable a)
=> TimeInterval
-> ProcessId
-> a
-> Process TimerRef
startTimer t pid msg = periodically t (send pid msg)
periodically :: TimeInterval -> Process () -> Process TimerRef
periodically t p = spawnLocal $ runTimer t p False
resetTimer :: TimerRef -> Process ()
resetTimer = (flip send) Reset
cancelTimer :: TimerRef -> Process ()
cancelTimer = (flip send) Cancel
flushTimer :: (Serializable a, Eq a) => TimerRef -> a -> Delay -> Process ()
flushTimer ref ignore t = do
mRef <- monitor ref
cancelTimer ref
performFlush mRef t
return ()
where performFlush mRef Infinity = receiveWait $ filters mRef
performFlush mRef NoDelay = performFlush mRef (Delay $ microSeconds 0)
performFlush mRef (Delay i) = receiveTimeout (asTimeout i) (filters mRef) >> return ()
filters mRef = [
matchIf (\x -> x == ignore)
(\_ -> return ())
, matchIf (\(ProcessMonitorNotification mRef' _ _) -> mRef == mRef')
(\_ -> return ()) ]
ticker :: TimeInterval -> ProcessId -> Process TimerRef
ticker t pid = startTimer t pid Tick
runTimer :: TimeInterval -> Process () -> Bool -> Process ()
runTimer t proc cancelOnReset = do
cancel <- expectTimeout (asTimeout t)
case cancel of
Nothing -> runProc cancelOnReset
Just Cancel -> return ()
Just Reset -> if cancelOnReset then return ()
else runTimer t proc cancelOnReset
where runProc True = proc
runProc False = proc >> runTimer t proc cancelOnReset