rio-0.1.12.0: A standard library for Haskell

Safe HaskellSafe
LanguageHaskell2010

RIO.Time

Synopsis

Documentation

formatTime :: FormatTime t => TimeLocale -> String -> t -> String #

Substitute various time-related information for each %-code in the string, as per formatCharacter.

The general form is %<modifier><width><specifier>, where <modifier> and <width> are optional.

<modifier>

glibc-style modifiers can be used before the specifier (here marked as z):

%-z
no padding
%_z
pad with spaces
%0z
pad with zeros
%^z
convert to upper case
%#z
convert to lower case (consistently, unlike glibc)

<width>

Width digits can also be used after any modifiers and before the specifier (here marked as z), for example:

%4z
pad to 4 characters (with default padding character)
%_12z
pad with spaces to 12 characters

<specifier>

For all types (note these three are done by formatTime, not by formatCharacter):

%%
%
%t
tab
%n
newline

TimeZone

For TimeZone (and ZonedTime and UTCTime):

%z
timezone offset in the format -HHMM.
%Z
timezone name

LocalTime

For LocalTime (and ZonedTime and UTCTime and UniversalTime):

%c
as dateTimeFmt locale (e.g. %a %b %e %H:%M:%S %Z %Y)

TimeOfDay

For TimeOfDay (and LocalTime and ZonedTime and UTCTime and UniversalTime):

%R
same as %H:%M
%T
same as %H:%M:%S
%X
as timeFmt locale (e.g. %H:%M:%S)
%r
as time12Fmt locale (e.g. %I:%M:%S %p)
%P
day-half of day from (amPm locale), converted to lowercase, am, pm
%p
day-half of day from (amPm locale), AM, PM
%H
hour of day (24-hour), 0-padded to two chars, 00 - 23
%k
hour of day (24-hour), space-padded to two chars, 0 - 23
%I
hour of day-half (12-hour), 0-padded to two chars, 01 - 12
%l
hour of day-half (12-hour), space-padded to two chars, 1 - 12
%M
minute of hour, 0-padded to two chars, 00 - 59
%S
second of minute (without decimal part), 0-padded to two chars, 00 - 60
%q
picosecond of second, 0-padded to twelve chars, 000000000000 - 999999999999.
%Q
decimal point and fraction of second, up to 12 second decimals, without trailing zeros. For a whole number of seconds, %Q omits the decimal point unless padding is specified.

UTCTime and ZonedTime

For UTCTime and ZonedTime:

%s
number of whole seconds since the Unix epoch. For times before the Unix epoch, this is a negative number. Note that in %s.%q and %s%Q the decimals are positive, not negative. For example, 0.9 seconds before the Unix epoch is formatted as -1.1 with %s%Q.

Day

For Day (and LocalTime and ZonedTime and UTCTime and UniversalTime):

%D
same as %m/%d/%y
%F
same as %Y-%m-%d
%x
as dateFmt locale (e.g. %m/%d/%y)
%Y
year, no padding. Note %0Y and %_Y pad to four chars
%y
year of century, 0-padded to two chars, 00 - 99
%C
century, no padding. Note %0C and %_C pad to two chars
%B
month name, long form (fst from months locale), January - December
%b, %h
month name, short form (snd from months locale), Jan - Dec
%m
month of year, 0-padded to two chars, 01 - 12
%d
day of month, 0-padded to two chars, 01 - 31
%e
day of month, space-padded to two chars, 1 - 31
%j
day of year, 0-padded to three chars, 001 - 366
%f
century for Week Date format, no padding. Note %0f and %_f pad to two chars
%V
week of year for Week Date format, 0-padded to two chars, 01 - 53
%u
day of week for Week Date format, 1 - 7
%a
day of week, short form (snd from wDays locale), Sun - Sat
%A
day of week, long form (fst from wDays locale), Sunday - Saturday
%U
week of year where weeks start on Sunday (as sundayStartWeek), 0-padded to two chars, 00 - 53
%w
day of week number, 0 (= Sunday) - 6 (= Saturday)
%W
week of year where weeks start on Monday (as mondayStartWeek), 0-padded to two chars, 00 - 53

readsTime #

Arguments

:: ParseTime t 
=> TimeLocale

Time locale.

-> String

Format string

-> ReadS t 

readTime #

Arguments

:: ParseTime t 
=> TimeLocale

