{-# LANGUAGE CPP #-}
module Foundation.Time.Bindings
    ( measuringNanoSeconds
    , getMonotonicTime
    ) where

import Basement.Imports
import Basement.Types.OffsetSize
import Basement.Types.Ptr
import Foundation.System.Bindings.Time
import Foundation.Time.Types
import Foundation.Foreign.Alloc
import Foreign.Storable

measuringNanoSeconds :: IO a -> IO (a, NanoSeconds)
measuringNanoSeconds :: forall a. IO a -> IO (a, NanoSeconds)
measuringNanoSeconds IO a
f =
    CountOf Word8
-> (Ptr CTimeSpec -> IO (a, NanoSeconds)) -> IO (a, NanoSeconds)
forall a b. CountOf Word8 -> (Ptr a -> IO b) -> IO b
allocaBytes (CSize -> CountOf Word8
sizeOfCSize CSize
size_CTimeSpec) ((Ptr CTimeSpec -> IO (a, NanoSeconds)) -> IO (a, NanoSeconds))
-> (Ptr CTimeSpec -> IO (a, NanoSeconds)) -> IO (a, NanoSeconds)
forall a b. (a -> b) -> a -> b
$ \Ptr CTimeSpec
t1 ->
    CountOf Word8
-> (Ptr CTimeSpec -> IO (a, NanoSeconds)) -> IO (a, NanoSeconds)
forall a b. CountOf Word8 -> (Ptr a -> IO b) -> IO b
allocaBytes (CSize -> CountOf Word8
sizeOfCSize CSize
size_CTimeSpec) ((Ptr CTimeSpec -> IO (a, NanoSeconds)) -> IO (a, NanoSeconds))
-> (Ptr CTimeSpec -> IO (a, NanoSeconds)) -> IO (a, NanoSeconds)
forall a b. (a -> b) -> a -> b
$ \Ptr CTimeSpec
t2 -> do
        _err1 <- CInt -> Ptr CTimeSpec -> IO CInt
sysTimeClockGetTime CInt
sysTime_CLOCK_MONOTONIC Ptr CTimeSpec
t1
        r <- f
        _err2 <- sysTimeClockGetTime sysTime_CLOCK_MONOTONIC t2
        return (r, NanoSeconds 0)

getMonotonicTime :: IO (Seconds, NanoSeconds)
getMonotonicTime :: IO (Seconds, NanoSeconds)
getMonotonicTime =
    CountOf Word8
-> (Ptr CTimeSpec -> IO (Seconds, NanoSeconds))
-> IO (Seconds, NanoSeconds)
forall a b. CountOf Word8 -> (Ptr a -> IO b) -> IO b
allocaBytes (CSize -> CountOf Word8
sizeOfCSize CSize
size_CTimeSpec) ((Ptr CTimeSpec -> IO (Seconds, NanoSeconds))
 -> IO (Seconds, NanoSeconds))
-> (Ptr CTimeSpec -> IO (Seconds, NanoSeconds))
-> IO (Seconds, NanoSeconds)
forall a b. (a -> b) -> a -> b
$ \Ptr CTimeSpec
tspec -> do
        _err1 <- CInt -> Ptr CTimeSpec -> IO CInt
sysTimeClockGetTime CInt
sysTime_CLOCK_MONOTONIC Ptr CTimeSpec
tspec
        s  <- Seconds     <$> peek (castPtr (tspec `ptrPlus` ofs_CTimeSpec_Seconds))
        ns <- NanoSeconds <$> peek (castPtr (tspec `ptrPlus` ofs_CTimeSpec_NanoSeconds))
        return (s,ns)