tztime-0.1.1.0: Safe timezone-aware handling of time.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Time.TZTime

Synopsis

TZTime

data TZTime Source #

A valid and unambiguous point in time in some time zone.

Instances

Instances details
Data TZTime Source # 
Instance details

Defined in Data.Time.TZTime.Internal

Methods

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

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

toConstr :: TZTime -> Constr #

dataTypeOf :: TZTime -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic TZTime Source # 
Instance details

Defined in Data.Time.TZTime.Internal

Associated Types

type Rep TZTime :: Type -> Type #

Methods

from :: TZTime -> Rep TZTime x #

to :: Rep TZTime x -> TZTime #

Read TZTime Source #

yyyy-mm-dd hh:mm:ss[.sss] [±hh:mm] [time zone]. Example: 2022-03-04 02:02:01 +01:00 [Europe/Rome].

The offset is optional, except when the local time is ambiguous (i.e. when the clocks are set forward around that time in that time zone).

The offset can also be expressed using military time zone abbreviations, and these time zones abbreviations as per RFC 822 section 5: "UTC", "UT", "GMT", "EST", "EDT", "CST", "CDT", "MST", "MDT", "PST", "PDT".

Note: the time zone's rules are loaded from the embedded database using fromIdentifier.

Instance details

Defined in Data.Time.TZTime.Internal

Show TZTime Source #

yyyy-mm-dd hh:mm:ss[.sss] ±hh:mm [time zone]. Example: 2022-03-04 02:02:01 +01:00 [Europe/Rome].

Instance details

Defined in Data.Time.TZTime.Internal

NFData TZTime Source # 
Instance details

Defined in Data.Time.TZTime.Internal

Methods

rnf :: TZTime -> () #

Eq TZTime Source # 
Instance details

Defined in Data.Time.TZTime.Internal

Methods

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

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

HasField "tzTimeLocalTime" TZTime LocalTime Source #

Since: 0.1.1.0

Instance details

Defined in Data.Time.TZTime.Internal

Methods

getField :: TZTime -> LocalTime #

HasField "tzTimeOffset" TZTime TimeZone Source #

Since: 0.1.1.0

Instance details

Defined in Data.Time.TZTime.Internal

Methods

getField :: TZTime -> TimeZone #

HasField "tzTimeTZInfo" TZTime TZInfo Source #

Since: 0.1.1.0

Instance details

Defined in Data.Time.TZTime.Internal

Methods

getField :: TZTime -> TZInfo #

type Rep TZTime Source # 
Instance details

Defined in Data.Time.TZTime.Internal

