{-# LINE 1 "src/Streamly/Internal/Data/Time/TimeSpec.hsc" #-}
{-# OPTIONS_GHC -Wno-identities          #-}


{-# LINE 4 "src/Streamly/Internal/Data/Time/TimeSpec.hsc" #-}


{-# LINE 6 "src/Streamly/Internal/Data/Time/TimeSpec.hsc" #-}





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

module Streamly.Internal.Data.Time.TimeSpec
    (
      TimeSpec(..)
    )
where

import Data.Int (Int64)

{-# LINE 29 "src/Streamly/Internal/Data/Time/TimeSpec.hsc" #-}
import Foreign.Storable (Storable(..), peek)


{-# LINE 34 "src/Streamly/Internal/Data/Time/TimeSpec.hsc" #-}

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

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

-------------------------------------------------------------------------------
-- TimeSpec representation
-------------------------------------------------------------------------------

-- A structure storing seconds and nanoseconds as 'Int64' is the simplest and
-- fastest way to store practically large quantities of time with efficient
-- arithmetic operations. If we store nanoseconds using 'Integer' it can store
-- practically unbounded quantities but it may not be as efficient to
-- manipulate in performance critical applications. XXX need to measure the
-- performance.
--
-- | Data type to represent practically large quantities of time efficiently.
-- It can represent time up to ~292 billion years at nanosecond resolution.
data TimeSpec = TimeSpec
  { TimeSpec -> Int64
sec  :: {-# UNPACK #-} !Int64 -- ^ seconds
  , TimeSpec -> Int64
nsec :: {-# UNPACK #-} !Int64 -- ^ nanoseconds
  } deriving (TimeSpec -> TimeSpec -> Bool
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]
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
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)

-- We assume that nsec is always less than 10^9. When TimeSpec is negative then
-- both sec and nsec are negative.
instance Ord TimeSpec where
    compare :: TimeSpec -> TimeSpec -> Ordering
compare (TimeSpec Int64
s1 Int64
ns1) (TimeSpec Int64
s2 Int64
ns2) =
        if Int64
s1 forall a. Eq a => a -> a -> Bool
== Int64
s2
        then forall a. Ord a => a -> a -> Ordering
compare Int64
ns1 Int64
ns2
        else forall a. Ord a => a -> a -> Ordering
compare Int64
s1 Int64
s2

-- make sure nsec is less than 10^9
{-# 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 forall a. Num a => a -> a -> a
+ Int64
ns2
        (Int64
s', Int64
ns) = if Int64
nsum forall a. Ord a => a -> a -> Bool
> Int64
tenPower9 Bool -> Bool -> Bool
|| Int64
nsum forall a. Ord a => a -> a -> Bool
< forall a. Num a => a -> a
negate Int64
tenPower9
                    then Int64
nsum forall a. Integral a => a -> a -> (a, a)
`divMod` Int64
tenPower9
                    else (Int64
0, Int64
nsum)
    in Int64 -> Int64 -> TimeSpec
TimeSpec (Int64
s1 forall a. Num a => a -> a -> a
+ Int64
s2 forall a. Num a => a -> a -> a
+ Int64
s') Int64
ns

-- make sure both sec and nsec have the same sign
{-# INLINE adjustSign #-}
adjustSign :: TimeSpec -> TimeSpec
adjustSign :: TimeSpec -> TimeSpec
adjustSign t :: TimeSpec
t@(TimeSpec Int64
s Int64
ns)
    | Int64
s forall a. Ord a => a -> a -> Bool
> Int64
0 Bool -> Bool -> Bool
&& Int64
ns forall a. Ord a => a -> a -> Bool
< Int64
0 = Int64 -> Int64 -> TimeSpec
TimeSpec (Int64
s forall a. Num a => a -> a -> a
- Int64
1) (Int64
ns forall a. Num a => a -> a -> a
+ Int64
tenPower9)
    | Int64
s forall a. Ord a => a -> a -> Bool
< Int64
0 Bool -> Bool -> Bool
&& Int64
ns forall a. Ord a => a -> a -> Bool
> Int64
0 = Int64 -> Int64 -> TimeSpec
TimeSpec (Int64
s forall a. Num a => a -> a -> a
+ Int64
1) (Int64
ns 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) = forall a. Integral a => a -> Integer
toInteger 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 Num TimeSpec where
    {-# INLINE (+) #-}
    TimeSpec
t1 + :: TimeSpec -> TimeSpec -> TimeSpec
+ TimeSpec
t2 = TimeSpec -> TimeSpec
adjustSign (TimeSpec -> TimeSpec -> TimeSpec
addWithOverflow TimeSpec
t1 TimeSpec
t2)

    -- XXX will this be more optimal if imlemented without "negate"?
    {-# INLINE (-) #-}
    TimeSpec
t1 - :: TimeSpec -> TimeSpec -> TimeSpec
- TimeSpec
t2 = TimeSpec
t1 forall a. Num a => a -> a -> a
+ forall a. Num a => a -> a
negate TimeSpec
t2
    TimeSpec
t1 * :: TimeSpec -> TimeSpec -> TimeSpec
* TimeSpec
t2 = forall a. Num a => Integer -> a
fromInteger forall a b. (a -> b) -> a -> b
$ TimeSpec -> Integer
timeSpecToInteger TimeSpec
t1 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 (forall a. Num a => a -> a
negate Int64
s) (forall a. Num a => a -> a
negate Int64
ns)
    {-# INLINE abs #-}
    abs :: TimeSpec -> TimeSpec
abs    (TimeSpec Int64
s Int64
ns) = Int64 -> Int64 -> TimeSpec
TimeSpec (forall a. Num a => a -> a
abs Int64
s) (forall a. Num a => a -> a
abs Int64
ns)
    {-# INLINE signum #-}
    signum :: TimeSpec -> TimeSpec
signum (TimeSpec Int64
s Int64
ns) | Int64
s forall a. Eq a => a -> a -> Bool
== Int64
0    = Int64 -> Int64 -> TimeSpec
TimeSpec (forall a. Num a => a -> a
signum Int64
ns) Int64
0
                           | Bool
otherwise = Int64 -> Int64 -> TimeSpec
TimeSpec (forall a. Num a => a -> a
signum Int64
s) Int64
0
    -- This is fromNanoSecond64 Integer
    {-# INLINE fromInteger #-}
    fromInteger :: Integer -> TimeSpec
fromInteger Integer
nanosec = Int64 -> Int64 -> TimeSpec
TimeSpec (forall a. Num a => Integer -> a
fromInteger Integer
s) (forall a. Num a => Integer -> a
fromInteger Integer
ns)
        where (Integer
s, Integer
ns) = Integer
nanosec forall a. Integral a => a -> a -> (a, a)
`divMod` forall a. Integral a => a -> Integer
toInteger Int64
tenPower9


{-# LINE 113 "src/Streamly/Internal/Data/Time/TimeSpec.hsc" #-}


{-# LINE 115 "src/Streamly/Internal/Data/Time/TimeSpec.hsc" #-}


{-# LINE 140 "src/Streamly/Internal/Data/Time/TimeSpec.hsc" #-}
instance Storable TimeSpec where
  sizeOf :: TimeSpec -> Int
sizeOf TimeSpec
_ = (Int
16)
{-# LINE 142 "src/Streamly/Internal/Data/Time/TimeSpec.hsc" #-}
  alignment _ = 8
{-# LINE 143 "src/Streamly/Internal/Data/Time/TimeSpec.hsc" #-}
  peek ptr = do
      s :: Int64 <- (\hsc_ptr -> peekByteOff hsc_ptr 0) ptr
{-# LINE 145 "src/Streamly/Internal/Data/Time/TimeSpec.hsc" #-}
      ns :: Int64 <- (\hsc_ptr -> peekByteOff hsc_ptr 8) ptr
{-# LINE 146 "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 = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ TimeSpec -> Int64
sec TimeSpec
ts
{-# LINE 149 "src/Streamly/Internal/Data/Time/TimeSpec.hsc" #-}
          Int64
ns :: Int64 = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ TimeSpec -> Int64
nsec TimeSpec
ts
{-# LINE 150 "src/Streamly/Internal/Data/Time/TimeSpec.hsc" #-}
      (\hsc_ptr -> pokeByteOff hsc_ptr 0) ptr (s)
{-# LINE 151 "src/Streamly/Internal/Data/Time/TimeSpec.hsc" #-}
      (\hsc_ptr -> pokeByteOff hsc_ptr 8) ptr (ns)
{-# LINE 152 "src/Streamly/Internal/Data/Time/TimeSpec.hsc" #-}

{-# LINE 153 "src/Streamly/Internal/Data/Time/TimeSpec.hsc" #-}