Safe Haskell | Trustworthy |
---|---|
Language | Haskell2010 |
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
- type Year = Integer
- type MonthOfYear = Int
- type DayOfMonth = Int
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.
Instances
Absolute intervals, DiffTime
This is a length of time, as measured by a clock.
Conversion functions such as fromInteger
and realToFrac
will treat it as seconds.
For example, (0.010 :: DiffTime)
corresponds to 10 milliseconds.
It has a precision of one picosecond (= 10^-12 s). Enumeration functions will treat it as picoseconds.
Instances
Data DiffTime | |
Defined in Data.Time.Clock.Internal.DiffTime 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 :: forall r r'. (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 # | |
Enum DiffTime | |
Defined in Data.Time.Clock.Internal.DiffTime | |
Num DiffTime | |
Read DiffTime | |
Fractional DiffTime | |
Real DiffTime | |
Defined in Data.Time.Clock.Internal.DiffTime toRational :: DiffTime -> Rational # | |
RealFrac DiffTime | |
Show DiffTime | |
NFData DiffTime | |
Defined in Data.Time.Clock.Internal.DiffTime | |
Eq DiffTime | |
Ord DiffTime | |
Defined in Data.Time.Clock.Internal.DiffTime | |
Hashable DiffTime Source # | |
Defined in Data.Time.Orphans | |
Lift DiffTime Source # | |
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.
UTCTime | |
|
Instances
Data UTCTime | |
Defined in Data.Time.Clock.Internal.UTCTime 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 :: forall r r'. (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 # | |
Generic UTCTime Source # | |
NFData UTCTime | |
Defined in Data.Time.Clock.Internal.UTCTime | |
Eq UTCTime | |
Ord UTCTime | |
Defined in Data.Time.Clock.Internal.UTCTime | |
Hashable UTCTime Source # | |
Defined in Data.Time.Orphans | |
ISO8601 UTCTime |
|
Defined in Data.Time.Format.ISO8601 | |
Lift UTCTime Source # | |
type Rep UTCTime Source # | |
Defined in Data.Time.Orphans type Rep UTCTime = D1 ('MetaData "UTCTime" "Data.Time.Clock.Internal.UTCTime" "time-1.12.2" 'False) (C1 ('MetaCons "UTCTime" 'PrefixI 'True) (S1 ('MetaSel ('Just "utctDay") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Day) :*: S1 ('MetaSel ('Just "utctDayTime") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DiffTime))) |
NominalDiffTime
data NominalDiffTime #
This is a length of time, as measured by UTC. It has a precision of 10^-12 s.
Conversion functions such as fromInteger
and realToFrac
will treat it as seconds.
For example, (0.010 :: NominalDiffTime)
corresponds to 10 milliseconds.
It has a precision of one picosecond (= 10^-12 s). Enumeration functions will treat it as picoseconds.
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 #
Create a NominalDiffTime
from a number of seconds.
Since: time-1.9.1
nominalDiffTimeToSeconds :: NominalDiffTime -> Pico #
Get the seconds in a NominalDiffTime
.
Since: time-1.9.1
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
.
On UNIX systems this uses clock_getres
, which may be wrong on WSL2.
Type aliases
type MonthOfYear = Int #
Month of year, in range 1 (January) to 12 (December).
type DayOfMonth = Int #
Day of month, in range 1 to 31.