{-# LANGUAGE TypeInType #-}
{-# LANGUAGE UnboxedTuples #-}

-- |
-- Module      : Streamly.Internal.Data.Time.Units
-- Copyright   : (c) 2019 Composewell Technologies
--
-- License     : BSD3
-- Maintainer  : streamly@composewell.com
-- Stability   : pre-release
-- Portability : GHC

module Streamly.Internal.Data.Time.Units
    (
    -- * Time Unit Conversions
      TimeUnit()
    -- , TimeUnitWide()
    , TimeUnit64()

    -- * Time Units
    , TimeSpec(..)
    , NanoSecond64(..)
    , MicroSecond64(..)
    , MilliSecond64(..)
    , showNanoSecond64

    -- * Absolute times (using TimeSpec)
    , AbsTime(..)
    , toAbsTime
    , fromAbsTime

    -- * Relative times (using TimeSpec)
    , RelTime
    , toRelTime
    , fromRelTime
    , diffAbsTime
    , addToAbsTime

    -- * Relative times (using NanoSecond64)
    , RelTime64
    , toRelTime64
    , fromRelTime64
    , diffAbsTime64
    , addToAbsTime64
    , showRelTime64
    )
where

#include "inline.hs"

import Text.Printf (printf)

import Data.Int
import Foreign.Storable (Storable)
import Streamly.Internal.Data.Unboxed (Unbox)
import Streamly.Internal.Data.Time.TimeSpec

-------------------------------------------------------------------------------
-- Some constants
-------------------------------------------------------------------------------

{-# INLINE tenPower3 #-}
tenPower3 :: Int64
tenPower3 :: Int64
tenPower3 = Int64
1000

{-# INLINE tenPower6 #-}
tenPower6 :: Int64
tenPower6 :: Int64
tenPower6 = Int64
1000000

{-# INLINE tenPower9 #-}
tenPower9 :: Int64
tenPower9 :: Int64
tenPower9 = Int64
1000000000


-------------------------------------------------------------------------------
-- Time Unit Representations
-------------------------------------------------------------------------------

-- XXX We should be able to use type families to use different represenations
-- for a unit.
--
-- Second Rational
-- Second Double
-- Second Int64
-- Second Integer
-- NanoSecond Int64
-- ...

-- Double or Fixed would be a much better representation so that we do not lose
-- information between conversions. However, for faster arithmetic operations
-- we use an 'Int64' here. When we need convservation of values we can use a
-- different system of units with a Fixed precision.

-------------------------------------------------------------------------------
-- Integral Units
-------------------------------------------------------------------------------

-- | An 'Int64' time representation with a nanosecond resolution. It can
-- represent time up to ~292 years.
newtype NanoSecond64 = NanoSecond64 Int64
    deriving ( NanoSecond64 -> NanoSecond64 -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NanoSecond64 -> NanoSecond64 -> Bool
$c/= :: NanoSecond64 -> NanoSecond64 -> Bool
== :: NanoSecond64 -> NanoSecond64 -> Bool
$c== :: NanoSecond64 -> NanoSecond64 -> Bool
Eq
             , ReadPrec [NanoSecond64]
ReadPrec NanoSecond64
Int -> ReadS NanoSecond64
ReadS [NanoSecond64]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [NanoSecond64]
$creadListPrec :: ReadPrec [NanoSecond64]
readPrec :: ReadPrec NanoSecond64
$creadPrec :: ReadPrec NanoSecond64
readList :: ReadS [NanoSecond64]
$creadList :: ReadS [NanoSecond64]
readsPrec :: Int -> ReadS NanoSecond64
$creadsPrec :: Int -> ReadS NanoSecond64
Read
             , Int -> NanoSecond64 -> ShowS
[NanoSecond64] -> ShowS
NanoSecond64 -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NanoSecond64] -> ShowS
$cshowList :: [NanoSecond64] -> ShowS
show :: NanoSecond64 -> String
$cshow :: NanoSecond64 -> String
showsPrec :: Int -> NanoSecond64 -> ShowS
$cshowsPrec :: Int -> NanoSecond64 -> ShowS
Show
             , Int -> NanoSecond64
NanoSecond64 -> Int
NanoSecond64 -> [NanoSecond64]
NanoSecond64 -> NanoSecond64
NanoSecond64 -> NanoSecond64 -> [NanoSecond64]
NanoSecond64 -> NanoSecond64 -> NanoSecond64 -> [NanoSecond64]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: NanoSecond64 -> NanoSecond64 -> NanoSecond64 -> [NanoSecond64]
$cenumFromThenTo :: NanoSecond64 -> NanoSecond64 -> NanoSecond64 -> [NanoSecond64]
enumFromTo :: NanoSecond64 -> NanoSecond64 -> [NanoSecond64]
$cenumFromTo :: NanoSecond64 -> NanoSecond64 -> [NanoSecond64]
enumFromThen :: NanoSecond64 -> NanoSecond64 -> [NanoSecond64]
$cenumFromThen :: NanoSecond64 -> NanoSecond64 -> [NanoSecond64]
enumFrom :: NanoSecond64 -> [NanoSecond64]
$cenumFrom :: NanoSecond64 -> [NanoSecond64]
fromEnum :: NanoSecond64 -> Int
$cfromEnum :: NanoSecond64 -> Int
toEnum :: Int -> NanoSecond64
$ctoEnum :: Int -> NanoSecond64
pred :: NanoSecond64 -> NanoSecond64
$cpred :: NanoSecond64 -> NanoSecond64
succ :: NanoSecond64 -> NanoSecond64
$csucc :: NanoSecond64 -> NanoSecond64
Enum
             , NanoSecond64
forall a. a -> a -> Bounded a
maxBound :: NanoSecond64
$cmaxBound :: NanoSecond64
minBound :: NanoSecond64
$cminBound :: NanoSecond64
Bounded
             , Integer -> NanoSecond64
NanoSecond64 -> NanoSecond64
NanoSecond64 -> NanoSecond64 -> NanoSecond64
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> NanoSecond64
$cfromInteger :: Integer -> NanoSecond64
signum :: NanoSecond64 -> NanoSecond64
$csignum :: NanoSecond64 -> NanoSecond64
abs :: NanoSecond64 -> NanoSecond64
$cabs :: NanoSecond64 -> NanoSecond64
negate :: NanoSecond64 -> NanoSecond64
$cnegate :: NanoSecond64 -> NanoSecond64
* :: NanoSecond64 -> NanoSecond64 -> NanoSecond64
$c* :: NanoSecond64 -> NanoSecond64 -> NanoSecond64
- :: NanoSecond64 -> NanoSecond64 -> NanoSecond64
$c- :: NanoSecond64 -> NanoSecond64 -> NanoSecond64
+ :: NanoSecond64 -> NanoSecond64 -> NanoSecond64
$c+ :: NanoSecond64 -> NanoSecond64 -> NanoSecond64
Num
             , Num NanoSecond64
Ord NanoSecond64
NanoSecond64 -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: NanoSecond64 -> Rational
$ctoRational :: NanoSecond64 -> Rational
Real
             , Enum NanoSecond64
Real NanoSecond64
NanoSecond64 -> Integer
NanoSecond64 -> NanoSecond64 -> (NanoSecond64, NanoSecond64)
NanoSecond64 -> NanoSecond64 -> NanoSecond64
forall a.
Real a
-> Enum a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
toInteger :: NanoSecond64 -> Integer
$ctoInteger :: NanoSecond64 -> Integer
divMod :: NanoSecond64 -> NanoSecond64 -> (NanoSecond64, NanoSecond64)
$cdivMod :: NanoSecond64 -> NanoSecond64 -> (NanoSecond64, NanoSecond64)
quotRem :: NanoSecond64 -> NanoSecond64 -> (NanoSecond64, NanoSecond64)
$cquotRem :: NanoSecond64 -> NanoSecond64 -> (NanoSecond64, NanoSecond64)
mod :: NanoSecond64 -> NanoSecond64 -> NanoSecond64
$cmod :: NanoSecond64 -> NanoSecond64 -> NanoSecond64
div :: NanoSecond64 -> NanoSecond64 -> NanoSecond64
$cdiv :: NanoSecond64 -> NanoSecond64 -> NanoSecond64
rem :: NanoSecond64 -> NanoSecond64 -> NanoSecond64
$crem :: NanoSecond64 -> NanoSecond64 -> NanoSecond64
quot :: NanoSecond64 -> NanoSecond64 -> NanoSecond64
$cquot :: NanoSecond64 -> NanoSecond64 -> NanoSecond64
Integral
             , Eq NanoSecond64
NanoSecond64 -> NanoSecond64 -> Bool
NanoSecond64 -> NanoSecond64 -> Ordering
NanoSecond64 -> NanoSecond64 -> NanoSecond64
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: NanoSecond64 -> NanoSecond64 -> NanoSecond64
$cmin :: NanoSecond64 -> NanoSecond64 -> NanoSecond64
max :: NanoSecond64 -> NanoSecond64 -> NanoSecond64
$cmax :: NanoSecond64 -> NanoSecond64 -> NanoSecond64
>= :: NanoSecond64 -> NanoSecond64 -> Bool
$c>= :: NanoSecond64 -> NanoSecond64 -> Bool
> :: NanoSecond64 -> NanoSecond64 -> Bool
$c> :: NanoSecond64 -> NanoSecond64 -> Bool
<= :: NanoSecond64 -> NanoSecond64 -> Bool
$c<= :: NanoSecond64 -> NanoSecond64 -> Bool
< :: NanoSecond64 -> NanoSecond64 -> Bool
$c< :: NanoSecond64 -> NanoSecond64 -> Bool
compare :: NanoSecond64 -> NanoSecond64 -> Ordering
$ccompare :: NanoSecond64 -> NanoSecond64 -> Ordering
Ord
             , Ptr NanoSecond64 -> IO NanoSecond64
Ptr NanoSecond64 -> Int -> IO NanoSecond64
Ptr NanoSecond64 -> Int -> NanoSecond64 -> IO ()
Ptr NanoSecond64 -> NanoSecond64 -> IO ()
NanoSecond64 -> Int
forall b. Ptr b -> Int -> IO NanoSecond64
forall b. Ptr b -> Int -> NanoSecond64 -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr NanoSecond64 -> NanoSecond64 -> IO ()
$cpoke :: Ptr NanoSecond64 -> NanoSecond64 -> IO ()
peek :: Ptr NanoSecond64 -> IO NanoSecond64
$cpeek :: Ptr NanoSecond64 -> IO NanoSecond64
pokeByteOff :: forall b. Ptr b -> Int -> NanoSecond64 -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> NanoSecond64 -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO NanoSecond64
$cpeekByteOff :: forall b. Ptr b -> Int -> IO NanoSecond64
pokeElemOff :: Ptr NanoSecond64 -> Int -> NanoSecond64 -> IO ()
$cpokeElemOff :: Ptr NanoSecond64 -> Int -> NanoSecond64 -> IO ()
peekElemOff :: Ptr NanoSecond64 -> Int -> IO NanoSecond64
$cpeekElemOff :: Ptr NanoSecond64 -> Int -> IO NanoSecond64
alignment :: NanoSecond64 -> Int
$calignment :: NanoSecond64 -> Int
sizeOf :: NanoSecond64 -> Int
$csizeOf :: NanoSecond64 -> Int
Storable
             , Int -> MutableByteArray -> IO NanoSecond64
Int -> MutableByteArray -> NanoSecond64 -> IO ()
Proxy NanoSecond64 -> Int
forall a.
(Proxy a -> Int)
-> (Int -> MutableByteArray -> IO a)
-> (Int -> MutableByteArray -> a -> IO ())
-> Unbox a
pokeByteIndex :: Int -> MutableByteArray -> NanoSecond64 -> IO ()
$cpokeByteIndex :: Int -> MutableByteArray -> NanoSecond64 -> IO ()
peekByteIndex :: Int -> MutableByteArray -> IO NanoSecond64
$cpeekByteIndex :: Int -> MutableByteArray -> IO NanoSecond64
sizeOf :: Proxy NanoSecond64 -> Int
$csizeOf :: Proxy NanoSecond64 -> Int
Unbox
             )

-- | An 'Int64' time representation with a microsecond resolution.
-- It can represent time up to ~292,000 years.
newtype MicroSecond64 = MicroSecond64 Int64
    deriving ( MicroSecond64 -> MicroSecond64 -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MicroSecond64 -> MicroSecond64 -> Bool
$c/= :: MicroSecond64 -> MicroSecond64 -> Bool
== :: MicroSecond64 -> MicroSecond64 -> Bool
$c== :: MicroSecond64 -> MicroSecond64 -> Bool
Eq
             , ReadPrec [MicroSecond64]
ReadPrec MicroSecond64
Int -> ReadS MicroSecond64
ReadS [MicroSecond64]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MicroSecond64]
$creadListPrec :: ReadPrec [MicroSecond64]
readPrec :: ReadPrec MicroSecond64
$creadPrec :: ReadPrec MicroSecond64
readList :: ReadS [MicroSecond64]
$creadList :: ReadS [MicroSecond64]
readsPrec :: Int -> ReadS MicroSecond64
$creadsPrec :: Int -> ReadS MicroSecond64
Read
             , Int -> MicroSecond64 -> ShowS
[MicroSecond64] -> ShowS
MicroSecond64 -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MicroSecond64] -> ShowS
$cshowList :: [MicroSecond64] -> ShowS
show :: MicroSecond64 -> String
$cshow :: MicroSecond64 -> String
showsPrec :: Int -> MicroSecond64 -> ShowS
$cshowsPrec :: Int -> MicroSecond64 -> ShowS
Show
             , Int -> MicroSecond64
MicroSecond64 -> Int
MicroSecond64 -> [MicroSecond64]
MicroSecond64 -> MicroSecond64
MicroSecond64 -> MicroSecond64 -> [MicroSecond64]
MicroSecond64 -> MicroSecond64 -> MicroSecond64 -> [MicroSecond64]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: MicroSecond64 -> MicroSecond64 -> MicroSecond64 -> [MicroSecond64]
$cenumFromThenTo :: MicroSecond64 -> MicroSecond64 -> MicroSecond64 -> [MicroSecond64]
enumFromTo :: MicroSecond64 -> MicroSecond64 -> [MicroSecond64]
$cenumFromTo :: MicroSecond64 -> MicroSecond64 -> [MicroSecond64]
enumFromThen :: MicroSecond64 -> MicroSecond64 -> [MicroSecond64]
$cenumFromThen :: MicroSecond64 -> MicroSecond64 -> [MicroSecond64]
enumFrom :: MicroSecond64 -> [MicroSecond64]
$cenumFrom :: MicroSecond64 -> [MicroSecond64]
fromEnum :: MicroSecond64 -> Int
$cfromEnum :: MicroSecond64 -> Int
toEnum :: Int -> MicroSecond64
$ctoEnum :: Int -> MicroSecond64
pred :: MicroSecond64 -> MicroSecond64
$cpred :: MicroSecond64 -> MicroSecond64
succ :: MicroSecond64 -> MicroSecond64
$csucc :: MicroSecond64 -> MicroSecond64
Enum
             , MicroSecond64
forall a. a -> a -> Bounded a
maxBound :: MicroSecond64
$cmaxBound :: MicroSecond64
minBound :: MicroSecond64
$cminBound :: MicroSecond64
Bounded
             , Integer -> MicroSecond64
MicroSecond64 -> MicroSecond64
MicroSecond64 -> MicroSecond64 -> MicroSecond64
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> MicroSecond64
$cfromInteger :: Integer -> MicroSecond64
signum :: MicroSecond64 -> MicroSecond64
$csignum :: MicroSecond64 -> MicroSecond64
abs :: MicroSecond64 -> MicroSecond64
$cabs :: MicroSecond64 -> MicroSecond64
negate :: MicroSecond64 -> MicroSecond64
$cnegate :: MicroSecond64 -> MicroSecond64
* :: MicroSecond64 -> MicroSecond64 -> MicroSecond64
$c* :: MicroSecond64 -> MicroSecond64 -> MicroSecond64
- :: MicroSecond64 -> MicroSecond64 -> MicroSecond64
$c- :: MicroSecond64 -> MicroSecond64 -> MicroSecond64
+ :: MicroSecond64 -> MicroSecond64 -> MicroSecond64
$c+ :: MicroSecond64 -> MicroSecond64 -> MicroSecond64
Num
             , Num MicroSecond64
Ord MicroSecond64
MicroSecond64 -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: MicroSecond64 -> Rational
$ctoRational :: MicroSecond64 -> Rational
Real
             , Enum MicroSecond64
Real MicroSecond64
MicroSecond64 -> Integer
MicroSecond64 -> MicroSecond64 -> (MicroSecond64, MicroSecond64)
MicroSecond64 -> MicroSecond64 -> MicroSecond64
forall a.
Real a
-> Enum a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
toInteger :: MicroSecond64 -> Integer
$ctoInteger :: MicroSecond64 -> Integer
divMod :: MicroSecond64 -> MicroSecond64 -> (MicroSecond64, MicroSecond64)
$cdivMod :: MicroSecond64 -> MicroSecond64 -> (MicroSecond64, MicroSecond64)
quotRem :: MicroSecond64 -> MicroSecond64 -> (MicroSecond64, MicroSecond64)
$cquotRem :: MicroSecond64 -> MicroSecond64 -> (MicroSecond64, MicroSecond64)
mod :: MicroSecond64 -> MicroSecond64 -> MicroSecond64
$cmod :: MicroSecond64 -> MicroSecond64 -> MicroSecond64
div :: MicroSecond64 -> MicroSecond64 -> MicroSecond64
$cdiv :: MicroSecond64 -> MicroSecond64 -> MicroSecond64
rem :: MicroSecond64 -> MicroSecond64 -> MicroSecond64
$crem :: MicroSecond64 -> MicroSecond64 -> MicroSecond64
quot :: MicroSecond64 -> MicroSecond64 -> MicroSecond64
$cquot :: MicroSecond64 -> MicroSecond64 -> MicroSecond64
Integral
             , Eq MicroSecond64
MicroSecond64 -> MicroSecond64 -> Bool
MicroSecond64 -> MicroSecond64 -> Ordering
MicroSecond64 -> MicroSecond64 -> MicroSecond64
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: MicroSecond64 -> MicroSecond64 -> MicroSecond64
$cmin :: MicroSecond64 -> MicroSecond64 -> MicroSecond64
max :: MicroSecond64 -> MicroSecond64 -> MicroSecond64
$cmax :: MicroSecond64 -> MicroSecond64 -> MicroSecond64
>= :: MicroSecond64 -> MicroSecond64 -> Bool
$c>= :: MicroSecond64 -> MicroSecond64 -> Bool
> :: MicroSecond64 -> MicroSecond64 -> Bool
$c> :: MicroSecond64 -> MicroSecond64 -> Bool
<= :: MicroSecond64 -> MicroSecond64 -> Bool
$c<= :: MicroSecond64 -> MicroSecond64 -> Bool
< :: MicroSecond64 -> MicroSecond64 -> Bool
$c< :: MicroSecond64 -> MicroSecond64 -> Bool
compare :: MicroSecond64 -> MicroSecond64 -> Ordering
$ccompare :: MicroSecond64 -> MicroSecond64 -> Ordering
Ord
             , Ptr MicroSecond64 -> IO MicroSecond64
Ptr MicroSecond64 -> Int -> IO MicroSecond64
Ptr MicroSecond64 -> Int -> MicroSecond64 -> IO ()
Ptr MicroSecond64 -> MicroSecond64 -> IO ()
MicroSecond64 -> Int
forall b. Ptr b -> Int -> IO MicroSecond64
forall b. Ptr b -> Int -> MicroSecond64 -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr MicroSecond64 -> MicroSecond64 -> IO ()
$cpoke :: Ptr MicroSecond64 -> MicroSecond64 -> IO ()
peek :: Ptr MicroSecond64 -> IO MicroSecond64
$cpeek :: Ptr MicroSecond64 -> IO MicroSecond64
pokeByteOff :: forall b. Ptr b -> Int -> MicroSecond64 -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> MicroSecond64 -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO MicroSecond64
$cpeekByteOff :: forall b. Ptr b -> Int -> IO MicroSecond64
pokeElemOff :: Ptr MicroSecond64 -> Int -> MicroSecond64 -> IO ()
$cpokeElemOff :: Ptr MicroSecond64 -> Int -> MicroSecond64 -> IO ()
peekElemOff :: Ptr MicroSecond64 -> Int -> IO MicroSecond64
$cpeekElemOff :: Ptr MicroSecond64 -> Int -> IO MicroSecond64
alignment :: MicroSecond64 -> Int
$calignment :: MicroSecond64 -> Int
sizeOf :: MicroSecond64 -> Int
$csizeOf :: MicroSecond64 -> Int
Storable
             , Int -> MutableByteArray -> IO MicroSecond64
Int -> MutableByteArray -> MicroSecond64 -> IO ()
Proxy MicroSecond64 -> Int
forall a.
(Proxy a -> Int)
-> (Int -> MutableByteArray -> IO a)
-> (Int -> MutableByteArray -> a -> IO ())
-> Unbox a
pokeByteIndex :: Int -> MutableByteArray -> MicroSecond64 -> IO ()
$cpokeByteIndex :: Int -> MutableByteArray -> MicroSecond64 -> IO ()
peekByteIndex :: Int -> MutableByteArray -> IO MicroSecond64
$cpeekByteIndex :: Int -> MutableByteArray -> IO MicroSecond64
sizeOf :: Proxy MicroSecond64 -> Int
$csizeOf :: Proxy MicroSecond64 -> Int
Unbox
             )

-- | An 'Int64' time representation with a millisecond resolution.
-- It can represent time up to ~292 million years.
newtype MilliSecond64 = MilliSecond64 Int64
    deriving ( MilliSecond64 -> MilliSecond64 -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MilliSecond64 -> MilliSecond64 -> Bool
$c/= :: MilliSecond64 -> MilliSecond64 -> Bool
== :: MilliSecond64 -> MilliSecond64 -> Bool
$c== :: MilliSecond64 -> MilliSecond64 -> Bool
Eq
             , ReadPrec [MilliSecond64]
ReadPrec MilliSecond64
Int -> ReadS MilliSecond64
ReadS [MilliSecond64]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MilliSecond64]
$creadListPrec :: ReadPrec [MilliSecond64]
readPrec :: ReadPrec MilliSecond64
$creadPrec :: ReadPrec MilliSecond64
readList :: ReadS [MilliSecond64]
$creadList :: ReadS [MilliSecond64]
readsPrec :: Int -> ReadS MilliSecond64
$creadsPrec :: Int -> ReadS MilliSecond64
Read
             , Int -> MilliSecond64 -> ShowS
[MilliSecond64] -> ShowS
MilliSecond64 -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MilliSecond64] -> ShowS
$cshowList :: [MilliSecond64] -> ShowS
show :: MilliSecond64 -> String
$cshow :: MilliSecond64 -> String
showsPrec :: Int -> MilliSecond64 -> ShowS
$cshowsPrec :: Int -> MilliSecond64 -> ShowS
Show
             , Int -> MilliSecond64
MilliSecond64 -> Int
MilliSecond64 -> [MilliSecond64]
MilliSecond64 -> MilliSecond64
MilliSecond64 -> MilliSecond64 -> [MilliSecond64]
MilliSecond64 -> MilliSecond64 -> MilliSecond64 -> [MilliSecond64]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: MilliSecond64 -> MilliSecond64 -> MilliSecond64 -> [MilliSecond64]
$cenumFromThenTo :: MilliSecond64 -> MilliSecond64 -> MilliSecond64 -> [MilliSecond64]
enumFromTo :: MilliSecond64 -> MilliSecond64 -> [MilliSecond64]
$cenumFromTo :: MilliSecond64 -> MilliSecond64 -> [MilliSecond64]
enumFromThen :: MilliSecond64 -> MilliSecond64 -> [MilliSecond64]
$cenumFromThen :: MilliSecond64 -> MilliSecond64 -> [MilliSecond64]
enumFrom :: MilliSecond64 -> [MilliSecond64]
$cenumFrom :: MilliSecond64 -> [MilliSecond64]
fromEnum :: MilliSecond64 -> Int
$cfromEnum :: MilliSecond64 -> Int
toEnum :: Int -> MilliSecond64
$ctoEnum :: Int -> MilliSecond64
pred :: MilliSecond64 -> MilliSecond64
$cpred :: MilliSecond64 -> MilliSecond64
succ :: MilliSecond64 -> MilliSecond64
$csucc :: MilliSecond64 -> MilliSecond64
Enum
             , MilliSecond64
forall a. a -> a -> Bounded a
maxBound :: MilliSecond64
$cmaxBound :: MilliSecond64
minBound :: MilliSecond64
$cminBound :: MilliSecond64
Bounded
             , Integer -> MilliSecond64
MilliSecond64 -> MilliSecond64
MilliSecond64 -> MilliSecond64 -> MilliSecond64
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> MilliSecond64
$cfromInteger :: Integer -> MilliSecond64
signum :: MilliSecond64 -> MilliSecond64
$csignum :: MilliSecond64 -> MilliSecond64
abs :: MilliSecond64 -> MilliSecond64
$cabs :: MilliSecond64 -> MilliSecond64
negate :: MilliSecond64 -> MilliSecond64
$cnegate :: MilliSecond64 -> MilliSecond64
* :: MilliSecond64 -> MilliSecond64 -> MilliSecond64
$c* :: MilliSecond64 -> MilliSecond64 -> MilliSecond64
- :: MilliSecond64 -> MilliSecond64 -> MilliSecond64
$c- :: MilliSecond64 -> MilliSecond64 -> MilliSecond64
+ :: MilliSecond64 -> MilliSecond64 -> MilliSecond64
$c+ :: MilliSecond64 -> MilliSecond64 -> MilliSecond64
Num
             , Num MilliSecond64
Ord MilliSecond64
MilliSecond64 -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: MilliSecond64 -> Rational
$ctoRational :: MilliSecond64 -> Rational
Real
             , Enum MilliSecond64
Real MilliSecond64
MilliSecond64 -> Integer
MilliSecond64 -> MilliSecond64 -> (MilliSecond64, MilliSecond64)
MilliSecond64 -> MilliSecond64 -> MilliSecond64
forall a.
Real a
-> Enum a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
toInteger :: MilliSecond64 -> Integer
$ctoInteger :: MilliSecond64 -> Integer
divMod :: MilliSecond64 -> MilliSecond64 -> (MilliSecond64, MilliSecond64)
$cdivMod :: MilliSecond64 -> MilliSecond64 -> (MilliSecond64, MilliSecond64)
quotRem :: MilliSecond64 -> MilliSecond64 -> (MilliSecond64, MilliSecond64)
$cquotRem :: MilliSecond64 -> MilliSecond64 -> (MilliSecond64, MilliSecond64)
mod :: MilliSecond64 -> MilliSecond64 -> MilliSecond64
$cmod :: MilliSecond64 -> MilliSecond64 -> MilliSecond64
div :: MilliSecond64 -> MilliSecond64 -> MilliSecond64
$cdiv :: MilliSecond64 -> MilliSecond64 -> MilliSecond64
rem :: MilliSecond64 -> MilliSecond64 -> MilliSecond64
$crem :: MilliSecond64 -> MilliSecond64 -> MilliSecond64
quot :: MilliSecond64 -> MilliSecond64 -> MilliSecond64
$cquot :: MilliSecond64 -> MilliSecond64 -> MilliSecond64
Integral
             , Eq MilliSecond64
MilliSecond64 -> MilliSecond64 -> Bool
MilliSecond64 -> MilliSecond64 -> Ordering
MilliSecond64 -> MilliSecond64 -> MilliSecond64
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: MilliSecond64 -> MilliSecond64 -> MilliSecond64
$cmin :: MilliSecond64 -> MilliSecond64 -> MilliSecond64
max :: MilliSecond64 -> MilliSecond64 -> MilliSecond64
$cmax :: MilliSecond64 -> MilliSecond64 -> MilliSecond64
>= :: MilliSecond64 -> MilliSecond64 -> Bool
$c>= :: MilliSecond64 -> MilliSecond64 -> Bool
> :: MilliSecond64 -> MilliSecond64 -> Bool
$c> :: MilliSecond64 -> MilliSecond64 -> Bool
<= :: MilliSecond64 -> MilliSecond64 -> Bool
$c<= :: MilliSecond64 -> MilliSecond64 -> Bool
< :: MilliSecond64 -> MilliSecond64 -> Bool
$c< :: MilliSecond64 -> MilliSecond64 -> Bool
compare :: MilliSecond64 -> MilliSecond64 -> Ordering
$ccompare :: MilliSecond64 -> MilliSecond64 -> Ordering
Ord
             , Ptr MilliSecond64 -> IO MilliSecond64
Ptr MilliSecond64 -> Int -> IO MilliSecond64
Ptr MilliSecond64 -> Int -> MilliSecond64 -> IO ()
Ptr MilliSecond64 -> MilliSecond64 -> IO ()
MilliSecond64 -> Int
forall b. Ptr b -> Int -> IO MilliSecond64
forall b. Ptr b -> Int -> MilliSecond64 -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr MilliSecond64 -> MilliSecond64 -> IO ()
$cpoke :: Ptr MilliSecond64 -> MilliSecond64 -> IO ()
peek :: Ptr MilliSecond64 -> IO MilliSecond64
$cpeek :: Ptr MilliSecond64 -> IO MilliSecond64
pokeByteOff :: forall b. Ptr b -> Int -> MilliSecond64 -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> MilliSecond64 -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO MilliSecond64
$cpeekByteOff :: forall b. Ptr b -> Int -> IO MilliSecond64
pokeElemOff :: Ptr MilliSecond64 -> Int -> MilliSecond64 -> IO ()
$cpokeElemOff :: Ptr MilliSecond64 -> Int -> MilliSecond64 -> IO ()
peekElemOff :: Ptr MilliSecond64 -> Int -> IO MilliSecond64
$cpeekElemOff :: Ptr MilliSecond64 -> Int -> IO MilliSecond64
alignment :: MilliSecond64 -> Int
$calignment :: MilliSecond64 -> Int
sizeOf :: MilliSecond64 -> Int
$csizeOf :: MilliSecond64 -> Int
Storable
             , Int -> MutableByteArray -> IO MilliSecond64
Int -> MutableByteArray -> MilliSecond64 -> IO ()
Proxy MilliSecond64 -> Int
forall a.
(Proxy a -> Int)
-> (Int -> MutableByteArray -> IO a)
-> (Int -> MutableByteArray -> a -> IO ())
-> Unbox a
pokeByteIndex :: Int -> MutableByteArray -> MilliSecond64 -> IO ()
$cpokeByteIndex :: Int -> MutableByteArray -> MilliSecond64 -> IO ()
peekByteIndex :: Int -> MutableByteArray -> IO MilliSecond64
$cpeekByteIndex :: Int -> MutableByteArray -> IO MilliSecond64
sizeOf :: Proxy MilliSecond64 -> Int
$csizeOf :: Proxy MilliSecond64 -> Int
Unbox
             )

