{-# LANGUAGE TypeInType #-}
{-# LANGUAGE UnboxedTuples #-}
module Streamly.Internal.Data.Time.Units
(
TimeUnit()
, TimeUnit64()
, TimeSpec(..)
, NanoSecond64(..)
, MicroSecond64(..)
, MilliSecond64(..)
, showNanoSecond64
, AbsTime(..)
, toAbsTime
, fromAbsTime
, RelTime
, toRelTime
, fromRelTime
, diffAbsTime
, addToAbsTime
, RelTime64
, toRelTime64
, fromRelTime64
, diffAbsTime64
, addToAbsTime64
, showRelTime64
)
where
#include "inline.hs"
import Text.Printf (printf)
import Data.Int
import Data.Primitive.Types (Prim(..))
import Streamly.Internal.Data.Time.TimeSpec
{-# 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
newtype NanoSecond64 = NanoSecond64 Int64
deriving ( NanoSecond64 -> NanoSecond64 -> Bool
(NanoSecond64 -> NanoSecond64 -> Bool)
-> (NanoSecond64 -> NanoSecond64 -> Bool) -> Eq NanoSecond64
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]
(Int -> ReadS NanoSecond64)
-> ReadS [NanoSecond64]
-> ReadPrec NanoSecond64
-> ReadPrec [NanoSecond64]
-> Read 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
(Int -> NanoSecond64 -> ShowS)
-> (NanoSecond64 -> String)
-> ([NanoSecond64] -> ShowS)
-> Show NanoSecond64
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]
(NanoSecond64 -> NanoSecond64)
-> (NanoSecond64 -> NanoSecond64)
-> (Int -> NanoSecond64)
-> (NanoSecond64 -> Int)
-> (NanoSecond64 -> [NanoSecond64])
-> (NanoSecond64 -> NanoSecond64 -> [NanoSecond64])
-> (NanoSecond64 -> NanoSecond64 -> [NanoSecond64])
-> (NanoSecond64 -> NanoSecond64 -> NanoSecond64 -> [NanoSecond64])
-> Enum 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
NanoSecond64 -> NanoSecond64 -> Bounded NanoSecond64
forall a. a -> a -> Bounded a
maxBound :: NanoSecond64
$cmaxBound :: NanoSecond64
minBound :: NanoSecond64
$cminBound :: NanoSecond64
Bounded
, Integer -> NanoSecond64
NanoSecond64 -> NanoSecond64
NanoSecond64 -> NanoSecond64 -> NanoSecond64
(NanoSecond64 -> NanoSecond64 -> NanoSecond64)
-> (NanoSecond64 -> NanoSecond64 -> NanoSecond64)
-> (NanoSecond64 -> NanoSecond64 -> NanoSecond64)
-> (NanoSecond64 -> NanoSecond64)
-> (NanoSecond64 -> NanoSecond64)
-> (NanoSecond64 -> NanoSecond64)
-> (Integer -> NanoSecond64)
-> Num 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
Num NanoSecond64
-> Ord NanoSecond64
-> (NanoSecond64 -> Rational)
-> Real NanoSecond64
NanoSecond64 -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: NanoSecond64 -> Rational
$ctoRational :: NanoSecond64 -> Rational
$cp2Real :: Ord NanoSecond64
$cp1Real :: Num NanoSecond64
Real
, Enum NanoSecond64
Real NanoSecond64
Real NanoSecond64
-> Enum NanoSecond64
-> (NanoSecond64 -> NanoSecond64 -> NanoSecond64)
-> (NanoSecond64 -> NanoSecond64 -> NanoSecond64)
-> (NanoSecond64 -> NanoSecond64 -> NanoSecond64)
-> (NanoSecond64 -> NanoSecond64 -> NanoSecond64)
-> (NanoSecond64 -> NanoSecond64 -> (NanoSecond64, NanoSecond64))
-> (NanoSecond64 -> NanoSecond64 -> (NanoSecond64, NanoSecond64))
-> (NanoSecond64 -> Integer)
-> Integral 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
$cp2Integral :: Enum NanoSecond64
$cp1Integral :: Real NanoSecond64
Integral
, Eq NanoSecond64
Eq NanoSecond64
-> (NanoSecond64 -> NanoSecond64 -> Ordering)
-> (NanoSecond64 -> NanoSecond64 -> Bool)
-> (NanoSecond64 -> NanoSecond64 -> Bool)
-> (NanoSecond64 -> NanoSecond64 -> Bool)
-> (NanoSecond64 -> NanoSecond64 -> Bool)
-> (NanoSecond64 -> NanoSecond64 -> NanoSecond64)
-> (NanoSecond64 -> NanoSecond64 -> NanoSecond64)
-> Ord 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
$cp1Ord :: Eq NanoSecond64
Ord
, Addr# -> Int# -> NanoSecond64
Addr# -> Int# -> Int# -> NanoSecond64 -> State# s -> State# s
Addr# -> Int# -> State# s -> (# State# s, NanoSecond64 #)
Addr# -> Int# -> NanoSecond64 -> State# s -> State# s
ByteArray# -> Int# -> NanoSecond64
MutableByteArray# s
-> Int# -> State# s -> (# State# s, NanoSecond64 #)
MutableByteArray# s -> Int# -> NanoSecond64 -> State# s -> State# s
MutableByteArray# s
-> Int# -> Int# -> NanoSecond64 -> State# s -> State# s
NanoSecond64 -> Int#
(NanoSecond64 -> Int#)
-> (NanoSecond64 -> Int#)
-> (ByteArray# -> Int# -> NanoSecond64)
-> (forall s.
MutableByteArray# s
-> Int# -> State# s -> (# State# s, NanoSecond64 #))
-> (forall s.
MutableByteArray# s
-> Int# -> NanoSecond64 -> State# s -> State# s)
-> (forall s.
MutableByteArray# s
-> Int# -> Int# -> NanoSecond64 -> State# s -> State# s)
-> (Addr# -> Int# -> NanoSecond64)
-> (forall s.
Addr# -> Int# -> State# s -> (# State# s, NanoSecond64 #))
-> (forall s.
Addr# -> Int# -> NanoSecond64 -> State# s -> State# s)
-> (forall s.
Addr# -> Int# -> Int# -> NanoSecond64 -> State# s -> State# s)
-> Prim NanoSecond64
forall s.
Addr# -> Int# -> Int# -> NanoSecond64 -> State# s -> State# s
forall s. Addr# -> Int# -> State# s -> (# State# s, NanoSecond64 #)
forall s. Addr# -> Int# -> NanoSecond64 -> State# s -> State# s
forall s.
MutableByteArray# s
-> Int# -> Int# -> NanoSecond64 -> State# s -> State# s
forall s.
MutableByteArray# s
-> Int# -> State# s -> (# State# s, NanoSecond64 #)
forall s.
MutableByteArray# s -> Int# -> NanoSecond64 -> State# s -> State# s
forall a.
(a -> Int#)
-> (a -> Int#)
-> (ByteArray# -> Int# -> a)
-> (forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, a #))
-> (forall s.
MutableByteArray# s -> Int# -> a -> State# s -> State# s)
-> (forall s.
MutableByteArray# s -> Int# -> Int# -> a -> State# s -> State# s)
-> (Addr# -> Int# -> a)
-> (forall s. Addr# -> Int# -> State# s -> (# State# s, a #))
-> (forall s. Addr# -> Int# -> a -> State# s -> State# s)
-> (forall s. Addr# -> Int# -> Int# -> a -> State# s -> State# s)
-> Prim a
setOffAddr# :: Addr# -> Int# -> Int# -> NanoSecond64 -> State# s -> State# s
$csetOffAddr# :: forall s.
Addr# -> Int# -> Int# -> NanoSecond64 -> State# s -> State# s
writeOffAddr# :: Addr# -> Int# -> NanoSecond64 -> State# s -> State# s
$cwriteOffAddr# :: forall s. Addr# -> Int# -> NanoSecond64 -> State# s -> State# s
readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, NanoSecond64 #)
$creadOffAddr# :: forall s. Addr# -> Int# -> State# s -> (# State# s, NanoSecond64 #)
indexOffAddr# :: Addr# -> Int# -> NanoSecond64
$cindexOffAddr# :: Addr# -> Int# -> NanoSecond64
setByteArray# :: MutableByteArray# s
-> Int# -> Int# -> NanoSecond64 -> State# s -> State# s
$csetByteArray# :: forall s.
MutableByteArray# s
-> Int# -> Int# -> NanoSecond64 -> State# s -> State# s
writeByteArray# :: MutableByteArray# s -> Int# -> NanoSecond64 -> State# s -> State# s
$cwriteByteArray# :: forall s.
MutableByteArray# s -> Int# -> NanoSecond64 -> State# s -> State# s
readByteArray# :: MutableByteArray# s
-> Int# -> State# s -> (# State# s, NanoSecond64 #)
$creadByteArray# :: forall s.
MutableByteArray# s
-> Int# -> State# s -> (# State# s, NanoSecond64 #)
indexByteArray# :: ByteArray# -> Int# -> NanoSecond64
$cindexByteArray# :: ByteArray# -> Int# -> NanoSecond64
alignment# :: NanoSecond64 -> Int#
$calignment# :: NanoSecond64 -> Int#
sizeOf# :: NanoSecond64 -> Int#
$csizeOf# :: NanoSecond64 -> Int#
Prim
)
newtype MicroSecond64 = MicroSecond64 Int64
deriving ( MicroSecond64 -> MicroSecond64 -> Bool
(MicroSecond64 -> MicroSecond64 -> Bool)
-> (MicroSecond64 -> MicroSecond64 -> Bool) -> Eq MicroSecond64
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]
(Int -> ReadS MicroSecond64)
-> ReadS [MicroSecond64]
-> ReadPrec MicroSecond64
-> ReadPrec [MicroSecond64]
-> Read 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
(Int -> MicroSecond64 -> ShowS)
-> (MicroSecond64 -> String)
-> ([MicroSecond64] -> ShowS)
-> Show MicroSecond64
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]
(MicroSecond64 -> MicroSecond64)
-> (MicroSecond64 -> MicroSecond64)
-> (Int -> MicroSecond64)
-> (MicroSecond64 -> Int)
-> (MicroSecond64 -> [MicroSecond64])
-> (MicroSecond64 -> MicroSecond64 -> [MicroSecond64])
-> (MicroSecond64 -> MicroSecond64 -> [MicroSecond64])
-> (MicroSecond64
-> MicroSecond64 -> MicroSecond64 -> [MicroSecond64])
-> Enum 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
MicroSecond64 -> MicroSecond64 -> Bounded MicroSecond64
forall a. a -> a -> Bounded a
maxBound :: MicroSecond64
$cmaxBound :: MicroSecond64
minBound :: MicroSecond64
$cminBound :: MicroSecond64
Bounded
, Integer -> MicroSecond64
MicroSecond64 -> MicroSecond64
MicroSecond64 -> MicroSecond64 -> MicroSecond64
(MicroSecond64 -> MicroSecond64 -> MicroSecond64)
-> (MicroSecond64 -> MicroSecond64 -> MicroSecond64)
-> (MicroSecond64 -> MicroSecond64 -> MicroSecond64)
-> (MicroSecond64 -> MicroSecond64)
-> (MicroSecond64 -> MicroSecond64)
-> (MicroSecond64 -> MicroSecond64)
-> (Integer -> MicroSecond64)
-> Num 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
Num MicroSecond64
-> Ord MicroSecond64
-> (MicroSecond64 -> Rational)
-> Real MicroSecond64
MicroSecond64 -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: MicroSecond64 -> Rational
$ctoRational :: MicroSecond64 -> Rational
$cp2Real :: Ord MicroSecond64
$cp1Real :: Num MicroSecond64
Real
, Enum MicroSecond64
Real MicroSecond64
Real MicroSecond64
-> Enum MicroSecond64
-> (MicroSecond64 -> MicroSecond64 -> MicroSecond64)
-> (MicroSecond64 -> MicroSecond64 -> MicroSecond64)
-> (MicroSecond64 -> MicroSecond64 -> MicroSecond64)
-> (MicroSecond64 -> MicroSecond64 -> MicroSecond64)
-> (MicroSecond64
-> MicroSecond64 -> (MicroSecond64, MicroSecond64))
-> (MicroSecond64
-> MicroSecond64 -> (MicroSecond64, MicroSecond64))
-> (MicroSecond64 -> Integer)
-> Integral 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
$cp2Integral :: Enum MicroSecond64
$cp1Integral :: Real MicroSecond64
Integral
, Eq MicroSecond64
Eq MicroSecond64
-> (MicroSecond64 -> MicroSecond64 -> Ordering)
-> (MicroSecond64 -> MicroSecond64 -> Bool)
-> (MicroSecond64 -> MicroSecond64 -> Bool)
-> (MicroSecond64 -> MicroSecond64 -> Bool)
-> (MicroSecond64 -> MicroSecond64 -> Bool)
-> (MicroSecond64 -> MicroSecond64 -> MicroSecond64)
-> (MicroSecond64 -> MicroSecond64 -> MicroSecond64)
-> Ord 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
$cp1Ord :: Eq MicroSecond64
Ord
, Addr# -> Int# -> MicroSecond64
Addr# -> Int# -> Int# -> MicroSecond64 -> State# s -> State# s
Addr# -> Int# -> State# s -> (# State# s, MicroSecond64 #)
Addr# -> Int# -> MicroSecond64 -> State# s -> State# s
ByteArray# -> Int# -> MicroSecond64
MutableByteArray# s
-> Int# -> State# s -> (# State# s, MicroSecond64 #)
MutableByteArray# s
-> Int# -> MicroSecond64 -> State# s -> State# s
MutableByteArray# s
-> Int# -> Int# -> MicroSecond64 -> State# s -> State# s
MicroSecond64 -> Int#
(MicroSecond64 -> Int#)
-> (MicroSecond64 -> Int#)
-> (ByteArray# -> Int# -> MicroSecond64)
-> (forall s.
MutableByteArray# s
-> Int# -> State# s -> (# State# s, MicroSecond64 #))
-> (forall s.
MutableByteArray# s
-> Int# -> MicroSecond64 -> State# s -> State# s)
-> (forall s.
MutableByteArray# s
-> Int# -> Int# -> MicroSecond64 -> State# s -> State# s)
-> (Addr# -> Int# -> MicroSecond64)
-> (forall s.
Addr# -> Int# -> State# s -> (# State# s, MicroSecond64 #))
-> (forall s.
Addr# -> Int# -> MicroSecond64 -> State# s -> State# s)
-> (forall s.
Addr# -> Int# -> Int# -> MicroSecond64 -> State# s -> State# s)
-> Prim MicroSecond64
forall s.
Addr# -> Int# -> Int# -> MicroSecond64 -> State# s -> State# s
forall s.
Addr# -> Int# -> State# s -> (# State# s, MicroSecond64 #)
forall s. Addr# -> Int# -> MicroSecond64 -> State# s -> State# s
forall s.
MutableByteArray# s
-> Int# -> Int# -> MicroSecond64 -> State# s -> State# s
forall s.
MutableByteArray# s
-> Int# -> State# s -> (# State# s, MicroSecond64 #)
forall s.
MutableByteArray# s
-> Int# -> MicroSecond64 -> State# s -> State# s
forall a.
(a -> Int#)
-> (a -> Int#)
-> (ByteArray# -> Int# -> a)
-> (forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, a #))
-> (forall s.
MutableByteArray# s -> Int# -> a -> State# s -> State# s)
-> (forall s.
MutableByteArray# s -> Int# -> Int# -> a -> State# s -> State# s)
-> (Addr# -> Int# -> a)
-> (forall s. Addr# -> Int# -> State# s -> (# State# s, a #))
-> (forall s. Addr# -> Int# -> a -> State# s -> State# s)
-> (forall s. Addr# -> Int# -> Int# -> a -> State# s -> State# s)
-> Prim a
setOffAddr# :: Addr# -> Int# -> Int# -> MicroSecond64 -> State# s -> State# s
$csetOffAddr# :: forall s.
Addr# -> Int# -> Int# -> MicroSecond64 -> State# s -> State# s
writeOffAddr# :: Addr# -> Int# -> MicroSecond64 -> State# s -> State# s
$cwriteOffAddr# :: forall s. Addr# -> Int# -> MicroSecond64 -> State# s -> State# s
readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, MicroSecond64 #)
$creadOffAddr# :: forall s.
Addr# -> Int# -> State# s -> (# State# s, MicroSecond64 #)
indexOffAddr# :: Addr# -> Int# -> MicroSecond64
$cindexOffAddr# :: Addr# -> Int# -> MicroSecond64
setByteArray# :: MutableByteArray# s
-> Int# -> Int# -> MicroSecond64 -> State# s -> State# s
$csetByteArray# :: forall s.
MutableByteArray# s
-> Int# -> Int# -> MicroSecond64 -> State# s -> State# s
writeByteArray# :: MutableByteArray# s
-> Int# -> MicroSecond64 -> State# s -> State# s
$cwriteByteArray# :: forall s.
MutableByteArray# s
-> Int# -> MicroSecond64 -> State# s -> State# s
readByteArray# :: MutableByteArray# s
-> Int# -> State# s -> (# State# s, MicroSecond64 #)
$creadByteArray# :: forall s.
MutableByteArray# s
-> Int# -> State# s -> (# State# s, MicroSecond64 #)
indexByteArray# :: ByteArray# -> Int# -> MicroSecond64
$cindexByteArray# :: ByteArray# -> Int# -> MicroSecond64
alignment# :: MicroSecond64 -> Int#
$calignment# :: MicroSecond64 -> Int#
sizeOf# :: MicroSecond64 -> Int#
$csizeOf# :: MicroSecond64 -> Int#
Prim
)
newtype MilliSecond64 = MilliSecond64 Int64
deriving ( MilliSecond64 -> MilliSecond64 -> Bool
(MilliSecond64 -> MilliSecond64 -> Bool)
-> (MilliSecond64 -> MilliSecond64 -> Bool) -> Eq MilliSecond64
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]
(Int -> ReadS MilliSecond64)
-> ReadS [MilliSecond64]
-> ReadPrec MilliSecond64
-> ReadPrec [MilliSecond64]
-> Read 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
(Int -> MilliSecond64 -> ShowS)
-> (MilliSecond64 -> String)
-> ([MilliSecond64] -> ShowS)
-> Show MilliSecond64
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]
(MilliSecond64 -> MilliSecond64)
-> (MilliSecond64 -> MilliSecond64)
-> (Int -> MilliSecond64)
-> (MilliSecond64 -> Int)
-> (MilliSecond64 -> [MilliSecond64])
-> (MilliSecond64 -> MilliSecond64 -> [MilliSecond64])
-> (MilliSecond64 -> MilliSecond64 -> [MilliSecond64])
-> (MilliSecond64
-> MilliSecond64 -> MilliSecond64 -> [MilliSecond64])
-> Enum 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
MilliSecond64 -> MilliSecond64 -> Bounded MilliSecond64
forall a. a -> a -> Bounded a
maxBound :: MilliSecond64
$cmaxBound :: MilliSecond64
minBound :: MilliSecond64
$cminBound :: MilliSecond64
Bounded
, Integer -> MilliSecond64
MilliSecond64 -> MilliSecond64
MilliSecond64 -> MilliSecond64 -> MilliSecond64
(MilliSecond64 -> MilliSecond64 -> MilliSecond64)
-> (MilliSecond64 -> MilliSecond64 -> MilliSecond64)
-> (MilliSecond64 -> MilliSecond64 -> MilliSecond64)
-> (MilliSecond64 -> MilliSecond64)
-> (MilliSecond64 -> MilliSecond64)
-> (MilliSecond64 -> MilliSecond64)
-> (Integer -> MilliSecond64)
-> Num 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
Num MilliSecond64
-> Ord MilliSecond64
-> (MilliSecond64 -> Rational)
-> Real MilliSecond64
MilliSecond64 -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: MilliSecond64 -> Rational
$ctoRational :: MilliSecond64 -> Rational
$cp2Real :: Ord MilliSecond64
$cp1Real :: Num MilliSecond64
Real
, Enum MilliSecond64
Real MilliSecond64
Real MilliSecond64
-> Enum MilliSecond64
-> (MilliSecond64 -> MilliSecond64 -> MilliSecond64)
-> (MilliSecond64 -> MilliSecond64 -> MilliSecond64)
-> (MilliSecond64 -> MilliSecond64 -> MilliSecond64)
-> (MilliSecond64 -> MilliSecond64 -> MilliSecond64)
-> (MilliSecond64
-> MilliSecond64 -> (MilliSecond64, MilliSecond64))
-> (MilliSecond64
-> MilliSecond64 -> (MilliSecond64, MilliSecond64))
-> (MilliSecond64 -> Integer)
-> Integral 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
$cp2Integral :: Enum MilliSecond64
$cp1Integral :: Real MilliSecond64
Integral
, Eq MilliSecond64
Eq MilliSecond64
-> (MilliSecond64 -> MilliSecond64 -> Ordering)
-> (MilliSecond64 -> MilliSecond64 -> Bool)
-> (MilliSecond64 -> MilliSecond64 -> Bool)
-> (MilliSecond64 -> MilliSecond64 -> Bool)
-> (MilliSecond64 -> MilliSecond64 -> Bool)
-> (MilliSecond64 -> MilliSecond64 -> MilliSecond64)
-> (MilliSecond64 -> MilliSecond64 -> MilliSecond64)
-> Ord 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
$cp1Ord :: Eq MilliSecond64
Ord
, Addr# -> Int# -> MilliSecond64
Addr# -> Int# -> Int# -> MilliSecond64 -> State# s -> State# s
Addr# -> Int# -> State# s -> (# State# s, MilliSecond64 #)
Addr# -> Int# -> MilliSecond64 -> State# s -> State# s
ByteArray# -> Int# -> MilliSecond64
MutableByteArray# s
-> Int# -> State# s -> (# State# s, MilliSecond64 #)
MutableByteArray# s
-> Int# -> MilliSecond64 -> State# s -> State# s
MutableByteArray# s
-> Int# -> Int# -> MilliSecond64 -> State# s -> State# s
MilliSecond64 -> Int#
(MilliSecond64 -> Int#)
-> (MilliSecond64 -> Int#)
-> (ByteArray# -> Int# -> MilliSecond64)
-> (forall s.
MutableByteArray# s
-> Int# -> State# s -> (# State# s, MilliSecond64 #))
-> (forall s.
MutableByteArray# s
-> Int# -> MilliSecond64 -> State# s -> State# s)
-> (forall s.
MutableByteArray# s
-> Int# -> Int# -> MilliSecond64 -> State# s -> State# s)
-> (Addr# -> Int# -> MilliSecond64)
-> (forall s.
Addr# -> Int# -> State# s -> (# State# s, MilliSecond64 #))
-> (forall s.
Addr# -> Int# -> MilliSecond64 -> State# s -> State# s)
-> (forall s.
Addr# -> Int# -> Int# -> MilliSecond64 -> State# s -> State# s)
-> Prim MilliSecond64
forall s.
Addr# -> Int# -> Int# -> MilliSecond64 -> State# s -> State# s
forall s.
Addr# -> Int# -> State# s -> (# State# s, MilliSecond64 #)
forall s. Addr# -> Int# -> MilliSecond64 -> State# s -> State# s
forall s.
MutableByteArray# s
-> Int# -> Int# -> MilliSecond64 -> State# s -> State# s
forall s.
MutableByteArray# s
-> Int# -> State# s -> (# State# s, MilliSecond64 #)
forall s.
MutableByteArray# s
-> Int# -> MilliSecond64 -> State# s -> State# s
forall a.
(a -> Int#)
-> (a -> Int#)
-> (ByteArray# -> Int# -> a)
-> (forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, a #))
-> (forall s.
MutableByteArray# s -> Int# -> a -> State# s -> State# s)
-> (forall s.
MutableByteArray# s -> Int# -> Int# -> a -> State# s -> State# s)
-> (Addr# -> Int# -> a)
-> (forall s. Addr# -> Int# -> State# s -> (# State# s, a #))
-> (forall s. Addr# -> Int# -> a -> State# s -> State# s)
-> (forall s. Addr# -> Int# -> Int# -> a -> State# s -> State# s)
-> Prim a
setOffAddr# :: Addr# -> Int# -> Int# -> MilliSecond64 -> State# s -> State# s
$csetOffAddr# :: forall s.
Addr# -> Int# -> Int# -> MilliSecond64 -> State# s -> State# s
writeOffAddr# :: Addr# -> Int# -> MilliSecond64 -> State# s -> State# s
$cwriteOffAddr# :: forall s. Addr# -> Int# -> MilliSecond64 -> State# s -> State# s
readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, MilliSecond64 #)
$creadOffAddr# :: forall s.
Addr# -> Int# -> State# s -> (# State# s, MilliSecond64 #)
indexOffAddr# :: Addr# -> Int# -> MilliSecond64
$cindexOffAddr# :: Addr# -> Int# -> MilliSecond64
setByteArray# :: MutableByteArray# s
-> Int# -> Int# -> MilliSecond64 -> State# s -> State# s
$csetByteArray# :: forall s.
MutableByteArray# s
-> Int# -> Int# -> MilliSecond64 -> State# s -> State# s
writeByteArray# :: MutableByteArray# s
-> Int# -> MilliSecond64 -> State# s -> State# s
$cwriteByteArray# :: forall s.
MutableByteArray# s
-> Int# -> MilliSecond64 -> State# s -> State# s
readByteArray# :: MutableByteArray# s
-> Int# -> State# s -> (# State# s, MilliSecond64 #)
$creadByteArray# :: forall s.
MutableByteArray# s
-> Int# -> State# s -> (# State# s, MilliSecond64 #)
indexByteArray# :: ByteArray# -> Int# -> MilliSecond64
$cindexByteArray# :: ByteArray# -> Int# -> MilliSecond64
alignment# :: MilliSecond64 -> Int#
$calignment# :: MilliSecond64 -> Int#
sizeOf# :: MilliSecond64 -> Int#
$csizeOf# :: MilliSecond64 -> Int#
Prim
)
class TimeUnit a where
toTimeSpec :: a -> TimeSpec
fromTimeSpec :: TimeSpec -> a
class TimeUnit64 a where
toNanoSecond64 :: a -> NanoSecond64
fromNanoSecond64 :: NanoSecond64 -> a
instance TimeUnit TimeSpec where
toTimeSpec :: TimeSpec -> TimeSpec
toTimeSpec = TimeSpec -> TimeSpec
forall a. a -> a
id
fromTimeSpec :: TimeSpec -> TimeSpec
fromTimeSpec = TimeSpec -> TimeSpec
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 Int64 -> Int64 -> (Int64, Int64)
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 (Int64 -> NanoSecond64) -> Int64 -> NanoSecond64
forall a b. (a -> b) -> a -> b
$ Int64
s Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int64
tenPower9 Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+ Int64
ns
instance TimeUnit64 NanoSecond64 where
{-# INLINE toNanoSecond64 #-}
toNanoSecond64 :: NanoSecond64 -> NanoSecond64
toNanoSecond64 = NanoSecond64 -> NanoSecond64
forall a. a -> a
id
{-# INLINE fromNanoSecond64 #-}
fromNanoSecond64 :: NanoSecond64 -> NanoSecond64
fromNanoSecond64 = NanoSecond64 -> NanoSecond64
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 Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int64
tenPower3)
where (Int64
s, Int64
us) = Int64
t Int64 -> Int64 -> (Int64, Int64)
forall a. Integral a => a -> a -> (a, a)
`divMod` Int64
tenPower6
{-# INLINE fromTimeSpec #-}
fromTimeSpec :: TimeSpec -> MicroSecond64
fromTimeSpec (TimeSpec Int64
s Int64
ns) =
Int64 -> MicroSecond64
MicroSecond64 (Int64 -> MicroSecond64) -> Int64 -> MicroSecond64
forall a b. (a -> b) -> a -> b
$ Int64
s Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int64
tenPower6 Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+ (Int64
ns Int64 -> Int64 -> Int64
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 (Int64 -> NanoSecond64) -> Int64 -> NanoSecond64
forall a b. (a -> b) -> a -> b
$ Int64
us Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int64
tenPower3
{-# INLINE fromNanoSecond64 #-}
fromNanoSecond64 :: NanoSecond64 -> MicroSecond64
fromNanoSecond64 (NanoSecond64 Int64
ns) = Int64 -> MicroSecond64
MicroSecond64 (Int64 -> MicroSecond64) -> Int64 -> MicroSecond64
forall a b. (a -> b) -> a -> b
$ Int64
ns Int64 -> Int64 -> Int64
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 Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int64
tenPower6)
where (Int64
s, Int64
ms) = Int64
t Int64 -> Int64 -> (Int64, Int64)
forall a. Integral a => a -> a -> (a, a)
`divMod` Int64
tenPower3
{-# INLINE fromTimeSpec #-}
fromTimeSpec :: TimeSpec -> MilliSecond64
fromTimeSpec (TimeSpec Int64
s Int64
ns) =
Int64 -> MilliSecond64
MilliSecond64 (Int64 -> MilliSecond64) -> Int64 -> MilliSecond64
forall a b. (a -> b) -> a -> b
$ Int64
s Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int64
tenPower3 Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+ (Int64
ns Int64 -> Int64 -> Int64
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 (Int64 -> NanoSecond64) -> Int64 -> NanoSecond64
forall a b. (a -> b) -> a -> b
$ Int64
ms Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int64
tenPower6
{-# INLINE fromNanoSecond64 #-}
fromNanoSecond64 :: NanoSecond64 -> MilliSecond64
fromNanoSecond64 (NanoSecond64 Int64
ns) = Int64 -> MilliSecond64
MilliSecond64 (Int64 -> MilliSecond64) -> Int64 -> MilliSecond64
forall a b. (a -> b) -> a -> b
$ Int64
ns Int64 -> Int64 -> Int64
forall a. Integral a => a -> a -> a
`div` Int64
tenPower6
newtype AbsTime = AbsTime TimeSpec
deriving (AbsTime -> AbsTime -> Bool
(AbsTime -> AbsTime -> Bool)
-> (AbsTime -> AbsTime -> Bool) -> Eq AbsTime
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
Eq AbsTime
-> (AbsTime -> AbsTime -> Ordering)
-> (AbsTime -> AbsTime -> Bool)
-> (AbsTime -> AbsTime -> Bool)
-> (AbsTime -> AbsTime -> Bool)
-> (AbsTime -> AbsTime -> Bool)
-> (AbsTime -> AbsTime -> AbsTime)
-> (AbsTime -> AbsTime -> AbsTime)
-> Ord 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
$cp1Ord :: Eq AbsTime
Ord, Int -> AbsTime -> ShowS
[AbsTime] -> ShowS
AbsTime -> String
(Int -> AbsTime -> ShowS)
-> (AbsTime -> String) -> ([AbsTime] -> ShowS) -> Show AbsTime
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)
{-# INLINE_NORMAL toAbsTime #-}
toAbsTime :: TimeUnit a => a -> AbsTime
toAbsTime :: a -> AbsTime
toAbsTime = TimeSpec -> AbsTime
AbsTime (TimeSpec -> AbsTime) -> (a -> TimeSpec) -> a -> AbsTime
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> TimeSpec
forall a. TimeUnit a => a -> TimeSpec
toTimeSpec
{-# INLINE_NORMAL fromAbsTime #-}
fromAbsTime :: TimeUnit a => AbsTime -> a
fromAbsTime :: AbsTime -> a
fromAbsTime (AbsTime TimeSpec
t) = TimeSpec -> a
forall a. TimeUnit a => TimeSpec -> a
fromTimeSpec TimeSpec
t
{-# RULES "fromAbsTime/toAbsTime" forall a. toAbsTime (fromAbsTime a) = a #-}
{-# RULES "toAbsTime/fromAbsTime" forall a. fromAbsTime (toAbsTime a) = a #-}
newtype RelTime64 = RelTime64 NanoSecond64
deriving ( RelTime64 -> RelTime64 -> Bool
(RelTime64 -> RelTime64 -> Bool)
-> (RelTime64 -> RelTime64 -> Bool) -> Eq RelTime64
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]
(Int -> ReadS RelTime64)
-> ReadS [RelTime64]
-> ReadPrec RelTime64
-> ReadPrec [RelTime64]
-> Read 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
(Int -> RelTime64 -> ShowS)
-> (RelTime64 -> String)
-> ([RelTime64] -> ShowS)
-> Show RelTime64
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]
(RelTime64 -> RelTime64)
-> (RelTime64 -> RelTime64)
-> (Int -> RelTime64)
-> (RelTime64 -> Int)
-> (RelTime64 -> [RelTime64])
-> (RelTime64 -> RelTime64 -> [RelTime64])
-> (RelTime64 -> RelTime64 -> [RelTime64])
-> (RelTime64 -> RelTime64 -> RelTime64 -> [RelTime64])
-> Enum 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
RelTime64 -> RelTime64 -> Bounded RelTime64
forall a. a -> a -> Bounded a
maxBound :: RelTime64
$cmaxBound :: RelTime64
minBound :: RelTime64
$cminBound :: RelTime64
Bounded
, Integer -> RelTime64
RelTime64 -> RelTime64
RelTime64 -> RelTime64 -> RelTime64
(RelTime64 -> RelTime64 -> RelTime64)
-> (RelTime64 -> RelTime64 -> RelTime64)
-> (RelTime64 -> RelTime64 -> RelTime64)
-> (RelTime64 -> RelTime64)
-> (RelTime64 -> RelTime64)
-> (RelTime64 -> RelTime64)
-> (Integer -> RelTime64)
-> Num 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
Num RelTime64
-> Ord RelTime64 -> (RelTime64 -> Rational) -> Real RelTime64
RelTime64 -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: RelTime64 -> Rational
$ctoRational :: RelTime64 -> Rational
$cp2Real :: Ord RelTime64
$cp1Real :: Num RelTime64
Real
, Enum RelTime64
Real RelTime64
Real RelTime64
-> Enum RelTime64
-> (RelTime64 -> RelTime64 -> RelTime64)
-> (RelTime64 -> RelTime64 -> RelTime64)
-> (RelTime64 -> RelTime64 -> RelTime64)
-> (RelTime64 -> RelTime64 -> RelTime64)
-> (RelTime64 -> RelTime64 -> (RelTime64, RelTime64))
-> (RelTime64 -> RelTime64 -> (RelTime64, RelTime64))
-> (RelTime64 -> Integer)
-> Integral 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
$cp2Integral :: Enum RelTime64
$cp1Integral :: Real RelTime64
Integral
, Eq RelTime64
Eq RelTime64
-> (RelTime64 -> RelTime64 -> Ordering)
-> (RelTime64 -> RelTime64 -> Bool)
-> (RelTime64 -> RelTime64 -> Bool)
-> (RelTime64 -> RelTime64 -> Bool)
-> (RelTime64 -> RelTime64 -> Bool)
-> (RelTime64 -> RelTime64 -> RelTime64)
-> (RelTime64 -> RelTime64 -> RelTime64)
-> Ord 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
$cp1Ord :: Eq RelTime64
Ord
)
{-# INLINE_NORMAL toRelTime64 #-}
toRelTime64 :: TimeUnit64 a => a -> RelTime64
toRelTime64 :: a -> RelTime64
toRelTime64 = NanoSecond64 -> RelTime64
RelTime64 (NanoSecond64 -> RelTime64)
-> (a -> NanoSecond64) -> a -> RelTime64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> NanoSecond64
forall a. TimeUnit64 a => a -> NanoSecond64
toNanoSecond64
{-# INLINE_NORMAL fromRelTime64 #-}
fromRelTime64 :: TimeUnit64 a => RelTime64 -> a
fromRelTime64 :: RelTime64 -> a
fromRelTime64 (RelTime64 NanoSecond64
t) = NanoSecond64 -> a
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 #-}
{-# 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 (NanoSecond64 -> RelTime64) -> NanoSecond64 -> RelTime64
forall a b. (a -> b) -> a -> b
$ Int64 -> NanoSecond64
NanoSecond64 (Int64 -> NanoSecond64) -> Int64 -> NanoSecond64
forall a b. (a -> b) -> a -> b
$ ((Int64
s1 Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
- Int64
s2) Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int64
tenPower9) Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+ (Int64
ns1 Int64 -> Int64 -> Int64
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 (TimeSpec -> AbsTime) -> TimeSpec -> AbsTime
forall a b. (a -> b) -> a -> b
$ Int64 -> Int64 -> TimeSpec
TimeSpec (Int64
s1 Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+ Int64
s) Int64
ns
where (Int64
s, Int64
ns) = (Int64
ns1 Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+ Int64
ns2) Int64 -> Int64 -> (Int64, Int64)
forall a. Integral a => a -> a -> (a, a)
`divMod` Int64
tenPower9
newtype RelTime = RelTime TimeSpec
deriving ( RelTime -> RelTime -> Bool
(RelTime -> RelTime -> Bool)
-> (RelTime -> RelTime -> Bool) -> Eq RelTime
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]
(Int -> ReadS RelTime)
-> ReadS [RelTime]
-> ReadPrec RelTime
-> ReadPrec [RelTime]
-> Read 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
(Int -> RelTime -> ShowS)
-> (RelTime -> String) -> ([RelTime] -> ShowS) -> Show RelTime
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
, Integer -> RelTime
RelTime -> RelTime
RelTime -> RelTime -> RelTime
(RelTime -> RelTime -> RelTime)
-> (RelTime -> RelTime -> RelTime)
-> (RelTime -> RelTime -> RelTime)
-> (RelTime -> RelTime)
-> (RelTime -> RelTime)
-> (RelTime -> RelTime)
-> (Integer -> RelTime)
-> Num 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
, Eq RelTime
Eq RelTime
-> (RelTime -> RelTime -> Ordering)
-> (RelTime -> RelTime -> Bool)
-> (RelTime -> RelTime -> Bool)
-> (RelTime -> RelTime -> Bool)
-> (RelTime -> RelTime -> Bool)
-> (RelTime -> RelTime -> RelTime)
-> (RelTime -> RelTime -> RelTime)
-> Ord 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
$cp1Ord :: Eq RelTime
Ord
)
{-# INLINE_NORMAL toRelTime #-}
toRelTime :: TimeUnit a => a -> RelTime
toRelTime :: a -> RelTime
toRelTime = TimeSpec -> RelTime
RelTime (TimeSpec -> RelTime) -> (a -> TimeSpec) -> a -> RelTime
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> TimeSpec
forall a. TimeUnit a => a -> TimeSpec
toTimeSpec
{-# INLINE_NORMAL fromRelTime #-}
fromRelTime :: TimeUnit a => RelTime -> a
fromRelTime :: RelTime -> a
fromRelTime (RelTime TimeSpec
t) = TimeSpec -> a
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 #-}
{-# INLINE diffAbsTime #-}
diffAbsTime :: AbsTime -> AbsTime -> RelTime
diffAbsTime :: AbsTime -> AbsTime -> RelTime
diffAbsTime (AbsTime TimeSpec
t1) (AbsTime TimeSpec
t2) = TimeSpec -> RelTime
RelTime (TimeSpec
t1 TimeSpec -> TimeSpec -> TimeSpec
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 (TimeSpec -> AbsTime) -> TimeSpec -> AbsTime
forall a b. (a -> b) -> a -> b
$ TimeSpec
t1 TimeSpec -> TimeSpec -> TimeSpec
forall a. Num a => a -> a -> a
+ TimeSpec
t2
showNanoSecond64 :: NanoSecond64 -> String
showNanoSecond64 :: NanoSecond64 -> String
showNanoSecond64 time :: NanoSecond64
time@(NanoSecond64 Int64
ns)
| NanoSecond64
time NanoSecond64 -> NanoSecond64 -> Bool
forall a. Ord a => a -> a -> Bool
< NanoSecond64
0 = Char
'-' Char -> ShowS
forall a. a -> [a] -> [a]
: NanoSecond64 -> String
showNanoSecond64 (-NanoSecond64
time)
| Int64
ns Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
< Int64
1000 = Int64 -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
ns Double -> ShowS
forall p. PrintfType p => Double -> String -> p
`with` String
"ns"
#ifdef mingw32_HOST_OS
| ns < 1000000 = (fromIntegral ns / 1000) `with` "us"
#else
| Int64
ns Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
< Int64
1000000 = (Int64 -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
ns Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
1000) Double -> ShowS
forall p. PrintfType p => Double -> String -> p
`with` String
"μs"
#endif
| Int64
ns Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
< Int64
1000000000 = (Int64 -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
ns Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
1000000) Double -> ShowS
forall p. PrintfType p => Double -> String -> p
`with` String
"ms"
| Int64
ns Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
< (Int64
60 Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int64
1000000000) = (Int64 -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
ns Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
1000000000) Double -> ShowS
forall p. PrintfType p => Double -> String -> p
`with` String
"s"
| Int64
ns Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
< (Int64
60 Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int64
60 Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int64
1000000000) =
(Int64 -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
ns Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ (Double
60 Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
1000000000)) Double -> ShowS
forall p. PrintfType p => Double -> String -> p
`with` String
"min"
| Int64
ns Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
< (Int64
24 Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int64
60 Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int64
60 Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int64
1000000000) =
(Int64 -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
ns Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ (Double
60 Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
60 Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
1000000000)) Double -> ShowS
forall p. PrintfType p => Double -> String -> p
`with` String
"hr"
| Int64
ns Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
< (Int64
365 Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int64
24 Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int64
60 Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int64
60 Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int64
1000000000) =
(Int64 -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
ns Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ (Double
24 Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
60 Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
60 Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
1000000000)) Double -> ShowS
forall p. PrintfType p => Double -> String -> p
`with` String
"days"
| Bool
otherwise =
(Int64 -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
ns Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ (Double
365 Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
24 Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
60 Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
60 Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
1000000000)) Double -> ShowS
forall p. PrintfType p => Double -> String -> p
`with` String
"years"
where with :: Double -> String -> p
with (Double
t :: Double) (String
u :: String)
| Double
t Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
>= Double
1e9 = String -> Double -> String -> p
forall r. PrintfType r => String -> r
printf String
"%.4g %s" Double
t String
u
| Double
t Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
>= Double
1e3 = String -> Double -> String -> p
forall r. PrintfType r => String -> r
printf String
"%.0f %s" Double
t String
u
| Double
t Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
>= Double
1e2 = String -> Double -> String -> p
forall r. PrintfType r => String -> r
printf String
"%.1f %s" Double
t String
u
| Double
t Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
>= Double
1e1 = String -> Double -> String -> p
forall r. PrintfType r => String -> r
printf String
"%.2f %s" Double
t String
u
| Bool
otherwise = String -> Double -> String -> p
forall r. PrintfType r => String -> r
printf String
"%.3f %s" Double
t String
u
showRelTime64 :: RelTime64 -> String
showRelTime64 :: RelTime64 -> String
showRelTime64 = NanoSecond64 -> String
showNanoSecond64 (NanoSecond64 -> String)
-> (RelTime64 -> NanoSecond64) -> RelTime64 -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RelTime64 -> NanoSecond64
forall a. TimeUnit64 a => RelTime64 -> a
fromRelTime64