module Data.Time.Zones.All (
toTZName,
fromTZName,
tzNameLabelMap,
tzByLabel,
tzByName,
TZLabel(..),
) where
import qualified Data.ByteString.Char8 as BS
import Data.Time.Zones.DB
import Data.Time.Zones.Read
import Data.Time.Zones.Types
import qualified Data.Vector as V
tzByLabel :: TZLabel -> TZ
tzByLabel :: TZLabel -> TZ
tzByLabel = (Vector TZ
v Vector TZ -> Int -> TZ
forall a. Vector a -> Int -> a
V.!) (Int -> TZ) -> (TZLabel -> Int) -> TZLabel -> TZ
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TZLabel -> Int
forall a. Enum a => a -> Int
fromEnum
where
v :: Vector TZ
v = [TZ] -> Vector TZ
forall a. [a] -> Vector a
V.fromList ([TZ] -> Vector TZ) -> [TZ] -> Vector TZ
forall a b. (a -> b) -> a -> b
$ [Either (ByteString, ByteString) (ByteString, TZLabel, ByteString)]
-> [TZ]
forall a a b. [Either a (a, b, ByteString)] -> [TZ]
go [Either (ByteString, ByteString) (ByteString, TZLabel, ByteString)]
tzDescriptions
go :: [Either a (a, b, ByteString)] -> [TZ]
go [] = []
go (Right (a
_, b
_, ByteString
desc) : [Either a (a, b, ByteString)]
zs) = ByteString -> TZ
parseOlson ByteString
desc TZ -> [TZ] -> [TZ]
forall a. a -> [a] -> [a]
: [Either a (a, b, ByteString)] -> [TZ]
go [Either a (a, b, ByteString)]
zs
go (Left a
_ : [Either a (a, b, ByteString)]
zs) = [Either a (a, b, ByteString)] -> [TZ]
go [Either a (a, b, ByteString)]
zs
tzByName :: BS.ByteString -> Maybe TZ
tzByName :: ByteString -> Maybe TZ
tzByName ByteString
n = TZLabel -> TZ
tzByLabel (TZLabel -> TZ) -> Maybe TZLabel -> Maybe TZ
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` ByteString -> Maybe TZLabel
fromTZName ByteString
n