{-# LANGUAGE OverloadedStrings #-} -- | Exposes data for a menu of timezones. module Text.HTML.Form.WebApp.Ginger.TZ(tzdata, continents) where import Text.Ginger.GVal as V (GVal, toGVal, orderedDict, (~>), list) import qualified Data.Map.Strict as M import Data.Time.Zones.All (tzNameLabelMap, tzByLabel) import Data.Time.Zones (diffForPOSIX) import Data.Int (Int64) import Data.List (nub) import qualified Data.ByteString as BS import qualified Data.ByteString.Char8 as BSC -- | Parses timezone data into a menu for Ginger templates. tzdata :: Int64 -> String -> GVal m tzdata now prefix = list [orderedDict [ "label" ~> label, "value" ~> (diffForPOSIX tz' now `div` 60), "offset" ~> formatOffset (diffForPOSIX tz' now `div` 60) ] | (label, tz) <- M.toList tzNameLabelMap, BSC.pack prefix `contains` label, let tz' = tzByLabel tz] where contains "" = BSC.notElem '/' contains "..." = BSC.notElem '/' contains x = BS.isPrefixOf x -- | Serialize an offset to string, ensuring 0 is prepended to minutes when needed. formatOffset :: (Show a, Integral a) => a -> [Char] formatOffset offset | minutes < 10 = show hours ++ ':':'0': show minutes | otherwise = show hours ++ ':': show minutes where hours = offset `div` 60 minutes = abs $ offset `rem` 60 -- | Retrieves continents list for Ginger templates. continents :: GVal m continents = list $ map toGVal $ nub $ "...":[prefix | (label, _) <- M.toList tzNameLabelMap, let (prefix, _) = BSC.breakEnd (== '/') label]