{-# LANGUAGE OverloadedStrings #-}
module Template where
import Control.Monad (sequence)
import Data.Array ((!))
import Data.Monoid ((<>))
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.Lazy as Lazy
import Numeric (showHex)
import Lucid
import Storage
import Style (style)
toHex :: (Integral a, Show a) => a -> String
toHex n
| n < 16 = "0" ++ showHex n ""
| otherwise = showHex n ""
paneList :: Pane -> Lazy.Text
paneList (Pane arr) = page "unalaq" $ do
table_ [class_ "pane"] $ do
sequence
[
tr_ $ sequence
[ td_ lang $
a_ [href_ (T.pack url)] (toHtml pNum)
| num <- [0x0..0xf],
let lang = case paneLang (arr ! (num + off)) of
Just lang -> [data_ "language" (T.pack lang)]
Nothing -> []
pNum = toHex (num + off)
url = "/chunk/" ++ (show (num + off))
]
| off <- [0x0,0x10..]
]
return ()
charList :: Int -> Int -> Lazy.Text
charList offset n = page ("unalaq pane " <> T.pack (toHex n)) $ do
h1_ $ toHtml ("page " <> T.pack (toHex n))
table_ [class_ "chars"] $ do
sequence $ [ tr_ $ do
td_ (toHtml ("U+" ++ toHex (offset + n)))
td_ "TRINAKO LETTER ASH"
| n <- [0..255]
]
return ()
page :: Text -> Html () -> Lazy.Text
page title contents = renderText $ html_ $ do
head_ $ do
meta_ [charset_ "utf-8"]
style_ [type_ "text/css"] style
title_ (toHtml title)
body_ $ do
div_ [class_ "main"] contents