{-# OPTIONS_GHC -optc-DHS_CLOCK_HAVE_PROCESS_CPUTIME #-}
{-# OPTIONS_GHC -optc-DHS_CLOCK_HAVE_THREAD_CPUTIME #-}
{-# LINE 1 "System/Clock.hsc" #-}
-- | High-resolution, realtime clock and timer functions for Posix
--   systems. This module is being developed according to IEEE Std
--   1003.1-2008: <http://www.opengroup.org/onlinepubs/9699919799/>,
--   <http://www.opengroup.org/onlinepubs/9699919799/functions/clock_getres.html#>

{-# LANGUAGE CApiFFI #-}
{-# OPTIONS_GHC -fno-warn-type-defaults #-}
-- To allow importing Data.Int and Data.Word indiscriminately on all platforms,
-- since we can't systematically predict what typedef's expand to.
{-# OPTIONS_GHC -fno-warn-unused-imports #-}

module System.Clock
  ( Clock(..)
  , TimeSpec(..)
  , getTime
  , getRes
  , fromNanoSecs
  , toNanoSecs
  , diffTimeSpec
  , timeSpecAsNanoSecs
  , normalize
  , s2ns
  ) where

import Control.Applicative ((<$>), (<*>))
import Data.Int
import Data.Word
import Data.Ratio
import Data.Typeable (Typeable)
import Foreign.C
import Foreign.Ptr
import Foreign.Storable
import Foreign.Marshal.Alloc
import GHC.Generics (Generic)


{-# LINE 41 "System/Clock.hsc" #-}


{-# LINE 43 "System/Clock.hsc" #-}


{-# LINE 45 "System/Clock.hsc" #-}

{-# LINE 46 "System/Clock.hsc" #-}


{-# LINE 48 "System/Clock.hsc" #-}
import System.Posix.Types

{-# LINE 50 "System/Clock.hsc" #-}


{-# LINE 54 "System/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 'Realtime'.
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.
    --   (Identical to 'Boottime' since Linux 4.17, see https://git.kernel.org/pub/scm/linux/kernel/git/torvalds/linux.git/commit/?id=d6ed449afdb38f89a7b38ec50e367559e1b8f71f)
    --  @CLOCK_MONOTONIC@ (macOS - @SYSTEM_CLOCK@)
  = 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.
    -- @CLOCK_REALTIME@ (macOS - @CALENDAR_CLOCK@, Windows - @GetSystemTimeAsFileTime@)
  | Realtime


{-# LINE 82 "System/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

{-# LINE 87 "System/Clock.hsc" #-}


{-# LINE 89 "System/Clock.hsc" #-}
    -- | 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 94 "System/Clock.hsc" #-}


{-# LINE 96 "System/Clock.hsc" #-}
    -- | (since Linux 2.6.28, macOS 10.12)
    --   Similar to '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).
    --   @CLOCK_MONOTONIC_RAW@ (Windows - @QueryPerformanceCounter@, @QueryPerformanceFrequency@)
  | MonotonicRaw

{-# LINE 104 "System/Clock.hsc" #-}


{-# LINE 106 "System/Clock.hsc" #-}
    -- | (since Linux 2.6.39; Linux-specific)
    --   Identical to `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 'Realtime',
    --   which may have discontinuities if the time is changed
    --   using settimeofday(2).
    --   (since Linux 4.17; identical to 'Monotonic')
    --   @CLOCK_BOOTTIME@
  | Boottime

{-# LINE 117 "System/Clock.hsc" #-}


{-# LINE 119 "System/Clock.hsc" #-}
    -- | (since Linux 2.6.32; Linux-specific)
    --   A faster but less precise version of 'Monotonic'.
    --   Use when you need very fast, but not fine-grained timestamps.
    --   @CLOCK_MONOTONIC_COARSE@
  | MonotonicCoarse

{-# LINE 125 "System/Clock.hsc" #-}


{-# LINE 127 "System/Clock.hsc" #-}
    -- | (since Linux 2.6.32; Linux-specific)
    --   A faster but less precise version of 'Realtime'.
    --   Use when you need very fast, but not fine-grained timestamps.
    --   @CLOCK_REALTIME_COARSE@
  | RealtimeCoarse

{-# LINE 133 "System/Clock.hsc" #-}

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


{-# LINE 146 "System/Clock.hsc" #-}

{-# LINE 147 "System/Clock.hsc" #-}
type ClockId = CClockId

{-# LINE 151 "System/Clock.hsc" #-}

foreign import ccall unsafe clock_gettime :: ClockId -> Ptr TimeSpec -> IO CInt
foreign import ccall unsafe clock_getres  :: ClockId -> Ptr TimeSpec -> IO CInt

foreign import capi unsafe "time.h value CLOCK_MONOTONIC" clock_MONOTONIC :: ClockId
foreign import capi unsafe "time.h value CLOCK_REALTIME" clock_REALTIME :: ClockId

{-# LINE 158 "System/Clock.hsc" #-}
foreign import capi unsafe "time.h value CLOCK_PROCESS_CPUTIME_ID" clock_PROCESS_CPUTIME_ID :: ClockId

{-# LINE 160 "System/Clock.hsc" #-}

{-# LINE 161 "System/Clock.hsc" #-}
foreign import capi unsafe "time.h value CLOCK_THREAD_CPUTIME_ID" clock_THREAD_CPUTIME_ID :: ClockId

{-# LINE 163 "System/Clock.hsc" #-}

{-# LINE 164 "System/Clock.hsc" #-}
foreign import capi unsafe "time.h value CLOCK_MONOTONIC_RAW" clock_MONOTONIC_RAW :: ClockId

{-# LINE 166 "System/Clock.hsc" #-}

{-# LINE 167 "System/Clock.hsc" #-}
foreign import capi unsafe "time.h value CLOCK_BOOTTIME" clock_BOOTTIME :: ClockId

{-# LINE 169 "System/Clock.hsc" #-}

{-# LINE 170 "System/Clock.hsc" #-}
foreign import capi unsafe "time.h value CLOCK_MONOTONIC_COARSE" clock_MONOTONIC_COARSE :: ClockId

{-# LINE 172 "System/Clock.hsc" #-}

{-# LINE 173 "System/Clock.hsc" #-}
foreign import capi unsafe "time.h value CLOCK_REALTIME_COARSE" clock_REALTIME_COARSE :: ClockId

{-# LINE 175 "System/Clock.hsc" #-}

{-# LINE 176 "System/Clock.hsc" #-}


{-# LINE 178 "System/Clock.hsc" #-}
clockToConst :: Clock -> ClockId
clockToConst Monotonic = clock_MONOTONIC
clockToConst  Realtime = clock_REALTIME

{-# LINE 182 "System/Clock.hsc" #-}
clockToConst ProcessCPUTime = clock_PROCESS_CPUTIME_ID

{-# LINE 184 "System/Clock.hsc" #-}

{-# LINE 185 "System/Clock.hsc" #-}
clockToConst  ThreadCPUTime = clock_THREAD_CPUTIME_ID

{-# LINE 187 "System/Clock.hsc" #-}

{-# LINE 188 "System/Clock.hsc" #-}
clockToConst    MonotonicRaw = clock_MONOTONIC_RAW

{-# LINE 190 "System/Clock.hsc" #-}

{-# LINE 191 "System/Clock.hsc" #-}
clockToConst        Boottime = clock_BOOTTIME

{-# LINE 193 "System/Clock.hsc" #-}

{-# LINE 194 "System/Clock.hsc" #-}
clockToConst MonotonicCoarse = clock_MONOTONIC_COARSE

{-# LINE 196 "System/Clock.hsc" #-}

{-# LINE 197 "System/Clock.hsc" #-}
clockToConst  RealtimeCoarse = clock_REALTIME_COARSE

{-# LINE 199 "System/Clock.hsc" #-}

{-# LINE 200 "System/Clock.hsc" #-}

allocaAndPeek :: Storable a => (Ptr a -> IO ()) -> IO a
allocaAndPeek f = alloca $ \ptr -> f ptr >> peek ptr

-- | The 'getTime' function shall return the current value for the
--   specified clock.
getTime :: Clock -> IO TimeSpec

-- | The 'getRes' function shall return the resolution of any clock.
--   Clock resolutions are implementation-defined and cannot be set
--   by a process.
getRes :: Clock -> IO TimeSpec


{-# LINE 219 "System/Clock.hsc" #-}
getTime clk = allocaAndPeek $! throwErrnoIfMinus1_ "clock_gettime" . clock_gettime (clockToConst clk)

{-# LINE 221 "System/Clock.hsc" #-}


{-# LINE 228 "System/Clock.hsc" #-}
getRes clk = allocaAndPeek $! throwErrnoIfMinus1_ "clock_getres" . clock_getres (clockToConst clk)

{-# LINE 230 "System/Clock.hsc" #-}

-- | TimeSpec structure
data TimeSpec = TimeSpec
  { sec  :: {-# UNPACK #-} !Int64 -- ^ seconds
  , nsec :: {-# UNPACK #-} !Int64 -- ^ nanoseconds
  } deriving (Generic, Read, Show, Typeable)


{-# LINE 249 "System/Clock.hsc" #-}
instance Storable TimeSpec where
  sizeOf _ = (16)
{-# LINE 251 "System/Clock.hsc" #-}
  alignment _ = 8
{-# LINE 252 "System/Clock.hsc" #-}
  poke ptr ts = do
      let xs :: Int64 = fromIntegral $ sec ts
{-# LINE 254 "System/Clock.hsc" #-}
          xn :: Int64 = fromIntegral $ nsec ts
{-# LINE 255 "System/Clock.hsc" #-}
      (\hsc_ptr -> pokeByteOff hsc_ptr 0) ptr (xs)
{-# LINE 256 "System/Clock.hsc" #-}
      (\hsc_ptr -> pokeByteOff hsc_ptr 8) ptr (xn)
{-# LINE 257 "System/Clock.hsc" #-}
  peek ptr = do
      xs :: Int64 <- (\hsc_ptr -> peekByteOff hsc_ptr 0) ptr
{-# LINE 259 "System/Clock.hsc" #-}
      xn :: Int64 <- (\hsc_ptr -> peekByteOff hsc_ptr 8) ptr
{-# LINE 260 "System/Clock.hsc" #-}
      return $ TimeSpec (fromIntegral xs) (fromIntegral xn)

{-# LINE 262 "System/Clock.hsc" #-}

s2ns :: Num a => a
s2ns = 10^9

normalize :: TimeSpec -> TimeSpec
normalize (TimeSpec xs xn) | xn < 0 || xn >= s2ns = TimeSpec (xs + q)  r
                           | otherwise            = TimeSpec  xs      xn
                             where (q, r) = xn `divMod` s2ns

instance Num TimeSpec where
  (TimeSpec xs xn) + (TimeSpec ys yn) = normalize $! TimeSpec (xs + ys) (xn + yn)
  (TimeSpec xs xn) - (TimeSpec ys yn) = normalize $! TimeSpec (xs - ys) (xn - yn)
  (normalize -> TimeSpec xs xn) * (normalize -> TimeSpec ys yn) = normalize $! TimeSpec (s2ns*xs*ys+xs*yn+xn*ys) (xn*yn)
  negate (TimeSpec xs xn) = normalize $! TimeSpec (negate xs) (negate xn)
  abs    (normalize -> TimeSpec xs xn) | xs == 0   = normalize $! TimeSpec 0 xn
                                       | otherwise = normalize $! TimeSpec (abs xs) (signum xs * xn)
  signum (normalize -> TimeSpec xs xn) | xs == 0   = TimeSpec 0 (signum xn)
                                       | otherwise = TimeSpec 0 (signum xs)
  fromInteger x = TimeSpec (fromInteger q) (fromInteger r) where (q, r) = x `divMod` s2ns

instance Enum TimeSpec where
  succ x = x + 1
  pred x = x - 1
  toEnum x = normalize $ TimeSpec 0 (fromIntegral x)
  fromEnum = fromEnum . toInteger

instance Real TimeSpec where
  toRational x = toInteger x % 1

instance Integral TimeSpec where
  toInteger = toNanoSecs
  quot (toInteger-> t1) (toInteger-> t2) = fromInteger $! quot t1 t2
  rem (toInteger-> t1) (toInteger-> t2) = fromInteger $! rem t1 t2
  div (toInteger-> t1) (toInteger-> t2) = fromInteger $! div t1 t2
  mod (toInteger-> t1) (toInteger-> t2) = fromInteger $! mod t1 t2
  divMod (toInteger-> t1) (toInteger-> t2) =
    let (q,r)=divMod t1 t2 in (fromInteger $! q, fromInteger $! r)
  quotRem (toInteger-> t1) (toInteger-> t2) =
    let (q,r)=quotRem t1 t2 in (fromInteger $! q, fromInteger $! r)

instance Eq TimeSpec where
  (normalize -> TimeSpec xs xn) == (normalize -> TimeSpec ys yn) | True == es = xn == yn
                                                                 | otherwise  = es
                                                                   where   es = xs == ys

instance Ord TimeSpec where
  compare (normalize -> TimeSpec xs xn) (normalize -> TimeSpec ys yn) | EQ ==  os = compare xn yn
                                                                      | otherwise = os
                                                                        where  os = compare xs ys

instance Bounded TimeSpec where
  minBound = TimeSpec minBound 0
  maxBound = TimeSpec maxBound (s2ns-1)

-- | TimeSpec from nano seconds.
fromNanoSecs :: Integer -> TimeSpec
fromNanoSecs x = TimeSpec (fromInteger  q) (fromInteger  r) where (q, r) = x `divMod` s2ns


-- | TimeSpec to nano seconds.
toNanoSecs :: TimeSpec -> Integer
toNanoSecs   (TimeSpec  (toInteger -> s) (toInteger -> n)) = s * s2ns + n

-- | Compute the absolute difference.
diffTimeSpec :: TimeSpec -> TimeSpec -> TimeSpec
diffTimeSpec ts1 ts2 = abs (ts1 - ts2)

{-# DEPRECATED timeSpecAsNanoSecs "Use toNanoSecs instead! Replaced timeSpecAsNanoSecs with the same signature TimeSpec -> Integer" #-}
-- | TimeSpec as nano seconds.
timeSpecAsNanoSecs :: TimeSpec -> Integer
timeSpecAsNanoSecs   (TimeSpec s n) = toInteger s * s2ns + toInteger n