{-# OPTIONS_GHC -optc-DHS_CLOCK_POSIX=1 #-}
{-# 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.hsc" #-}
{-# LANGUAGE CPP                         #-}
{-# LANGUAGE DeriveGeneric               #-}
{-# LANGUAGE GeneralizedNewtypeDeriving  #-}
{-# LANGUAGE ScopedTypeVariables         #-}


{-# LINE 7 "src/Streamly/Internal/Data/Time/Clock.hsc" #-}
{-# OPTIONS_GHC -Wno-identities          #-}
{-# OPTIONS_GHC -Wno-orphans             #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}

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


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


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

-- |
-- Module      : Streamly.Internal.Data.Time.Clock
-- Copyright   : (c) 2019 Harendra Kumar
--               (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.


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


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

module Streamly.Internal.Data.Time.Clock
    (
    -- * 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 64 "src/Streamly/Internal/Data/Time/Clock.hsc" #-}



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


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

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

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


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


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


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


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


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


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


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


{-# LINE 92 "src/Streamly/Internal/Data/Time/Clock.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 118 "src/Streamly/Internal/Data/Time/Clock.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 128 "src/Streamly/Internal/Data/Time/Clock.hsc" #-}


{-# LINE 130 "src/Streamly/Internal/Data/Time/Clock.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 137 "src/Streamly/Internal/Data/Time/Clock.hsc" #-}


{-# LINE 139 "src/Streamly/Internal/Data/Time/Clock.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 144 "src/Streamly/Internal/Data/Time/Clock.hsc" #-}


{-# LINE 146 "src/Streamly/Internal/Data/Time/Clock.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 155 "src/Streamly/Internal/Data/Time/Clock.hsc" #-}


{-# LINE 157 "src/Streamly/Internal/Data/Time/Clock.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 162 "src/Streamly/Internal/Data/Time/Clock.hsc" #-}

  deriving (Eq, Enum, Generic, Read, Show, Typeable)

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


{-# LINE 170 "src/Streamly/Internal/Data/Time/Clock.hsc" #-}
-- Posix systems (Linux and Mac OSX 10.12 and later)
clockToPosixClockId :: Clock -> Int32
{-# LINE 172 "src/Streamly/Internal/Data/Time/Clock.hsc" #-}
clockToPosixClockId Monotonic      = 1
{-# LINE 173 "src/Streamly/Internal/Data/Time/Clock.hsc" #-}
clockToPosixClockId Realtime       = 0
{-# LINE 174 "src/Streamly/Internal/Data/Time/Clock.hsc" #-}
clockToPosixClockId ProcessCPUTime = 2
{-# LINE 175 "src/Streamly/Internal/Data/Time/Clock.hsc" #-}
clockToPosixClockId ThreadCPUTime  = 3
{-# LINE 176 "src/Streamly/Internal/Data/Time/Clock.hsc" #-}


{-# LINE 178 "src/Streamly/Internal/Data/Time/Clock.hsc" #-}
clockToPosixClockId MonotonicRaw = 4
{-# LINE 179 "src/Streamly/Internal/Data/Time/Clock.hsc" #-}

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


{-# LINE 182 "src/Streamly/Internal/Data/Time/Clock.hsc" #-}
clockToPosixClockId MonotonicCoarse = 6
{-# LINE 183 "src/Streamly/Internal/Data/Time/Clock.hsc" #-}

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


{-# LINE 188 "src/Streamly/Internal/Data/Time/Clock.hsc" #-}
clockToPosixClockId RealtimeCoarse = 5
{-# LINE 189 "src/Streamly/Internal/Data/Time/Clock.hsc" #-}

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


{-# LINE 192 "src/Streamly/Internal/Data/Time/Clock.hsc" #-}
clockToPosixClockId Uptime = 7
{-# LINE 193 "src/Streamly/Internal/Data/Time/Clock.hsc" #-}

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


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

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


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


{-# LINE 246 "src/Streamly/Internal/Data/Time/Clock.hsc" #-}
instance Storable TimeSpec where
  sizeOf _ = (16)
{-# LINE 248 "src/Streamly/Internal/Data/Time/Clock.hsc" #-}
  alignment _ = 8
{-# LINE 249 "src/Streamly/Internal/Data/Time/Clock.hsc" #-}
  peek ptr = do
      s :: Int64 <- (\hsc_ptr -> peekByteOff hsc_ptr 0) ptr
{-# LINE 251 "src/Streamly/Internal/Data/Time/Clock.hsc" #-}
      ns :: Int64 <- (\hsc_ptr -> peekByteOff hsc_ptr 8) ptr
{-# LINE 252 "src/Streamly/Internal/Data/Time/Clock.hsc" #-}
      return $ TimeSpec (fromIntegral s) (fromIntegral ns)
  poke ptr ts = do
      let s :: Int64 = fromIntegral $ sec ts
{-# LINE 255 "src/Streamly/Internal/Data/Time/Clock.hsc" #-}
          ns :: Int64 = fromIntegral $ nsec ts
{-# LINE 256 "src/Streamly/Internal/Data/Time/Clock.hsc" #-}
      (\hsc_ptr -> pokeByteOff hsc_ptr 0) ptr (s)
{-# LINE 257 "src/Streamly/Internal/Data/Time/Clock.hsc" #-}
      (\hsc_ptr -> pokeByteOff hsc_ptr 8) ptr (ns)
{-# LINE 258 "src/Streamly/Internal/Data/Time/Clock.hsc" #-}

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

{-# INLINE getTimeWith #-}
getTimeWith :: (Ptr TimeSpec -> IO ()) -> IO AbsTime
getTimeWith f = do
    t <- alloca (\ptr -> f ptr >> peek ptr)
    return $ AbsTime t


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

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

{-# INLINABLE getTime #-}
getTime :: Clock -> IO AbsTime
getTime clock =
    getTimeWith (throwErrnoIfMinus1_ "clock_gettime" .
        clock_gettime (clockToPosixClockId clock))


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