{-# OPTIONS_GHC -optc-DHAVE_CLOCK_MONOTONIC_RAW #-}
{-# OPTIONS_GHC -optc-DHAVE_CLOCK_MONOTONIC_COARSE #-}
{-# OPTIONS_GHC -optc-DHAVE_CLOCK_MONOTONIC_UPTIME #-}
{-# OPTIONS_GHC -optc-DHAVE_CLOCK_REALTIME_COARSE #-}
{-# LINE 1 "src/Streamly/Internal/Data/Time/Clock/Type.hsc" #-}
{-# OPTIONS_GHC -Wno-identities          #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}


{-# LINE 5 "src/Streamly/Internal/Data/Time/Clock/Type.hsc" #-}


{-# LINE 7 "src/Streamly/Internal/Data/Time/Clock/Type.hsc" #-}



-- |
-- Module      : Streamly.Internal.Data.Time.Clock.Type
-- Copyright   : (c) 2019 Composewell Technologies
--               (c) 2009-2012, Cetin Sert
--               (c) 2010, Eugene Kirpichov
-- License     : BSD3
-- Maintainer  : streamly@composewell.com
-- Stability   : experimental
-- Portability : GHC

-- A majority of the code below has been stolen from the "clock" package.

module Streamly.Internal.Data.Time.Clock.Type
    (
    -- * get time from the system clock
      Clock(..)
    , getTime
    )
where

import Data.Int (Int32, Int64)
import Data.Typeable (Typeable)
import Data.Word (Word32)
import Foreign.C (CInt(..), throwErrnoIfMinus1_, CTime(..), CLong(..))
import Foreign.Marshal.Alloc (alloca)
import Foreign.Ptr (Ptr)
import Foreign.Storable (Storable(..), peek)
import GHC.Generics (Generic)

import Streamly.Internal.Data.Time.Units (TimeSpec(..), AbsTime(..))

-------------------------------------------------------------------------------
-- Clock Types
-------------------------------------------------------------------------------


{-# LINE 46 "src/Streamly/Internal/Data/Time/Clock/Type.hsc" #-}



{-# LINE 49 "src/Streamly/Internal/Data/Time/Clock/Type.hsc" #-}


{-# LINE 51 "src/Streamly/Internal/Data/Time/Clock/Type.hsc" #-}

-- XXX this may be RAW on apple not RAW on linux

{-# LINE 54 "src/Streamly/Internal/Data/Time/Clock/Type.hsc" #-}


{-# LINE 56 "src/Streamly/Internal/Data/Time/Clock/Type.hsc" #-}


{-# LINE 60 "src/Streamly/Internal/Data/Time/Clock/Type.hsc" #-}


{-# LINE 62 "src/Streamly/Internal/Data/Time/Clock/Type.hsc" #-}


{-# LINE 64 "src/Streamly/Internal/Data/Time/Clock/Type.hsc" #-}


{-# LINE 68 "src/Streamly/Internal/Data/Time/Clock/Type.hsc" #-}


{-# LINE 70 "src/Streamly/Internal/Data/Time/Clock/Type.hsc" #-}


{-# LINE 72 "src/Streamly/Internal/Data/Time/Clock/Type.hsc" #-}


{-# LINE 74 "src/Streamly/Internal/Data/Time/Clock/Type.hsc" #-}

-- | Clock types. A clock may be system-wide (that is, visible to all processes)
--   or per-process (measuring time that is meaningful only within a process).
--   All implementations shall support CLOCK_REALTIME. (The only suspend-aware
--   monotonic is CLOCK_BOOTTIME on Linux.)
data Clock

    -- | The identifier for the system-wide monotonic clock, which is defined as
    --   a clock measuring real time, whose value cannot be set via
    --   @clock_settime@ and which cannot have negative clock jumps. The maximum
    --   possible clock jump shall be implementation defined. For this clock,
    --   the value returned by 'getTime' represents the amount of time (in
    --   seconds and nanoseconds) since an unspecified point in the past (for
    --   example, system start-up time, or the Epoch). This point does not
    --   change after system start-up time. Note that the absolute value of the
    --   monotonic clock is meaningless (because its origin is arbitrary), and
    --   thus there is no need to set it. Furthermore, realtime applications can
    --   rely on the fact that the value of this clock is never set.
  = Monotonic

    -- | The identifier of the system-wide clock measuring real time. For this
    --   clock, the value returned by 'getTime' represents the amount of time (in
    --   seconds and nanoseconds) since the Epoch.
  | Realtime


{-# LINE 100 "src/Streamly/Internal/Data/Time/Clock/Type.hsc" #-}
    -- | The identifier of the CPU-time clock associated with the calling
    --   process. For this clock, the value returned by 'getTime' represents the
    --   amount of execution time of the current process.
  | ProcessCPUTime

    -- | The identifier of the CPU-time clock associated with the calling OS
    --   thread. For this clock, the value returned by 'getTime' represents the
    --   amount of execution time of the current OS thread.
  | ThreadCPUTime

{-# LINE 110 "src/Streamly/Internal/Data/Time/Clock/Type.hsc" #-}


{-# LINE 112 "src/Streamly/Internal/Data/Time/Clock/Type.hsc" #-}
    -- | (since Linux 2.6.28; Linux and Mac OSX)
    --   Similar to CLOCK_MONOTONIC, but provides access to a
    --   raw hardware-based time that is not subject to NTP
    --   adjustments or the incremental adjustments performed by
    --   adjtime(3).
  | MonotonicRaw

{-# LINE 119 "src/Streamly/Internal/Data/Time/Clock/Type.hsc" #-}


{-# LINE 121 "src/Streamly/Internal/Data/Time/Clock/Type.hsc" #-}
    -- | (since Linux 2.6.32; Linux and Mac OSX)
    --   A faster but less precise version of CLOCK_MONOTONIC.
    --   Use when you need very fast, but not fine-grained timestamps.
  | MonotonicCoarse

{-# LINE 126 "src/Streamly/Internal/Data/Time/Clock/Type.hsc" #-}


{-# LINE 128 "src/Streamly/Internal/Data/Time/Clock/Type.hsc" #-}
    -- | (since Linux 2.6.39; Linux and Mac OSX)
    --   Identical to CLOCK_MONOTONIC, except it also includes
    --   any time that the system is suspended.  This allows
    --   applications to get a suspend-aware monotonic clock
    --   without having to deal with the complications of
    --   CLOCK_REALTIME, which may have discontinuities if the
    --   time is changed using settimeofday(2).
  | Uptime

{-# LINE 137 "src/Streamly/Internal/Data/Time/Clock/Type.hsc" #-}


{-# LINE 139 "src/Streamly/Internal/Data/Time/Clock/Type.hsc" #-}
    -- | (since Linux 2.6.32; Linux-specific)
    --   A faster but less precise version of CLOCK_REALTIME.
    --   Use when you need very fast, but not fine-grained timestamps.
  | RealtimeCoarse

{-# LINE 144 "src/Streamly/Internal/Data/Time/Clock/Type.hsc" #-}

  deriving (Clock -> Clock -> Bool
(Clock -> Clock -> Bool) -> (Clock -> Clock -> Bool) -> Eq Clock
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Clock -> Clock -> Bool
$c/= :: Clock -> Clock -> Bool
== :: Clock -> Clock -> Bool
$c== :: Clock -> Clock -> Bool
Eq, Int -> Clock
Clock -> Int
Clock -> [Clock]
Clock -> Clock
Clock -> Clock -> [Clock]
Clock -> Clock -> Clock -> [Clock]
(Clock -> Clock)
-> (Clock -> Clock)
-> (Int -> Clock)
-> (Clock -> Int)
-> (Clock -> [Clock])
-> (Clock -> Clock -> [Clock])
-> (Clock -> Clock -> [Clock])
-> (Clock -> Clock -> Clock -> [Clock])
-> Enum Clock
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 :: Clock -> Clock -> Clock -> [Clock]
$cenumFromThenTo :: Clock -> Clock -> Clock -> [Clock]
enumFromTo :: Clock -> Clock -> [Clock]
$cenumFromTo :: Clock -> Clock -> [Clock]
enumFromThen :: Clock -> Clock -> [Clock]
$cenumFromThen :: Clock -> Clock -> [Clock]
enumFrom :: Clock -> [Clock]
$cenumFrom :: Clock -> [Clock]
fromEnum :: Clock -> Int
$cfromEnum :: Clock -> Int
toEnum :: Int -> Clock
$ctoEnum :: Int -> Clock
pred :: Clock -> Clock
$cpred :: Clock -> Clock
succ :: Clock -> Clock
$csucc :: Clock -> Clock
Enum, (forall x. Clock -> Rep Clock x)
-> (forall x. Rep Clock x -> Clock) -> Generic Clock
forall x. Rep Clock x -> Clock
forall x. Clock -> Rep Clock x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Clock x -> Clock
$cfrom :: forall x. Clock -> Rep Clock x
Generic, ReadPrec [Clock]
ReadPrec Clock
Int -> ReadS Clock
ReadS [Clock]
(Int -> ReadS Clock)
-> ReadS [Clock]
-> ReadPrec Clock
-> ReadPrec [Clock]
-> Read Clock
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Clock]
$creadListPrec :: ReadPrec [Clock]
readPrec :: ReadPrec Clock
$creadPrec :: ReadPrec Clock
readList :: ReadS [Clock]
$creadList :: ReadS [Clock]
readsPrec :: Int -> ReadS Clock
$creadsPrec :: Int -> ReadS Clock
Read, Int -> Clock -> ShowS
[Clock] -> ShowS
Clock -> String
(Int -> Clock -> ShowS)
-> (Clock -> String) -> ([Clock] -> ShowS) -> Show Clock
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Clock] -> ShowS
$cshowList :: [Clock] -> ShowS
show :: Clock -> String
$cshow :: Clock -> String
showsPrec :: Int -> Clock -> ShowS
$cshowsPrec :: Int -> Clock -> ShowS
Show, Typeable)

-------------------------------------------------------------------------------
-- Translate the Haskell "Clock" type to C
-------------------------------------------------------------------------------


{-# LINE 152 "src/Streamly/Internal/Data/Time/Clock/Type.hsc" #-}
-- Posix systems (Linux and Mac OSX 10.12 and later)
clockToPosixClockId :: Clock -> Int32
{-# LINE 154 "src/Streamly/Internal/Data/Time/Clock/Type.hsc" #-}
clockToPosixClockId Monotonic      = 1
{-# LINE 155 "src/Streamly/Internal/Data/Time/Clock/Type.hsc" #-}
clockToPosixClockId Realtime       = 0
{-# LINE 156 "src/Streamly/Internal/Data/Time/Clock/Type.hsc" #-}
clockToPosixClockId ProcessCPUTime = 2
{-# LINE 157 "src/Streamly/Internal/Data/Time/Clock/Type.hsc" #-}
clockToPosixClockId ThreadCPUTime  = 3
{-# LINE 158 "src/Streamly/Internal/Data/Time/Clock/Type.hsc" #-}


{-# LINE 160 "src/Streamly/Internal/Data/Time/Clock/Type.hsc" #-}
clockToPosixClockId MonotonicRaw = 4
{-# LINE 161 "src/Streamly/Internal/Data/Time/Clock/Type.hsc" #-}

{-# LINE 162 "src/Streamly/Internal/Data/Time/Clock/Type.hsc" #-}


{-# LINE 164 "src/Streamly/Internal/Data/Time/Clock/Type.hsc" #-}
clockToPosixClockId MonotonicCoarse = 6
{-# LINE 165 "src/Streamly/Internal/Data/Time/Clock/Type.hsc" #-}

{-# LINE 168 "src/Streamly/Internal/Data/Time/Clock/Type.hsc" #-}


{-# LINE 170 "src/Streamly/Internal/Data/Time/Clock/Type.hsc" #-}
clockToPosixClockId RealtimeCoarse = 5
{-# LINE 171 "src/Streamly/Internal/Data/Time/Clock/Type.hsc" #-}

{-# LINE 172 "src/Streamly/Internal/Data/Time/Clock/Type.hsc" #-}


{-# LINE 174 "src/Streamly/Internal/Data/Time/Clock/Type.hsc" #-}
clockToPosixClockId Uptime = 7
{-# LINE 175 "src/Streamly/Internal/Data/Time/Clock/Type.hsc" #-}

{-# LINE 178 "src/Streamly/Internal/Data/Time/Clock/Type.hsc" #-}


{-# LINE 195 "src/Streamly/Internal/Data/Time/Clock/Type.hsc" #-}

-------------------------------------------------------------------------------
-- Clock time
-------------------------------------------------------------------------------

{-# INLINE getTimeWith #-}
getTimeWith :: (Ptr TimeSpec -> IO ()) -> IO AbsTime
getTimeWith :: (Ptr TimeSpec -> IO ()) -> IO AbsTime
getTimeWith Ptr TimeSpec -> IO ()
f = do
    TimeSpec
t <- (Ptr TimeSpec -> IO TimeSpec) -> IO TimeSpec
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca (\Ptr TimeSpec
ptr -> Ptr TimeSpec -> IO ()
f Ptr TimeSpec
ptr IO () -> IO TimeSpec -> IO TimeSpec
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr TimeSpec -> IO TimeSpec
forall a. Storable a => Ptr a -> IO a
peek Ptr TimeSpec
ptr)
    AbsTime -> IO AbsTime
forall (m :: * -> *) a. Monad m => a -> m a
return (AbsTime -> IO AbsTime) -> AbsTime -> IO AbsTime
forall a b. (a -> b) -> a -> b
$ TimeSpec -> AbsTime
AbsTime TimeSpec
t


{-# LINE 218 "src/Streamly/Internal/Data/Time/Clock/Type.hsc" #-}

foreign import ccall unsafe "time.h clock_gettime"
    clock_gettime :: Int32 -> Ptr TimeSpec -> IO CInt
{-# LINE 221 "src/Streamly/Internal/Data/Time/Clock/Type.hsc" #-}

{-# INLINABLE getTime #-}
getTime :: Clock -> IO AbsTime
getTime :: Clock -> IO AbsTime
getTime Clock
clock =
    (Ptr TimeSpec -> IO ()) -> IO AbsTime
getTimeWith (String -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> IO a -> IO ()
throwErrnoIfMinus1_ String
"clock_gettime" (IO CInt -> IO ())
-> (Ptr TimeSpec -> IO CInt) -> Ptr TimeSpec -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
        Int32 -> Ptr TimeSpec -> IO CInt
clock_gettime (Clock -> Int32
clockToPosixClockId Clock
clock))


{-# LINE 253 "src/Streamly/Internal/Data/Time/Clock/Type.hsc" #-}