-------------------------------------------------------------------------------
-- Fractional Units
-------------------------------------------------------------------------------

-------------------------------------------------------------------------------
-- Time unit conversions
-------------------------------------------------------------------------------

-- TODO: compare whether using TimeSpec instead of Integer provides significant
-- performance boost. If not then we can just use Integer nanoseconds and get
-- rid of TimeUnitWide.
--
-- | A type class for converting between time units using 'Integer' as the
-- intermediate and the widest representation with a nanosecond resolution.
-- This system of units can represent arbitrarily large times but provides
-- least efficient arithmetic operations due to 'Integer' arithmetic.
--
-- NOTE: Converting to and from units may truncate the value depending on the
-- original value and the size and resolution of the destination unit.
{-
class TimeUnitWide a where
    toTimeInteger   :: a -> Integer
    fromTimeInteger :: Integer -> a
-}

-- | A type class for converting between units of time using 'TimeSpec' as the
-- intermediate representation.  This system of units can represent up to ~292
-- billion years at nanosecond resolution with reasonably efficient arithmetic
-- operations.
--
-- NOTE: Converting to and from units may truncate the value depending on the
-- original value and the size and resolution of the destination unit.
class TimeUnit a where
    toTimeSpec   :: a -> TimeSpec
    fromTimeSpec :: TimeSpec -> a

