time-1.12.2: A time library
Safe HaskellSafe
LanguageHaskell2010

Data.Time.LocalTime

Contents

Synopsis

Time zones

data TimeZone Source #

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

Instances details
NFData TimeZone Source # 
Instance details

Defined in Data.Time.LocalTime.Internal.TimeZone

Methods

rnf :: TimeZone -> () Source #

Data TimeZone Source # 
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 #

Read TimeZone Source #

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

Show TimeZone Source #

This only shows the time zone name, or offset if the name is empty.

Instance details

Defined in Data.Time.LocalTime.Internal.TimeZone

Eq TimeZone Source # 
Instance details

Defined in Data.Time.LocalTime.Internal.TimeZone

Ord TimeZone Source # 
Instance details

Defined in Data.Time.LocalTime.Internal.TimeZone

FormatTime TimeZone Source # 
Instance details

Defined in Data.Time.Format.Format.Instances

ISO8601 TimeZone Source #

±hh:mm (ISO 8601:2004(E) sec. 4.2.5.1 extended format)

Instance details

Defined in Data.Time.Format.ISO8601

ParseTime TimeZone Source # 
Instance details

Defined in Data.Time.Format.Parse.Instances

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.

utc :: TimeZone Source #

The UTC time zone.

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:

  1. The value of TZ environment variable (if set)
  2. The system time zone (usually configured by /etc/localtime symlink)

For details see tzset(3) and localtime(3).

Example:

> let t = UTCTime (fromGregorian 2021 7 1) 0
> getTimeZone t
CEST
> setEnv "TZ" "America/New_York" >> getTimeZone t
EDT
> setEnv "TZ" "Europe/Berlin" >> getTimeZone t
CEST

On Windows systems the output of this function depends on:

  1. The value of TZ environment variable (if set). See here for how Windows interprets this variable.
  2. The system time zone, configured in Settings

getCurrentTimeZone :: IO TimeZone Source #

Get the configured time-zone for the current time.

data TimeOfDay Source #

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

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

Instances details
NFData TimeOfDay Source # 
Instance details

Defined in Data.Time.LocalTime.Internal.TimeOfDay

Methods

rnf :: TimeOfDay -> () Source #

Data TimeOfDay Source # 
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 #

Read TimeOfDay Source # 
Instance details

Defined in Data.Time.Format.Parse

Show TimeOfDay Source # 
Instance details

Defined in Data.Time.LocalTime.Internal.TimeOfDay

Eq TimeOfDay Source # 
Instance details

Defined in Data.Time.LocalTime.Internal.TimeOfDay

Ord TimeOfDay Source # 
Instance details

Defined in Data.Time.LocalTime.Internal.TimeOfDay

FormatTime TimeOfDay Source # 
Instance details

Defined in Data.Time.Format.Format.Instances

ISO8601 TimeOfDay Source #

hh:mm:ss[.sss] (ISO 8601:2004(E) sec. 4.2.2.2, 4.2.2.4(a) extended format)

Instance details

Defined in Data.Time.Format.ISO8601

ParseTime TimeOfDay Source # 
Instance details

Defined in Data.Time.Format.Parse.Instances

midday :: TimeOfDay Source #

Hour twelve

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.

timeOfDayToTime :: TimeOfDay -> DiffTime Source #

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

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.

data CalendarDiffTime Source #

Instances

Instances details
NFData CalendarDiffTime Source # 
Instance details

Defined in Data.Time.LocalTime.Internal.CalendarDiffTime

Methods

rnf :: CalendarDiffTime -> () Source #

Monoid CalendarDiffTime Source #

Additive

Instance details

Defined in Data.Time.LocalTime.Internal.CalendarDiffTime

Semigroup CalendarDiffTime Source #

Additive

Instance details

Defined in Data.Time.LocalTime.Internal.CalendarDiffTime

Data CalendarDiffTime Source #

Since: time-1.9.2

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 #

Show CalendarDiffTime Source # 
Instance details

Defined in Data.Time.LocalTime.Internal.CalendarDiffTime

Eq CalendarDiffTime Source # 
Instance details

Defined in Data.Time.LocalTime.Internal.CalendarDiffTime

FormatTime CalendarDiffTime Source # 
Instance details

Defined in Data.Time.Format.Format.Instances

ISO8601 CalendarDiffTime Source #

PyYmMdDThHmMs[.sss]S (ISO 8601:2004(E) sec. 4.4.3.2)

Instance details

Defined in Data.Time.Format.ISO8601

ParseTime CalendarDiffTime Source # 
Instance details

Defined in Data.Time.Format.Parse.Instances

scaleCalendarDiffTime :: Integer -> CalendarDiffTime -> CalendarDiffTime Source #

Scale by a factor. Note that scaleCalendarDiffTime (-1) will not perfectly invert a duration, due to variable month lengths.

data LocalTime Source #

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

Instances details
NFData LocalTime Source # 
Instance details

Defined in Data.Time.LocalTime.Internal.LocalTime

Methods

rnf :: LocalTime -> () Source #

Data LocalTime Source # 
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 #

Read LocalTime Source # 
Instance details

Defined in Data.Time.Format.Parse

Show LocalTime Source # 
Instance details

Defined in Data.Time.LocalTime.Internal.LocalTime

Eq LocalTime Source # 
Instance details

Defined in Data.Time.LocalTime.Internal.LocalTime

Ord LocalTime Source # 
Instance details

Defined in Data.Time.LocalTime.Internal.LocalTime

FormatTime LocalTime Source # 
Instance details

Defined in Data.Time.Format.Format.Instances

ISO8601 LocalTime Source #

yyyy-mm-ddThh:mm:ss[.sss] (ISO 8601:2004(E) sec. 4.3.2 extended format)

Instance details

Defined in Data.Time.Format.ISO8601

ParseTime LocalTime Source # 
Instance details

Defined in Data.Time.Format.Parse.Instances

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).

data ZonedTime Source #

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
NFData ZonedTime Source # 
Instance details

Defined in Data.Time.LocalTime.Internal.ZonedTime

Methods

rnf :: ZonedTime -> () Source #

Data ZonedTime Source # 
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 #

Read ZonedTime Source #

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.

Instance details

Defined in Data.Time.Format.Parse

Show ZonedTime Source #

For the time zone, this only shows the name, or offset if the name is empty.

Instance details

Defined in Data.Time.LocalTime.Internal.ZonedTime

FormatTime ZonedTime Source # 
Instance details

Defined in Data.Time.Format.Format.Instances

ISO8601 ZonedTime Source #

yyyy-mm-ddThh:mm:ss[.sss]±hh:mm (ISO 8601:2004(E) sec. 4.3.2 extended format)

Instance details

Defined in Data.Time.Format.ISO8601

ParseTime ZonedTime Source # 
Instance details

Defined in Data.Time.Format.Parse.Instances