~alcinnz/bureaucromancy

ref: c1e09d4ada65150d6bd9c391dd1aa4a1bf20b539 bureaucromancy/src/Text/HTML/Form/WebApp.hs -rw-r--r-- 3.5 KiB
c1e09d4a — Adrian Cochrane Render onscreen keyboards (not interactive yet). 1 year, 3 months ago
                                                                                
fa8b4fac Adrian Cochrane
a3d5ae54 Adrian Cochrane
8a7fc937 Adrian Cochrane
b77ee394 Adrian Cochrane
c1e09d4a Adrian Cochrane
8a7fc937 Adrian Cochrane
c1e09d4a Adrian Cochrane
a3d5ae54 Adrian Cochrane
fa8b4fac Adrian Cochrane
a3d5ae54 Adrian Cochrane
703b3073 Adrian Cochrane
a3d5ae54 Adrian Cochrane
c1e09d4a Adrian Cochrane
8a7fc937 Adrian Cochrane
703b3073 Adrian Cochrane
8a7fc937 Adrian Cochrane
b77ee394 Adrian Cochrane
703b3073 Adrian Cochrane
a3d5ae54 Adrian Cochrane
b77ee394 Adrian Cochrane
a3d5ae54 Adrian Cochrane
703b3073 Adrian Cochrane
b77ee394 Adrian Cochrane
a3d5ae54 Adrian Cochrane
703b3073 Adrian Cochrane
b77ee394 Adrian Cochrane
c1e09d4a Adrian Cochrane
b77ee394 Adrian Cochrane
a3d5ae54 Adrian Cochrane
b77ee394 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
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
{-# LANGUAGE OverloadedStrings #-}
module Text.HTML.Form.WebApp (renderPage, Form(..)) where

import Data.ByteString as BS
import Data.Text as Txt
import Data.Text.Encoding as Txt
import Text.Read (readMaybe)
import Network.URI (unEscapeString)
import System.IO (readFile')
import System.FilePath ((</>))
import System.Directory (XdgDirectory(..), getXdgDirectory, doesFileExist)

import Text.HTML.Form (Form(..), Input(..))
import Text.HTML.Form.WebApp.Ginger (template, resolveSource)
import Text.HTML.Form.Query (renderQueryString)

renderPage :: Form -> [Text] -> [(ByteString, Maybe ByteString)] -> IO (Maybe Text)
renderPage form (n:path) query
    | Just ix <- readMaybe $ Txt.unpack n, ix < Prelude.length (inputs form) =
        renderInput form ix (inputs form !! ix) path query
renderPage form [] _ = return $ Just $ Txt.concat [
    "<a href='/0/?", Txt.pack $ renderQueryString form, "'>Start!</a>"]
renderPage _ _ _ = return Nothing

renderInput :: Form -> Int -> Input -> [Text] -> [(ByteString, Maybe ByteString)] ->
    IO (Maybe Text)
renderInput form ix input [""] qs = renderInput form ix input [] qs
renderInput form ix input@Input { multiple = True } [p] qs
    | '=':v' <- Txt.unpack p,
            (utf8 $ inputName input, Just $ utf8' v') `Prelude.elem` qs =
        renderInput form ix input [] $
            unset (inputName input) (Txt.pack $ unEscapeString v') qs
    | '=':v' <- Txt.unpack p = renderInput form ix input [] $
        (utf8 $ inputName input, Just $ utf8' $ unEscapeString v'):qs
renderInput form ix input [p] qs
    | '=':v' <- Txt.unpack p = renderInput form ix input [] $
        set (inputName input) (Txt.pack $ unEscapeString v') qs
renderInput form ix input@Input {inputType="checkbox", inputName=k', value=v'} [] qs
    | (utf8 k', Just $ utf8 v') `Prelude.elem` qs =
        template "checkbox.html" form ix input $ unset k' v' qs
    | v' == "", (utf8 k', Nothing) `Prelude.elem` qs =
        template "checkbox.html" form ix input [
            q | q@(k, v) <- qs, not (k == utf8 k' && v == Nothing)]
    | otherwise =
        template "checkbox.html" form ix input $ (utf8 k', Just $ utf8 v'):qs
renderInput form ix input@Input {inputType="radio", inputName=k', value=v'} [] qs =
    template "checkbox.html" form ix input $ set k' v' qs
renderInput form ix input@Input { inputType="<select>" } [] qs =
    template "select.html" form ix input qs
renderInput form ix input [keyboard] qs =
    template (Txt.unpack keyboard ++ ".html") form ix input qs
renderInput form ix input [keyboard, ""] qs =
    template (Txt.unpack keyboard ++ ".html") form ix input qs
renderInput form ix input [] qs = do
    path <- getXdgDirectory XdgConfig "bureaucromancy"
    exists <- doesFileExist $ path </> "keyboard"
    keyboard <- if exists then readFile' $ path </> "keyboard"
        else return "latin1"
    let keyboard' | Just (Just _) <- resolveSource (keyboard ++ ".html") = keyboard
            | otherwise = "latin1"
    template (keyboard' ++ ".html") form ix input qs
renderInput _ _ input _ _ =
    return $ Just $ Txt.concat ["Unknown input type: ", inputType input]

utf8 :: Text -> ByteString
utf8 = Txt.encodeUtf8
utf8' :: String -> ByteString
utf8' = utf8 . Txt.pack
set :: Text -> Text -> [(ByteString, Maybe ByteString)]
    -> [(ByteString, Maybe ByteString)]
set k' v' qs = (utf8 k', Just $ utf8 v'):[q | q@(k, _) <- qs, k /= utf8 k']
unset :: Text -> Text -> [(ByteString, Maybe ByteString)]
    -> [(ByteString, Maybe ByteString)]
unset k' v' qs = [q | q@(k, v) <- qs, not (k == utf8 k' && v == Just (utf8 v'))]