{-# LANGUAGE FlexibleContexts, FlexibleInstances, MultiParamTypeClasses, ScopedTypeVariables, TypeFamilies, UndecidableInstances, ViewPatterns #-}
{- |
This module provides functions creating Reform using HSP markup.

This module assumes that you wish for text based controls such as 'inputText' and 'textarea' to using 'String' values. If you prefer 'Data.Text.Text' see "Text.Reform.HSP.Text".

-}
module Text.Reform.HSP.String
    ( -- * \<input\> element
      inputEmail
    , inputText
    , inputPassword
    , inputSubmit
    , inputReset
    , inputHidden
    , inputButton
    , inputCheckbox
    , inputCheckboxes
    , inputRadio
    , inputRadioForms
    , inputFile
      -- * \<textarea\> element
    , textarea
      -- * \<button\> element
    , buttonSubmit
    , buttonReset
    , button
      -- * \<select\> element
    , select
    , selectMultiple
      -- * \<label\> element
    , label
      -- * errors
    , errorList
    , childErrorList
      -- * layout functions
    , br
    , fieldset
    , ol
    , ul
    , li
    , form
    , setAttrs
    ) where

import Data.Text.Lazy (Text, pack)
import HSP.XMLGenerator
import Text.Reform
import qualified Text.Reform.HSP.Common as C

-- | Create an @\<input type=\"email\"\>@ element
inputEmail :: (Monad m, FormInput input, FormError error, ErrorInputType error ~ input, XMLGenerator x, StringType x ~ Text, EmbedAsAttr x (Attr Text FormId), EmbedAsAttr x (Attr Text String)) =>
               String -- ^ initial value
            -> Form m input error [XMLGenT x (XMLType x)] () String
inputEmail :: String -> Form m input error [XMLGenT x (XMLType x)] () String
inputEmail initialValue :: String
initialValue = (input -> Either error String)
-> String -> Form m input error [XMLGenT x (XMLType x)] () String
forall (m :: * -> *) error (x :: * -> *) text input.
(Monad m, FormError error, XMLGenerator x, StringType x ~ Text,
 EmbedAsAttr x (Attr Text FormId),
 EmbedAsAttr x (Attr Text text)) =>
(input -> Either error text)
-> text -> Form m input error [XMLGenT x (XMLType x)] () text
C.inputEmail input -> Either error String
forall input error.
(FormInput input, FormError error, ErrorInputType error ~ input) =>
input -> Either error String
getInputString String
initialValue

-- | Create an @\<input type=\"text\"\>@ element
inputText :: (Monad m, FormInput input, FormError error, ErrorInputType error ~ input, XMLGenerator x, StringType x ~ Text, EmbedAsAttr x (Attr Text FormId), EmbedAsAttr x (Attr Text String)) =>
               String -- ^ initial value
            -> Form m input error [XMLGenT x (XMLType x)] () String
inputText :: String -> Form m input error [XMLGenT x (XMLType x)] () String
inputText initialValue :: String
initialValue = (input -> Either error String)
-> String -> Form m input error [XMLGenT x (XMLType x)] () String
forall (m :: * -> *) error (x :: * -> *) text input.
(Monad m, FormError error, XMLGenerator x, StringType x ~ Text,
 EmbedAsAttr x (Attr Text FormId),
 EmbedAsAttr x (Attr Text text)) =>
(input -> Either error text)
-> text -> Form m input error [XMLGenT x (XMLType x)] () text
C.inputText input -> Either error String
forall input error.
(FormInput input, FormError error, ErrorInputType error ~ input) =>
input -> Either error String
getInputString String
initialValue

-- | Create an @\<input type=\"password\"\>@ element
inputPassword :: (Monad m, FormInput input, FormError error, ErrorInputType error ~ input, XMLGenerator x, StringType x ~ Text, EmbedAsAttr x (Attr Text FormId), EmbedAsAttr x (Attr Text String)) =>
                 Form m input error [XMLGenT x (XMLType x)] () String
inputPassword :: Form m input error [XMLGenT x (XMLType x)] () String
inputPassword = (input -> Either error String)
-> String -> Form m input error [XMLGenT x (XMLType x)] () String
forall (m :: * -> *) error (x :: * -> *) text input.
(Monad m, FormError error, XMLGenerator x, StringType x ~ Text,
 EmbedAsAttr x (Attr Text FormId),
 EmbedAsAttr x (Attr Text text)) =>
(input -> Either error text)
-> text -> Form m input error [XMLGenT x (XMLType x)] () text
C.inputPassword input -> Either error String
forall input error.
(FormInput input, FormError error, ErrorInputType error ~ input) =>
input -> Either error String
getInputString ""

-- | Create an @\<input type=\"submit\"\>@ element
--
-- returns:
--
--   [@Just@ /value/] if this button was used to submit the form.
--
--   [@Nothing@]    if this button was not used to submit the form.
inputSubmit :: (Monad m, FormInput input, FormError error, ErrorInputType error ~ input, XMLGenerator x, StringType x ~ Text, EmbedAsAttr x (Attr Text FormId), EmbedAsAttr x (Attr Text String)) =>
               String -- ^ @value@ attribute. Used for button label, and value if button is submitted.
            -> Form m input error [XMLGenT x (XMLType x)] () (Maybe String)
inputSubmit :: String
-> Form m input error [XMLGenT x (XMLType x)] () (Maybe String)
inputSubmit initialValue :: String
initialValue = (input -> Either error String)
-> String
-> Form m input error [XMLGenT x (XMLType x)] () (Maybe String)
forall (m :: * -> *) error (x :: * -> *) text input.
(Monad m, FormError error, XMLGenerator x, StringType x ~ Text,
 EmbedAsAttr x (Attr Text FormId),
 EmbedAsAttr x (Attr Text text)) =>
(input -> Either error text)
-> text
-> Form m input error [XMLGenT x (XMLType x)] () (Maybe text)
C.inputSubmit input -> Either error String
forall input error.
(FormInput input, FormError error, ErrorInputType error ~ input) =>
input -> Either error String
getInputString String
initialValue

-- | Create an @\<input type=\"reset\"\>@ element
--
-- This element does not add any data to the form data set.
inputReset :: (Monad m, FormInput input, FormError error, ErrorInputType error ~ input, XMLGenerator x, StringType x ~ Text, EmbedAsAttr x (Attr Text FormId), EmbedAsAttr x (Attr Text String)) =>
              String -- ^ value attribute. Used only to label the button.
           -> Form m input error [XMLGenT x (XMLType x)] () ()
inputReset :: String -> Form m input error [XMLGenT x (XMLType x)] () ()
inputReset = String -> Form m input error [XMLGenT x (XMLType x)] () ()
forall (m :: * -> *) error (x :: * -> *) text input.
(Monad m, FormError error, XMLGenerator x, StringType x ~ Text,
 EmbedAsAttr x (Attr Text FormId),
 EmbedAsAttr x (Attr Text text)) =>
text -> Form m input error [XMLGenT x (XMLType x)] () ()
C.inputReset

-- | Create an @\<input type=\"hidden\"\>@ element
inputHidden :: (Monad m, FormInput input, FormError error, ErrorInputType error ~ input, XMLGenerator x, StringType x ~ Text, EmbedAsAttr x (Attr Text FormId), EmbedAsAttr x (Attr Text String)) =>
               String -- ^ value to store in the hidden element
            -> Form m input error [XMLGenT x (XMLType x)] () String
inputHidden :: String -> Form m input error [XMLGenT x (XMLType x)] () String
inputHidden initialValue :: String
initialValue = (input -> Either error String)
-> String -> Form m input error [XMLGenT x (XMLType x)] () String
forall (m :: * -> *) error (x :: * -> *) text input.
(Monad m, FormError error, XMLGenerator x, StringType x ~ Text,
 EmbedAsAttr x (Attr Text FormId),
 EmbedAsAttr x (Attr Text text)) =>
(input -> Either error text)
-> text -> Form m input error [XMLGenT x (XMLType x)] () text
C.inputHidden input -> Either error String
forall input error.
(FormInput input, FormError error, ErrorInputType error ~ input) =>
input -> Either error String
getInputString String
initialValue

-- | Create an @\<input type=\"button\"\>@ element
--
-- The element is a push button with a text label. The button does nothing by default, but actions can be added using javascript. This element does not add any data to the form data set.
--
-- see also: 'C.button'
inputButton :: (Monad m, FormInput input, FormError error, ErrorInputType error ~ input, XMLGenerator x, StringType x ~ Text, EmbedAsAttr x (Attr Text FormId), EmbedAsAttr x (Attr Text String)) =>
               String -- ^ value attribute. Used to label the button.
            -> Form m input error [XMLGenT x (XMLType x)] () ()
inputButton :: String -> Form m input error [XMLGenT x (XMLType x)] () ()
inputButton label :: String
label = String -> Form m input error [XMLGenT x (XMLType x)] () ()
forall (m :: * -> *) error (x :: * -> *) text input.
(Monad m, FormError error, XMLGenerator x, StringType x ~ Text,
 EmbedAsAttr x (Attr Text FormId),
 EmbedAsAttr x (Attr Text text)) =>
text -> Form m input error [XMLGenT x (XMLType x)] () ()
C.inputButton String
label

-- | Create a \<textarea\>\<\/textarea\> element
textarea :: (Monad m, FormInput input, FormError error, ErrorInputType error ~ input, XMLGenerator x, StringType x ~ Text, EmbedAsAttr x (Attr Text FormId)) =>
            Int    -- ^ cols
         -> Int    -- ^ rows
         -> String -- ^ initial contents
         -> Form m input error [XMLGenT x (XMLType x)] () String
textarea :: Int
-> Int
-> String
-> Form m input error [XMLGenT x (XMLType x)] () String
textarea rows :: Int
rows cols :: Int
cols initialValue :: String
initialValue = (input -> Either error String)
-> Int
-> Int
-> String
-> Form m input error [XMLGenT x (XMLType x)] () String
forall (m :: * -> *) error (x :: * -> *) text input.
(Monad m, FormError error, XMLGenerator x, StringType x ~ Text,
 EmbedAsAttr x (Attr Text FormId), EmbedAsChild x text) =>
(input -> Either error text)
-> Int
-> Int
-> text
-> Form m input error [XMLGenT x (XMLType x)] () text
C.textarea input -> Either error String
forall input error.
(FormInput input, FormError error, ErrorInputType error ~ input) =>
input -> Either error String
getInputString Int
rows Int
cols String
initialValue

-- | create a  @\<button type=\"submit\"\>\<\/button\>@ element
buttonSubmit :: ( Monad m, FormError error, FormInput input, ErrorInputType error ~ input, XMLGenerator x, StringType x ~ Text, EmbedAsChild x children , EmbedAsAttr x (Attr Text FormId), EmbedAsAttr x (Attr Text String)) =>
                String -- ^ value attribute. Returned if this button submits the form.
             -> children -- ^ children to embed in the \<button\>
             -> Form m input error [XMLGenT x (XMLType x)] () (Maybe String)
buttonSubmit :: String
-> children
-> Form m input error [XMLGenT x (XMLType x)] () (Maybe String)
buttonSubmit = (input -> Either error String)
-> String
-> children
-> Form m input error [XMLGenT x (XMLType x)] () (Maybe String)
forall (m :: * -> *) error (x :: * -> *) children text input.
(Monad m, FormError error, XMLGenerator x, StringType x ~ Text,
 EmbedAsChild x children, EmbedAsAttr x (Attr Text FormId),
 EmbedAsAttr x (Attr Text text)) =>
(input -> Either error text)
-> text
-> children
-> Form m input error [XMLGenT x (XMLType x)] () (Maybe text)
C.buttonSubmit input -> Either error String
forall input error.
(FormInput input, FormError error, ErrorInputType error ~ input) =>
input -> Either error String
getInputString

--------------------------------------------------------------------------------
-- re-exports from .Common. In theory we could just put the docs in .Common,
-- but, currently HSX strips them out.

-- | Create a single @\<input type=\"checkbox\"\>@ element
--
-- returns a 'Bool' indicating if it was checked or not.
--
-- see also 'inputCheckboxes'
inputCheckbox :: forall x error input m. (Monad m, FormInput input, FormError error, ErrorInputType error ~ input, XMLGenerator x, StringType x ~ Text, EmbedAsAttr x (Attr Text FormId)) =>
                   Bool  -- ^ initially checked
                -> Form m input error [XMLGenT x (XMLType x)] () Bool
inputCheckbox :: Bool -> Form m input error [XMLGenT x (XMLType x)] () Bool
inputCheckbox = Bool -> Form m input error [XMLGenT x (XMLType x)] () Bool
forall (x :: * -> *) error input (m :: * -> *).
(Monad m, FormInput input, FormError error,
 ErrorInputType error ~ input, XMLGenerator x, StringType x ~ Text,
 EmbedAsAttr x (Attr Text FormId)) =>
Bool -> Form m input error [XMLGenT x (XMLType x)] () Bool
C.inputCheckbox

-- | Create a group of @\<input type=\"checkbox\"\>@ elements
--
inputCheckboxes :: (Functor m, Monad m, FormError error, ErrorInputType error ~ input, FormInput input, XMLGenerator x, StringType x ~ Text, EmbedAsChild x lbl, EmbedAsAttr x (Attr Text FormId)) =>
                   [(a, lbl)]  -- ^ (value, label)
                -> (a -> Bool) -- ^ function which marks if a value should be checked (aka, selected) initially or not. Can match zero or more elements.
                -> Form m input error [XMLGenT x (XMLType x)] () [a]
inputCheckboxes :: [(a, lbl)]
-> (a -> Bool) -> Form m input error [XMLGenT x (XMLType x)] () [a]
inputCheckboxes = [(a, lbl)]
-> (a -> Bool) -> Form m input error [XMLGenT x (XMLType x)] () [a]
forall (m :: * -> *) error input (x :: * -> *) lbl a.
(Functor m, Monad m, FormError error, ErrorInputType error ~ input,
 FormInput input, XMLGenerator x, StringType x ~ Text,
 EmbedAsChild x lbl, EmbedAsAttr x (Attr Text FormId)) =>
[(a, lbl)]
-> (a -> Bool) -> Form m input error [XMLGenT x (XMLType x)] () [a]
C.inputCheckboxes

-- | Create a group of @\<input type=\"radio\"\>@ elements
inputRadio :: (Functor m, Monad m, FormError error, ErrorInputType error ~ input, FormInput input, XMLGenerator x, StringType x ~ Text, EmbedAsChild x lbl, EmbedAsAttr x (Attr Text FormId)) =>
              [(a, lbl)]  -- ^ (value, label)
           -> (a -> Bool) -- ^ predicate which returns @True@ if @a@ should be initially checked. Must match exactly one value in the previous argument.
           -> Form m input error [XMLGenT x (XMLType x)] () a
inputRadio :: [(a, lbl)]
-> (a -> Bool) -> Form m input error [XMLGenT x (XMLType x)] () a
inputRadio = [(a, lbl)]
-> (a -> Bool) -> Form m input error [XMLGenT x (XMLType x)] () a
forall (m :: * -> *) error input (x :: * -> *) lbl a.
(Functor m, Monad m, FormError error, ErrorInputType error ~ input,
 FormInput input, XMLGenerator x, StringType x ~ Text,
 EmbedAsChild x lbl, EmbedAsAttr x (Attr Text FormId)) =>
[(a, lbl)]
-> (a -> Bool) -> Form m input error [XMLGenT x (XMLType x)] () a
C.inputRadio

-- | Create a group of radio buttons that select between sub-forms
inputRadioForms :: (Functor m, Monad m, FormError error, ErrorInputType error ~ input, FormInput input, XMLGenerator x, StringType x ~ Text, EmbedAsChild x lbl, EmbedAsAttr x (Attr Text FormId)) =>
              [(Form m input error [XMLGenT x (XMLType x)] proof a, lbl)]  -- ^ value, label, initially checked
           -> a -- ^ default
           -> Form m input error [XMLGenT x (XMLType x)] proof a
inputRadioForms :: [(Form m input error [XMLGenT x (XMLType x)] proof a, lbl)]
-> a -> Form m input error [XMLGenT x (XMLType x)] proof a
inputRadioForms = [(Form m input error [XMLGenT x (XMLType x)] proof a, lbl)]
-> a -> Form m input error [XMLGenT x (XMLType x)] proof a
forall (m :: * -> *) (x :: * -> *) error input lbl proof a.
(Functor m, Monad m, FormError error, ErrorInputType error ~ input,
 FormInput input, XMLGenerator x, StringType x ~ Text,
 EmbedAsChild x lbl, EmbedAsAttr x (Attr Text FormId)) =>
[(Form m input error [XMLGenT x (XMLType x)] proof a, lbl)]
-> a -> Form m input error [XMLGenT x (XMLType x)] proof a
C.inputRadioForms

-- | Create an @\<input type=\"file\"\>@ element
--
-- This control may succeed even if the user does not actually select a file to upload. In that case the uploaded name will likely be \"\" and the file contents will be empty as well.
inputFile :: (Monad m, FormError error, FormInput input, ErrorInputType error ~ input, XMLGenerator x, StringType x ~ Text, EmbedAsAttr x (Attr Text FormId)) =>
             Form m input error [XMLGenT x (XMLType x)] () (FileType input)
inputFile :: Form m input error [XMLGenT x (XMLType x)] () (FileType input)
inputFile = Form m input error [XMLGenT x (XMLType x)] () (FileType input)
forall (m :: * -> *) error input (x :: * -> *).
(Monad m, FormError error, FormInput input,
 ErrorInputType error ~ input, XMLGenerator x, StringType x ~ Text,
 EmbedAsAttr x (Attr Text FormId)) =>
Form m input error [XMLGenT x (XMLType x)] () (FileType input)
C.inputFile

-- | create a  @\<button type=\"reset\"\>\<\/button\>@ element
--
-- This element does not add any data to the form data set.
buttonReset :: ( Monad m, FormError error, XMLGenerator x, StringType x ~ Text, EmbedAsChild x children , EmbedAsAttr x (Attr Text FormId)
                ) =>
               children -- ^ children of the @<\/button\>@ element
             -> Form m input error [XMLGenT x (XMLType x)] () ()
buttonReset :: children -> Form m input error [XMLGenT x (XMLType x)] () ()
buttonReset = children -> Form m input error [XMLGenT x (XMLType x)] () ()
forall (m :: * -> *) error (x :: * -> *) children input.
(Monad m, FormError error, XMLGenerator x, StringType x ~ Text,
 EmbedAsChild x children, EmbedAsAttr x (Attr Text FormId)) =>
children -> Form m input error [XMLGenT x (XMLType x)] () ()
C.buttonReset

-- | create a  @\<button type=\"button\"\>\<\/button\>@ element
--
-- This element does not add any data to the form data set.
button :: ( Monad m, FormError error, FormInput input, ErrorInputType error ~ input, XMLGenerator x, StringType x ~ Text, EmbedAsChild x children , EmbedAsAttr x (Attr Text FormId)) =>
          children -- ^ children to embed in the \<button\>
       -> Form m input error [XMLGenT x (XMLType x)] () ()
button :: children -> Form m input error [XMLGenT x (XMLType x)] () ()
button = children -> Form m input error [XMLGenT x (XMLType x)] () ()
forall (m :: * -> *) error (x :: * -> *) children input.
(Monad m, FormError error, XMLGenerator x, StringType x ~ Text,
 EmbedAsChild x children, EmbedAsAttr x (Attr Text FormId)) =>
children -> Form m input error [XMLGenT x (XMLType x)] () ()
C.button

-- | create @\<select\>\<\/select\>@ element plus its @\<option\>\<\/option\>@ children.
--
-- see also: 'selectMultiple'
select :: (Functor m, Monad m, FormError error, ErrorInputType error ~ input, FormInput input, XMLGenerator x, StringType x ~ Text, EmbedAsChild x lbl, EmbedAsAttr x (Attr Text FormId)) =>
              [(a, lbl)]  -- ^ (value, label)
           -> (a -> Bool) -- ^ specifies which value is initially selected. Must match *exactly one* element in the list of choices
           -> Form m input error [XMLGenT x (XMLType x)] () a
select :: [(a, lbl)]
-> (a -> Bool) -> Form m input error [XMLGenT x (XMLType x)] () a
select = [(a, lbl)]
-> (a -> Bool) -> Form m input error [XMLGenT x (XMLType x)] () a
forall (m :: * -> *) error input (x :: * -> *) lbl a.
(Functor m, Monad m, FormError error, ErrorInputType error ~ input,
 FormInput input, XMLGenerator x, StringType x ~ Text,
 EmbedAsChild x lbl, EmbedAsAttr x (Attr Text FormId)) =>
[(a, lbl)]
-> (a -> Bool) -> Form m input error [XMLGenT x (XMLType x)] () a
C.select

-- | create @\<select multiple=\"multiple\"\>\<\/select\>@ element plus its @\<option\>\<\/option\>@ children.
--
-- This creates a @\<select\>@ element which allows more than one item to be selected.
selectMultiple :: (Functor m, Monad m, FormError error, ErrorInputType error ~ input, FormInput input, XMLGenerator x, StringType x ~ Text, EmbedAsChild x lbl, EmbedAsAttr x (Attr Text FormId)) =>
                  [(a, lbl)]  -- ^ (value, label)
               -> (a -> Bool) -- ^ specifies which values are initially selected. Can match 0 or more elements.
               -> Form m input error [XMLGenT x (XMLType x)] () [a]
selectMultiple :: [(a, lbl)]
-> (a -> Bool) -> Form m input error [XMLGenT x (XMLType x)] () [a]
selectMultiple = [(a, lbl)]
-> (a -> Bool) -> Form m input error [XMLGenT x (XMLType x)] () [a]
forall (m :: * -> *) error input (x :: * -> *) lbl a.
(Functor m, Monad m, FormError error, ErrorInputType error ~ input,
 FormInput input, XMLGenerator x, StringType x ~ Text,
 EmbedAsChild x lbl, EmbedAsAttr x (Attr Text FormId)) =>
[(a, lbl)]
-> (a -> Bool) -> Form m input error [XMLGenT x (XMLType x)] () [a]
C.selectMultiple

-- | create a @\<label\>@ element.
--
-- Use this with <++ or ++> to ensure that the @for@ attribute references the correct @id@.
--
-- > label "some input field: " ++> inputText ""
label :: (Monad m, XMLGenerator x, StringType x ~ Text, EmbedAsAttr x (Attr Text FormId), EmbedAsChild x c) =>
         c
      -> Form m input error [XMLGenT x (XMLType x)] () ()
label :: c -> Form m input error [XMLGenT x (XMLType x)] () ()
label = c -> Form m input error [XMLGenT x (XMLType x)] () ()
forall (m :: * -> *) (x :: * -> *) c input error.
(Monad m, XMLGenerator x, StringType x ~ Text,
 EmbedAsAttr x (Attr Text FormId), EmbedAsChild x c) =>
c -> Form m input error [XMLGenT x (XMLType x)] () ()
C.label

-- | create a @\<ul\>@ which contains all the errors related to the 'Form'.
--
-- The @<\ul\>@ will have the attribute @class=\"reform-error-list\"@.
errorList :: (Monad m, XMLGenerator x, StringType x ~ Text, EmbedAsChild x error) =>
             Form m input error [XMLGenT x (XMLType x)] () ()
errorList :: Form m input error [XMLGenT x (XMLType x)] () ()
errorList = Form m input error [XMLGenT x (XMLType x)] () ()
forall (m :: * -> *) (x :: * -> *) error input.
(Monad m, XMLGenerator x, StringType x ~ Text,
 EmbedAsChild x error) =>
Form m input error [XMLGenT x (XMLType x)] () ()
C.errorList

-- | create a @\<ul\>@ which contains all the errors related to the 'Form'.
--
-- Includes errors from children of the current form.
--
-- The @<\ul\>@ will have the attribute @class=\"reform-error-list\"@.
childErrorList :: (Monad m, XMLGenerator x, StringType x ~ Text, EmbedAsChild x error) =>
             Form m input error [XMLGenT x (XMLType x)] () ()
childErrorList :: Form m input error [XMLGenT x (XMLType x)] () ()
childErrorList = Form m input error [XMLGenT x (XMLType x)] () ()
forall (m :: * -> *) (x :: * -> *) error input.
(Monad m, XMLGenerator x, StringType x ~ Text,
 EmbedAsChild x error) =>
Form m input error [XMLGenT x (XMLType x)] () ()
C.childErrorList

-- | create a @\<br\>@ tag.
br :: (Monad m, XMLGenerator x, StringType x ~ Text) => Form m input error [XMLGenT x (XMLType x)] () ()
br :: Form m input error [XMLGenT x (XMLType x)] () ()
br = Form m input error [XMLGenT x (XMLType x)] () ()
forall (m :: * -> *) (x :: * -> *) input error.
(Monad m, XMLGenerator x, StringType x ~ Text) =>
Form m input error [XMLGenT x (XMLType x)] () ()
C.br

-- | wrap a @\<fieldset class=\"reform\"\>@ around a 'Form'
--
fieldset :: (Monad m, Functor m, XMLGenerator x, StringType x ~ Text, EmbedAsChild x c) =>
            Form m input error c proof a
         -> Form m input error [XMLGenT x (XMLType x)] proof a
fieldset :: Form m input error c proof a
-> Form m input error [XMLGenT x (XMLType x)] proof a
fieldset = Form m input error c proof a
-> Form m input error [XMLGenT x (XMLType x)] proof a
forall (m :: * -> *) (x :: * -> *) c input error proof a.
(Monad m, Functor m, XMLGenerator x, StringType x ~ Text,
 EmbedAsChild x c) =>
Form m input error c proof a
-> Form m input error [XMLGenT x (XMLType x)] proof a
C.fieldset

-- | wrap an @\<ol class=\"reform\"\>@ around a 'Form'
ol :: (Monad m, Functor m, XMLGenerator x, StringType x ~ Text, EmbedAsChild x c) =>
      Form m input error c proof a
   -> Form m input error [XMLGenT x (XMLType x)] proof a
ol :: Form m input error c proof a
-> Form m input error [XMLGenT x (XMLType x)] proof a
ol = Form m input error c proof a
-> Form m input error [XMLGenT x (XMLType x)] proof a
forall (m :: * -> *) (x :: * -> *) c input error proof a.
(Monad m, Functor m, XMLGenerator x, StringType x ~ Text,
 EmbedAsChild x c) =>
Form m input error c proof a
-> Form m input error [XMLGenT x (XMLType x)] proof a
C.ol

-- | wrap a @\<ul class=\"reform\"\>@ around a 'Form'
ul :: (Monad m, Functor m, XMLGenerator x, StringType x ~ Text, EmbedAsChild x c) =>
      Form m input error c proof a
   -> Form m input error [XMLGenT x (XMLType x)] proof a
ul :: Form m input error c proof a
-> Form m input error [XMLGenT x (XMLType x)] proof a
ul = Form m input error c proof a
-> Form m input error [XMLGenT x (XMLType x)] proof a
forall (m :: * -> *) (x :: * -> *) c input error proof a.
(Monad m, Functor m, XMLGenerator x, StringType x ~ Text,
 EmbedAsChild x c) =>
Form m input error c proof a
-> Form m input error [XMLGenT x (XMLType x)] proof a
C.ul

-- | wrap a @\<li class=\"reform\"\>@ around a 'Form'
li :: (Monad m, Functor m, XMLGenerator x, StringType x ~ Text, EmbedAsChild x c) =>
      Form m input error c proof a
   -> Form m input error [XMLGenT x (XMLType x)] proof a
li :: Form m input error c proof a
-> Form m input error [XMLGenT x (XMLType x)] proof a
li = Form m input error c proof a
-> Form m input error [XMLGenT x (XMLType x)] proof a
forall (m :: * -> *) (x :: * -> *) c input error proof a.
(Monad m, Functor m, XMLGenerator x, StringType x ~ Text,
 EmbedAsChild x c) =>
Form m input error c proof a
-> Form m input error [XMLGenT x (XMLType x)] proof a
C.li

-- | create @\<form action=action method=\"POST\" enctype=\"multipart/form-data\"\>@
form :: (XMLGenerator x, StringType x ~ Text, EmbedAsAttr x (Attr Text action)) =>
        action                  -- ^ action url
     -> [(Text, Text)]       -- ^ extra hidden fields to add to form
     -> [XMLGenT x (XMLType x)] -- ^ children
     -> [XMLGenT x (XMLType x)]
form :: action
-> [(Text, Text)]
-> [XMLGenT x (XMLType x)]
-> [XMLGenT x (XMLType x)]
form = action
-> [(Text, Text)]
-> [XMLGenT x (XMLType x)]
-> [XMLGenT x (XMLType x)]
forall (x :: * -> *) action.
(XMLGenerator x, StringType x ~ Text,
 EmbedAsAttr x (Attr Text action)) =>
action
-> [(Text, Text)]
-> [XMLGenT x (XMLType x)]
-> [XMLGenT x (XMLType x)]
C.form

-- | set the attributes on the top-level elements of 'Form'
setAttrs :: (EmbedAsAttr x attr, XMLGenerator x, StringType x ~ Text, Monad m, Functor m) =>
            Form m input error [XMLGenT x (XMLType x)] proof a
         -> attr
         -> Form m input error [GenXML x] proof a
setAttrs :: Form m input error [XMLGenT x (XMLType x)] proof a
-> attr -> Form m input error [XMLGenT x (XMLType x)] proof a
setAttrs = Form m input error [XMLGenT x (XMLType x)] proof a
-> attr -> Form m input error [XMLGenT x (XMLType x)] proof a
forall (x :: * -> *) attr (m :: * -> *) input error proof a.
(EmbedAsAttr x attr, XMLGenerator x, StringType x ~ Text, Monad m,
 Functor m) =>
Form m input error [GenXML x] proof a
-> attr -> Form m input error [GenXML x] proof a
C.setAttrs