{-# LINE 1 "src/Streamly/Internal/Data/Time/TimeSpec.hsc" #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# OPTIONS_GHC -Wno-identities #-}
{-# LINE 7 "src/Streamly/Internal/Data/Time/TimeSpec.hsc" #-}
{-# LINE 9 "src/Streamly/Internal/Data/Time/TimeSpec.hsc" #-}
module Streamly.Internal.Data.Time.TimeSpec
(
TimeSpec(..)
)
where
import Data.Int (Int64)
{-# LINE 32 "src/Streamly/Internal/Data/Time/TimeSpec.hsc" #-}
import Foreign.Storable (Storable(..), peek)
{-# LINE 37 "src/Streamly/Internal/Data/Time/TimeSpec.hsc" #-}
{-# INLINE tenPower9 #-}
tenPower9 :: Int64
tenPower9 :: Int64
tenPower9 = Int64
1000000000
data TimeSpec = TimeSpec
{ TimeSpec -> Int64
sec :: {-# UNPACK #-} !Int64
, TimeSpec -> Int64
nsec :: {-# UNPACK #-} !Int64
} deriving (TimeSpec -> TimeSpec -> Bool
(TimeSpec -> TimeSpec -> Bool)
-> (TimeSpec -> TimeSpec -> Bool) -> Eq TimeSpec
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TimeSpec -> TimeSpec -> Bool
$c/= :: TimeSpec -> TimeSpec -> Bool
== :: TimeSpec -> TimeSpec -> Bool
$c== :: TimeSpec -> TimeSpec -> Bool
Eq, ReadPrec [TimeSpec]
ReadPrec TimeSpec
Int -> ReadS TimeSpec
ReadS [TimeSpec]
(Int -> ReadS TimeSpec)
-> ReadS [TimeSpec]
-> ReadPrec TimeSpec
-> ReadPrec [TimeSpec]
-> Read TimeSpec
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TimeSpec]
$creadListPrec :: ReadPrec [TimeSpec]
readPrec :: ReadPrec TimeSpec
$creadPrec :: ReadPrec TimeSpec
readList :: ReadS [TimeSpec]
$creadList :: ReadS [TimeSpec]
readsPrec :: Int -> ReadS TimeSpec
$creadsPrec :: Int -> ReadS TimeSpec
Read, Int -> TimeSpec -> ShowS
[TimeSpec] -> ShowS
TimeSpec -> String
(Int -> TimeSpec -> ShowS)
-> (TimeSpec -> String) -> ([TimeSpec] -> ShowS) -> Show TimeSpec
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TimeSpec] -> ShowS
$cshowList :: [TimeSpec] -> ShowS
show :: TimeSpec -> String
$cshow :: TimeSpec -> String
showsPrec :: Int -> TimeSpec -> ShowS
$cshowsPrec :: Int -> TimeSpec -> ShowS
Show)
instance Ord TimeSpec where
compare :: TimeSpec -> TimeSpec -> Ordering
compare (TimeSpec Int64
s1 Int64
ns1) (TimeSpec Int64
s2 Int64
ns2) =
if Int64
s1 Int64 -> Int64 -> Bool
forall a. Eq a => a -> a -> Bool
== Int64
s2
then Int64 -> Int64 -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Int64
ns1 Int64
ns2
else Int64 -> Int64 -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Int64
s1 Int64
s2
{-# INLINE addWithOverflow #-}
addWithOverflow :: TimeSpec -> TimeSpec -> TimeSpec
addWithOverflow :: TimeSpec -> TimeSpec -> TimeSpec
addWithOverflow (TimeSpec Int64
s1 Int64
ns1) (TimeSpec Int64
s2 Int64
ns2) =
let nsum :: Int64
nsum = Int64
ns1 Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+ Int64
ns2
(Int64
s', Int64
ns) = if Int64
nsum Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
> Int64
tenPower9 Bool -> Bool -> Bool
|| Int64
nsum Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
< Int64 -> Int64
forall a. Num a => a -> a
negate Int64
tenPower9
then Int64
nsum Int64 -> Int64 -> (Int64, Int64)
forall a. Integral a => a -> a -> (a, a)
`divMod` Int64
tenPower9
else (Int64
0, Int64
nsum)
in Int64 -> Int64 -> TimeSpec
TimeSpec (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
s') Int64
ns
{-# INLINE adjustSign #-}
adjustSign :: TimeSpec -> TimeSpec
adjustSign :: TimeSpec -> TimeSpec
adjustSign t :: TimeSpec
t@(TimeSpec Int64
s Int64
ns)
| Int64
s Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
> Int64
0 Bool -> Bool -> Bool
&& Int64
ns Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
< Int64
0 = Int64 -> Int64 -> TimeSpec
TimeSpec (Int64
s Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
- Int64
1) (Int64
ns Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+ Int64
tenPower9)
| Int64
s Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
< Int64
0 Bool -> Bool -> Bool
&& Int64
ns Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
> Int64
0 = Int64 -> Int64 -> TimeSpec
TimeSpec (Int64
s Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+ Int64
1) (Int64
ns Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
- Int64
tenPower9)
| Bool
otherwise = TimeSpec
t
{-# INLINE timeSpecToInteger #-}
timeSpecToInteger :: TimeSpec -> Integer
timeSpecToInteger :: TimeSpec -> Integer
timeSpecToInteger (TimeSpec Int64
s Int64
ns) = Int64 -> Integer
forall a. Integral a => a -> Integer
toInteger (Int64 -> Integer) -> Int64 -> Integer
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 Num TimeSpec where
{-# INLINE (+) #-}
TimeSpec
t1 + :: TimeSpec -> TimeSpec -> TimeSpec
+ TimeSpec
t2 = TimeSpec -> TimeSpec
adjustSign (TimeSpec -> TimeSpec -> TimeSpec
addWithOverflow TimeSpec
t1 TimeSpec
t2)
{-# INLINE (-) #-}
TimeSpec
t1 - :: TimeSpec -> TimeSpec -> TimeSpec
- TimeSpec
t2 = TimeSpec
t1 TimeSpec -> TimeSpec -> TimeSpec
forall a. Num a => a -> a -> a
+ TimeSpec -> TimeSpec
forall a. Num a => a -> a
negate TimeSpec
t2
TimeSpec
t1 * :: TimeSpec -> TimeSpec -> TimeSpec
* TimeSpec
t2 = Integer -> TimeSpec
forall a. Num a => Integer -> a
fromInteger (Integer -> TimeSpec) -> Integer -> TimeSpec
forall a b. (a -> b) -> a -> b
$ TimeSpec -> Integer
timeSpecToInteger TimeSpec
t1 Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* TimeSpec -> Integer
timeSpecToInteger TimeSpec
t2
{-# INLINE negate #-}
negate :: TimeSpec -> TimeSpec
negate (TimeSpec Int64
s Int64
ns) = Int64 -> Int64 -> TimeSpec
TimeSpec (Int64 -> Int64
forall a. Num a => a -> a
negate Int64
s) (Int64 -> Int64
forall a. Num a => a -> a
negate Int64
ns)
{-# INLINE abs #-}
abs :: TimeSpec -> TimeSpec
abs (TimeSpec Int64
s Int64
ns) = Int64 -> Int64 -> TimeSpec
TimeSpec (Int64 -> Int64
forall a. Num a => a -> a
abs Int64
s) (Int64 -> Int64
forall a. Num a => a -> a
abs Int64
ns)
{-# INLINE signum #-}
signum :: TimeSpec -> TimeSpec
signum (TimeSpec Int64
s Int64
ns) | Int64
s Int64 -> Int64 -> Bool
forall a. Eq a => a -> a -> Bool
== Int64
0 = Int64 -> Int64 -> TimeSpec
TimeSpec (Int64 -> Int64
forall a. Num a => a -> a
signum Int64
ns) Int64
0
| Bool
otherwise = Int64 -> Int64 -> TimeSpec
TimeSpec (Int64 -> Int64
forall a. Num a => a -> a
signum Int64
s) Int64
0
{-# INLINE fromInteger #-}
fromInteger :: Integer -> TimeSpec
fromInteger Integer
nanosec = Int64 -> Int64 -> TimeSpec
TimeSpec (Integer -> Int64
forall a. Num a => Integer -> a
fromInteger Integer
s) (Integer -> Int64
forall a. Num a => Integer -> a
fromInteger Integer
ns)
where (Integer
s, Integer
ns) = Integer
nanosec Integer -> Integer -> (Integer, Integer)
forall a. Integral a => a -> a -> (a, a)
`divMod` Int64 -> Integer
forall a. Integral a => a -> Integer
toInteger Int64
tenPower9
{-# LINE 116 "src/Streamly/Internal/Data/Time/TimeSpec.hsc" #-}
{-# LINE 118 "src/Streamly/Internal/Data/Time/TimeSpec.hsc" #-}
{-# LINE 143 "src/Streamly/Internal/Data/Time/TimeSpec.hsc" #-}
instance Storable TimeSpec where
sizeOf :: TimeSpec -> Int
sizeOf TimeSpec
_ = (Int
16)
{-# LINE 145 "src/Streamly/Internal/Data/Time/TimeSpec.hsc" #-}
alignment _ = 8
{-# LINE 146 "src/Streamly/Internal/Data/Time/TimeSpec.hsc" #-}
peek ptr = do
s :: Int64 <- (\hsc_ptr -> peekByteOff hsc_ptr 0) ptr
{-# LINE 148 "src/Streamly/Internal/Data/Time/TimeSpec.hsc" #-}
ns :: Int64 <- (\hsc_ptr -> peekByteOff hsc_ptr 8) ptr
{-# LINE 149 "src/Streamly/Internal/Data/Time/TimeSpec.hsc" #-}
return $ TimeSpec (fromIntegral s) (fromIntegral ns)
poke :: Ptr TimeSpec -> TimeSpec -> IO ()
poke Ptr TimeSpec
ptr TimeSpec
ts = do
let Int64
s :: Int64 = Int64 -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int64 -> Int64) -> Int64 -> Int64
forall a b. (a -> b) -> a -> b
$ TimeSpec -> Int64
sec TimeSpec
ts
{-# LINE 152 "src/Streamly/Internal/Data/Time/TimeSpec.hsc" #-}
Int64
ns :: Int64 = Int64 -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int64 -> Int64) -> Int64 -> Int64
forall a b. (a -> b) -> a -> b
$ TimeSpec -> Int64
nsec TimeSpec
ts
{-# LINE 153 "src/Streamly/Internal/Data/Time/TimeSpec.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 0) ptr (s)
{-# LINE 154 "src/Streamly/Internal/Data/Time/TimeSpec.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 8) ptr (ns)
{-# LINE 155 "src/Streamly/Internal/Data/Time/TimeSpec.hsc" #-}
{-# LINE 156 "src/Streamly/Internal/Data/Time/TimeSpec.hsc" #-}