{-# LINE 1 "System/Clock.hsc" #-}
-- | High-resolution, realtime clock and timer functions for Posix
{-# LINE 2 "System/Clock.hsc" #-}
--   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#>

{-# OPTIONS_GHC -fno-warn-type-defaults #-}

module System.Clock
  ( Clock(..)
  , TimeSpec(..)
  , getTime
  , getRes
  , diffTimeSpec
  ) where

import Control.Applicative
import Data.Int
import Data.Typeable (Typeable)
import Foreign.Ptr
import Foreign.Storable
import Foreign.Marshal.Alloc
import GHC.Generics (Generic)


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

{-# LINE 30 "System/Clock.hsc" #-}
-- Due to missing define in FreeBSD 9.0 and 9.1
-- (http://lists.freebsd.org/pipermail/freebsd-stable/2013-September/075095.html).

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

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


{-# LINE 38 "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 CLOCK_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.
  = 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
    -- | 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
  deriving (Eq, Enum, Generic, Read, Show, Typeable)


{-# LINE 82 "System/Clock.hsc" #-}
foreign import ccall clock_gettime :: Int32 -> Ptr TimeSpec -> IO ()
{-# LINE 83 "System/Clock.hsc" #-}
foreign import ccall clock_getres  :: Int32 -> Ptr TimeSpec -> IO ()
{-# LINE 84 "System/Clock.hsc" #-}

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


{-# LINE 94 "System/Clock.hsc" #-}
clockToConst :: Clock -> Int32
{-# LINE 95 "System/Clock.hsc" #-}
clockToConst Monotonic = 1
{-# LINE 96 "System/Clock.hsc" #-}
clockToConst Realtime = 0
{-# LINE 97 "System/Clock.hsc" #-}
clockToConst ProcessCPUTime = 2
{-# LINE 98 "System/Clock.hsc" #-}
clockToConst ThreadCPUTime = 3
{-# LINE 99 "System/Clock.hsc" #-}

{-# LINE 100 "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 121 "System/Clock.hsc" #-}
getTime clk = allocaAndPeek $ clock_gettime $ clockToConst clk

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


{-# LINE 132 "System/Clock.hsc" #-}
getRes clk = allocaAndPeek $ clock_getres $ clockToConst clk

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

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


{-# LINE 153 "System/Clock.hsc" #-}
instance Storable TimeSpec where
  sizeOf _ = (16)
{-# LINE 155 "System/Clock.hsc" #-}
  alignment _ = 8
{-# LINE 156 "System/Clock.hsc" #-}
  poke ptr ts = do
      let xs :: Int64 = fromIntegral $ sec ts
{-# LINE 158 "System/Clock.hsc" #-}
          xn :: Int64 = fromIntegral $ nsec ts
{-# LINE 159 "System/Clock.hsc" #-}
      (\hsc_ptr -> pokeByteOff hsc_ptr 0) ptr (xs)
{-# LINE 160 "System/Clock.hsc" #-}
      (\hsc_ptr -> pokeByteOff hsc_ptr 8) ptr (xn)
{-# LINE 161 "System/Clock.hsc" #-}
  peek ptr = do
      xs :: Int64 <- (\hsc_ptr -> peekByteOff hsc_ptr 0) ptr
{-# LINE 163 "System/Clock.hsc" #-}
      xn :: Int64 <- (\hsc_ptr -> peekByteOff hsc_ptr 8) ptr
{-# LINE 164 "System/Clock.hsc" #-}
      return $ TimeSpec (fromIntegral xs) (fromIntegral xn)

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

normalize :: TimeSpec -> TimeSpec
normalize (TimeSpec xs xn) =
    let (q, r) = xn `divMod` (10^9)
    in TimeSpec (xs + q) r

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)
  (TimeSpec xs xn) * (TimeSpec ys yn) =
      normalize $ TimeSpec (xs * ys) (xn * yn)
  negate (TimeSpec xs xn) =
      normalize $ TimeSpec (negate xs) (negate xn)
  abs (TimeSpec xs xn) =
      normalize $ TimeSpec (abs xs) (signum xs * xn)
  signum (normalize -> TimeSpec xs yn)
    | signum xs == 0 = TimeSpec 0 (signum yn)
    | otherwise = TimeSpec 0 (signum xs)
  fromInteger x =
      -- For range, compute div, mod over integers, not any bounded type.
      let (q, r) = x `divMod` (10^9)
      in TimeSpec (fromInteger q) (fromInteger r)

instance Ord TimeSpec where
  compare (TimeSpec xs xn) (TimeSpec ys yn)
    | EQ == ordering = compare xn yn
    | otherwise = ordering
    where
      ordering = compare xs ys

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