{-# LINE 1 "GHC/Clock.hsc" #-}
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE NoImplicitPrelude #-}

module GHC.Clock
    ( getMonotonicTime
    , getMonotonicTimeNSec
    ) where

import GHC.Base
import GHC.Real
import Data.Word

-- | Return monotonic time in seconds, since some unspecified starting point
--
-- @since 4.11.0.0
getMonotonicTime :: IO Double
getMonotonicTime :: IO Double
getMonotonicTime = do Word64
w <- IO Word64
getMonotonicTimeNSec
                      Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return (Word64 -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
w Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
1000000000)

-- | Return monotonic time in nanoseconds, since some unspecified starting point
--
-- @since 4.11.0.0
foreign import ccall unsafe "getMonotonicNSec"
    getMonotonicTimeNSec :: IO Word64