{-# LANGUAGE FlexibleContexts, FlexibleInstances, MultiParamTypeClasses, ScopedTypeVariables, TypeFamilies, UndecidableInstances, ViewPatterns #-}
module Text.Reform.HSP.String
(
inputEmail
, inputText
, inputPassword
, inputSubmit
, inputReset
, inputHidden
, inputButton
, inputCheckbox
, inputCheckboxes
, inputRadio
, inputRadioForms
, inputFile
, textarea
, buttonSubmit
, buttonReset
, button
, select
, selectMultiple
, label
, errorList
, childErrorList
, 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
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
-> Form m input error [XMLGenT x (XMLType x)] () String
inputEmail :: forall (m :: * -> *) input error (x :: * -> *).
(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 -> Form m input error [XMLGenT x (XMLType x)] () String
inputEmail 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
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
-> Form m input error [XMLGenT x (XMLType x)] () String
inputText :: forall (m :: * -> *) input error (x :: * -> *).
(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 -> Form m input error [XMLGenT x (XMLType x)] () String
inputText 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
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 :: forall (m :: * -> *) input error (x :: * -> *).
(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 = (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 String
""
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
-> Form m input error [XMLGenT x (XMLType x)] () (Maybe String)
inputSubmit :: forall (m :: * -> *) input error (x :: * -> *).
(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
-> Form m input error [XMLGenT x (XMLType x)] () (Maybe String)
inputSubmit 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
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
-> Form m input error [XMLGenT x (XMLType x)] () ()
inputReset :: forall (m :: * -> *) input error (x :: * -> *).
(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 -> 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
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
-> Form m input error [XMLGenT x (XMLType x)] () String
inputHidden :: forall (m :: * -> *) input error (x :: * -> *).
(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 -> Form m input error [XMLGenT x (XMLType x)] () String
inputHidden 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
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
-> Form m input error [XMLGenT x (XMLType x)] () ()
inputButton :: forall (m :: * -> *) input error (x :: * -> *).
(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 -> Form m input error [XMLGenT x (XMLType x)] () ()
inputButton 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
textarea :: (Monad m, FormInput input, FormError error, ErrorInputType error ~ input, XMLGenerator x, StringType x ~ Text, EmbedAsAttr x (Attr Text FormId)) =>
Int
-> Int
-> String
-> Form m input error [XMLGenT x (XMLType x)] () String
textarea :: forall (m :: * -> *) input error (x :: * -> *).
(Monad m, FormInput input, FormError error,
ErrorInputType error ~ input, XMLGenerator x, StringType x ~ Text,
EmbedAsAttr x (Attr Text FormId)) =>
Int
-> Int
-> String
-> Form m input error [XMLGenT x (XMLType x)] () String
textarea Int
rows Int
cols 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
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
-> children
-> Form m input error [XMLGenT x (XMLType x)] () (Maybe String)
buttonSubmit :: forall (m :: * -> *) error input (x :: * -> *) children.
(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
-> 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
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
-> Form m input error [XMLGenT x (XMLType x)] () Bool
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 -> 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
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)]
-> (a -> Bool)
-> Form m input error [XMLGenT x (XMLType x)] () [a]
inputCheckboxes :: 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]
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
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)]
-> (a -> Bool)
-> Form m input error [XMLGenT x (XMLType x)] () a
inputRadio :: 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
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
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)]
-> a
-> Form m input error [XMLGenT x (XMLType x)] proof a
inputRadioForms :: forall (m :: * -> *) error input (x :: * -> *) 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
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
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 :: 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)
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
buttonReset :: ( 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)] () ()
buttonReset :: 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)] () ()
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
button :: ( Monad m, FormError error, FormInput input, ErrorInputType error ~ input, XMLGenerator x, StringType x ~ Text, EmbedAsChild x children , EmbedAsAttr x (Attr Text FormId)) =>
children
-> Form m input error [XMLGenT x (XMLType x)] () ()
button :: forall (m :: * -> *) error input (x :: * -> *) children.
(Monad m, FormError error, FormInput input,
ErrorInputType error ~ input, XMLGenerator x, StringType x ~ Text,
EmbedAsChild x children, EmbedAsAttr x (Attr Text FormId)) =>
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
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)]
-> (a -> Bool)
-> Form m input error [XMLGenT x (XMLType x)] () a
select :: 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
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
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)]
-> (a -> Bool)
-> Form m input error [XMLGenT x (XMLType x)] () [a]
selectMultiple :: 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]
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
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 :: 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)] () ()
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
errorList :: (Monad m, XMLGenerator x, StringType x ~ Text, EmbedAsChild x error) =>
Form m input error [XMLGenT x (XMLType x)] () ()
errorList :: forall (m :: * -> *) (x :: * -> *) error input.
(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)] () ()
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
childErrorList :: (Monad m, XMLGenerator x, StringType x ~ Text, EmbedAsChild x error) =>
Form m input error [XMLGenT x (XMLType x)] () ()
childErrorList :: forall (m :: * -> *) (x :: * -> *) error input.
(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)] () ()
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
br :: (Monad m, XMLGenerator x, StringType x ~ Text) => Form m input error [XMLGenT x (XMLType x)] () ()
br :: forall (m :: * -> *) (x :: * -> *) input error.
(Monad m, XMLGenerator x, StringType x ~ Text) =>
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
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 :: 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
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
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 :: 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
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
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 :: 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
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
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 :: 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
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
form :: (XMLGenerator x, StringType x ~ Text, EmbedAsAttr x (Attr Text action)) =>
action
-> [(Text, Text)]
-> [XMLGenT x (XMLType x)]
-> [XMLGenT x (XMLType x)]
form :: forall (x :: * -> *) action.
(XMLGenerator x, StringType x ~ Text,
EmbedAsAttr x (Attr Text action)) =>
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
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 :: forall (x :: * -> *) attr (m :: * -> *) input error proof a.
(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 [XMLGenT x (XMLType x)] proof a
setAttrs = Form m input error [GenXML x] proof a
-> attr -> Form m input error [GenXML 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 [XMLGenT x (XMLType x)] proof a
-> attr -> Form m input error [XMLGenT x (XMLType x)] proof a
C.setAttrs