-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Efficient time zone handling -- -- The goal of this package is to provide a library that can read time -- zone info files (aka. Olson files), and does time zone conversions in -- a pure and efficient way. -- -- We also provide platform-independent and/or compiled-in access to the -- standard Time Zone Dabase by the means of the companion -- tzdata package -- http://hackage.haskell.org/package/tzdata. -- -- The package is currently in an alpha phase, I'm still experimenting -- with different ideas wrt. scope/API/implementation/etc. All comments -- are welcome! @package tz @version 0.1.3.6 module Data.Time.Zones.Internal.CoerceTH getNewTypeCon :: Name -> Q Name constructNewType :: Name -> Q Exp destructNewType :: Name -> Q Exp module Data.Time.Zones.Internal utcTimeToInt64 :: UTCTime -> Int64 utcTimeToInt64Pair :: UTCTime -> (Int64, Int64) localTimeToInt64Pair :: LocalTime -> (Int64, Int64) int64PairToUTCTime :: Int64 -> Int64 -> UTCTime int64PairToLocalTime :: Int64 -> Int64 -> LocalTime picoToInteger :: Pico -> Integer integerToPico :: Integer -> Pico diffTimeToPico :: DiffTime -> Pico picoToDiffTime :: Pico -> DiffTime diffTimeToInteger :: DiffTime -> Integer integerToDiffTime :: Integer -> DiffTime module Data.Time.Zones.Types data TZ TZ :: !Vector Int64 -> !Vector Int -> !Vector (Bool, String) -> TZ [_tzTrans] :: TZ -> !Vector Int64 [_tzDiffs] :: TZ -> !Vector Int [_tzInfos] :: TZ -> !Vector (Bool, String) -- | The TZ definition for UTC. utcTZ :: TZ instance GHC.Read.Read Data.Time.Zones.Types.TZ instance Data.Data.Data Data.Time.Zones.Types.TZ instance GHC.Show.Show Data.Time.Zones.Types.TZ instance GHC.Classes.Eq Data.Time.Zones.Types.TZ instance Control.DeepSeq.NFData Data.Time.Zones.Types.TZ instance Data.Default.Class.Default Data.Time.Zones.Types.TZ module Data.Time.Zones.Read -- | Reads and parses a time zone information file (in tzfile(5) -- aka. Olson file format) and returns the corresponding TZ data -- structure. loadTZFromFile :: FilePath -> IO TZ -- | 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. loadSystemTZ :: String -> IO TZ -- | Return the path for a time zone file in the system time zone -- directory. -- -- The system directory is specified by the TZDIR environment -- variable, or /usr/share/zoneinfo if it's not set. pathForSystemTZ :: String -> IO FilePath -- | Returns the local TZ based on the TZ and -- TZDIR environment variables. -- -- See tzset(3) for details, but basically: -- --
-- {-# LANGUAGE TemplateHaskell #-} -- -- import Data.Time -- import Data.Time.Zones -- import Data.Time.Zones.TH -- -- tzBudapest :: TZ -- tzBudapest = $(includeTZFromDB "Europe/Budapest") -- -- tzLosAngeles :: TZ -- tzLosAngeles = $(includeTZFromDB "America/Los_Angeles") -- -- main :: IO () -- main = do -- t <- getCurrentTime -- putStrLn $ "Time in Budapest: " ++ show (utcToLocalTimeTZ tzBudapest t) -- putStrLn $ "Time in Los Angeles: " ++ show (utcToLocalTimeTZ tzLosAngeles t) --module Data.Time.Zones.TH -- | Generate a TZ definition from an entry out of the time zone -- database shipped with this package. includeTZFromDB :: String -> Q Exp -- | Generate a TZ definition from a system time zone information -- file. -- -- See also: loadSystemTZ for details on how system time zone -- files are located. -- -- Note, this is unlikely to work on non-posix systems (e.g., Windows), -- use includeTZFromDB or includeTZFromFile instead. includeSystemTZ :: String -> Q Exp -- | Generate a TZ definition from the given time zone information -- file. includeTZFromFile :: FilePath -> Q Exp module Data.Time.Zones.All -- | Convert a TZLabel to the usual name of the location. -- --
-- > toTZName Europe__Paris -- "Europe/Paris" --toTZName :: TZLabel -> ByteString -- | Lookup the TZLabel by the name of the location. -- -- Returns Nothing if the location is unknown. -- --
-- > :set -XOverloadedStrings -- > fromTZName "Europe/Paris" -- Just Europe__Paris -- > fromTZName "Foo/Bar" -- Nothing --fromTZName :: ByteString -> Maybe TZLabel -- | Map mapping know time zone locations to their canonical -- TZLabels. tzNameLabelMap :: Map ByteString TZLabel -- | Lookup a TZ by its label. -- --
-- utcToNewYork :: UTCTime -> LocalTime -- utcToNewYork = utcToLocalTimeTZ $ tzByLabel America__New_York --tzByLabel :: TZLabel -> TZ -- | Lookup a TZ by the name of it's location. -- -- Returns Nothing if the location is unknown. tzByName :: ByteString -> Maybe TZ -- | Enumeration of time zone locations. data TZLabel Africa__Abidjan :: TZLabel Africa__Algiers :: TZLabel Africa__Bissau :: TZLabel Africa__Cairo :: TZLabel Africa__Casablanca :: TZLabel Africa__Ceuta :: TZLabel Africa__El_Aaiun :: TZLabel Africa__Johannesburg :: TZLabel Africa__Juba :: TZLabel Africa__Khartoum :: TZLabel Africa__Lagos :: TZLabel Africa__Maputo :: TZLabel Africa__Monrovia :: TZLabel Africa__Nairobi :: TZLabel Africa__Ndjamena :: TZLabel Africa__Sao_Tome :: TZLabel Africa__Tripoli :: TZLabel Africa__Tunis :: TZLabel Africa__Windhoek :: TZLabel America__Adak :: TZLabel America__Anchorage :: TZLabel America__Araguaina :: TZLabel America__Argentina__Buenos_Aires :: TZLabel America__Argentina__Catamarca :: TZLabel America__Argentina__Cordoba :: TZLabel America__Argentina__Jujuy :: TZLabel America__Argentina__La_Rioja :: TZLabel America__Argentina__Mendoza :: TZLabel America__Argentina__Rio_Gallegos :: TZLabel America__Argentina__Salta :: TZLabel America__Argentina__San_Juan :: TZLabel America__Argentina__San_Luis :: TZLabel America__Argentina__Tucuman :: TZLabel America__Argentina__Ushuaia :: TZLabel America__Asuncion :: TZLabel America__Bahia :: TZLabel America__Bahia_Banderas :: TZLabel America__Barbados :: TZLabel America__Belem :: TZLabel America__Belize :: TZLabel America__Boa_Vista :: TZLabel America__Bogota :: TZLabel America__Boise :: TZLabel America__Cambridge_Bay :: TZLabel America__Campo_Grande :: TZLabel America__Cancun :: TZLabel America__Caracas :: TZLabel America__Cayenne :: TZLabel America__Chicago :: TZLabel America__Chihuahua :: TZLabel America__Costa_Rica :: TZLabel America__Cuiaba :: TZLabel America__Danmarkshavn :: TZLabel America__Dawson :: TZLabel America__Dawson_Creek :: TZLabel America__Denver :: TZLabel America__Detroit :: TZLabel America__Edmonton :: TZLabel America__Eirunepe :: TZLabel America__El_Salvador :: TZLabel America__Fort_Nelson :: TZLabel America__Fortaleza :: TZLabel America__Glace_Bay :: TZLabel America__Goose_Bay :: TZLabel America__Grand_Turk :: TZLabel America__Guatemala :: TZLabel America__Guayaquil :: TZLabel America__Guyana :: TZLabel America__Halifax :: TZLabel America__Havana :: TZLabel America__Hermosillo :: TZLabel America__Indiana__Indianapolis :: TZLabel America__Indiana__Knox :: TZLabel America__Indiana__Marengo :: TZLabel America__Indiana__Petersburg :: TZLabel America__Indiana__Tell_City :: TZLabel America__Indiana__Vevay :: TZLabel America__Indiana__Vincennes :: TZLabel America__Indiana__Winamac :: TZLabel America__Inuvik :: TZLabel America__Iqaluit :: TZLabel America__Jamaica :: TZLabel America__Juneau :: TZLabel America__Kentucky__Louisville :: TZLabel America__Kentucky__Monticello :: TZLabel America__La_Paz :: TZLabel America__Lima :: TZLabel America__Los_Angeles :: TZLabel America__Maceio :: TZLabel America__Managua :: TZLabel America__Manaus :: TZLabel America__Martinique :: TZLabel America__Matamoros :: TZLabel America__Mazatlan :: TZLabel America__Menominee :: TZLabel America__Merida :: TZLabel America__Metlakatla :: TZLabel America__Mexico_City :: TZLabel America__Miquelon :: TZLabel America__Moncton :: TZLabel America__Monterrey :: TZLabel America__Montevideo :: TZLabel America__New_York :: TZLabel America__Nipigon :: TZLabel America__Nome :: TZLabel America__Noronha :: TZLabel America__North_Dakota__Beulah :: TZLabel America__North_Dakota__Center :: TZLabel America__North_Dakota__New_Salem :: TZLabel America__Nuuk :: TZLabel America__Ojinaga :: TZLabel America__Panama :: TZLabel America__Pangnirtung :: TZLabel America__Paramaribo :: TZLabel America__Phoenix :: TZLabel America__Port_au_Prince :: TZLabel America__Porto_Velho :: TZLabel America__Puerto_Rico :: TZLabel America__Punta_Arenas :: TZLabel America__Rainy_River :: TZLabel America__Rankin_Inlet :: TZLabel America__Recife :: TZLabel America__Regina :: TZLabel America__Resolute :: TZLabel America__Rio_Branco :: TZLabel America__Santarem :: TZLabel America__Santiago :: TZLabel America__Santo_Domingo :: TZLabel America__Sao_Paulo :: TZLabel America__Scoresbysund :: TZLabel America__Sitka :: TZLabel America__St_Johns :: TZLabel America__Swift_Current :: TZLabel America__Tegucigalpa :: TZLabel America__Thule :: TZLabel America__Thunder_Bay :: TZLabel America__Tijuana :: TZLabel America__Toronto :: TZLabel America__Vancouver :: TZLabel America__Whitehorse :: TZLabel America__Winnipeg :: TZLabel America__Yakutat :: TZLabel America__Yellowknife :: TZLabel Antarctica__Casey :: TZLabel Antarctica__Davis :: TZLabel Antarctica__Macquarie :: TZLabel Antarctica__Mawson :: TZLabel Antarctica__Palmer :: TZLabel Antarctica__Rothera :: TZLabel Antarctica__Troll :: TZLabel Antarctica__Vostok :: TZLabel Asia__Almaty :: TZLabel Asia__Amman :: TZLabel Asia__Anadyr :: TZLabel Asia__Aqtau :: TZLabel Asia__Aqtobe :: TZLabel Asia__Ashgabat :: TZLabel Asia__Atyrau :: TZLabel Asia__Baghdad :: TZLabel Asia__Baku :: TZLabel Asia__Bangkok :: TZLabel Asia__Barnaul :: TZLabel Asia__Beirut :: TZLabel Asia__Bishkek :: TZLabel Asia__Brunei :: TZLabel Asia__Chita :: TZLabel Asia__Choibalsan :: TZLabel Asia__Colombo :: TZLabel Asia__Damascus :: TZLabel Asia__Dhaka :: TZLabel Asia__Dili :: TZLabel Asia__Dubai :: TZLabel Asia__Dushanbe :: TZLabel Asia__Famagusta :: TZLabel Asia__Gaza :: TZLabel Asia__Hebron :: TZLabel Asia__Ho_Chi_Minh :: TZLabel Asia__Hong_Kong :: TZLabel Asia__Hovd :: TZLabel Asia__Irkutsk :: TZLabel Asia__Jakarta :: TZLabel Asia__Jayapura :: TZLabel Asia__Jerusalem :: TZLabel Asia__Kabul :: TZLabel Asia__Kamchatka :: TZLabel Asia__Karachi :: TZLabel Asia__Kathmandu :: TZLabel Asia__Khandyga :: TZLabel Asia__Kolkata :: TZLabel Asia__Krasnoyarsk :: TZLabel Asia__Kuala_Lumpur :: TZLabel Asia__Kuching :: TZLabel Asia__Macau :: TZLabel Asia__Magadan :: TZLabel Asia__Makassar :: TZLabel Asia__Manila :: TZLabel Asia__Nicosia :: TZLabel Asia__Novokuznetsk :: TZLabel Asia__Novosibirsk :: TZLabel Asia__Omsk :: TZLabel Asia__Oral :: TZLabel Asia__Pontianak :: TZLabel Asia__Pyongyang :: TZLabel Asia__Qatar :: TZLabel Asia__Qostanay :: TZLabel Asia__Qyzylorda :: TZLabel Asia__Riyadh :: TZLabel Asia__Sakhalin :: TZLabel Asia__Samarkand :: TZLabel Asia__Seoul :: TZLabel Asia__Shanghai :: TZLabel Asia__Singapore :: TZLabel Asia__Srednekolymsk :: TZLabel Asia__Taipei :: TZLabel Asia__Tashkent :: TZLabel Asia__Tbilisi :: TZLabel Asia__Tehran :: TZLabel Asia__Thimphu :: TZLabel Asia__Tokyo :: TZLabel Asia__Tomsk :: TZLabel Asia__Ulaanbaatar :: TZLabel Asia__Urumqi :: TZLabel Asia__Ust_Nera :: TZLabel Asia__Vladivostok :: TZLabel Asia__Yakutsk :: TZLabel Asia__Yangon :: TZLabel Asia__Yekaterinburg :: TZLabel Asia__Yerevan :: TZLabel Atlantic__Azores :: TZLabel Atlantic__Bermuda :: TZLabel Atlantic__Canary :: TZLabel Atlantic__Cape_Verde :: TZLabel Atlantic__Faroe :: TZLabel Atlantic__Madeira :: TZLabel Atlantic__Reykjavik :: TZLabel Atlantic__South_Georgia :: TZLabel Atlantic__Stanley :: TZLabel Australia__Adelaide :: TZLabel Australia__Brisbane :: TZLabel Australia__Broken_Hill :: TZLabel Australia__Darwin :: TZLabel Australia__Eucla :: TZLabel Australia__Hobart :: TZLabel Australia__Lindeman :: TZLabel Australia__Lord_Howe :: TZLabel Australia__Melbourne :: TZLabel Australia__Perth :: TZLabel Australia__Sydney :: TZLabel Etc__GMT :: TZLabel Etc__GMT'1 :: TZLabel Etc__GMT'10 :: TZLabel Etc__GMT'11 :: TZLabel Etc__GMT'12 :: TZLabel Etc__GMT'2 :: TZLabel Etc__GMT'3 :: TZLabel Etc__GMT'4 :: TZLabel Etc__GMT'5 :: TZLabel Etc__GMT'6 :: TZLabel Etc__GMT'7 :: TZLabel Etc__GMT'8 :: TZLabel Etc__GMT'9 :: TZLabel Etc__GMT_1 :: TZLabel Etc__GMT_10 :: TZLabel Etc__GMT_11 :: TZLabel Etc__GMT_12 :: TZLabel Etc__GMT_13 :: TZLabel Etc__GMT_14 :: TZLabel Etc__GMT_2 :: TZLabel Etc__GMT_3 :: TZLabel Etc__GMT_4 :: TZLabel Etc__GMT_5 :: TZLabel Etc__GMT_6 :: TZLabel Etc__GMT_7 :: TZLabel Etc__GMT_8 :: TZLabel Etc__GMT_9 :: TZLabel Etc__UTC :: TZLabel Europe__Amsterdam :: TZLabel Europe__Andorra :: TZLabel Europe__Astrakhan :: TZLabel Europe__Athens :: TZLabel Europe__Belgrade :: TZLabel Europe__Berlin :: TZLabel Europe__Brussels :: TZLabel Europe__Bucharest :: TZLabel Europe__Budapest :: TZLabel Europe__Chisinau :: TZLabel Europe__Copenhagen :: TZLabel Europe__Dublin :: TZLabel Europe__Gibraltar :: TZLabel Europe__Helsinki :: TZLabel Europe__Istanbul :: TZLabel Europe__Kaliningrad :: TZLabel Europe__Kiev :: TZLabel Europe__Kirov :: TZLabel Europe__Lisbon :: TZLabel Europe__London :: TZLabel Europe__Luxembourg :: TZLabel Europe__Madrid :: TZLabel Europe__Malta :: TZLabel Europe__Minsk :: TZLabel Europe__Monaco :: TZLabel Europe__Moscow :: TZLabel Europe__Oslo :: TZLabel Europe__Paris :: TZLabel Europe__Prague :: TZLabel Europe__Riga :: TZLabel Europe__Rome :: TZLabel Europe__Samara :: TZLabel Europe__Saratov :: TZLabel Europe__Simferopol :: TZLabel Europe__Sofia :: TZLabel Europe__Stockholm :: TZLabel Europe__Tallinn :: TZLabel Europe__Tirane :: TZLabel Europe__Ulyanovsk :: TZLabel Europe__Uzhgorod :: TZLabel Europe__Vienna :: TZLabel Europe__Vilnius :: TZLabel Europe__Volgograd :: TZLabel Europe__Warsaw :: TZLabel Europe__Zaporozhye :: TZLabel Europe__Zurich :: TZLabel Indian__Chagos :: TZLabel Indian__Christmas :: TZLabel Indian__Cocos :: TZLabel Indian__Kerguelen :: TZLabel Indian__Mahe :: TZLabel Indian__Maldives :: TZLabel Indian__Mauritius :: TZLabel Indian__Reunion :: TZLabel Pacific__Apia :: TZLabel Pacific__Auckland :: TZLabel Pacific__Bougainville :: TZLabel Pacific__Chatham :: TZLabel Pacific__Chuuk :: TZLabel Pacific__Easter :: TZLabel Pacific__Efate :: TZLabel Pacific__Fakaofo :: TZLabel Pacific__Fiji :: TZLabel Pacific__Funafuti :: TZLabel Pacific__Galapagos :: TZLabel Pacific__Gambier :: TZLabel Pacific__Guadalcanal :: TZLabel Pacific__Guam :: TZLabel Pacific__Honolulu :: TZLabel Pacific__Kanton :: TZLabel Pacific__Kiritimati :: TZLabel Pacific__Kosrae :: TZLabel Pacific__Kwajalein :: TZLabel Pacific__Majuro :: TZLabel Pacific__Marquesas :: TZLabel Pacific__Nauru :: TZLabel Pacific__Niue :: TZLabel Pacific__Norfolk :: TZLabel Pacific__Noumea :: TZLabel Pacific__Pago_Pago :: TZLabel Pacific__Palau :: TZLabel Pacific__Pitcairn :: TZLabel Pacific__Pohnpei :: TZLabel Pacific__Port_Moresby :: TZLabel Pacific__Rarotonga :: TZLabel Pacific__Tahiti :: TZLabel Pacific__Tarawa :: TZLabel Pacific__Tongatapu :: TZLabel Pacific__Wake :: TZLabel Pacific__Wallis :: TZLabel Root__CET :: TZLabel Root__CST6CDT :: TZLabel Root__EET :: TZLabel Root__EST :: TZLabel Root__EST5EDT :: TZLabel Root__HST :: TZLabel Root__MET :: TZLabel Root__MST :: TZLabel Root__MST7MDT :: TZLabel Root__PST8PDT :: TZLabel Root__WET :: TZLabel module Data.Time.Zones data TZ -- | The TZ definition for UTC. utcTZ :: TZ -- | Returns the time difference (in seconds) for TZ at the given POSIX -- time. diffForPOSIX :: TZ -> Int64 -> Int -- | Returns the TimeZone for the TZ at the given POSIX time. timeZoneForPOSIX :: TZ -> Int64 -> TimeZone -- | Returns the TimeZone for the TZ at the given -- UTCTime. timeZoneForUTCTime :: TZ -> UTCTime -> TimeZone -- | 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 utcToLocalTimeTZ :: TZ -> UTCTime -> LocalTime -- | 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. data LocalToUTCResult LTUNone :: UTCTime -> TimeZone -> LocalToUTCResult [_ltuResult] :: LocalToUTCResult -> UTCTime [_ltuZone] :: LocalToUTCResult -> TimeZone LTUUnique :: UTCTime -> TimeZone -> LocalToUTCResult [_ltuResult] :: LocalToUTCResult -> UTCTime [_ltuZone] :: LocalToUTCResult -> TimeZone LTUAmbiguous :: UTCTime -> UTCTime -> TimeZone -> TimeZone -> LocalToUTCResult [_ltuFirst] :: LocalToUTCResult -> UTCTime [_ltuSecond] :: LocalToUTCResult -> UTCTime [_ltuFirstZone] :: LocalToUTCResult -> TimeZone [_ltuSecondZone] :: LocalToUTCResult -> TimeZone localTimeToUTCFull :: TZ -> LocalTime -> LocalToUTCResult localTimeToUTCTZ :: TZ -> LocalTime -> UTCTime -- | Internal representation of LocalTime -> UTCTime conversion result: data FromLocal FLGap :: {-# UNPACK #-} !Int -> {-# UNPACK #-} !Int64 -> FromLocal [_flIx] :: FromLocal -> {-# UNPACK #-} !Int [_flRes] :: FromLocal -> {-# UNPACK #-} !Int64 FLUnique :: {-# UNPACK #-} !Int -> {-# UNPACK #-} !Int64 -> FromLocal [_flIx] :: FromLocal -> {-# UNPACK #-} !Int [_flRes] :: FromLocal -> {-# UNPACK #-} !Int64 FLDouble :: {-# UNPACK #-} !Int -> {-# UNPACK #-} !Int64 -> {-# UNPACK #-} !Int64 -> FromLocal [_flIx] :: FromLocal -> {-# UNPACK #-} !Int [_flRes1] :: FromLocal -> {-# UNPACK #-} !Int64 [_flRes2] :: FromLocal -> {-# UNPACK #-} !Int64 localToPOSIX :: TZ -> Int64 -> FromLocal -- | Reads and parses a time zone information file (in tzfile(5) -- aka. Olson file format) and returns the corresponding TZ data -- structure. loadTZFromFile :: FilePath -> IO TZ -- | Reads the corresponding file from the time zone database shipped with -- this package. loadTZFromDB :: String -> IO TZ -- | 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. loadSystemTZ :: String -> IO TZ -- | Returns the local TZ based on the TZ and -- TZDIR environment variables. -- -- See tzset(3) for details, but basically: -- --