{-# LINE 1 "libraries/ghc-internal/src/GHC/Internal/Clock.hsc" #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE NoImplicitPrelude #-}
module GHC.Internal.Clock
( getMonotonicTime
, getMonotonicTimeNSec
) where
import GHC.Internal.Base
import GHC.Internal.Real
import GHC.Internal.Word
import GHC.Internal.Float ()
{-# LINE 17 "libraries/ghc-internal/src/GHC/Internal/Clock.hsc" #-}
getMonotonicTime :: IO Double
getMonotonicTime :: IO Double
getMonotonicTime = do
{-# LINE 27 "libraries/ghc-internal/src/GHC/Internal/Clock.hsc" #-}
w <- IO Word64
getMonotonicTimeNSec
return (fromIntegral w / 1000000000)
{-# LINE 30 "libraries/ghc-internal/src/GHC/Internal/Clock.hsc" #-}
{-# LINE 44 "libraries/ghc-internal/src/GHC/Internal/Clock.hsc" #-}
foreign import ccall unsafe "getMonotonicNSec"
getMonotonicTimeNSec :: IO Word64
{-# LINE 47 "libraries/ghc-internal/src/GHC/Internal/Clock.hsc" #-}