{-# 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 () -- for Num Double instance

{-# LINE 17 "libraries/ghc-internal/src/GHC/Internal/Clock.hsc" #-}

-- | Return monotonic time in seconds, since some unspecified starting point
--
-- @since base-4.11.0.0
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" #-}

-- | Return monotonic time in nanoseconds, since some unspecified starting point
--
-- @since base-4.11.0.0

{-# 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" #-}