~alcinnz/bureaucromancy

ref: 34609eabb4afdbcc219c0bd461891e5ed83e73ba bureaucromancy/src/Text/HTML/Form/WebApp/Ginger/TZ.hs -rw-r--r-- 1.3 KiB
34609eab — Adrian Cochrane Add timezone selector! 1 year, 1 month ago
                                                                                
93bfa89a 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
34609eab Adrian Cochrane
93bfa89a Adrian Cochrane
34609eab Adrian Cochrane
93bfa89a Adrian Cochrane
34609eab Adrian Cochrane
93bfa89a 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
{-# LANGUAGE OverloadedStrings #-}
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

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
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

continents :: GVal m
continents = list $ map toGVal $ nub $ "...":[prefix |
        (label, _) <- M.toList tzNameLabelMap,
        let (prefix, _) = BSC.breakEnd (== '/') label]