Time locale.

-> String

Format string.

-> String

Input string.

-> t

The time value.

parseTime #

Arguments

:: ParseTime t 
=> TimeLocale

Time locale.

-> String

Format string.

-> String

Input string.

-> Maybe t

The time value, or Nothing if the input could not be parsed using the given format.

readPTime #

Arguments

:: ParseTime t 
=> Bool

Accept leading whitespace?

-> TimeLocale

Time locale.

-> String

Format string

-> ReadP t 

Parse a time value given a format string. See parseTimeM for details.

readSTime #

Arguments

:: ParseTime t 
=> Bool

Accept leading whitespace?

-> TimeLocale

Time locale.

-> String

Format string

-> ReadS t 

Parse a time value given a format string. See parseTimeM for details.

parseTimeOrError #

Arguments

:: ParseTime t 
=> Bool

Accept leading and trailing whitespace?

-> TimeLocale

Time locale.

-> String

Format string.

-> String

Input string.

-> t

The time value.

Parse a time value given a format string. Fails if the input could not be parsed using the given format. See parseTimeM for details.

parseTimeM #

Arguments

:: (Monad m, ParseTime t) 
=> Bool

Accept leading and trailing whitespace?

-> TimeLocale

Time locale.

-> String

Format string.

-> String

Input string.

-> m t

Return the time value, or fail if the input could not be parsed using the given format.

Parses a time value given a format string. Supports the same %-codes as formatTime, including %-, %_ and %0 modifiers, however padding widths are not supported. Case is not significant in the input string. Some variations in the input are accepted:

%z
accepts any of -HHMM or -HH:MM.
%Z
accepts any string of letters, or any of the formats accepted by %z.
%0Y
accepts exactly four digits.
%0G
accepts exactly four digits.
%0C
accepts exactly two digits.
%0f
accepts exactly two digits.

class ParseTime t where #

The class of types which can be parsed given a UNIX-style time format string.

Methods

buildTime #

Arguments

:: TimeLocale

The time locale.

-> [(Char, String)]

Pairs of format characters and the corresponding part of the input.

-> Maybe t 

Builds a time value from a parsed input string. If the input does not include all the information needed to construct a complete value, any missing parts should be taken from 1970-01-01 00:00:00 +0000 (which was a Thursday). In the absence of %C or %Y, century is 1969 - 2068.

Instances
ParseTime ZonedTime 
Instance details

Defined in Data.Time.Format.Parse

ParseTime LocalTime 
Instance details

Defined in Data.Time.Format.Parse

ParseTime TimeOfDay 
Instance details

Defined in Data.Time.Format.Parse

ParseTime TimeZone 
Instance details

Defined in Data.Time.Format.Parse

ParseTime UniversalTime 
Instance details

Defined in Data.Time.Format.Parse

ParseTime UTCTime 
Instance details

Defined in Data.Time.Format.Parse

ParseTime Day 
Instance details

Defined in Data.Time.Format.Parse

Methods

buildTime :: TimeLocale -> [(Char, String)] -> Maybe Day #

data ZonedTime #

A local time together with a time zone.

Instances
Data ZonedTime 
Instance details

Defined in Data.Time.LocalTime.Internal.ZonedTime

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ZonedTime -> c ZonedTime #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ZonedTime #

toConstr :: ZonedTime -> Constr #

dataTypeOf :: ZonedTime -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ZonedTime) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ZonedTime) #

gmapT :: (forall b. Data b => b -> b) -> ZonedTime -> ZonedTime #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ZonedTime -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ZonedTime -> r #

gmapQ :: (forall d. Data d => d -> u) -> ZonedTime -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ZonedTime -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ZonedTime -> m ZonedTime #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ZonedTime -> m ZonedTime #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ZonedTime -> m ZonedTime #

Show ZonedTime 
Instance details

Defined in Data.Time.LocalTime.Internal.ZonedTime

NFData ZonedTime 
Instance details

Defined in Data.Time.LocalTime.Internal.ZonedTime

Methods

rnf :: ZonedTime -> () #

FormatTime ZonedTime 
Instance details

Defined in Data.Time.Format

ParseTime ZonedTime 
Instance details

Defined in Data.Time.Format.Parse

rfc822DateFormat :: String #

Format string according to RFC822.

iso8601DateFormat :: Maybe String -> String #

Construct format string according to ISO-8601.

