{-# LANGUAGE RankNTypes, TypeFamilies #-} {- | This module provides functions creating Reform using Hamlet 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.Hamlet.Text". -} module Text.Reform.Hamlet.String ( -- * \ element inputText , inputPassword , inputSubmit , inputReset , inputHidden , inputButton , inputCheckbox , inputCheckboxes , inputRadio , inputFile -- * \ element , textarea -- * \ element , buttonSubmit , buttonReset , button -- * \ element , select , selectMultiple -- * \ element , label -- * errors , errorList , childErrorList -- * layout functions , br , fieldset , ol , ul , li , form ) where import Data.Text.Lazy (Text, pack) import Text.Blaze (ToMarkup(..)) import Text.Reform import qualified Text.Reform.Hamlet.Common as C import Text.Hamlet (HtmlUrl) -- | Create an @\@ element inputText :: (Monad m, FormInput input, FormError error, ErrorInputType error ~ input) => String -- ^ initial value -> Form m input error (HtmlUrl url) () String inputText initialValue = C.inputText getInputString initialValue -- | Create an @\@ element inputPassword :: (Monad m, FormInput input, FormError error, ErrorInputType error ~ input) => Form m input error (HtmlUrl url) () String inputPassword = C.inputPassword getInputString "" -- | 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) => String -- ^ @value@ attribute. Used for button label, and value if button is submitted. -> Form m input error (HtmlUrl url) () (Maybe String) inputSubmit initialValue = C.inputSubmit getInputString 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) => String -- ^ value attribute. Used only to label the button. -> Form m input error (HtmlUrl url) () () inputReset = C.inputReset -- | Create an @\@ element inputHidden :: (Monad m, FormInput input, FormError error, ErrorInputType error ~ input) => String -- ^ value to store in the hidden element -> Form m input error (HtmlUrl url) () String inputHidden initialValue = C.inputHidden getInputString 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) => String -- ^ value attribute. Used to label the button. -> Form m input error (HtmlUrl url) () () inputButton label = C.inputButton label -- | Create a \\<\/textarea\> element textarea :: (Monad m, FormInput input, FormError error, ErrorInputType error ~ input) => Int -- ^ cols -> Int -- ^ rows -> String -- ^ initial contents -> Form m input error (HtmlUrl url) () String textarea rows cols initialValue = C.textarea getInputString rows cols initialValue -- | create a @\