{-# LINE 1 "System/Clock.hsc" #-}
{-# OPTIONS_GHC -fno-warn-type-defaults #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
module System.Clock
  ( Clock(..)
  , TimeSpec(..)
  , getTime
  , getRes
  , fromNanoSecs
  , toNanoSecs
  , diffTimeSpec
  , timeSpecAsNanoSecs
  ) where
import Control.Applicative ((<$>), (<*>))
import Data.Int
import Data.Word
import Data.Typeable (Typeable)
import Foreign.C
import Foreign.Ptr
import Foreign.Storable
import Foreign.Marshal.Alloc
import GHC.Generics (Generic)
{-# LINE 35 "System/Clock.hsc" #-}
{-# LINE 39 "System/Clock.hsc" #-}
{-# LINE 40 "System/Clock.hsc" #-}
{-# LINE 44 "System/Clock.hsc" #-}
data Clock
    
    
    
    
    
    
    
    
    
    
    
    
    
  = Monotonic
    
    
    
    
  | Realtime
    
    
    
  | ProcessCPUTime
    
    
    
  | ThreadCPUTime
{-# LINE 82 "System/Clock.hsc" #-}
    
    
    
    
    
    
  | MonotonicRaw
{-# LINE 90 "System/Clock.hsc" #-}
{-# LINE 92 "System/Clock.hsc" #-}
    
    
    
    
    
    
    
    
    
  | Boottime
{-# LINE 103 "System/Clock.hsc" #-}
{-# LINE 105 "System/Clock.hsc" #-}
    
    
    
    
  | MonotonicCoarse
{-# LINE 111 "System/Clock.hsc" #-}
{-# LINE 113 "System/Clock.hsc" #-}
    
    
    
    
  | RealtimeCoarse
{-# LINE 119 "System/Clock.hsc" #-}
  deriving (Eq, Enum, Generic, Read, Show, Typeable)
{-# LINE 132 "System/Clock.hsc" #-}
foreign import ccall unsafe clock_gettime :: Int32 -> Ptr TimeSpec -> IO CInt
{-# LINE 133 "System/Clock.hsc" #-}
foreign import ccall unsafe clock_getres  :: Int32 -> Ptr TimeSpec -> IO CInt
{-# LINE 134 "System/Clock.hsc" #-}
{-# LINE 135 "System/Clock.hsc" #-}
{-# LINE 137 "System/Clock.hsc" #-}
clockToConst :: Clock -> Int32
{-# LINE 138 "System/Clock.hsc" #-}
clockToConst Monotonic = 1
{-# LINE 139 "System/Clock.hsc" #-}
clockToConst  Realtime = 0
{-# LINE 140 "System/Clock.hsc" #-}
clockToConst ProcessCPUTime = 2
{-# LINE 141 "System/Clock.hsc" #-}
clockToConst  ThreadCPUTime = 3
{-# LINE 142 "System/Clock.hsc" #-}
{-# LINE 144 "System/Clock.hsc" #-}
clockToConst    MonotonicRaw = 4
{-# LINE 145 "System/Clock.hsc" #-}
{-# LINE 146 "System/Clock.hsc" #-}
{-# LINE 147 "System/Clock.hsc" #-}
clockToConst        Boottime = 7
{-# LINE 148 "System/Clock.hsc" #-}
{-# LINE 149 "System/Clock.hsc" #-}
{-# LINE 150 "System/Clock.hsc" #-}
clockToConst MonotonicCoarse = 6
{-# LINE 151 "System/Clock.hsc" #-}
{-# LINE 152 "System/Clock.hsc" #-}
{-# LINE 153 "System/Clock.hsc" #-}
clockToConst  RealtimeCoarse = 5
{-# LINE 154 "System/Clock.hsc" #-}
{-# LINE 155 "System/Clock.hsc" #-}
{-# LINE 156 "System/Clock.hsc" #-}
allocaAndPeek :: Storable a => (Ptr a -> IO ()) -> IO a
allocaAndPeek f = alloca $ \ptr -> f ptr >> peek ptr
getTime :: Clock -> IO TimeSpec
getRes :: Clock -> IO TimeSpec
{-# LINE 175 "System/Clock.hsc" #-}
getTime clk = allocaAndPeek $! throwErrnoIfMinus1_ "clock_gettime" . clock_gettime (clockToConst clk)
{-# LINE 177 "System/Clock.hsc" #-}
{-# LINE 184 "System/Clock.hsc" #-}
getRes clk = allocaAndPeek $! throwErrnoIfMinus1_ "clock_getres" . clock_getres (clockToConst clk)
{-# LINE 186 "System/Clock.hsc" #-}
data TimeSpec = TimeSpec
  { sec  :: {-# UNPACK #-} !Int64 
  , nsec :: {-# UNPACK #-} !Int64 
  } deriving (Generic, Read, Show, Typeable)
{-# LINE 205 "System/Clock.hsc" #-}
instance Storable TimeSpec where
  sizeOf _ = (16)
{-# LINE 207 "System/Clock.hsc" #-}
  alignment _ = 8
{-# LINE 208 "System/Clock.hsc" #-}
  poke ptr ts = do
      let xs :: Int64 = fromIntegral $ sec ts
{-# LINE 210 "System/Clock.hsc" #-}
          xn :: Int64 = fromIntegral $ nsec ts
{-# LINE 211 "System/Clock.hsc" #-}
      (\hsc_ptr -> pokeByteOff hsc_ptr 0) ptr (xs)
{-# LINE 212 "System/Clock.hsc" #-}
      (\hsc_ptr -> pokeByteOff hsc_ptr 8) ptr (xn)
{-# LINE 213 "System/Clock.hsc" #-}
  peek ptr = do
      xs :: Int64 <- (\hsc_ptr -> peekByteOff hsc_ptr 0) ptr
{-# LINE 215 "System/Clock.hsc" #-}
      xn :: Int64 <- (\hsc_ptr -> peekByteOff hsc_ptr 8) ptr
{-# LINE 216 "System/Clock.hsc" #-}
      return $ TimeSpec (fromIntegral xs) (fromIntegral xn)
{-# LINE 218 "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)
  (TimeSpec xs xn) * (TimeSpec ys yn) = normalize $! TimeSpec (xsi_ysi) (xni_yni)
                                         where xsi_ysi = fromInteger $!  xsi*ysi 
                                               xni_yni = fromInteger $! (xni*yni + (xni*ysi + xsi*yni) * s2ns) `div` s2ns
                                               xsi     =   toInteger  xs
                                               ysi     =   toInteger  ys
                                               xni     =   toInteger  xn
                                               yni     =   toInteger  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 (signum xn) 0
                                       | otherwise = TimeSpec (signum xs) 0
  fromInteger x = TimeSpec (fromInteger q) (fromInteger r) where (q, r) = x `divMod` s2ns
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
fromNanoSecs :: Integer -> TimeSpec
fromNanoSecs x = TimeSpec (fromInteger  q) (fromInteger  r) where (q, r) = x `divMod` s2ns
toNanoSecs :: TimeSpec -> Integer
toNanoSecs   (TimeSpec  (toInteger -> s) (toInteger -> n)) = s * s2ns + n
diffTimeSpec :: TimeSpec -> TimeSpec -> TimeSpec
diffTimeSpec ts1 ts2 = abs (ts1 - ts2)
{-# DEPRECATED timeSpecAsNanoSecs "Use toNanoSecs instead! Replaced timeSpecAsNanoSecs with the same signature TimeSpec -> Integer" #-}
timeSpecAsNanoSecs :: TimeSpec -> Integer
timeSpecAsNanoSecs   (TimeSpec s n) = toInteger s * s2ns + toInteger n