The Maybe String argument allows to supply an optional time specification. E.g.:

iso8601DateFormat Nothing            == "%Y-%m-%d"           -- i.e. YYYY-MM-DD
iso8601DateFormat (Just "%H:%M:%S")  == "%Y-%m-%dT%H:%M:%S"  -- i.e. YYYY-MM-DDTHH:MM:SS

defaultTimeLocale :: TimeLocale #

Locale representing American usage.

knownTimeZones contains only the ten time-zones mentioned in RFC 822 sec. 5: "UT", "GMT", "EST", "EDT", "CST", "CDT", "MST", "MDT", "PST", "PDT". Note that the parsing functions will regardless parse single-letter military time-zones and +HHMM format.

data TimeLocale #

Constructors

TimeLocale 

Fields

localTimeToUT1 :: Rational -> LocalTime -> UniversalTime #

Get the UT1 time of a local time on a particular meridian (in degrees, positive is East).

ut1ToLocalTime :: Rational -> UniversalTime -> LocalTime #

Get the local time of a UT1 time on a particular meridian (in degrees, positive is East).

localTimeToUTC :: TimeZone -> LocalTime -> UTCTime #

Get the UTC time of a local time in a time zone.

utcToLocalTime :: TimeZone -> UTCTime -> LocalTime #

Get the local time of a UTC time in a time zone.

data LocalTime #

A simple day and time aggregate, where the day is of the specified parameter, and the time is a TimeOfDay. Conversion of this (as local civil time) to UTC depends on the time zone. Conversion of this (as local mean time) to UT1 depends on the longitude.

Constructors

LocalTime 
Instances
Eq LocalTime 
Instance details

Defined in Data.Time.LocalTime.Internal.LocalTime

Data LocalTime 
Instance details

Defined in Data.Time.LocalTime.Internal.LocalTime

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LocalTime -> c LocalTime #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LocalTime #

toConstr :: LocalTime -> Constr #

dataTypeOf :: LocalTime -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LocalTime) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LocalTime) #

gmapT :: (forall b. Data b => b -> b) -> LocalTime -> LocalTime #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LocalTime -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LocalTime -> r #

gmapQ :: (forall d. Data d => d -> u) -> LocalTime -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LocalTime -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LocalTime -> m LocalTime #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LocalTime -> m LocalTime #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LocalTime -> m LocalTime #

Ord LocalTime 
Instance details

Defined in Data.Time.LocalTime.Internal.LocalTime

Show LocalTime 
Instance details

Defined in Data.Time.LocalTime.Internal.LocalTime

NFData LocalTime 
Instance details

Defined in Data.Time.LocalTime.Internal.LocalTime

Methods

rnf :: LocalTime -> () #

FormatTime LocalTime 
Instance details

Defined in Data.Time.Format

ParseTime LocalTime 
Instance details

Defined in Data.Time.Format.Parse

timeOfDayToDayFraction :: TimeOfDay -> Rational #

Get the fraction of a day since midnight given a time of day.

dayFractionToTimeOfDay :: Rational -> TimeOfDay #

Get the time of day given the fraction of a day since midnight.

timeOfDayToTime :: TimeOfDay -> DiffTime #

Get the time since midnight for a given time of day.

timeToTimeOfDay :: DiffTime -> TimeOfDay #

Get the time of day given a time since midnight. Time more than 24h will be converted to leap-seconds.

localToUTCTimeOfDay :: TimeZone -> TimeOfDay -> (Integer, TimeOfDay) #

Convert a time of day in some timezone to a time of day in UTC, together with a day adjustment.

utcToLocalTimeOfDay :: TimeZone -> TimeOfDay -> (Integer, TimeOfDay) #

Convert a time of day in UTC to a time of day in some timezone, together with a day adjustment.

midday :: TimeOfDay #

Hour twelve

midnight :: TimeOfDay #

Hour zero

data TimeOfDay #

Time of day as represented in hour, minute and second (with picoseconds), typically used to express local time of day.

Constructors

TimeOfDay 

Fields

  • todHour :: Int

    range 0 - 23

  • todMin :: Int

    range 0 - 59

  • todSec :: Pico

    Note that 0 <= todSec < 61, accomodating leap seconds. Any local minute may have a leap second, since leap seconds happen in all zones simultaneously

Instances
Eq TimeOfDay 
Instance details

