~alcinnz/bureaucromancy

ref: 696da319f63881a1482a71ef5d7c067fb471b61e bureaucromancy/src/Text/HTML/Form/WebApp/Ginger/TZ.hs -rw-r--r-- 1.5 KiB
696da319 — Adrian Cochrane Document & add missing files. 1 year, 5 days ago
                                                                                
93bfa89a Adrian Cochrane
696da319 Adrian Cochrane
34609eab Adrian Cochrane
93bfa89a Adrian Cochrane
34609eab Adrian Cochrane
93bfa89a Adrian Cochrane
34609eab Adrian Cochrane
93bfa89a Adrian Cochrane
34609eab Adrian Cochrane
93bfa89a Adrian Cochrane
696da319 Adrian Cochrane
34609eab Adrian Cochrane
93bfa89a Adrian Cochrane
34609eab Adrian Cochrane
696da319 Adrian Cochrane
93bfa89a Adrian Cochrane
34609eab Adrian Cochrane
93bfa89a Adrian Cochrane
34609eab Adrian Cochrane
696da319 Adrian Cochrane
34609eab Adrian Cochrane
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
{-# 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]