{-# LANGUAGE CPP #-}

-- |
-- Module: Pact.Time.System
-- Copyright: Copyright © 2021 Kadena LLC.
-- License: MIT
-- Maintainer: Lars Kuhtz <lars@kadena.io>
-- Stability: experimental
--
-- Returns the time of the system clock as 64-bit value that counts microseconds
-- since the POSIX epoch.
--
module Pact.Time.System
( getSystemTimeMicros
) where

import Data.Int (Int64)

#if WITH_TIME
import qualified Data.Time.Clock.POSIX (getPOSIXTime)
#else
import System.Clock (getTime, TimeSpec(..), Clock(Realtime))
#endif

getSystemTimeMicros :: IO Int64
getSystemTimeMicros :: IO Int64
getSystemTimeMicros = do

#if WITH_TIME
    s <- Data.Time.Clock.POSIX.getPOSIXTime
    return $ round $ s * 1000000
#else
    TimeSpec Int64
s Int64
ns <- Clock -> IO TimeSpec
getTime Clock
Realtime
    forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ (Int64
s forall a. Num a => a -> a -> a
* Int64
1000000) forall a. Num a => a -> a -> a
+ (Int64
ns forall a. Integral a => a -> a -> a
`quot` Int64
1000)
#endif

{-# INLINE getSystemTimeMicros #-}