Defined in Data.Time.LocalTime.Internal.TimeOfDay

Data TimeOfDay 
Instance details

Defined in Data.Time.LocalTime.Internal.TimeOfDay

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TimeOfDay -> c TimeOfDay #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TimeOfDay #

toConstr :: TimeOfDay -> Constr #

dataTypeOf :: TimeOfDay -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TimeOfDay) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TimeOfDay) #

gmapT :: (forall b. Data b => b -> b) -> TimeOfDay -> TimeOfDay #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TimeOfDay -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TimeOfDay -> r #

gmapQ :: (forall d. Data d => d -> u) -> TimeOfDay -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TimeOfDay -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TimeOfDay -> m TimeOfDay #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TimeOfDay -> m TimeOfDay #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TimeOfDay -> m TimeOfDay #

Ord TimeOfDay 
Instance details

Defined in Data.Time.LocalTime.Internal.TimeOfDay

Show TimeOfDay 
Instance details

Defined in Data.Time.LocalTime.Internal.TimeOfDay

NFData TimeOfDay 
Instance details

Defined in Data.Time.LocalTime.Internal.TimeOfDay

Methods

rnf :: TimeOfDay -> () #

FormatTime TimeOfDay 
Instance details

Defined in Data.Time.Format

ParseTime TimeOfDay 
Instance details

Defined in Data.Time.Format.Parse

utc :: TimeZone #

The UTC time zone.

timeZoneOffsetString :: TimeZone -> String #

Text representing the offset of this timezone, such as "-0800" or "+0400" (like %z in formatTime).

timeZoneOffsetString' :: Maybe Char -> TimeZone -> String #

Text representing the offset of this timezone, such as "-0800" or "+0400" (like %z in formatTime), with arbitrary padding.

hoursToTimeZone :: Int -> TimeZone #

Create a nameless non-summer timezone for this number of hours.

minutesToTimeZone :: Int -> TimeZone #

Create a nameless non-summer timezone for this number of minutes.

data TimeZone #

A TimeZone is a whole number of minutes offset from UTC, together with a name and a "just for summer" flag.

Constructors

TimeZone 

Fields

Instances
Eq TimeZone 
Instance details

Defined in Data.Time.LocalTime.Internal.TimeZone

Data TimeZone 
Instance details

Defined in Data.Time.LocalTime.Internal.TimeZone

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TimeZone -> c TimeZone #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TimeZone #

toConstr :: TimeZone -> Constr #

dataTypeOf :: TimeZone -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TimeZone) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TimeZone) #

gmapT :: (forall b. Data b => b -> b) -> TimeZone -> TimeZone #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TimeZone -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TimeZone -> r #

gmapQ :: (forall d. Data d => d -> u) -> TimeZone -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TimeZone -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TimeZone -> m TimeZone #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TimeZone -> m TimeZone #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TimeZone -> m TimeZone #

Ord TimeZone 
Instance details

Defined in Data.Time.LocalTime.Internal.TimeZone

Show TimeZone 
Instance details

Defined in Data.Time.LocalTime.Internal.TimeZone

NFData TimeZone 
Instance details

Defined in Data.Time.LocalTime.Internal.TimeZone

Methods

rnf :: TimeZone -> () #

FormatTime TimeZone 
Instance details

Defined in Data.Time.Format

ParseTime TimeZone 
Instance details

Defined in Data.Time.Format.Parse

diffUTCTime :: UTCTime -> UTCTime -> NominalDiffTime #

diffUTCTime a b = a - b

addUTCTime :: NominalDiffTime -> UTCTime -> UTCTime #

addUTCTime a b = a + b

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 
Instances
Eq UniversalTime 
Instance details

Defined in Data.Time.Clock.Internal.UniversalTime

Data UniversalTime 
Instance details

Defined in Data.Time.Clock.Internal.UniversalTime

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UniversalTime -> c UniversalTime #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UniversalTime #

toConstr :: UniversalTime -> Constr #

dataTypeOf :: UniversalTime -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c UniversalTime) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UniversalTime) #

gmapT :: (forall b. Data b => b -> b) -> UniversalTime -> UniversalTime #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UniversalTime -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UniversalTime -> r #

gmapQ :: (forall d. Data d => d -> u) -> UniversalTime -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UniversalTime -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UniversalTime -> m UniversalTime #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UniversalTime -> m UniversalTime #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UniversalTime -> m UniversalTime #

