{-# 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 Text.HTML.Form (Form(..), Input(..))
import Text.HTML.Form.WebApp.Ginger (template)
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 [
"Start!"]
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="