| Safe Haskell | Trustworthy | 
|---|---|
| Language | Haskell2010 | 
Data.Time.Clock.Compat
Synopsis
- newtype UniversalTime = ModJulianDate {}
- data DiffTime
- secondsToDiffTime :: Integer -> DiffTime
- picosecondsToDiffTime :: Integer -> DiffTime
- diffTimeToPicoseconds :: DiffTime -> Integer
- data UTCTime = UTCTime {- utctDay :: Day
- utctDayTime :: DiffTime
 
- data NominalDiffTime
- secondsToNominalDiffTime :: Pico -> NominalDiffTime
- nominalDiffTimeToSeconds :: NominalDiffTime -> Pico
- nominalDay :: NominalDiffTime
- addUTCTime :: NominalDiffTime -> UTCTime -> UTCTime
- diffUTCTime :: UTCTime -> UTCTime -> NominalDiffTime
- getCurrentTime :: IO UTCTime
- getTime_resolution :: DiffTime
Universal Time
Time as measured by the Earth.
newtype UniversalTime #
The Modified Julian Date is the day with the fraction of the day, measured from UT midnight. It's used to represent UT1, which is time as measured by the earth's rotation, adjusted for various wobbles.
Constructors
| ModJulianDate | |
| Fields | |
Instances
Absolute intervals, DiffTime
This is a length of time, as measured by a clock. Conversion functions will treat it as seconds. It has a precision of 10^-12 s.
Instances
| Enum DiffTime | |
| Defined in Data.Time.Clock.Internal.DiffTime | |
| Eq DiffTime | |
| Fractional DiffTime | |
| Data DiffTime | |
| Defined in Data.Time.Clock.Internal.DiffTime Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DiffTime -> c DiffTime # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DiffTime # toConstr :: DiffTime -> Constr # dataTypeOf :: DiffTime -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DiffTime) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DiffTime) # gmapT :: (forall b. Data b => b -> b) -> DiffTime -> DiffTime # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DiffTime -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DiffTime -> r # gmapQ :: (forall d. Data d => d -> u) -> DiffTime -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DiffTime -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DiffTime -> m DiffTime # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DiffTime -> m DiffTime # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DiffTime -> m DiffTime # | |
| Num DiffTime | |
| Defined in Data.Time.Clock.Internal.DiffTime | |
| Ord DiffTime | |
| Defined in Data.Time.Clock.Internal.DiffTime | |
| Real DiffTime | |
| Defined in Data.Time.Clock.Internal.DiffTime Methods toRational :: DiffTime -> Rational # | |
| RealFrac DiffTime | |
| Show DiffTime | |
| NFData DiffTime | |
| Defined in Data.Time.Clock.Internal.DiffTime | |
secondsToDiffTime :: Integer -> DiffTime #
Create a DiffTime which represents an integral number of seconds.
picosecondsToDiffTime :: Integer -> DiffTime #
Create a DiffTime from a number of picoseconds.
diffTimeToPicoseconds :: DiffTime -> Integer #
Get the number of picoseconds in a DiffTime.
UTCTime
This is the simplest representation of UTC. It consists of the day number, and a time offset from midnight. Note that if a day has a leap second added to it, it will have 86401 seconds.
Constructors
| UTCTime | |
| Fields 
 | |
Instances
| Eq UTCTime | |
| Data UTCTime | |
| Defined in Data.Time.Clock.Internal.UTCTime Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UTCTime -> c UTCTime # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UTCTime # toConstr :: UTCTime -> Constr # dataTypeOf :: UTCTime -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c UTCTime) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UTCTime) # gmapT :: (forall b. Data b => b -> b) -> UTCTime -> UTCTime # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UTCTime -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UTCTime -> r # gmapQ :: (forall d. Data d => d -> u) -> UTCTime -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> UTCTime -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> UTCTime -> m UTCTime # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UTCTime -> m UTCTime # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UTCTime -> m UTCTime # | |
| Ord UTCTime | |
| Defined in Data.Time.Clock.Internal.UTCTime | |
| NFData UTCTime | |
| Defined in Data.Time.Clock.Internal.UTCTime | |
| FormatTime UTCTime | |
| Defined in Data.Time.Format Methods formatCharacter :: Char -> Maybe (TimeLocale -> Maybe NumericPadOption -> Maybe Int -> UTCTime -> String) # | |
| ParseTime UTCTime | |
| Defined in Data.Time.Format.Parse | |
| ISO8601 UTCTime Source # | 
 | 
| Defined in Data.Time.Format.ISO8601.Compat Methods | |
NominalDiffTime
data NominalDiffTime #
This is a length of time, as measured by UTC. Conversion functions will treat it as seconds. It has a precision of 10^-12 s. It ignores leap-seconds, so it's not necessarily a fixed amount of clock time. For instance, 23:00 UTC + 2 hours of NominalDiffTime = 01:00 UTC (+ 1 day), regardless of whether a leap-second intervened.
Instances
secondsToNominalDiffTime :: Pico -> NominalDiffTime Source #
Create a NominalDiffTime from a number of seconds.
nominalDiffTimeToSeconds :: NominalDiffTime -> Pico Source #
Get the seconds in a NominalDiffTime.
nominalDay :: NominalDiffTime #
One day in NominalDiffTime.
UTC differences
addUTCTime :: NominalDiffTime -> UTCTime -> UTCTime #
addUTCTime a b = a + b
diffUTCTime :: UTCTime -> UTCTime -> NominalDiffTime #
diffUTCTime a b = a - b
Current time
getCurrentTime :: IO UTCTime #
Get the current UTCTime from the system clock.
getTime_resolution :: DiffTime #
The resolution of getSystemTime, getCurrentTime, getPOSIXTime