module System.CPUTime.Utils
    ( -- * Integer conversions
      -- | These types have no 'Integral' instances in the Haskell report
      -- so we must do this ourselves.
      cClockToInteger
    , cTimeToInteger
    , csuSecondsToInteger
    ) where

import Foreign.C.Types

cClockToInteger :: CClock -> Integer
cClockToInteger :: CClock -> Integer
cClockToInteger (CClock Int64
n) = Int64 -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
n

cTimeToInteger :: CTime -> Integer
cTimeToInteger :: CTime -> Integer
cTimeToInteger (CTime Int64
n) = Int64 -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
n

csuSecondsToInteger :: CSUSeconds -> Integer
csuSecondsToInteger :: CSUSeconds -> Integer
csuSecondsToInteger (CSUSeconds Int64
n) = Int64 -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
n