#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
    { systemSeconds ::     {-# UNPACK #-} !Int64
    , systemNanoseconds :: {-# UNPACK #-} !Word32
    } deriving (Eq,Ord,Show)
instance NFData SystemTime where
    rnf a = a `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 (MkCTimespec (CTime s) (CLong ns)) = (MkSystemTime (fromIntegral s) (fromIntegral ns))
timespecToDiffTime :: CTimespec -> DiffTime
timespecToDiffTime (MkCTimespec (CTime s) ns) = (fromIntegral s) + (fromIntegral ns) * 1E-9
clockGetSystemTime :: ClockID -> IO SystemTime
clockGetSystemTime clock = fmap timespecToSystemTime $ clockGetTime clock
getSystemTime = clockGetSystemTime clock_REALTIME
getTime_resolution = timespecToDiffTime realtimeRes
getTAISystemTime = fmap (\resolution -> (timespecToDiffTime resolution,clockGetSystemTime clock_TAI)) $ clockResolution 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