{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE ExplicitForAll #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Time.Units
(
Time (..)
, Second
, Millisecond
, Microsecond
, Nanosecond
, Picosecond
, Minute
, Hour
, Day
, Week
, Fortnight
, UnitName
, KnownUnitName
, KnownRatName
, unitNameVal
, time
, floorUnit
, floorRat
, toNum
, sec
, ms
, mcs
, ns
, ps
, minute
, hour
, day
, week
, fortnight
, toUnit
, threadDelay
, getCPUTime
, timeout
) where
import Control.Applicative ((*>))
import Control.Monad (unless)
import Control.Monad.IO.Class (MonadIO, liftIO)
import Data.Char (isDigit, isLetter)
import Data.Foldable (foldl')
import Data.Proxy (Proxy (..))
import Data.Semigroup (Semigroup (..))
import GHC.Generics (Generic)
import GHC.Natural (Natural)
import GHC.Prim (coerce)
import GHC.Read (Read (readPrec))
import GHC.Real (denominator, numerator, (%))
import GHC.TypeLits (KnownSymbol, Symbol, symbolVal)
import Text.ParserCombinators.ReadP (ReadP, char, munch1, option, pfail, (+++))
import Text.ParserCombinators.ReadPrec (ReadPrec, lift)
#ifdef HAS_hashable
import Data.Hashable (Hashable)
#endif
#ifdef HAS_deepseq
import Control.DeepSeq (NFData)
#endif
#ifdef HAS_serialise
import Codec.Serialise (Serialise (..))
#endif
#ifdef HAS_aeson
import Data.Aeson (ToJSON (..), FromJSON (..), withText)
import Text.Read (readMaybe)
import qualified Data.Text as Text
#endif
#if ( __GLASGOW_HASKELL__ >= 804 )
import Time.Rational (type (*), type (/))
#endif
import Time.Rational (type (:%), KnownDivRat, Rat, RatioNat, KnownRat, ratVal)
import qualified Control.Concurrent as Concurrent
import qualified System.CPUTime as CPUTime
import qualified System.Timeout as Timeout
#if ( __GLASGOW_HASKELL__ >= 804 )
type Second = 1 / 1
type Millisecond = Second / 1000
type Microsecond = Millisecond / 1000
type Nanosecond = Microsecond / 1000
type Picosecond = Nanosecond / 1000
type Minute = 60 * Second
type Hour = 60 * Minute
type Day = 24 * Hour
type Week = 7 * Day
type Fortnight = 2 * Week
#else
type Second = 1 :% 1
type Millisecond = 1 :% 1000
type Microsecond = 1 :% 1000000
type Nanosecond = 1 :% 1000000000
type Picosecond = 1 :% 1000000000000
type Minute = 60 :% 1
type Hour = 3600 :% 1
type Day = 86400 :% 1
type Week = 604800 :% 1
type Fortnight = 1209600 :% 1
#endif
newtype Time (rat :: Rat) = Time { unTime :: RatioNat }
deriving (Eq, Ord, Enum, Generic)
instance Semigroup (Time (rat :: Rat)) where
(<>) = coerce ((+) :: RatioNat -> RatioNat -> RatioNat)
{-# INLINE (<>) #-}
sconcat = foldl' (<>) mempty
{-# INLINE sconcat #-}
stimes n (Time t) = Time (fromIntegral n * t)
{-# INLINE stimes #-}
instance Monoid (Time (rat :: Rat)) where
mempty = Time 0
{-# INLINE mempty #-}
mappend = (<>)
{-# INLINE mappend #-}
mconcat = foldl' (<>) mempty
{-# INLINE mconcat #-}
#ifdef HAS_hashable
instance Hashable (Time (rat :: Rat))
#endif
#ifdef HAS_deepseq
instance NFData (Time (rat :: Rat))
#endif
#ifdef HAS_serialise
instance Serialise (Time (rat :: Rat))
#endif
#ifdef HAS_aeson
instance (KnownUnitName unit) => ToJSON (Time (unit :: Rat)) where
toJSON = toJSON . show
instance (KnownUnitName unit) => FromJSON (Time (unit :: Rat)) where
parseJSON = withText "time" $ maybe parseFail pure . maybeTime
where
parseFail = fail $ "Can not parse Time. Expected unit: " ++ unitNameVal @unit
maybeTime = readMaybe @(Time unit) . Text.unpack
#endif
type family UnitName (unit :: Rat) :: Symbol
type instance UnitName (1 :% 1) = "s"
type instance UnitName (1 :% 1000) = "ms"
type instance UnitName (1 :% 1000000) = "mcs"
type instance UnitName (1 :% 1000000000) = "ns"
type instance UnitName (1 :% 1000000000000) = "ps"
type instance UnitName (60 :% 1) = "m"
type instance UnitName (3600 :% 1) = "h"
type instance UnitName (86400 :% 1) = "d"
type instance UnitName (604800 :% 1) = "w"
type instance UnitName (1209600 :% 1) = "fn"
type KnownUnitName unit = KnownSymbol (UnitName unit)
type KnownRatName unit = (KnownUnitName unit, KnownRat unit)
unitNameVal :: forall (unit :: Rat) . (KnownUnitName unit) => String
unitNameVal = symbolVal (Proxy @(UnitName unit))
instance KnownUnitName unit => Show (Time unit) where
showsPrec p (Time t) = showParen (p > 6)
$ showsMixed t
. showString (unitNameVal @unit)
where
showsMixed 0 = showString "0"
showsMixed rat =
let (n,d) = (numerator rat, denominator rat)
(q,r) = n `quotRem` d
op = if q == 0 || r == 0 then "" else "+"
quotStr = if q == 0
then id
else shows q
remStr = if r == 0
then id
else shows r
. showString "/"
. shows d
in
quotStr . showString op . remStr
instance KnownUnitName unit => Read (Time unit) where
readPrec :: ReadPrec (Time unit)
readPrec = lift readP
where
readP :: ReadP (Time unit)
readP = do
let naturalP = read <$> munch1 isDigit
let fullMixedExpr = (,,) <$> (naturalP <* char '+')
<*> (naturalP <* char '/')
<*> naturalP
let improperExpr = (,,) 0 <$> naturalP
<*> option 1 (char '/' *> naturalP)
(q,r,d) <- fullMixedExpr +++ improperExpr
let n = (q * d + r)
timeUnitStr <- munch1 isLetter
unless (timeUnitStr == unitNameVal @unit) pfail
pure $ Time (n % d)
time :: RatioNat -> Time unit
time n = Time n
{-# INLINE time #-}
sec :: RatioNat -> Time Second
sec = time
{-# INLINE sec #-}
ms :: RatioNat -> Time Millisecond
ms = time
{-# INLINE ms #-}
mcs :: RatioNat -> Time Microsecond
mcs = time
{-# INLINE mcs #-}
ns :: RatioNat -> Time Nanosecond
ns = time
{-# INLINE ns #-}
ps :: RatioNat -> Time Picosecond
ps = time
{-# INLINE ps #-}
minute :: RatioNat -> Time Minute
minute = time
{-# INLINE minute #-}
hour :: RatioNat -> Time Hour
hour = time
{-# INLINE hour #-}
day :: RatioNat -> Time Day
day = time
{-# INLINE day #-}
week :: RatioNat -> Time Week
week = time
{-# INLINE week #-}
fortnight :: RatioNat -> Time Fortnight
fortnight = time
{-# INLINE fortnight #-}
floorRat :: forall (unit :: Rat) b . (Integral b) => Time unit -> b
floorRat = floor . unTime
floorUnit :: forall (unit :: Rat) . Time unit -> Time unit
floorUnit = time . fromIntegral @Natural . floorRat
toNum :: forall (unitTo :: Rat) n (unit :: Rat) . (KnownDivRat unit unitTo, Num n)
=> Time unit -> n
toNum = fromIntegral @Natural . floorRat . toUnit @unitTo
toUnit :: forall (unitTo :: Rat) (unitFrom :: Rat) . KnownDivRat unitFrom unitTo
=> Time unitFrom
-> Time unitTo
#if ( __GLASGOW_HASKELL__ >= 804 )
toUnit Time{..} = Time $ unTime * ratVal @(unitFrom / unitTo)
#else
toUnit (Time t) = Time (t * ratVal @unitFrom / ratVal @unitTo)
#endif
{-# INLINE toUnit #-}
threadDelay :: forall (unit :: Rat) m . (KnownDivRat unit Microsecond, MonadIO m)
=> Time unit
-> m ()
threadDelay = liftIO . Concurrent.threadDelay . floorRat . toUnit @Microsecond
{-# INLINE threadDelay #-}
getCPUTime :: forall (unit :: Rat) m . (KnownDivRat Picosecond unit, MonadIO m)
=> m (Time unit)
getCPUTime = toUnit . ps . fromInteger <$> liftIO CPUTime.getCPUTime
{-# INLINE getCPUTime #-}
timeout :: forall (unit :: Rat) m a . (MonadIO m, KnownDivRat unit Microsecond)
=> Time unit
-> IO a
-> m (Maybe a)
timeout t = liftIO . Timeout.timeout (floorRat $ toUnit @Microsecond t)
{-# INLINE timeout #-}