{-# 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 'Text' values. If you prefer 'String' see "Text.Reform.HSP.String". -} module Text.Reform.HSP.Text ( -- * \ element inputText , inputPassword , inputSubmit , inputReset , inputHidden , inputButton , inputCheckbox , inputCheckboxes , inputRadio , inputRadioForms , inputFile -- * \ element , textarea -- * \ element , buttonSubmit , buttonReset , button -- * \ element , select , selectMultiple -- * \ element , label , labelText -- * errors , errorList , childErrorList -- * layout functions , 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 -- | Create an @\@ 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 T.Text)) => T.Text -- ^ initial value -> Form m input error [XMLGenT x (XMLType x)] () T.Text inputText initialValue = C.inputText getInputText initialValue -- | Create an @\@ 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 T.Text)) => Form m input error [XMLGenT x (XMLType x)] () T.Text inputPassword = C.inputPassword getInputText empty -- | Create an @\@ 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 T.Text)) => T.Text -- ^ @value@ attribute. Used for button label, and value if button is submitted. -> Form m input error [XMLGenT x (XMLType x)] () (Maybe T.Text) inputSubmit initialValue = C.inputSubmit getInputText initialValue -- | Create an @\@ 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 T.Text)) => T.Text -- ^ value attribute. Used only to label the button. -> Form m input error [XMLGenT x (XMLType x)] () () inputReset = C.inputReset -- | Create an @\@ 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 T.Text)) => T.Text -- ^ value to store in the hidden element -> Form m input error [XMLGenT x (XMLType x)] () T.Text inputHidden initialValue = C.inputHidden getInputText initialValue -- | Create an @\@ 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 Text)) => Text -- ^ value attribute. Used to label the button. -> Form m input error [XMLGenT x (XMLType x)] () () inputButton label = C.inputButton label -- | Create a \\<\/textarea\> element 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 -- ^ cols -> Int -- ^ rows -> T.Text -- ^ initial contents -> Form m input error [XMLGenT x (XMLType x)] () T.Text textarea rows cols initialValue = C.textarea getInputText rows cols initialValue -- | create a @\