{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
module Control.Distributed.Process.Extras.Time
(
microSeconds
, milliSeconds
, seconds
, minutes
, hours
, asTimeout
, after
, within
, timeToMicros
, TimeInterval
, TimeUnit(..)
, Delay(..)
, timeIntervalToDiffTime
, diffTimeToTimeInterval
, diffTimeToDelay
, delayToDiffTime
, microsecondsToNominalDiffTime
, Timeout
, TimeoutNotification(..)
, timeout
, infiniteWait
, noWait
) where
import Control.Concurrent (threadDelay)
import Control.DeepSeq (NFData)
import Control.Distributed.Process
import Control.Distributed.Process.Extras.Internal.Types
import Control.Monad (void)
import Data.Binary
import Data.Ratio ((%))
import Data.Time.Clock
import Data.Typeable (Typeable)
import GHC.Generics
data TimeUnit = Days | Hours | Minutes | Seconds | Millis | Micros
deriving (Typeable, Generic, Eq, Show)
instance Binary TimeUnit where
instance NFData TimeUnit where
data TimeInterval = TimeInterval TimeUnit Int
deriving (Typeable, Generic, Eq, Show)
instance Binary TimeInterval where
instance NFData TimeInterval where
data Delay = Delay TimeInterval | Infinity | NoDelay
deriving (Typeable, Generic, Eq, Show)
instance Binary Delay where
instance NFData Delay where
type Timeout = Maybe Int
data TimeoutNotification = TimeoutNotification Tag
deriving (Typeable)
instance Binary TimeoutNotification where
get = fmap TimeoutNotification $ get
put (TimeoutNotification n) = put n
asTimeout :: TimeInterval -> Int
asTimeout (TimeInterval u v) = timeToMicros u v
after :: Int -> TimeUnit -> Int
after n m = timeToMicros m n
within :: Int -> TimeUnit -> TimeInterval
within n m = TimeInterval m n
microSeconds :: Int -> TimeInterval
microSeconds = TimeInterval Micros
milliSeconds :: Int -> TimeInterval
milliSeconds = TimeInterval Millis
seconds :: Int -> TimeInterval
seconds = TimeInterval Seconds
minutes :: Int -> TimeInterval
minutes = TimeInterval Minutes
hours :: Int -> TimeInterval
hours = TimeInterval Hours
{-# INLINE timeToMicros #-}
timeToMicros :: TimeUnit -> Int -> Int
timeToMicros Micros us = us
timeToMicros Millis ms = ms * (10 ^ (3 :: Int))
timeToMicros Seconds secs = timeToMicros Millis (secs * milliSecondsPerSecond)
timeToMicros Minutes mins = timeToMicros Seconds (mins * secondsPerMinute)
timeToMicros Hours hrs = timeToMicros Minutes (hrs * minutesPerHour)
timeToMicros Days days = timeToMicros Hours (days * hoursPerDay)
{-# INLINE hoursPerDay #-}
hoursPerDay :: Int
hoursPerDay = 24
{-# INLINE minutesPerHour #-}
minutesPerHour :: Int
minutesPerHour = 60
{-# INLINE secondsPerMinute #-}
secondsPerMinute :: Int
secondsPerMinute = 60
{-# INLINE milliSecondsPerSecond #-}
milliSecondsPerSecond :: Int
milliSecondsPerSecond = 1000
{-# INLINE microSecondsPerSecond #-}
microSecondsPerSecond :: Int
microSecondsPerSecond = 1000000
infiniteWait :: Timeout
infiniteWait = Nothing
noWait :: Timeout
noWait = Just 0
timeout :: Int -> Tag -> ProcessId -> Process ()
timeout time tag p =
void $ spawnLocal $
do liftIO $ threadDelay time
send p (TimeoutNotification tag)
timeIntervalToDiffTime :: TimeInterval -> NominalDiffTime
timeIntervalToDiffTime ti = microsecondsToNominalDiffTime (fromIntegral $ asTimeout ti)
diffTimeToTimeInterval :: NominalDiffTime -> TimeInterval
diffTimeToTimeInterval dt = microSeconds $ (fromIntegral (round (dt * 1000000) :: Integer))
delayToDiffTime :: Delay -> NominalDiffTime
delayToDiffTime (Delay ti) = timeIntervalToDiffTime ti
delayToDiffTime Infinity = error "trying to convert Delay.Infinity to a NominalDiffTime"
delayToDiffTime (NoDelay) = microsecondsToNominalDiffTime 0
diffTimeToDelay :: NominalDiffTime -> Delay
diffTimeToDelay dt = Delay $ diffTimeToTimeInterval dt
microsecondsToNominalDiffTime :: Integer -> NominalDiffTime
microsecondsToNominalDiffTime x = fromRational (x % (fromIntegral microSecondsPerSecond))
instance Num TimeInterval where
t1 + t2 = microSeconds $ asTimeout t1 + asTimeout t2
t1 - t2 = microSeconds $ asTimeout t1 - asTimeout t2
_ * _ = error "trying to multiply two TimeIntervals"
abs t = microSeconds $ abs (asTimeout t)
signum t = if (asTimeout t) == 0
then 0
else if (asTimeout t) < 0 then -1
else 1
fromInteger _ = error "trying to call fromInteger for a TimeInterval. Cannot guess units"
instance Num Delay where
NoDelay + x = x
Infinity + _ = Infinity
x + NoDelay = x
_ + Infinity = Infinity
(Delay t1 ) + (Delay t2) = Delay (t1 + t2)
NoDelay - x = x
Infinity - _ = Infinity
x - NoDelay = x
_ - Infinity = Infinity
(Delay t1 ) - (Delay t2) = Delay (t1 - t2)
_ * _ = error "trying to multiply two Delays"
abs NoDelay = NoDelay
abs Infinity = Infinity
abs (Delay t) = Delay (abs t)
signum (NoDelay) = 0
signum Infinity = 1
signum (Delay t) = Delay (signum t)
fromInteger 0 = NoDelay
fromInteger _ = error "trying to call fromInteger for a Delay. Cannot guess units"