{-# LINE 1 "libraries/base/src/System/CPUTime/Posix/Times.hsc" #-}
{-# LANGUAGE CPP, CApiFFI, NumDecimals #-}
module System.CPUTime.Posix.Times
( getCPUTime
, getCpuTimePrecision
) where
import Prelude
import Foreign
import Data.Ratio
import GHC.Internal.Foreign.C.Types
import System.CPUTime.Utils
{-# LINE 19 "libraries/base/src/System/CPUTime/Posix/Times.hsc" #-}
{-# LINE 21 "libraries/base/src/System/CPUTime/Posix/Times.hsc" #-}
{-# LINE 23 "libraries/base/src/System/CPUTime/Posix/Times.hsc" #-}
getCPUTime :: IO Integer
getCPUTime :: IO Integer
getCPUTime = Int -> (Ptr CTms -> IO Integer) -> IO Integer
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes (Int
32) ((Ptr CTms -> IO Integer) -> IO Integer)
-> (Ptr CTms -> IO Integer) -> IO Integer
forall a b. (a -> b) -> a -> b
$ \ Ptr CTms
p_tms -> do
{-# LINE 26 "libraries/base/src/System/CPUTime/Posix/Times.hsc" #-}
_ <- times p_tms
u_ticks <- ((\hsc_ptr -> peekByteOff hsc_ptr 0)) p_tms :: IO CClock
{-# LINE 28 "libraries/base/src/System/CPUTime/Posix/Times.hsc" #-}
s_ticks <- ((\hsc_ptr -> peekByteOff hsc_ptr 8)) p_tms :: IO CClock
{-# LINE 29 "libraries/base/src/System/CPUTime/Posix/Times.hsc" #-}
return (( (cClockToInteger u_ticks + cClockToInteger s_ticks) * 1e12)
`div` fromIntegral clockTicks)
type CTms = ()
foreign import ccall unsafe times :: Ptr CTms -> IO CClock
getCpuTimePrecision :: IO Integer
getCpuTimePrecision :: IO Integer
getCpuTimePrecision =
Integer -> IO Integer
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Integer -> IO Integer) -> Integer -> IO Integer
forall a b. (a -> b) -> a -> b
$ Ratio Integer -> Integer
forall b. Integral b => Ratio Integer -> b
forall a b. (RealFrac a, Integral b) => a -> b
round ((Integer
1e12::Integer) Integer -> Integer -> Ratio Integer
forall a. Integral a => a -> a -> Ratio a
% Integer
clockTicks)
foreign import ccall unsafe clk_tck :: CLong
clockTicks :: Integer
clockTicks :: Integer
clockTicks = CLong -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral CLong
clk_tck
{-# LINE 53 "libraries/base/src/System/CPUTime/Posix/Times.hsc" #-}