{-# LANGUAGE CPP #-}
module Data.Time.Clock.Compat (
UniversalTime(..),
DiffTime,
secondsToDiffTime,
picosecondsToDiffTime,
diffTimeToPicoseconds,
UTCTime (..),
NominalDiffTime,
secondsToNominalDiffTime,
nominalDiffTimeToSeconds,
nominalDay,
addUTCTime,
diffUTCTime,
getCurrentTime,
getTime_resolution
) where
import Data.Time.Orphans ()
import Data.Time.Clock
import Data.Fixed (Pico)
#if !MIN_VERSION_time(1,9,1)
secondsToNominalDiffTime :: Pico -> NominalDiffTime
secondsToNominalDiffTime = realToFrac
nominalDiffTimeToSeconds :: NominalDiffTime -> Pico
nominalDiffTimeToSeconds = realToFrac
#endif
#if !MIN_VERSION_time(1,8,0)
nominalDay :: NominalDiffTime
nominalDay = 86400
#endif
#if !MIN_VERSION_time(1,8,0)
getTime_resolution :: DiffTime
getTime_resolution = 1E-6
#endif
#if !MIN_VERSION_time(1,6,0)
diffTimeToPicoseconds :: DiffTime -> Integer
#if MIN_VERSION_time(1,4,0)
diffTimeToPicoseconds = truncate . (1000000000000 *)
#else
diffTimeToPicoseconds = truncate . toRational . (1000000000000 *)
#endif
#endif