type Rep TZTime = D1 ('MetaData "TZTime" "Data.Time.TZTime.Internal" "tztime-0.1.1.0-AlwWFgZtNspHPa4GB9WvU4" 'False) (C1 ('MetaCons "UnsafeTZTime" 'PrefixI 'True) (S1 ('MetaSel ('Just "tztLocalTime") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 LocalTime) :*: (S1 ('MetaSel ('Just "tztTZInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 TZInfo) :*: S1 ('MetaSel ('Just "tztOffset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 TimeZone))))

tzTimeLocalTime :: TZTime -> LocalTime Source #

The local time of this TZTime.

tzTimeTZInfo :: TZTime -> TZInfo Source #

The time zone of this TZTime.

tzTimeOffset :: TZTime -> TimeZone Source #

The offset observed in this time zone at this moment in time.

Constructors

getCurrentTZTime :: IO TZTime Source #

Returns the current time with the local time zone information based on the TZ and TZDIR environment variables.

See tzset(3) for details, but basically:

  • If TZ environment variable is unset, we use /etc/localtime.
  • If TZ is set, but empty, we use utc.
  • If TZ is set and not empty, we use loadFromSystem to read that file.

fromUTC :: TZInfo -> UTCTime -> TZTime Source #

Converts a UTCTime to the given time zone.

fromPOSIXTime :: TZInfo -> POSIXTime -> TZTime Source #

Converts a POSIXTime to the given time zone.

fromZonedTime :: TZInfo -> ZonedTime -> TZTime Source #

Converts a ZonedTime to UTC and then to the given time zone.

From LocalTime

fromLocalTime :: TZInfo -> LocalTime -> TZTime Source #

Constructs a TZTime from a local time in the given time zone.

  • If the local time lands on a "gap" (e.g. when the clocks are set forward in spring and a local time is skipped), we shift the time forward by the duration of the gap.
  • If it lands on an "overlap" (e.g. when the clocks are set back in autumn and a local time happens twice), we use the earliest offset.

fromLocalTimeStrict :: MonadError TZError m => TZInfo -> LocalTime -> m TZTime Source #

Similar to fromLocalTime, but returns a TZError if the local time is ambiguous/invalid.

fromLocalTimeThrow :: MonadThrow m => TZInfo -> LocalTime -> m TZTime Source #

Similar to fromLocalTime, but throws a TZError in MonadThrow if the local time is ambiguous/invalid.

unsafeFromLocalTime :: HasCallStack => TZInfo -> LocalTime -> TZTime Source #

Similar to fromLocalTime, but throws an error if the local time is ambiguous/invalid.

data TZError Source #

Attempted to construct a TZTime from an invalid or ambiguous LocalTime.

Constructors

TZOverlap 

Fields

  • LocalTime

    The LocalTime is ambiguous. This usually happens when the clocks are set back in autumn and a local time happens twice.

  • ~TZTime

    The first occurrence of the given LocalTime, at the earliest offset.

  • ~TZTime

    The second occurrence of the given LocalTime, at the latest offset.

TZGap 

Fields

  • LocalTime

    The LocalTime is invalid. This usually happens when the clocks are set forward in spring and a local time is skipped.

  • ~TZTime

    The given LocalTime adjusted back by the length of the gap.

  • ~TZTime

    The given LocalTime adjusted forward by the length of the gap.

Instances

Instances details
Data TZError Source # 
Instance details

Defined in Data.Time.TZTime.Internal

Methods

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

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

toConstr :: TZError -> Constr #

dataTypeOf :: TZError -> DataType #

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

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

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

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

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

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

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

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

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

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

Exception TZError Source # 
Instance details

Defined in Data.Time.TZTime.Internal

Generic TZError Source # 
Instance details

Defined in Data.Time.TZTime.Internal

Associated Types

type Rep TZError :: Type -> Type #

Methods

from :: TZError -> Rep TZError x #

to :: Rep TZError x -> TZError #

Show TZError Source # 
Instance details

Defined in Data.Time.TZTime.Internal

NFData TZError Source # 
Instance details

Defined in Data.Time.TZTime.Internal

Methods

rnf :: TZError -> () #

Eq TZError Source # 
Instance details

Defined in Data.Time.TZTime.Internal

Methods

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

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

type Rep TZError Source # 
Instance details

Defined in Data.Time.TZTime.Internal

Conversions

toUTC :: TZTime -> UTCTime Source #

Converts this moment in time to the universal time-line.

toPOSIXTime :: TZTime -> POSIXTime Source #

Converts this moment in time to a POSIX timestamp.

toZonedTime :: TZTime -> ZonedTime Source #

Converts this moment in time to a ZonedTime (discarding time zone rules).

inTZ :: TZInfo -> TZTime -> TZTime Source #

Converts this moment in time to some other time zone.

Modifying a TZTime

atEarliestOffset :: TZTime -> TZTime Source #

If this local time happens to be on an overlap, switch to the earliest of the two offsets.

>>> atEarliestOffset [tz|2022-11-06 01:30:00 -06:00 [America/Winnipeg]|]
2022-11-06 01:30:00 -05:00 [America/Winnipeg]

atLatestOffset :: TZTime -> TZTime Source #

If this local time happens to be on an overlap, switch to the latest of the two offsets.

>>> atLatestOffset [tz|2022-11-06 01:30:00 -05:00 [America/Winnipeg]|]
2022-11-06 01:30:00 -06:00 [America/Winnipeg]

atStartOfDay :: TZTime -> TZTime Source #

Changes the time to the earliest time possible on that day.

This is usually 00:00, but, if, on that day:

  • the clocks are turned, for example, from 23:59 to 01:00 and midnight is skipped, this will return 01:00.
  • the clocks are turned, for example, from 01:00 to 00:00 and midnight happens twice, this will return the first occurrence (i.e. midnight at the earliest offset).

Universal time-line

Adding seconds/minutes/hours

addTime :: NominalDiffTime -> TZTime -> TZTime Source #

Adds the given amount of seconds

>>> [tz|2022-03-04 10:15:00 [Europe/Rome]|] & addTime (hours 2 + minutes 20)
2022-03-04 12:35:00 +01:00 [Europe/Rome]

hours :: Pico -> NominalDiffTime Source #

A standard hour of 3600 seconds.

minutes :: Pico -> NominalDiffTime Source #

A standard minute of 60 seconds.

Local time-line

modifyLocal :: (LocalTime -> LocalTime) -> TZTime -> TZTime Source #

Modifies the date/time on the local time-line.

The result may:

  • Land on a "gap", e.g. when the clocks are set forward in spring and a local time is skipped. When this happens, we shift the time forward by the duration of the gap.

    For example, on the 13th, the clocks skip one hour, from 01:59 (at the -06:00 offset) straight to 03:00 (at the -05:00 offset):

    >>> [tz|2022-03-12 02:15:00 -06:00 [America/Winnipeg]|] & modifyLocal (addCalendarClip (calendarDays 1))
    2022-03-13 03:15:00 -05:00 [America/Winnipeg]
    
  • Land on an "overlap", e.g. when the clocks are set back in autumn and a local time happens twice. When this happens, we attempt to preserve the offset of the original TZTime. This ensures that modifyLocal id == id. If this is not possible, use the earliest of the two offsets.

    For example, on the 6th, the clocks are set back one hour, from 01:59 (at the -05:00 offset) back to 01:00 (at the -06:00 offset). This means the time 01:15 happens twice, first at -05:00 and then again at -06:00.

    >>> [tz|2022-11-05 01:15:00 -05:00 [America/Winnipeg]|] & modifyLocal (addCalendarClip (calendarDays 1))
    2022-11-06 01:15:00 -05:00 [America/Winnipeg]
    
    >>> [tz|2022-11-07 01:15:00 -06:00 [America/Winnipeg]|] & modifyLocal (addCalendarClip (calendarDays -1))
    2022-11-06 01:15:00 -06:00 [America/Winnipeg]
    

This behaviour should be suitable for most use cases.

Note: modifyLocal (g . f) may not always be equivalent to modifyLocal g . modifyLocal f.

If modifyLocal f lands on a gap or an overlap, the time will be corrected as described above; but there's a chance modifyLocal (g . f) would skip right over the gap/overlap and no correction is needed. As a rule of thumb, apply all modifications to the local time-line in one go.

>>> import Control.Arrow ((>>>))
>>> :{
[tz|2022-03-04 10:15:00 +01:00 [Europe/Rome]|]
  & modifyLocal (
      addCalendarClip (calendarMonths 2 <> calendarDays 3) >>>
      atFirstDayOfWeekOnAfter Wednesday >>>
      atMidnight
    )
:}
2022-05-11 00:00:00 +02:00 [Europe/Rome]

modifyLocalStrict :: MonadError TZError m => (LocalTime -> LocalTime) -> TZTime -> m TZTime Source #

Similar to modifyLocal, but returns a TZError if the result lands in a gap/overlap.

modifyLocalThrow :: MonadThrow m => (LocalTime -> LocalTime) -> TZTime -> m TZTime Source #

Similar to modifyLocal, but throws a TZError in MonadThrow if the result lands in a gap/overlap.

Adding days/weeks/months/years.

Use these with one of the modifyLocal* functions.

addCalendarClip :: CalendarDiffDays -> LocalTime -> LocalTime Source #

Add the given number of months first and then the given number of days, using the proleptic Gregorian calendar.

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

addCalendarRollOver :: CalendarDiffDays -> LocalTime -> LocalTime Source #

Add the given number of months first and then the given number of days. using the proleptic Gregorian calendar.

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

Setting date/time components.

Use these with one of the modifyLocal* functions.

atYear :: Year -> LocalTime -> LocalTime Source #

Sets the year using the proleptic Gregorian calendar.

atMonthOfYear :: MonthOfYear -> LocalTime -> LocalTime Source #

Sets the month using the proleptic Gregorian calendar. Invalid values will be clipped to the correct range.

atDayOfMonth :: DayOfMonth -> LocalTime -> LocalTime Source #

Sets the day of month using the proleptic Gregorian calendar. Invalid values will be clipped to the correct range.

atDay :: Day -> LocalTime -> LocalTime Source #

Sets the day.

atMidnight :: LocalTime -> LocalTime Source #

Sets the time to 00:00.

atFirstDayOfWeekOnAfter :: DayOfWeek -> LocalTime -> LocalTime Source #

Moves the date to the next given DayOfWeek. If the current date is already a match, then the current date is returned unmodified.

>>> tzt = [tz|2022-02-24 10:00:00 [Europe/London]|]
>>> tzt & modifyLocal (atFirstDayOfWeekOnAfter Thursday)
2022-02-24 10:00:00 +00:00 [Europe/London]
>>> tzt & modifyLocal (atFirstDayOfWeekOnAfter Wednesday)
2022-03-02 10:00:00 +00:00 [Europe/London]

Other

diffTZTime :: TZTime -> TZTime -> NominalDiffTime Source #

Calculate the difference in seconds between two points in time.