{-# 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" #-}
{-# LINE 31 "src/Streamly/Internal/Data/Time/Clock.hsc" #-}
{-# LINE 39 "src/Streamly/Internal/Data/Time/Clock.hsc" #-}
module Streamly.Internal.Data.Time.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(..))
{-# 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" #-}
{-# 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" #-}
data Clock
= Monotonic
| Realtime
{-# LINE 118 "src/Streamly/Internal/Data/Time/Clock.hsc" #-}
| ProcessCPUTime
| ThreadCPUTime
{-# LINE 128 "src/Streamly/Internal/Data/Time/Clock.hsc" #-}
{-# LINE 130 "src/Streamly/Internal/Data/Time/Clock.hsc" #-}
| MonotonicRaw
{-# LINE 137 "src/Streamly/Internal/Data/Time/Clock.hsc" #-}
{-# LINE 139 "src/Streamly/Internal/Data/Time/Clock.hsc" #-}
| MonotonicCoarse
{-# LINE 144 "src/Streamly/Internal/Data/Time/Clock.hsc" #-}
{-# LINE 146 "src/Streamly/Internal/Data/Time/Clock.hsc" #-}
| Uptime
{-# LINE 155 "src/Streamly/Internal/Data/Time/Clock.hsc" #-}
{-# LINE 157 "src/Streamly/Internal/Data/Time/Clock.hsc" #-}
| RealtimeCoarse
{-# LINE 162 "src/Streamly/Internal/Data/Time/Clock.hsc" #-}
deriving (Eq, Enum, Generic, Read, Show, Typeable)
{-# LINE 170 "src/Streamly/Internal/Data/Time/Clock.hsc" #-}
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" #-}
{-# 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 310 "src/Streamly/Internal/Data/Time/Clock.hsc" #-}