{-# LANGUAGE FlexibleContexts, FlexibleInstances, MultiParamTypeClasses, ScopedTypeVariables, TypeFamilies, UndecidableInstances, ViewPatterns #-}
module Text.Reform.HSP.Text
(
inputEmail
, inputText
, inputPassword
, inputSubmit
, inputReset
, inputHidden
, inputButton
, inputCheckbox
, inputCheckboxes
, inputRadio
, inputRadioForms
, inputFile
, textarea
, buttonSubmit
, buttonReset
, button
, select
, selectMultiple
, label
, labelText
, errorList
, childErrorList
, br
, fieldset
, ol
, ul
, li
, form
, setAttrs
) where
import Data.Text (empty)
import qualified Data.Text as T
import Data.Text.Lazy (Text)
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 T.Text)) =>
T.Text
-> Form m input error [XMLGenT x (XMLType x)] () T.Text
inputEmail :: Text -> Form m input error [XMLGenT x (XMLType x)] () Text
inputEmail initialValue :: Text
initialValue = (input -> Either error Text)
-> Text -> Form m input error [XMLGenT x (XMLType x)] () Text
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 Text
forall input error.
(FormInput input, FormError error, ErrorInputType error ~ input) =>
input -> Either error Text
getInputText Text
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 T.Text)) =>
T.Text
-> Form m input error [XMLGenT x (XMLType x)] () T.Text
inputText :: Text -> Form m input error [XMLGenT x (XMLType x)] () Text
inputText initialValue :: Text
initialValue = (input -> Either error Text)
-> Text -> Form m input error [XMLGenT x (XMLType x)] () Text
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 Text
forall input error.
(FormInput input, FormError error, ErrorInputType error ~ input) =>
input -> Either error Text
getInputText Text
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 T.Text)) =>
Form m input error [XMLGenT x (XMLType x)] () T.Text
inputPassword :: Form m input error [XMLGenT x (XMLType x)] () Text
inputPassword = (input -> Either error Text)
-> Text -> Form m input error [XMLGenT x (XMLType x)] () Text
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 Text
forall input error.
(FormInput input, FormError error, ErrorInputType error ~ input) =>
input -> Either error Text
getInputText Text
empty
inputSubmit :: (Monad m, FormInput input, FormError error, ErrorInputType error ~ input, XMLGenerator x, StringType x ~ Text, EmbedAsAttr x (Attr Text FormId), EmbedAsAttr x (Attr Text T.Text)) =>
T.Text
-> Form m input error [XMLGenT x (XMLType x)] () (Maybe T.Text)
inputSubmit :: Text -> Form m input error [XMLGenT x (XMLType x)] () (Maybe Text)
inputSubmit initialValue :: Text
initialValue = (input -> Either error Text)
-> Text
-> Form m input error [XMLGenT x (XMLType x)] () (Maybe Text)
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 Text
forall input error.
(FormInput input, FormError error, ErrorInputType error ~ input) =>
input -> Either error Text
getInputText Text
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 T.Text)) =>
T.Text
-> Form m input error [XMLGenT x (XMLType x)] () ()
inputReset :: Text -> Form m input error [XMLGenT x (XMLType x)] () ()
inputReset = Text -> 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 T.Text)) =>
T.Text
-> Form m input error [XMLGenT x (XMLType x)] () T.Text
inputHidden :: Text -> Form m input error [XMLGenT x (XMLType x)] () Text
inputHidden initialValue :: Text
initialValue = (input -> Either error Text)
-> Text -> Form m input error [XMLGenT x (XMLType x)] () Text
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 Text
forall input error.
(FormInput input, FormError error, ErrorInputType error ~ input) =>
input -> Either error Text
getInputText Text
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 Text)) =>
Text
-> Form m input error [XMLGenT x (XMLType x)] () ()
inputButton :: Text -> Form m input error [XMLGenT x (XMLType x)] () ()
inputButton label :: Text
label = Text -> 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 Text
label
textarea :: (Monad m, FormInput input, FormError error, ErrorInputType error ~ input, XMLGenerator x, StringType x ~ Text, EmbedAsAttr x (Attr Text FormId), EmbedAsAttr x (Attr Text T.Text), EmbedAsChild x T.Text) =>
Int
-> Int
-> T.Text
-> Form m input error [XMLGenT x (XMLType x)] () T.Text
textarea :: Int
-> Int
-> Text
-> Form m input error [XMLGenT x (XMLType x)] () Text
textarea rows :: Int
rows cols :: Int
cols initialValue :: Text
initialValue = (input -> Either error Text)
-> Int
-> Int
-> Text
-> Form m input error [XMLGenT x (XMLType x)] () Text
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 Text
forall input error.
(FormInput input, FormError error, ErrorInputType error ~ input) =>
input -> Either error Text
getInputText Int
rows Int
cols Text
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 T.Text)) =>
T.Text
-> children
-> Form m input error [XMLGenT x (XMLType x)] () (Maybe T.Text)
buttonSubmit :: Text
-> children
-> Form m input error [XMLGenT x (XMLType x)] () (Maybe Text)
buttonSubmit = (input -> Either error Text)
-> Text
-> children
-> Form m input error [XMLGenT x (XMLType x)] () (Maybe Text)
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 Text
forall input error.
(FormInput input, FormError error, ErrorInputType error ~ input) =>
input -> Either error Text
getInputText
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
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 :: [(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 :: [(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 :: [(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 :: 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 :: 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 :: 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 :: [(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 :: [(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 :: 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
labelText :: (Monad m, XMLGenerator x, StringType x ~ Text, EmbedAsAttr x (Attr Text FormId), EmbedAsChild x Text) =>
Text
-> Form m input error [XMLGenT x (XMLType x)] () ()
labelText :: Text -> Form m input error [XMLGenT x (XMLType x)] () ()
labelText = Text -> 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 :: 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 :: 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 :: 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 :: 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 :: 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 :: 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 :: 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 :: 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 :: 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