Ord UniversalTime 
Instance details

Defined in Data.Time.Clock.Internal.UniversalTime

NFData UniversalTime 
Instance details

Defined in Data.Time.Clock.Internal.UniversalTime

Methods

rnf :: UniversalTime -> () #

FormatTime UniversalTime 
Instance details

Defined in Data.Time.Format

ParseTime UniversalTime 
Instance details

Defined in Data.Time.Format.Parse

data 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 
Instance details

Defined in Data.Time.Clock.Internal.UTCTime

Methods

(==) :: UTCTime -> UTCTime -> Bool #

(/=) :: UTCTime -> UTCTime -> Bool #

Data UTCTime 
Instance details

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 
Instance details

Defined in Data.Time.Clock.Internal.UTCTime

NFData UTCTime 
Instance details

Defined in Data.Time.Clock.Internal.UTCTime

Methods

rnf :: UTCTime -> () #

FormatTime UTCTime 
Instance details

Defined in Data.Time.Format

ParseTime UTCTime 
Instance details

Defined in Data.Time.Format.Parse

getTime_resolution :: DiffTime #

The resolution of getSystemTime, getCurrentTime, getPOSIXTime

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
Enum NominalDiffTime 
Instance details

Defined in Data.Time.Clock.Internal.NominalDiffTime

Eq NominalDiffTime 
Instance details

Defined in Data.Time.Clock.Internal.NominalDiffTime

Fractional NominalDiffTime 
Instance details

Defined in Data.Time.Clock.Internal.NominalDiffTime

Data NominalDiffTime 
Instance details

Defined in Data.Time.Clock.Internal.NominalDiffTime

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NominalDiffTime -> c NominalDiffTime #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NominalDiffTime #

toConstr :: NominalDiffTime -> Constr #

dataTypeOf :: NominalDiffTime -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NominalDiffTime) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NominalDiffTime) #

gmapT :: (forall b. Data b => b -> b) -> NominalDiffTime -> NominalDiffTime #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NominalDiffTime -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NominalDiffTime -> r #

gmapQ :: (forall d. Data d => d -> u) -> NominalDiffTime -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NominalDiffTime -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NominalDiffTime -> m NominalDiffTime #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NominalDiffTime -> m NominalDiffTime #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NominalDiffTime -> m NominalDiffTime #

Num NominalDiffTime 
Instance details

Defined in Data.Time.Clock.Internal.NominalDiffTime

Ord NominalDiffTime 
Instance details

Defined in Data.Time.Clock.Internal.NominalDiffTime

Real NominalDiffTime 
Instance details

Defined in Data.Time.Clock.Internal.NominalDiffTime

RealFrac NominalDiffTime 
Instance details

Defined in Data.Time.Clock.Internal.NominalDiffTime

Show NominalDiffTime 
Instance details

Defined in Data.Time.Clock.Internal.NominalDiffTime

NFData NominalDiffTime 
Instance details

Defined in Data.Time.Clock.Internal.NominalDiffTime

Methods

rnf :: NominalDiffTime -> () #

diffTimeToPicoseconds :: DiffTime -> Integer #

Get the number of picoseconds in a DiffTime.

picosecondsToDiffTime :: Integer -> DiffTime #

Create a DiffTime from a number of picoseconds.

secondsToDiffTime :: Integer -> DiffTime #

Create a DiffTime which represents an integral number of seconds.

data 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 
Instance details

Defined in Data.Time.Clock.Internal.DiffTime

Eq DiffTime 
Instance details

Defined in Data.Time.Clock.Internal.DiffTime

Fractional DiffTime 
Instance details

Defined in Data.Time.Clock.Internal.DiffTime

Data DiffTime 
Instance details

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 
Instance details

Defined in Data.Time.Clock.Internal.DiffTime

Ord DiffTime 
Instance details

Defined in Data.Time.Clock.Internal.DiffTime

Real DiffTime 
Instance details

Defined in Data.Time.Clock.Internal.DiffTime

RealFrac DiffTime 
Instance details

Defined in Data.Time.Clock.Internal.DiffTime

Methods

properFraction :: Integral b => DiffTime -> (b, DiffTime) #

truncate :: Integral b => DiffTime -> b #

round :: Integral b => DiffTime -> b #

ceiling :: Integral b => DiffTime -> b #

