-- -*- haskell -*- {- | Module : Data.Time.Zones.All Copyright : (C) 2014 Mihaly Barasz License : Apache-2.0, see LICENSE Maintainer : Mihaly Barasz Stability : experimental -} module Data.Time.Zones.All ( toTZName, fromTZName, tzByLabel, tzByName, TZLabel(..), -- * Access to raw data TZDescription, tzDescriptions, ) where import qualified Data.ByteString.Char8 as BS import qualified Data.ByteString.Lazy.Char8 as BL import Data.Time.Zones.Read import Data.Time.Zones.Types import qualified Data.Map.Lazy as M import qualified Data.Vector as V -- | Enumeration of time zone locations. data TZLabel TZ_LABEL_DECL deriving (Eq,Ord,Enum,Bounded,Show,Read) -- | Type of the elements of the compiled-in time zone info database. -- -- @Right@ is a primary location; -- fields: name, label, abridged content of the Time Zone info file -- -- @Left@ is a location which is an alias for a primary location; -- fields: name, name of the target -- -- "Abridged" means that we only store the second part of the TZif -- file for version '2' and '3' files. type TZDescription = Either (BS.ByteString, BS.ByteString) (BS.ByteString, TZLabel, BL.ByteString) -- | Convert a `TZLabel` to the usual name of the location. -- -- >> toTZName Europe__Paris -- >"Europe/Paris" toTZName :: TZLabel -> BS.ByteString toTZName = (v V.!) . fromEnum where v = V.fromList $ go tzDescriptions go [] = [] go (Right (name, _, _) : zs) = name : go zs go (Left _ : zs) = go zs -- | 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 :: BS.ByteString -> Maybe TZLabel fromTZName = flip M.lookup m where m = M.fromList $ map g tzDescriptions g (Right (name,label,_)) = (name, label) g (Left (name, target)) = (name, m M.! target) -- | Lookup a `TZ` by its label. -- -- >utcToNewYork :: UTCTime -> LocalTime -- >utcToNewYork = utcToLocalTimeTZ $ tzByLabel America__New_York tzByLabel :: TZLabel -> TZ tzByLabel = (v V.!) . fromEnum where v = V.fromList $ go tzDescriptions go [] = [] go (Right (_, _, desc) : zs) = parseTZDescription desc : go zs go (Left _ : zs) = go zs -- | Lookup a `TZ` by the name of it's location. -- -- Returns `Nothing` if the location is unknown. tzByName :: BS.ByteString -> Maybe TZ tzByName n = tzByLabel `fmap` fromTZName n -- | The list with raw data of the compiled-in time zone info database. -- -- The list is guaranteed to be in the order of `TZLabel` constructors -- (it is sorted by name). tzDescriptions :: [TZDescription] tzDescriptions = zones where {-# NOINLINE p #-} p name label desc = Right (BS.pack name, label, BL.pack desc) {-# NOINLINE l #-} l name target = Left (BS.pack name, BS.pack target) zones = [ TZ_DESCRIPTIONS ]