-- XXX we can use a fromNanoSecond64 for conversion with overflow check and
-- fromNanoSecond64Unsafe for conversion without overflow check.
--
-- | A type class for converting between units of time using 'Int64' as the
-- intermediate representation with a nanosecond resolution.  This system of
-- units can represent up to ~292 years at nanosecond resolution with fast
-- arithmetic operations.
--
-- NOTE: Converting to and from units may truncate the value depending on the
-- original value and the size and resolution of the destination unit.
class TimeUnit64 a where
    toNanoSecond64   :: a -> NanoSecond64
    fromNanoSecond64 :: NanoSecond64 -> a

-------------------------------------------------------------------------------
-- Time units
-------------------------------------------------------------------------------

instance TimeUnit TimeSpec where
    toTimeSpec :: TimeSpec -> TimeSpec
toTimeSpec = forall a. a -> a
id
    fromTimeSpec :: TimeSpec -> TimeSpec
fromTimeSpec = forall a. a -> a
id

instance TimeUnit NanoSecond64 where
    {-# INLINE toTimeSpec #-}
    toTimeSpec :: NanoSecond64 -> TimeSpec
toTimeSpec (NanoSecond64 Int64
t) = Int64 -> Int64 -> TimeSpec
TimeSpec Int64
s Int64
ns
        where (Int64
s, Int64
ns) = Int64
t forall a. Integral a => a -> a -> (a, a)
`divMod` Int64
tenPower9

    {-# INLINE fromTimeSpec #-}
    fromTimeSpec :: TimeSpec -> NanoSecond64
fromTimeSpec (TimeSpec Int64
s Int64
ns) =
        Int64 -> NanoSecond64
NanoSecond64 forall a b. (a -> b) -> a -> b
$ Int64
s forall a. Num a => a -> a -> a
* Int64
tenPower9 forall a. Num a => a -> a -> a
+ Int64
ns

instance TimeUnit64 NanoSecond64 where
    {-# INLINE toNanoSecond64 #-}
    toNanoSecond64 :: NanoSecond64 -> NanoSecond64
toNanoSecond64 = forall a. a -> a
id

    {-# INLINE fromNanoSecond64 #-}
    fromNanoSecond64 :: NanoSecond64 -> NanoSecond64
fromNanoSecond64 = forall a. a -> a
id

instance TimeUnit MicroSecond64 where
    {-# INLINE toTimeSpec #-}
    toTimeSpec :: MicroSecond64 -> TimeSpec
toTimeSpec (MicroSecond64 Int64
t) = Int64 -> Int64 -> TimeSpec
TimeSpec Int64
s (Int64
us forall a. Num a => a -> a -> a
* Int64
tenPower3)
        where (Int64
s, Int64
us) = Int64
t forall a. Integral a => a -> a -> (a, a)
`divMod` Int64
tenPower6

    {-# INLINE fromTimeSpec #-}
    fromTimeSpec :: TimeSpec -> MicroSecond64
fromTimeSpec (TimeSpec Int64
s Int64
ns) =
        -- XXX round ns to nearest microsecond?
        Int64 -> MicroSecond64
MicroSecond64 forall a b. (a -> b) -> a -> b
$ Int64
s forall a. Num a => a -> a -> a
* Int64
tenPower6 forall a. Num a => a -> a -> a
+ (Int64
ns forall a. Integral a => a -> a -> a
`div` Int64
tenPower3)

instance TimeUnit64 MicroSecond64 where
    {-# INLINE toNanoSecond64 #-}
    toNanoSecond64 :: MicroSecond64 -> NanoSecond64
toNanoSecond64 (MicroSecond64 Int64
us) = Int64 -> NanoSecond64
NanoSecond64 forall a b. (a -> b) -> a -> b
$ Int64
us forall a. Num a => a -> a -> a
* Int64
tenPower3

    {-# INLINE fromNanoSecond64 #-}
    -- XXX round ns to nearest microsecond?
    fromNanoSecond64 :: NanoSecond64 -> MicroSecond64
fromNanoSecond64 (NanoSecond64 Int64
ns) = Int64 -> MicroSecond64
MicroSecond64 forall a b. (a -> b) -> a -> b
$ Int64
ns forall a. Integral a => a -> a -> a
`div` Int64
tenPower3

instance TimeUnit MilliSecond64 where
    {-# INLINE toTimeSpec #-}
    toTimeSpec :: MilliSecond64 -> TimeSpec
toTimeSpec (MilliSecond64 Int64
t) = Int64 -> Int64 -> TimeSpec
TimeSpec Int64
s (Int64
ms forall a. Num a => a -> a -> a
* Int64
tenPower6)
        where (Int64
s, Int64
ms) = Int64
t forall a. Integral a => a -> a -> (a, a)
`divMod` Int64
tenPower3

    {-# INLINE fromTimeSpec #-}
    fromTimeSpec :: TimeSpec -> MilliSecond64
fromTimeSpec (TimeSpec Int64
s Int64
ns) =
        -- XXX round ns to nearest millisecond?
        Int64 -> MilliSecond64
MilliSecond64 forall a b. (a -> b) -> a -> b
$ Int64
s forall a. Num a => a -> a -> a
* Int64
tenPower3 forall a. Num a => a -> a -> a
+ (Int64
ns forall a. Integral a => a -> a -> a
`div` Int64
tenPower6)

instance TimeUnit64 MilliSecond64 where
    {-# INLINE toNanoSecond64 #-}
    toNanoSecond64 :: MilliSecond64 -> NanoSecond64
toNanoSecond64 (MilliSecond64 Int64
ms) = Int64 -> NanoSecond64
NanoSecond64 forall a b. (a -> b) -> a -> b
$ Int64
ms forall a. Num a => a -> a -> a
* Int64
tenPower6

    {-# INLINE fromNanoSecond64 #-}
    -- XXX round ns to nearest millisecond?
    fromNanoSecond64 :: NanoSecond64 -> MilliSecond64
fromNanoSecond64 (NanoSecond64 Int64
ns) = Int64 -> MilliSecond64
MilliSecond64 forall a b. (a -> b) -> a -> b
$ Int64
ns forall a. Integral a => a -> a -> a
`div` Int64
tenPower6

-------------------------------------------------------------------------------
-- Absolute time
-------------------------------------------------------------------------------

-- | Absolute times are relative to a predefined epoch in time. 'AbsTime'
-- represents times using 'TimeSpec' which can represent times up to ~292
-- billion years at a nanosecond resolution.
newtype AbsTime = AbsTime TimeSpec
    deriving (AbsTime -> AbsTime -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AbsTime -> AbsTime -> Bool
$c/= :: AbsTime -> AbsTime -> Bool
== :: AbsTime -> AbsTime -> Bool
$c== :: AbsTime -> AbsTime -> Bool
Eq, Eq AbsTime
AbsTime -> AbsTime -> Bool
AbsTime -> AbsTime -> Ordering
AbsTime -> AbsTime -> AbsTime
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AbsTime -> AbsTime -> AbsTime
$cmin :: AbsTime -> AbsTime -> AbsTime
max :: AbsTime -> AbsTime -> AbsTime
$cmax :: AbsTime -> AbsTime -> AbsTime
>= :: AbsTime -> AbsTime -> Bool
$c>= :: AbsTime -> AbsTime -> Bool
> :: AbsTime -> AbsTime -> Bool
$c> :: AbsTime -> AbsTime -> Bool
<= :: AbsTime -> AbsTime -> Bool
$c<= :: AbsTime -> AbsTime -> Bool
< :: AbsTime -> AbsTime -> Bool
$c< :: AbsTime -> AbsTime -> Bool
compare :: AbsTime -> AbsTime -> Ordering
$ccompare :: AbsTime -> AbsTime -> Ordering
Ord, Int -> AbsTime -> ShowS
[AbsTime] -> ShowS
AbsTime -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AbsTime] -> ShowS
$cshowList :: [AbsTime] -> ShowS
show :: AbsTime -> String
$cshow :: AbsTime -> String
showsPrec :: Int -> AbsTime -> ShowS
$cshowsPrec :: Int -> AbsTime -> ShowS
Show)

-- | Convert a 'TimeUnit' to an absolute time.
{-# INLINE_NORMAL toAbsTime #-}
toAbsTime :: TimeUnit a => a -> AbsTime
toAbsTime :: forall a. TimeUnit a => a -> AbsTime
toAbsTime = TimeSpec -> AbsTime
AbsTime forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. TimeUnit a => a -> TimeSpec
toTimeSpec

-- | Convert absolute time to a 'TimeUnit'.
{-# INLINE_NORMAL fromAbsTime #-}
fromAbsTime :: TimeUnit a => AbsTime -> a
fromAbsTime :: forall a. TimeUnit a => AbsTime -> a
fromAbsTime (AbsTime TimeSpec
t) = forall a. TimeUnit a => TimeSpec -> a
fromTimeSpec TimeSpec
t

-- XXX We can also write rewrite rules to simplify divisions multiplications
-- and additions when manipulating units. Though, that might get simplified at
-- the assembly (llvm) level as well. Note to/from conversions may be lossy and
-- therefore this equation may not hold, but that's ok.
{-# RULES "fromAbsTime/toAbsTime" forall a. toAbsTime (fromAbsTime a) = a #-}
{-# RULES "toAbsTime/fromAbsTime" forall a. fromAbsTime (toAbsTime a) = a #-}

-------------------------------------------------------------------------------
-- Relative time using NaonoSecond64 as the underlying representation
-------------------------------------------------------------------------------

-- We use a separate type to represent relative time for safety and speed.
-- RelTime has a Num instance, absolute time doesn't.  Relative times are
-- usually shorter and for our purposes an Int64 nanoseconds can hold close to
-- thousand year duration. It is also faster to manipulate. We do not check for
-- overflows during manipulations so use it only when you know the time cannot
-- be too big. If you need a bigger RelTime representation then use RelTimeBig.

-- | Relative times are relative to some arbitrary point of time. Unlike
-- 'AbsTime' they are not relative to a predefined epoch.
newtype RelTime64 = RelTime64 NanoSecond64
    deriving ( RelTime64 -> RelTime64 -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RelTime64 -> RelTime64 -> Bool
$c/= :: RelTime64 -> RelTime64 -> Bool
== :: RelTime64 -> RelTime64 -> Bool
$c== :: RelTime64 -> RelTime64 -> Bool
Eq
             , ReadPrec [RelTime64]
ReadPrec RelTime64
Int -> ReadS RelTime64
ReadS [RelTime64]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RelTime64]
$creadListPrec :: ReadPrec [RelTime64]
readPrec :: ReadPrec RelTime64
$creadPrec :: ReadPrec RelTime64
readList :: ReadS [RelTime64]
$creadList :: ReadS [RelTime64]
readsPrec :: Int -> ReadS RelTime64
$creadsPrec :: Int -> ReadS RelTime64
Read
             , Int -> RelTime64 -> ShowS
[RelTime64] -> ShowS
RelTime64 -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RelTime64] -> ShowS
$cshowList :: [RelTime64] -> ShowS
show :: RelTime64 -> String
$cshow :: RelTime64 -> String
showsPrec :: Int -> RelTime64 -> ShowS
$cshowsPrec :: Int -> RelTime64 -> ShowS
Show
             , Int -> RelTime64
RelTime64 -> Int
RelTime64 -> [RelTime64]
RelTime64 -> RelTime64
RelTime64 -> RelTime64 -> [RelTime64]
RelTime64 -> RelTime64 -> RelTime64 -> [RelTime64]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: RelTime64 -> RelTime64 -> RelTime64 -> [RelTime64]
$cenumFromThenTo :: RelTime64 -> RelTime64 -> RelTime64 -> [RelTime64]
enumFromTo :: RelTime64 -> RelTime64 -> [RelTime64]
$cenumFromTo :: RelTime64 -> RelTime64 -> [RelTime64]
enumFromThen :: RelTime64 -> RelTime64 -> [RelTime64]
$cenumFromThen :: RelTime64 -> RelTime64 -> [RelTime64]
enumFrom :: RelTime64 -> [RelTime64]
$cenumFrom :: RelTime64 -> [RelTime64]
fromEnum :: RelTime64 -> Int
$cfromEnum :: RelTime64 -> Int
toEnum :: Int -> RelTime64
$ctoEnum :: Int -> RelTime64
pred :: RelTime64 -> RelTime64
$cpred :: RelTime64 -> RelTime64
succ :: RelTime64 -> RelTime64
$csucc :: RelTime64 -> RelTime64
Enum
             , RelTime64
forall a. a -> a -> Bounded a
maxBound :: RelTime64
$cmaxBound :: RelTime64
minBound :: RelTime64
$cminBound :: RelTime64
Bounded
             , Integer -> RelTime64
RelTime64 -> RelTime64
RelTime64 -> RelTime64 -> RelTime64
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> RelTime64
$cfromInteger :: Integer -> RelTime64
signum :: RelTime64 -> RelTime64
$csignum :: RelTime64 -> RelTime64
abs :: RelTime64 -> RelTime64
$cabs :: RelTime64 -> RelTime64
negate :: RelTime64 -> RelTime64
$cnegate :: RelTime64 -> RelTime64
* :: RelTime64 -> RelTime64 -> RelTime64
$c* :: RelTime64 -> RelTime64 -> RelTime64
- :: RelTime64 -> RelTime64 -> RelTime64
$c- :: RelTime64 -> RelTime64 -> RelTime64
+ :: RelTime64 -> RelTime64 -> RelTime64
$c+ :: RelTime64 -> RelTime64 -> RelTime64
Num
             , Num RelTime64
Ord RelTime64
RelTime64 -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: RelTime64 -> Rational
$ctoRational :: RelTime64 -> Rational
Real
             , Enum RelTime64
Real RelTime64
RelTime64 -> Integer
RelTime64 -> RelTime64 -> (RelTime64, RelTime64)
RelTime64 -> RelTime64 -> RelTime64
forall a.
Real a
-> Enum a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
toInteger :: RelTime64 -> Integer
$ctoInteger :: RelTime64 -> Integer
divMod :: RelTime64 -> RelTime64 -> (RelTime64, RelTime64)
$cdivMod :: RelTime64 -> RelTime64 -> (RelTime64, RelTime64)
quotRem :: RelTime64 -> RelTime64 -> (RelTime64, RelTime64)
$cquotRem :: RelTime64 -> RelTime64 -> (RelTime64, RelTime64)
mod :: RelTime64 -> RelTime64 -> RelTime64
$cmod :: RelTime64 -> RelTime64 -> RelTime64
div :: RelTime64 -> RelTime64 -> RelTime64
$cdiv :: RelTime64 -> RelTime64 -> RelTime64
rem :: RelTime64 -> RelTime64 -> RelTime64
$crem :: RelTime64 -> RelTime64 -> RelTime64
quot :: RelTime64 -> RelTime64 -> RelTime64
$cquot :: RelTime64 -> RelTime64 -> RelTime64
Integral
             , Eq RelTime64
RelTime64 -> RelTime64 -> Bool
RelTime64 -> RelTime64 -> Ordering
RelTime64 -> RelTime64 -> RelTime64
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RelTime64 -> RelTime64 -> RelTime64
$cmin :: RelTime64 -> RelTime64 -> RelTime64
max :: RelTime64 -> RelTime64 -> RelTime64
$cmax :: RelTime64 -> RelTime64 -> RelTime64
>= :: RelTime64 -> RelTime64 -> Bool
$c>= :: RelTime64 -> RelTime64 -> Bool
> :: RelTime64 -> RelTime64 -> Bool
$c> :: RelTime64 -> RelTime64 -> Bool
<= :: RelTime64 -> RelTime64 -> Bool
$c<= :: RelTime64 -> RelTime64 -> Bool
< :: RelTime64 -> RelTime64 -> Bool
$c< :: RelTime64 -> RelTime64 -> Bool
compare :: RelTime64 -> RelTime64 -> Ordering
$ccompare :: RelTime64 -> RelTime64 -> Ordering
Ord
             )

-- | Convert a 'TimeUnit' to a relative time.
{-# INLINE_NORMAL toRelTime64 #-}
toRelTime64 :: TimeUnit64 a => a -> RelTime64
toRelTime64 :: forall a. TimeUnit64 a => a -> RelTime64
toRelTime64 = NanoSecond64 -> RelTime64
RelTime64 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. TimeUnit64 a => a -> NanoSecond64
toNanoSecond64

-- | Convert relative time to a 'TimeUnit'.
{-# INLINE_NORMAL fromRelTime64 #-}
fromRelTime64 :: TimeUnit64 a => RelTime64 -> a
fromRelTime64 :: forall a. TimeUnit64 a => RelTime64 -> a
fromRelTime64 (RelTime64 NanoSecond64
t) = forall a. TimeUnit64 a => NanoSecond64 -> a
fromNanoSecond64 NanoSecond64
t

{-# RULES "fromRelTime64/toRelTime64" forall a .
          toRelTime64 (fromRelTime64 a) = a #-}

{-# RULES "toRelTime64/fromRelTime64" forall a .
          fromRelTime64 (toRelTime64 a) = a #-}

-- | Difference between two absolute points of time.
{-# INLINE diffAbsTime64 #-}
diffAbsTime64 :: AbsTime -> AbsTime -> RelTime64
diffAbsTime64 :: AbsTime -> AbsTime -> RelTime64
diffAbsTime64 (AbsTime (TimeSpec Int64
s1 Int64
ns1)) (AbsTime (TimeSpec Int64
s2 Int64
ns2)) =
    NanoSecond64 -> RelTime64
RelTime64 forall a b. (a -> b) -> a -> b
$ Int64 -> NanoSecond64
NanoSecond64 forall a b. (a -> b) -> a -> b
$ ((Int64
s1 forall a. Num a => a -> a -> a
- Int64
s2) forall a. Num a => a -> a -> a
* Int64
tenPower9) forall a. Num a => a -> a -> a
+ (Int64
ns1 forall a. Num a => a -> a -> a
- Int64
ns2)

{-# INLINE addToAbsTime64 #-}
addToAbsTime64 :: AbsTime -> RelTime64 -> AbsTime
addToAbsTime64 :: AbsTime -> RelTime64 -> AbsTime
addToAbsTime64 (AbsTime (TimeSpec Int64
s1 Int64
ns1)) (RelTime64 (NanoSecond64 Int64
ns2)) =
    TimeSpec -> AbsTime
AbsTime forall a b. (a -> b) -> a -> b
$ Int64 -> Int64 -> TimeSpec
TimeSpec (Int64
s1 forall a. Num a => a -> a -> a
+ Int64
s) Int64
ns
    where (Int64
s, Int64
ns) = (Int64
ns1 forall a. Num a => a -> a -> a
+ Int64
ns2) forall a. Integral a => a -> a -> (a, a)
`divMod` Int64
tenPower9

-------------------------------------------------------------------------------
-- Relative time using TimeSpec as the underlying representation
-------------------------------------------------------------------------------

newtype RelTime = RelTime TimeSpec
    deriving ( RelTime -> RelTime -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RelTime -> RelTime -> Bool
$c/= :: RelTime -> RelTime -> Bool
== :: RelTime -> RelTime -> Bool
$c== :: RelTime -> RelTime -> Bool
Eq
             , ReadPrec [RelTime]
ReadPrec RelTime
Int -> ReadS RelTime
ReadS [RelTime]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RelTime]
$creadListPrec :: ReadPrec [RelTime]
readPrec :: ReadPrec RelTime
$creadPrec :: ReadPrec RelTime
readList :: ReadS [RelTime]
$creadList :: ReadS [RelTime]
readsPrec :: Int -> ReadS RelTime
$creadsPrec :: Int -> ReadS RelTime
Read
             , Int -> RelTime -> ShowS
[RelTime] -> ShowS
RelTime -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RelTime] -> ShowS
$cshowList :: [RelTime] -> ShowS
show :: RelTime -> String
$cshow :: RelTime -> String
showsPrec :: Int -> RelTime -> ShowS
$cshowsPrec :: Int -> RelTime -> ShowS
Show
             -- , Enum
             -- , Bounded
             , Integer -> RelTime
RelTime -> RelTime
RelTime -> RelTime -> RelTime
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> RelTime
$cfromInteger :: Integer -> RelTime
signum :: RelTime -> RelTime
$csignum :: RelTime -> RelTime
abs :: RelTime -> RelTime
$cabs :: RelTime -> RelTime
negate :: RelTime -> RelTime
$cnegate :: RelTime -> RelTime
* :: RelTime -> RelTime -> RelTime
$c* :: RelTime -> RelTime -> RelTime
- :: RelTime -> RelTime -> RelTime
$c- :: RelTime -> RelTime -> RelTime
+ :: RelTime -> RelTime -> RelTime
$c+ :: RelTime -> RelTime -> RelTime
Num
             -- , Real
             -- , Integral
             , Eq RelTime
RelTime -> RelTime -> Bool
RelTime -> RelTime -> Ordering
RelTime -> RelTime -> RelTime
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RelTime -> RelTime -> RelTime
$cmin :: RelTime -> RelTime -> RelTime
max :: RelTime -> RelTime -> RelTime
$cmax :: RelTime -> RelTime -> RelTime
>= :: RelTime -> RelTime -> Bool
$c>= :: RelTime -> RelTime -> Bool
> :: RelTime -> RelTime -> Bool
$c> :: RelTime -> RelTime -> Bool
<= :: RelTime -> RelTime -> Bool
$c<= :: RelTime -> RelTime -> Bool
< :: RelTime -> RelTime -> Bool
$c< :: RelTime -> RelTime -> Bool
compare :: RelTime -> RelTime -> Ordering
$ccompare :: RelTime -> RelTime -> Ordering
Ord
             )

{-# INLINE_NORMAL toRelTime #-}
toRelTime :: TimeUnit a => a -> RelTime
toRelTime :: forall a. TimeUnit a => a -> RelTime
toRelTime = TimeSpec -> RelTime
RelTime forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. TimeUnit a => a -> TimeSpec
toTimeSpec

{-# INLINE_NORMAL fromRelTime #-}
fromRelTime :: TimeUnit a => RelTime -> a
fromRelTime :: forall a. TimeUnit a => RelTime -> a
fromRelTime (RelTime TimeSpec
t) = forall a. TimeUnit a => TimeSpec -> a
fromTimeSpec TimeSpec
t

{-# RULES "fromRelTime/toRelTime" forall a. toRelTime (fromRelTime a) = a #-}
{-# RULES "toRelTime/fromRelTime" forall a. fromRelTime (toRelTime a) = a #-}

-- XXX rename to diffAbsTimes?
{-# INLINE diffAbsTime #-}
diffAbsTime :: AbsTime -> AbsTime -> RelTime
diffAbsTime :: AbsTime -> AbsTime -> RelTime
diffAbsTime (AbsTime TimeSpec
t1) (AbsTime TimeSpec
t2) = TimeSpec -> RelTime
RelTime (TimeSpec
t1 forall a. Num a => a -> a -> a
- TimeSpec
t2)

{-# INLINE addToAbsTime #-}
addToAbsTime :: AbsTime -> RelTime -> AbsTime
addToAbsTime :: AbsTime -> RelTime -> AbsTime
addToAbsTime (AbsTime TimeSpec
t1) (RelTime TimeSpec
t2) = TimeSpec -> AbsTime
AbsTime forall a b. (a -> b) -> a -> b
$ TimeSpec
t1 forall a. Num a => a -> a -> a
+ TimeSpec
t2

-------------------------------------------------------------------------------
-- Formatting and printing
-------------------------------------------------------------------------------

-- | Convert nanoseconds to a string showing time in an appropriate unit.
showNanoSecond64 :: NanoSecond64 -> String
showNanoSecond64 :: NanoSecond64 -> String
showNanoSecond64 time :: NanoSecond64
time@(NanoSecond64 Int64
ns)
    | NanoSecond64
time forall a. Ord a => a -> a -> Bool
< NanoSecond64
0    = Char
'-' forall a. a -> [a] -> [a]
: NanoSecond64 -> String
showNanoSecond64 (-NanoSecond64
time)
    | Int64
ns forall a. Ord a => a -> a -> Bool
< Int64
1000 = forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
ns forall {t}. PrintfType t => Double -> String -> t
`with` String
"ns"
#ifdef mingw32_HOST_OS
    | ns < 1000000 = (fromIntegral ns / 1000) `with` "us"
#else
    | Int64
ns forall a. Ord a => a -> a -> Bool
< Int64
1000000 = (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
ns forall a. Fractional a => a -> a -> a
/ Double
1000) forall {t}. PrintfType t => Double -> String -> t
`with` String
"μs"
#endif
    | Int64
ns forall a. Ord a => a -> a -> Bool
< Int64
1000000000 = (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
ns forall a. Fractional a => a -> a -> a
/ Double
1000000) forall {t}. PrintfType t => Double -> String -> t
`with` String
"ms"
    | Int64
ns forall a. Ord a => a -> a -> Bool
< (Int64
60 forall a. Num a => a -> a -> a
* Int64
1000000000) = (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
ns forall a. Fractional a => a -> a -> a
/ Double
1000000000) forall {t}. PrintfType t => Double -> String -> t
`with` String
"s"
    | Int64
ns forall a. Ord a => a -> a -> Bool
< (Int64
60 forall a. Num a => a -> a -> a
* Int64
60 forall a. Num a => a -> a -> a
* Int64
1000000000) =
        (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
ns forall a. Fractional a => a -> a -> a
/ (Double
60 forall a. Num a => a -> a -> a
* Double
1000000000)) forall {t}. PrintfType t => Double -> String -> t
`with` String
"min"
    | Int64
ns forall a. Ord a => a -> a -> Bool
< (Int64
24 forall a. Num a => a -> a -> a
* Int64
60 forall a. Num a => a -> a -> a
* Int64
60 forall a. Num a => a -> a -> a
* Int64
1000000000) =
        (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
ns forall a. Fractional a => a -> a -> a
/ (Double
60 forall a. Num a => a -> a -> a
* Double
60 forall a. Num a => a -> a -> a
* Double
1000000000)) forall {t}. PrintfType t => Double -> String -> t
`with` String
"hr"
    | Int64
ns forall a. Ord a => a -> a -> Bool
< (Int64
365 forall a. Num a => a -> a -> a
* Int64
24 forall a. Num a => a -> a -> a
* Int64
60 forall a. Num a => a -> a -> a
* Int64
60 forall a. Num a => a -> a -> a
* Int64
1000000000) =
        (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
ns forall a. Fractional a => a -> a -> a
/ (Double
24 forall a. Num a => a -> a -> a
* Double
60 forall a. Num a => a -> a -> a
* Double
60 forall a. Num a => a -> a -> a
* Double
1000000000)) forall {t}. PrintfType t => Double -> String -> t
`with` String
"days"
    | Bool
otherwise =
        (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
ns forall a. Fractional a => a -> a -> a
/ (Double
365 forall a. Num a => a -> a -> a
* Double
24 forall a. Num a => a -> a -> a
* Double
60 forall a. Num a => a -> a -> a
* Double
60 forall a. Num a => a -> a -> a
* Double
1000000000)) forall {t}. PrintfType t => Double -> String -> t
`with` String
"years"
     where with :: Double -> String -> t
with (Double
t :: Double) (String
u :: String)
               | Double
t forall a. Ord a => a -> a -> Bool
>= Double
1e9  = forall r. PrintfType r => String -> r
printf String
"%.4g %s" Double
t String
u
               | Double
t forall a. Ord a => a -> a -> Bool
>= Double
1e3  = forall r. PrintfType r => String -> r
printf String
"%.0f %s" Double
t String
u
               | Double
t forall a. Ord a => a -> a -> Bool
>= Double
1e2  = forall r. PrintfType r => String -> r
printf String
"%.1f %s" Double
t String
u
               | Double
t forall a. Ord a => a -> a -> Bool
>= Double
1e1  = forall r. PrintfType r => String -> r
printf String
"%.2f %s" Double
t String
u
               | Bool
otherwise = forall r. PrintfType r => String -> r
printf String
"%.3f %s" Double
t String
u

-- In general we should be able to show the time in a specified unit, if we
-- omit the unit we can show it in an automatically chosen one.
{-
data UnitName =
      Nano
    | Micro
    | Milli
    | Sec
-}

showRelTime64 :: RelTime64 -> String
showRelTime64 :: RelTime64 -> String
showRelTime64 = NanoSecond64 -> String
showNanoSecond64 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. TimeUnit64 a => RelTime64 -> a
fromRelTime64