tz-0.1.3.6: Efficient time zone handling
Copyright(C) 2014 Mihaly Barasz
LicenseApache-2.0, see LICENSE
MaintainerJanus Troelsen <ysangkok@gmail.com>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Data.Time.Zones

Description

 
Synopsis

Documentation

data TZ Source #

Instances

Instances details
Eq TZ Source # 
Instance details

Defined in Data.Time.Zones.Types

Methods

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

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

Data TZ Source # 
Instance details

Defined in Data.Time.Zones.Types

Methods

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

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

toConstr :: TZ -> Constr #

dataTypeOf :: TZ -> DataType #

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

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

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

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

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

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

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

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

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

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

Read TZ Source # 
Instance details

Defined in Data.Time.Zones.Types

Show TZ Source # 
Instance details

Defined in Data.Time.Zones.Types

Methods

showsPrec :: Int -> TZ -> ShowS #

show :: TZ -> String #

showList :: [TZ] -> ShowS #

Default TZ Source # 
Instance details

Defined in Data.Time.Zones.Types

Methods

def :: TZ #

NFData TZ Source # 
Instance details

Defined in Data.Time.Zones.Types

Methods

rnf :: TZ -> () #

utcTZ :: TZ Source #

The TZ definition for UTC.

Universal -> Local direction

diffForPOSIX :: TZ -> Int64 -> Int Source #

Returns the time difference (in seconds) for TZ at the given POSIX time.

timeZoneForPOSIX :: TZ -> Int64 -> TimeZone Source #

Returns the TimeZone for the TZ at the given POSIX time.

timeZoneForUTCTime :: TZ -> UTCTime -> TimeZone Source #

Returns the TimeZone for the TZ at the given UTCTime.

utcToLocalTimeTZ :: TZ -> UTCTime -> LocalTime Source #

Returns the LocalTime corresponding to the given UTCTime in TZ.

utcToLocalTimeTZ tz ut is equivalent to utcToLocalTime (timeZoneForPOSIX tz ut) ut except when the time difference is not an integral number of minutes

Local -> Universal direction

data LocalToUTCResult Source #

Fully descriptive result of a LocalTime to UTCTime conversion.

In case of LTUAmbiguous the first result is always earlier than the second one. Generally this only happens during the daylight saving -> standard time transition (ie. summer -> winter). So, the first result corresponds to interpreting the LocalTime as a daylight saving time and the second result as standard time in the given location.

But, if the location had some kind of administrative time transition during which the clocks jumped back, then both results can correspond to standard times (or daylight saving times) just before and after the transition. You can always inspect the timeZoneSummerOnly field of the returned TimeZones to get an idea what kind of transition was taking place.

TODO(klao): document the LTUNone behavior.

Instances

Instances details
Eq LocalToUTCResult Source # 
Instance details

Defined in Data.Time.Zones

Data LocalToUTCResult Source # 
Instance details

Defined in Data.Time.Zones

Methods

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

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

toConstr :: LocalToUTCResult -> Constr #

dataTypeOf :: LocalToUTCResult -> DataType #

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

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

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

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

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

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

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

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

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

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

Read LocalToUTCResult Source # 
Instance details

Defined in Data.Time.Zones

Show LocalToUTCResult Source # 
Instance details

Defined in Data.Time.Zones

NFData LocalToUTCResult Source # 
Instance details

Defined in Data.Time.Zones

Methods

rnf :: LocalToUTCResult -> () #

data FromLocal Source #

Internal representation of LocalTime -> UTCTime conversion result:

Constructors

FLGap 

Fields

FLUnique 

Fields

FLDouble 

Fields

Instances

Instances details
Eq FromLocal Source # 
Instance details

Defined in Data.Time.Zones

Data FromLocal Source # 
Instance details

Defined in Data.Time.Zones

Methods

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

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

toConstr :: FromLocal -> Constr #

dataTypeOf :: FromLocal -> DataType #

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

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

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

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

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

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

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

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

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

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

Read FromLocal Source # 
Instance details

Defined in Data.Time.Zones

Show FromLocal Source # 
Instance details

Defined in Data.Time.Zones

NFData FromLocal Source # 
Instance details

Defined in Data.Time.Zones

Methods

rnf :: FromLocal -> () #

Acquiring TZ information

loadTZFromFile :: FilePath -> IO TZ Source #

Reads and parses a time zone information file (in tzfile(5) aka. Olson file format) and returns the corresponding TZ data structure.

loadTZFromDB :: String -> IO TZ Source #

Reads the corresponding file from the time zone database shipped with this package.

loadSystemTZ :: String -> IO TZ Source #

Looks for the time zone file in the system timezone directory, which is /usr/share/zoneinfo, or if the TZDIR environment variable is set, then there.

Note, this is unlikely to work on non-posix systems (e.g., Windows), use loadTZFromDB or loadTZFromFile instead.

loadLocalTZ :: IO TZ Source #

Returns the local TZ based on the TZ and TZDIR environment variables.

See tzset(3) for details, but basically:

  • If TZ environment variable is unset, we loadTZFromFile "/etc/localtime".
  • If TZ is set, but empty, we loadSystemTZ "UTC".
  • Otherwise, we just loadSystemTZ it.

Note, this means we don't support POSIX-style TZ variables (like "EST5EDT"), only those that are explicitly present in the time zone database.

Utilities

diffForAbbr :: TZ -> String -> Maybe Int Source #

Returns a time difference (in seconds) corresponding to the abbreviation in the given time zone.

If there are multiple time differences associated with the same abbreviation, the one corresponding to the latest use is returned. (The latest use might be in the past or the future depending on whether the abbreviation is still in use.)

This function is here for informational purpose only, do not use it for time conversion. (Instead, use localTimeToUTCFull, and if the result is ambiguous disambiguate between the possible results based on the abbreviation.)