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

Data.Time.TZTime.Internal

Synopsis

Documentation

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 #

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.0.0-KGq7AVbuMAdIORAuMR3S2S" '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.

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.

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

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

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

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.

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.

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.

modifyUniversalTimeLine :: (UTCTime -> UTCTime) -> TZTime -> TZTime Source #

Modify this moment in time along the universal time-line.

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

Modify this moment in time along the local time-line.

getValidTZTimes :: MonadFail m => LocalTime -> TZIdentifier -> m (NonEmpty TZTime) Source #

Try to construct a TZTime from the given components.

checkOffset :: MonadFail m => Maybe TimeZone -> NonEmpty TZTime -> m (NonEmpty TZTime) Source #

If the user specified an offset, check that it matches at least one of the valid TZTimes.

liftTZTime :: Quote m => TZTime -> Code m TZTime Source #

NOTE: this assumes the time zone identifier used to construct TZTime exists in the embedded time zone database, i.e. it can be loaded using fromIdentifier.