| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Data.Time.LocalTime
Synopsis
- data TimeZone = TimeZone {}
- timeZoneOffsetString :: TimeZone -> String
- timeZoneOffsetString' :: Maybe Char -> TimeZone -> String
- minutesToTimeZone :: Int -> TimeZone
- hoursToTimeZone :: Int -> TimeZone
- utc :: TimeZone
- getTimeZone :: UTCTime -> IO TimeZone
- getCurrentTimeZone :: IO TimeZone
- data TimeOfDay = TimeOfDay {}
- midnight :: TimeOfDay
- midday :: TimeOfDay
- makeTimeOfDayValid :: Int -> Int -> Pico -> Maybe TimeOfDay
- timeToDaysAndTimeOfDay :: NominalDiffTime -> (Integer, TimeOfDay)
- daysAndTimeOfDayToTime :: Integer -> TimeOfDay -> NominalDiffTime
- utcToLocalTimeOfDay :: TimeZone -> TimeOfDay -> (Integer, TimeOfDay)
- localToUTCTimeOfDay :: TimeZone -> TimeOfDay -> (Integer, TimeOfDay)
- timeToTimeOfDay :: DiffTime -> TimeOfDay
- pastMidnight :: DiffTime -> TimeOfDay
- timeOfDayToTime :: TimeOfDay -> DiffTime
- sinceMidnight :: TimeOfDay -> DiffTime
- dayFractionToTimeOfDay :: Rational -> TimeOfDay
- timeOfDayToDayFraction :: TimeOfDay -> Rational
- data CalendarDiffTime = CalendarDiffTime {
- ctMonths :: Integer
- ctTime :: NominalDiffTime
- calendarTimeDays :: CalendarDiffDays -> CalendarDiffTime
- calendarTimeTime :: NominalDiffTime -> CalendarDiffTime
- scaleCalendarDiffTime :: Integer -> CalendarDiffTime -> CalendarDiffTime
- data LocalTime = LocalTime {
- localDay :: Day
- localTimeOfDay :: TimeOfDay
- addLocalTime :: NominalDiffTime -> LocalTime -> LocalTime
- diffLocalTime :: LocalTime -> LocalTime -> NominalDiffTime
- utcToLocalTime :: TimeZone -> UTCTime -> LocalTime
- localTimeToUTC :: TimeZone -> LocalTime -> UTCTime
- ut1ToLocalTime :: Rational -> UniversalTime -> LocalTime
- localTimeToUT1 :: Rational -> LocalTime -> UniversalTime
- data ZonedTime = ZonedTime {}
- utcToZonedTime :: TimeZone -> UTCTime -> ZonedTime
- zonedTimeToUTC :: ZonedTime -> UTCTime
- getZonedTime :: IO ZonedTime
- utcToLocalZonedTime :: UTCTime -> IO ZonedTime
Time zones
A TimeZone is a whole number of minutes offset from UTC, together with a name and a "just for summer" flag.
Constructors
Fields
- timeZoneMinutes :: Int
The number of minutes offset from UTC. Positive means local time will be later in the day than UTC.
- timeZoneSummerOnly :: Bool
Is this time zone just persisting for the summer?
- timeZoneName :: String
The name of the zone, typically a three- or four-letter acronym.
Instances
Instances details
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 :: forall r r'. (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 #
Instance details
Defined in Data.Time.LocalTime.Internal.TimeZone
This only works for ±HHMM format,
single-letter military time-zones,
and these time-zones: "UTC", "UT", "GMT", "EST", "EDT", "CST", "CDT", "MST", "MDT", "PST", "PDT",
per RFC 822 section 5.
Instance details
Defined in Data.Time.Format.Parse.Instances
Methods
substituteTimeSpecifier :: Proxy TimeZone -> TimeLocale -> Char -> Maybe String Source #
parseTimeSpecifier :: Proxy TimeZone -> TimeLocale -> Maybe ParseNumericPadding -> Char -> ReadP String Source #
buildTime :: TimeLocale -> [(Char, String)] -> Maybe TimeZone Source #
Instance details
Defined in Data.Time.Format.Format.Instances
Methods
formatCharacter :: Bool -> Char -> Maybe (FormatOptions -> TimeZone -> String) Source #
timeZoneOffsetString :: TimeZone -> String Source #
Text representing the offset of this timezone, such as "-0800" or "+0400" (like %z in formatTime).
timeZoneOffsetString' :: Maybe Char -> TimeZone -> String Source #
Text representing the offset of this timezone, such as "-0800" or "+0400" (like %z in formatTime), with arbitrary padding.
minutesToTimeZone :: Int -> TimeZone Source #
Create a nameless non-summer timezone for this number of minutes.
hoursToTimeZone :: Int -> TimeZone Source #
Create a nameless non-summer timezone for this number of hours.
getTimeZone :: UTCTime -> IO TimeZone Source #
Get the configured time-zone for a given time (varying as per summertime adjustments).
On Unix systems the output of this function depends on:
- The value of
TZenvironment variable (if set) - The system time zone (usually configured by
/etc/localtimesymlink)
For details see tzset(3) and localtime(3).
Example:
> let t =UTCTime(fromGregorian2021 7 1) 0 >getTimeZonet CEST >setEnv"TZ" "America/New_York" >>getTimeZonet EDT >setEnv"TZ" "Europe/Berlin" >>getTimeZonet CEST
On Windows systems the output of this function depends on:
- The value of
TZenvironment variable (if set). See here for how Windows interprets this variable. - The system time zone, configured in Settings
getCurrentTimeZone :: IO TimeZone Source #
Get the configured time-zone for the current time.
Time of day
Time of day as represented in hour, minute and second (with picoseconds), typically used to express local time of day.
TimeOfDay 24 0 0 is considered invalid for the purposes of makeTimeOfDayValid , as well as reading and parsing,
but valid for ISO 8601 parsing in Data.Time.Format.ISO8601.
Constructors
Instances
Instances details
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 :: forall r r'. (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 #
Instance details
Defined in Data.Time.LocalTime.Internal.TimeOfDay
Instance details
Defined in Data.Time.Format.Parse.Instances
Methods
substituteTimeSpecifier :: Proxy TimeOfDay -> TimeLocale -> Char -> Maybe String Source #
parseTimeSpecifier :: Proxy TimeOfDay -> TimeLocale -> Maybe ParseNumericPadding -> Char -> ReadP String Source #
buildTime :: TimeLocale -> [(Char, String)] -> Maybe TimeOfDay Source #
Instance details
Defined in Data.Time.Format.Format.Instances
Methods
formatCharacter :: Bool -> Char -> Maybe (FormatOptions -> TimeOfDay -> String) Source #
hh:mm:ss[.sss] (ISO 8601:2004(E) sec. 4.2.2.2, 4.2.2.4(a) extended format)
timeToDaysAndTimeOfDay :: NominalDiffTime -> (Integer, TimeOfDay) Source #
Convert a period of time into a count of days and a time of day since midnight. The time of day will never have a leap second.
daysAndTimeOfDayToTime :: Integer -> TimeOfDay -> NominalDiffTime Source #
Convert a count of days and a time of day since midnight into a period of time.
utcToLocalTimeOfDay :: TimeZone -> TimeOfDay -> (Integer, TimeOfDay) Source #
Convert a time of day in UTC to a time of day in some timezone, together with a day adjustment.
localToUTCTimeOfDay :: TimeZone -> TimeOfDay -> (Integer, TimeOfDay) Source #
Convert a time of day in some timezone to a time of day in UTC, together with a day adjustment.
timeToTimeOfDay :: DiffTime -> TimeOfDay Source #
Get the time of day given a time since midnight. Time more than 24h will be converted to leap-seconds.
pastMidnight :: DiffTime -> TimeOfDay Source #
Same as timeToTimeOfDay .
timeOfDayToTime :: TimeOfDay -> DiffTime Source #
Get the time since midnight for a given time of day.
sinceMidnight :: TimeOfDay -> DiffTime Source #
Same as timeOfDayToTime .
dayFractionToTimeOfDay :: Rational -> TimeOfDay Source #
Get the time of day given the fraction of a day since midnight.
timeOfDayToDayFraction :: TimeOfDay -> Rational Source #
Get the fraction of a day since midnight given a time of day.
Calendar Duration
data CalendarDiffTime Source #
Instances
Instances details
Instance details
Defined in Data.Time.LocalTime.Internal.CalendarDiffTime
Methods
(==) :: CalendarDiffTime -> CalendarDiffTime -> Bool #
(/=) :: CalendarDiffTime -> CalendarDiffTime -> Bool #
Instance details
Defined in Data.Time.LocalTime.Internal.CalendarDiffTime
Methods
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CalendarDiffTime -> c CalendarDiffTime #
gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CalendarDiffTime #
toConstr :: CalendarDiffTime -> Constr #
dataTypeOf :: CalendarDiffTime -> DataType #
dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CalendarDiffTime) #
dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CalendarDiffTime) #
gmapT :: (forall b. Data b => b -> b) -> CalendarDiffTime -> CalendarDiffTime #
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CalendarDiffTime -> r #
gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CalendarDiffTime -> r #
gmapQ :: (forall d. Data d => d -> u) -> CalendarDiffTime -> [u] #
gmapQi :: Int -> (forall d. Data d => d -> u) -> CalendarDiffTime -> u #
gmapM :: Monad m => (forall d. Data d => d -> m d) -> CalendarDiffTime -> m CalendarDiffTime #
gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CalendarDiffTime -> m CalendarDiffTime #
gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CalendarDiffTime -> m CalendarDiffTime #
Instance details
Defined in Data.Time.LocalTime.Internal.CalendarDiffTime
Methods
showsPrec :: Int -> CalendarDiffTime -> ShowS #
show :: CalendarDiffTime -> String #
showList :: [CalendarDiffTime] -> ShowS #
Instance details
Defined in Data.Time.LocalTime.Internal.CalendarDiffTime
Methods
(<>) :: CalendarDiffTime -> CalendarDiffTime -> CalendarDiffTime #
sconcat :: NonEmpty CalendarDiffTime -> CalendarDiffTime #
stimes :: Integral b => b -> CalendarDiffTime -> CalendarDiffTime #
Instance details
Defined in Data.Time.LocalTime.Internal.CalendarDiffTime
Methods
mappend :: CalendarDiffTime -> CalendarDiffTime -> CalendarDiffTime #
mconcat :: [CalendarDiffTime] -> CalendarDiffTime #
Instance details
Defined in Data.Time.LocalTime.Internal.CalendarDiffTime
Methods
rnf :: CalendarDiffTime -> () #
Instance details
Defined in Data.Time.Format.Parse.Instances
Methods
substituteTimeSpecifier :: Proxy CalendarDiffTime -> TimeLocale -> Char -> Maybe String Source #
parseTimeSpecifier :: Proxy CalendarDiffTime -> TimeLocale -> Maybe ParseNumericPadding -> Char -> ReadP String Source #
buildTime :: TimeLocale -> [(Char, String)] -> Maybe CalendarDiffTime Source #
Instance details
Defined in Data.Time.Format.Format.Instances
Methods
formatCharacter :: Bool -> Char -> Maybe (FormatOptions -> CalendarDiffTime -> String) Source #
scaleCalendarDiffTime :: Integer -> CalendarDiffTime -> CalendarDiffTime Source #
Scale by a factor. Note that scaleCalendarDiffTime (-1) will not perfectly invert a duration, due to variable month lengths.
Local Time
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.
Instances
Instances details
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 :: forall r r'. (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 #
Instance details
Defined in Data.Time.LocalTime.Internal.LocalTime
Instance details
Defined in Data.Time.Format.Parse.Instances
Methods
substituteTimeSpecifier :: Proxy LocalTime -> TimeLocale -> Char -> Maybe String Source #
parseTimeSpecifier :: Proxy LocalTime -> TimeLocale -> Maybe ParseNumericPadding -> Char -> ReadP String Source #
buildTime :: TimeLocale -> [(Char, String)] -> Maybe LocalTime Source #
Instance details
Defined in Data.Time.Format.Format.Instances
Methods
formatCharacter :: Bool -> Char -> Maybe (FormatOptions -> LocalTime -> String) Source #
addLocalTime :: NominalDiffTime -> LocalTime -> LocalTime Source #
addLocalTime a b = a + b
diffLocalTime :: LocalTime -> LocalTime -> NominalDiffTime Source #
diffLocalTime a b = a - b
utcToLocalTime :: TimeZone -> UTCTime -> LocalTime Source #
Get the local time of a UTC time in a time zone.
localTimeToUTC :: TimeZone -> LocalTime -> UTCTime Source #
Get the UTC time of a local time in a time zone.
ut1ToLocalTime :: Rational -> UniversalTime -> LocalTime Source #
Get the local time of a UT1 time on a particular meridian (in degrees, positive is East).
localTimeToUT1 :: Rational -> LocalTime -> UniversalTime Source #
Get the UT1 time of a local time on a particular meridian (in degrees, positive is East).
A local time together with a time zone.
There is no Eq instance for ZonedTime.
If you want to compare local times, use zonedTimeToLocalTime .
If you want to compare absolute times, use zonedTimeToUTC .
Instances
Instances details
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 :: forall r r'. (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 #
This only works for a zonedTimeZone in ±HHMM format,
single-letter military time-zones,
and these time-zones: "UTC", "UT", "GMT", "EST", "EDT", "CST", "CDT", "MST", "MDT", "PST", "PDT",
per RFC 822 section 5.
For the time zone, this only shows the name, or offset if the name is empty.
Instance details
Defined in Data.Time.Format.Parse.Instances
Methods
substituteTimeSpecifier :: Proxy ZonedTime -> TimeLocale -> Char -> Maybe String Source #
parseTimeSpecifier :: Proxy ZonedTime -> TimeLocale -> Maybe ParseNumericPadding -> Char -> ReadP String Source #
buildTime :: TimeLocale -> [(Char, String)] -> Maybe ZonedTime Source #
Instance details
Defined in Data.Time.Format.Format.Instances
Methods
formatCharacter :: Bool -> Char -> Maybe (FormatOptions -> ZonedTime -> String) Source #
yyyy-mm-ddThh:mm:ss[.sss]±hh:mm (ISO 8601:2004(E) sec. 4.3.2 extended format)
zonedTimeToUTC :: ZonedTime -> UTCTime Source #