Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data TZTime = UnsafeTZTime {}
- tzTimeLocalTime :: TZTime -> LocalTime
- tzTimeTZInfo :: TZTime -> TZInfo
- tzTimeOffset :: TZTime -> TimeZone
- fromUTC :: TZInfo -> UTCTime -> TZTime
- fromPOSIXTime :: TZInfo -> POSIXTime -> TZTime
- fromZonedTime :: TZInfo -> ZonedTime -> TZTime
- data TZError
- fromLocalTimeStrict :: MonadError TZError m => TZInfo -> LocalTime -> m TZTime
- fromLocalTime :: TZInfo -> LocalTime -> TZTime
- fromLocalTimeThrow :: MonadThrow m => TZInfo -> LocalTime -> m TZTime
- unsafeFromLocalTime :: HasCallStack => TZInfo -> LocalTime -> TZTime
- toUTC :: TZTime -> UTCTime
- toPOSIXTime :: TZTime -> POSIXTime
- toZonedTime :: TZTime -> ZonedTime
- inTZ :: TZInfo -> TZTime -> TZTime
- modifyUniversalTimeLine :: (UTCTime -> UTCTime) -> TZTime -> TZTime
- modifyLocalTimeLine :: MonadError TZError m => (LocalTime -> LocalTime) -> TZTime -> m TZTime
- readComponentsP :: ReadP (LocalTime, Maybe TimeZone, TZIdentifier)
- readTZIdentP :: ReadP TZIdentifier
- getValidTZTimes :: MonadFail m => LocalTime -> TZIdentifier -> m (NonEmpty TZTime)
- checkOffset :: MonadFail m => Maybe TimeZone -> NonEmpty TZTime -> m (NonEmpty TZTime)
- mkSuggestions :: NonEmpty TZTime -> String
- readP_to_Q :: String -> ReadP a -> Q a
- liftTZTime :: Quote m => TZTime -> Code m TZTime
- liftLocalTime :: Quote m => LocalTime -> Code m LocalTime
- liftTimeZone :: Quote m => TimeZone -> Code m TimeZone
Documentation
A valid and unambiguous point in time in some time zone.
Instances
Data TZTime Source # | |
Defined in Data.Time.TZTime.Internal 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 # | |
Read TZTime Source # |
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 |
Show TZTime Source # |
|
NFData TZTime Source # | |
Defined in Data.Time.TZTime.Internal | |
Eq TZTime Source # | |
HasField "tzTimeLocalTime" TZTime LocalTime Source # | Since: 0.1.1.0 |
Defined in Data.Time.TZTime.Internal | |
HasField "tzTimeOffset" TZTime TimeZone Source # | Since: 0.1.1.0 |
Defined in Data.Time.TZTime.Internal | |
HasField "tzTimeTZInfo" TZTime TZInfo Source # | Since: 0.1.1.0 |
Defined in Data.Time.TZTime.Internal | |
type Rep TZTime Source # | |
Defined in Data.Time.TZTime.Internal type Rep TZTime = D1 ('MetaData "TZTime" "Data.Time.TZTime.Internal" "tztime-0.1.1.0-inplace" '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)))) |
tzTimeOffset :: TZTime -> TimeZone Source #
The offset observed in this time zone at this moment in time.
fromZonedTime :: TZInfo -> ZonedTime -> TZTime Source #
Converts a ZonedTime
to UTC and then to the given time zone.
Instances
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.
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).
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 TZTime
s.
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
.