floor :: Integral b => DiffTime -> b #

Show DiffTime 
Instance details

Defined in Data.Time.Clock.Internal.DiffTime

NFData DiffTime 
Instance details

Defined in Data.Time.Clock.Internal.DiffTime

Methods

rnf :: DiffTime -> () #

addGregorianYearsRollOver :: Integer -> Day -> Day #

Add years, matching month and day, with Feb 29th rolled over to Mar 1st if necessary. For instance, 2004-02-29 + 2 years = 2006-03-01.

addGregorianYearsClip :: Integer -> Day -> Day #

Add years, matching month and day, with Feb 29th clipped to Feb 28th if necessary. For instance, 2004-02-29 + 2 years = 2006-02-28.

addGregorianMonthsRollOver :: Integer -> Day -> Day #

Add months, with days past the last day of the month rolling over to the next month. For instance, 2005-01-30 + 1 month = 2005-03-02.

addGregorianMonthsClip :: Integer -> Day -> Day #

Add months, with days past the last day of the month clipped to the last day. For instance, 2005-01-30 + 1 month = 2005-02-28.

gregorianMonthLength :: Integer -> Int -> Int #

The number of days in a given month according to the proleptic Gregorian calendar. First argument is year, second is month.

showGregorian :: Day -> String #

Show in ISO 8601 format (yyyy-mm-dd)

fromGregorianValid :: Integer -> Int -> Int -> Maybe Day #

Convert from proleptic Gregorian calendar. First argument is year, second month number (1-12), third day (1-31). Invalid values will return Nothing

fromGregorian :: Integer -> Int -> Int -> Day #

Convert from proleptic Gregorian calendar. First argument is year, second month number (1-12), third day (1-31). Invalid values will be clipped to the correct range, month first, then day.

toGregorian :: Day -> (Integer, Int, Int) #

Convert to proleptic Gregorian calendar. First element of result is year, second month number (1-12), third day (1-31).

isLeapYear :: Integer -> Bool #

Is this year a leap year according to the proleptic Gregorian calendar?

newtype Day #

The Modified Julian Day is a standard count of days, with zero being the day 1858-11-17.

Instances
Enum Day 
Instance details

Defined in Data.Time.Calendar.Days

Methods

succ :: Day -> Day #

pred :: Day -> Day #

toEnum :: Int -> Day #

fromEnum :: Day -> Int #

enumFrom :: Day -> [Day] #

enumFromThen :: Day -> Day -> [Day] #

enumFromTo :: Day -> Day -> [Day] #

enumFromThenTo :: Day -> Day -> Day -> [Day] #

Eq Day 
Instance details

Defined in Data.Time.Calendar.Days

Methods

(==) :: Day -> Day -> Bool #

(/=) :: Day -> Day -> Bool #

Data Day 
Instance details

Defined in Data.Time.Calendar.Days

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Day -> c Day #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Day #

toConstr :: Day -> Constr #

dataTypeOf :: Day -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Day) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Day) #

gmapT :: (forall b. Data b => b -> b) -> Day -> Day #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Day -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Day -> r #

gmapQ :: (forall d. Data d => d -> u) -> Day -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Day -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Day -> m Day #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Day -> m Day #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Day -> m Day #

Ord Day 
Instance details

Defined in Data.Time.Calendar.Days

Methods

compare :: Day -> Day -> Ordering #

(<) :: Day -> Day -> Bool #

(<=) :: Day -> Day -> Bool #

(>) :: Day -> Day -> Bool #

(>=) :: Day -> Day -> Bool #

max :: Day -> Day -> Day #

min :: Day -> Day -> Day #

Ix Day 
Instance details

Defined in Data.Time.Calendar.Days

Methods

range :: (Day, Day) -> [Day] #

index :: (Day, Day) -> Day -> Int #

unsafeIndex :: (Day, Day) -> Day -> Int

inRange :: (Day, Day) -> Day -> Bool #

rangeSize :: (Day, Day) -> Int #

unsafeRangeSize :: (Day, Day) -> Int

NFData Day 
Instance details

Defined in Data.Time.Calendar.Days

Methods

rnf :: Day -> () #

FormatTime Day 
Instance details

Defined in Data.Time.Format

ParseTime Day 
Instance details

Defined in Data.Time.Format.Parse

Methods

buildTime :: TimeLocale -> [(Char, String)] -> Maybe Day #