#if __GLASGOW_HASKELL__ >= 710
{-# OPTIONS -fno-warn-trustworthy-safe #-}
#endif
{-# LANGUAGE Trustworthy #-}
module Data.Time.Clock.Internal.SystemTime
(
SystemTime(..),
getSystemTime,
getTime_resolution,
getTAISystemTime,
) where
import Data.Int (Int64)
import Data.Word
import Control.DeepSeq
import Data.Time.Clock.Internal.DiffTime
#include "HsTimeConfig.h"
#ifdef mingw32_HOST_OS
import qualified System.Win32.Time as Win32
#elif defined(HAVE_CLOCK_GETTIME)
import Data.Time.Clock.Internal.CTimespec
import Foreign.C.Types (CTime(..), CLong(..))
#else
import Data.Time.Clock.Internal.CTimeval
import Foreign.C.Types (CLong(..))
#endif
data SystemTime = MkSystemTime
{ SystemTime -> Int64
systemSeconds :: {-# UNPACK #-} !Int64
, SystemTime -> Word32
systemNanoseconds :: {-# UNPACK #-} !Word32
} deriving (SystemTime -> SystemTime -> Bool
(SystemTime -> SystemTime -> Bool)
-> (SystemTime -> SystemTime -> Bool) -> Eq SystemTime
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SystemTime -> SystemTime -> Bool
$c/= :: SystemTime -> SystemTime -> Bool
== :: SystemTime -> SystemTime -> Bool
$c== :: SystemTime -> SystemTime -> Bool
Eq,Eq SystemTime
Eq SystemTime
-> (SystemTime -> SystemTime -> Ordering)
-> (SystemTime -> SystemTime -> Bool)
-> (SystemTime -> SystemTime -> Bool)
-> (SystemTime -> SystemTime -> Bool)
-> (SystemTime -> SystemTime -> Bool)
-> (SystemTime -> SystemTime -> SystemTime)
-> (SystemTime -> SystemTime -> SystemTime)
-> Ord SystemTime
SystemTime -> SystemTime -> Bool
SystemTime -> SystemTime -> Ordering
SystemTime -> SystemTime -> SystemTime
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SystemTime -> SystemTime -> SystemTime
$cmin :: SystemTime -> SystemTime -> SystemTime
max :: SystemTime -> SystemTime -> SystemTime
$cmax :: SystemTime -> SystemTime -> SystemTime
>= :: SystemTime -> SystemTime -> Bool
$c>= :: SystemTime -> SystemTime -> Bool
> :: SystemTime -> SystemTime -> Bool
$c> :: SystemTime -> SystemTime -> Bool
<= :: SystemTime -> SystemTime -> Bool
$c<= :: SystemTime -> SystemTime -> Bool
< :: SystemTime -> SystemTime -> Bool
$c< :: SystemTime -> SystemTime -> Bool
compare :: SystemTime -> SystemTime -> Ordering
$ccompare :: SystemTime -> SystemTime -> Ordering
Ord,Int -> SystemTime -> ShowS
[SystemTime] -> ShowS
SystemTime -> String
(Int -> SystemTime -> ShowS)
-> (SystemTime -> String)
-> ([SystemTime] -> ShowS)
-> Show SystemTime
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SystemTime] -> ShowS
$cshowList :: [SystemTime] -> ShowS
show :: SystemTime -> String
$cshow :: SystemTime -> String
showsPrec :: Int -> SystemTime -> ShowS
$cshowsPrec :: Int -> SystemTime -> ShowS
Show)
instance NFData SystemTime where
rnf :: SystemTime -> ()
rnf SystemTime
a = SystemTime
a SystemTime -> () -> ()
`seq` ()
getSystemTime :: IO SystemTime
getTime_resolution :: DiffTime
getTAISystemTime :: Maybe (DiffTime,IO SystemTime)
#ifdef mingw32_HOST_OS
getSystemTime = do
Win32.FILETIME ft <- Win32.getSystemTimeAsFileTime
let (s, us) = (ft - win32_epoch_adjust) `divMod` 10000000
return (MkSystemTime (fromIntegral s) (fromIntegral us * 100))
where
win32_epoch_adjust :: Word64
win32_epoch_adjust = 116444736000000000
getTime_resolution = 100E-9
getTAISystemTime = Nothing
#elif defined(HAVE_CLOCK_GETTIME)
timespecToSystemTime :: CTimespec -> SystemTime
timespecToSystemTime :: CTimespec -> SystemTime
timespecToSystemTime (MkCTimespec (CTime Int64
s) (CLong Int64
ns)) = (Int64 -> Word32 -> SystemTime
MkSystemTime (Int64 -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
s) (Int64 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
ns))
timespecToDiffTime :: CTimespec -> DiffTime
timespecToDiffTime :: CTimespec -> DiffTime
timespecToDiffTime (MkCTimespec (CTime Int64
s) CLong
ns) = (Int64 -> DiffTime
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
s) DiffTime -> DiffTime -> DiffTime
forall a. Num a => a -> a -> a
+ (CLong -> DiffTime
forall a b. (Integral a, Num b) => a -> b
fromIntegral CLong
ns) DiffTime -> DiffTime -> DiffTime
forall a. Num a => a -> a -> a
* DiffTime
1E-9
clockGetSystemTime :: ClockID -> IO SystemTime
clockGetSystemTime :: ClockID -> IO SystemTime
clockGetSystemTime ClockID
clock = (CTimespec -> SystemTime) -> IO CTimespec -> IO SystemTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap CTimespec -> SystemTime
timespecToSystemTime (IO CTimespec -> IO SystemTime) -> IO CTimespec -> IO SystemTime
forall a b. (a -> b) -> a -> b
$ ClockID -> IO CTimespec
clockGetTime ClockID
clock
getSystemTime :: IO SystemTime
getSystemTime = ClockID -> IO SystemTime
clockGetSystemTime ClockID
clock_REALTIME
getTime_resolution :: DiffTime
getTime_resolution = CTimespec -> DiffTime
timespecToDiffTime CTimespec
realtimeRes
getTAISystemTime :: Maybe (DiffTime, IO SystemTime)
getTAISystemTime = (CTimespec -> (DiffTime, IO SystemTime))
-> Maybe CTimespec -> Maybe (DiffTime, IO SystemTime)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\CTimespec
resolution -> (CTimespec -> DiffTime
timespecToDiffTime CTimespec
resolution,ClockID -> IO SystemTime
clockGetSystemTime ClockID
clock_TAI)) (Maybe CTimespec -> Maybe (DiffTime, IO SystemTime))
-> Maybe CTimespec -> Maybe (DiffTime, IO SystemTime)
forall a b. (a -> b) -> a -> b
$ ClockID -> Maybe CTimespec
clockResolution ClockID
clock_TAI
#else
getSystemTime = do
MkCTimeval (CLong s) (CLong us) <- getCTimeval
return (MkSystemTime (fromIntegral s) (fromIntegral us * 1000))
getTime_resolution = 1E-6
getTAISystemTime = Nothing
#endif