yesod-form-1.6.1: Form handling support for Yesod Web Framework

Safe HaskellNone
LanguageHaskell98

Yesod.Form.Functions

Contents

Synopsis

Running in MForm monad

newFormIdent :: Monad m => MForm m Text Source #

Get a unique identifier.

Applicative/Monadic conversion

formToAForm :: (HandlerSite m ~ site, Monad m) => MForm m (FormResult a, [FieldView site]) -> AForm m a Source #

aFormToForm :: (Monad m, HandlerSite m ~ site) => AForm m a -> MForm m (FormResult a, [FieldView site] -> [FieldView site]) Source #

mFormToWForm Source #

Arguments

:: (MonadHandler m, HandlerSite m ~ site) 
=> MForm m (a, FieldView site)

input form

-> WForm m a

output form

Converts a monadic form MForm into another monadic form WForm.

Since: 1.4.14

wFormToAForm Source #

Arguments

:: MonadHandler m 
=> WForm m (FormResult a)

input form

-> AForm m a

output form

Converts a monadic form WForm into an applicative form AForm.

Since: 1.4.14

wFormToMForm Source #

Arguments

:: (MonadHandler m, HandlerSite m ~ site) 
=> WForm m a

input form

-> MForm m (a, [FieldView site])

output form

Converts a monadic form WForm into another monadic form MForm.

Since: 1.4.14

Fields to Forms

wreq Source #

Arguments

:: (RenderMessage site FormMessage, HandlerSite m ~ site, MonadHandler m) 
=> Field m a

form field

-> FieldSettings site

settings for this field

-> Maybe a

optional default value

-> WForm m (FormResult a) 

Converts a form field into monadic form WForm. This field requires a value and will return FormFailure if left empty.

Since: 1.4.14

wopt Source #

Arguments

:: (MonadHandler m, HandlerSite m ~ site) 
=> Field m a

form field

-> FieldSettings site

settings for this field

-> Maybe (Maybe a)

optional default value

-> WForm m (FormResult (Maybe a)) 

Converts a form field into monadic form WForm. This field is optional, i.e. if filled in, it returns 'Just a', if left empty, it returns Nothing. Arguments are the same as for wreq (apart from type of default value).

Since: 1.4.14

mreq Source #

Arguments

:: (RenderMessage site FormMessage, HandlerSite m ~ site, MonadHandler m) 
=> Field m a

form field

-> FieldSettings site

settings for this field

-> Maybe a

optional default value

-> MForm m (FormResult a, FieldView site) 

Converts a form field into monadic form. This field requires a value and will return FormFailure if left empty.

mopt :: (site ~ HandlerSite m, MonadHandler m) => Field m a -> FieldSettings site -> Maybe (Maybe a) -> MForm m (FormResult (Maybe a), FieldView site) Source #

Converts a form field into monadic form. This field is optional, i.e. if filled in, it returns 'Just a', if left empty, it returns Nothing. Arguments are the same as for mreq (apart from type of default value).

areq :: (RenderMessage site FormMessage, HandlerSite m ~ site, MonadHandler m) => Field m a -> FieldSettings site -> Maybe a -> AForm m a Source #

Applicative equivalent of mreq.

aopt :: MonadHandler m => Field m a -> FieldSettings (HandlerSite m) -> Maybe (Maybe a) -> AForm m (Maybe a) Source #

Applicative equivalent of mopt.

Run a form

runFormPost :: (RenderMessage (HandlerSite m) FormMessage, MonadResource m, MonadHandler m) => (Markup -> MForm m (FormResult a, xml)) -> m ((FormResult a, xml), Enctype) Source #

This function is used to both initially render a form and to later extract results from it. Note that, due to CSRF protection and a few other issues, forms submitted via GET and POST are slightly different. As such, be sure to call the relevant function based on how the form will be submitted, not the current request method.

For example, a common case is displaying a form on a GET request and having the form submit to a POST page. In such a case, both the GET and POST handlers should use runFormPost.

runFormGet :: MonadHandler m => (Markup -> MForm m a) -> m (a, Enctype) Source #

Generate a blank form

generateFormPost :: (RenderMessage (HandlerSite m) FormMessage, MonadHandler m) => (Markup -> MForm m (FormResult a, xml)) -> m (xml, Enctype) Source #

Similar to runFormPost, except it always ignores the currently available environment. This is necessary in cases like a wizard UI, where a single page will both receive and incoming form and produce a new, blank form. For general usage, you can stick with runFormPost.

generateFormGet' :: MonadHandler m => (Markup -> MForm m (FormResult a, xml)) -> m (xml, Enctype) Source #

Since 1.3.11

generateFormGet :: MonadHandler m => (Markup -> MForm m a) -> m (a, Enctype) Source #

Deprecated: Will require RenderMessage in next version of Yesod

More than one form on a handler

identifyForm Source #

Arguments

:: Monad m 
=> Text

Form identification string.

-> (Markup -> MForm m (FormResult a, WidgetFor (HandlerSite m) ())) 
-> Markup -> MForm m (FormResult a, WidgetFor (HandlerSite m) ()) 

Creates a hidden field on the form that identifies it. This identification is then used to distinguish between missing and wrong form data when a single handler contains more than one form.

For instance, if you have the following code on your handler:

((fooRes, fooWidget), fooEnctype) <- runFormPost fooForm
((barRes, barWidget), barEnctype) <- runFormPost barForm

Then replace it with

((fooRes, fooWidget), fooEnctype) <- runFormPost $ identifyForm "foo" fooForm
((barRes, barWidget), barEnctype) <- runFormPost $ identifyForm "bar" barForm

Note that it's your responsibility to ensure that the identification strings are unique (using the same one twice on a single handler will not generate any errors). This allows you to create a variable number of forms and still have them work even if their number or order change between the HTML generation and the form submission.

Rendering

type FormRender m a = AForm m a -> Markup -> MForm m (FormResult a, WidgetFor (HandlerSite m) ()) Source #

renderTable :: Monad m => FormRender m a Source #

Render a form into a series of tr tags. Note that, in order to allow you to add extra rows to the table, this function does not wrap up the resulting HTML in a table tag; you must do that yourself.

renderDivs :: Monad m => FormRender m a Source #

render a field inside a div

renderDivsNoLabels :: Monad m => FormRender m a Source #

render a field inside a div, not displaying any label

renderBootstrap :: Monad m => FormRender m a Source #

Deprecated: Please use the Yesod.Form.Bootstrap3 module.

Deprecated synonym for renderBootstrap2.

renderBootstrap2 :: Monad m => FormRender m a Source #

Render a form using Bootstrap v2-friendly shamlet syntax. If you're using Bootstrap v3, then you should use the functions from module Yesod.Form.Bootstrap3.

Sample Hamlet:

 <form .form-horizontal method=post action=@{ActionR} enctype=#{formEnctype}>
   <fieldset>
     <legend>_{MsgLegend}
     $case result
       $of FormFailure reasons
         $forall reason <- reasons
           <div .alert .alert-error>#{reason}
       $of _
     ^{formWidget}
     <div .form-actions>
       <input .btn .primary type=submit value=_{MsgSubmit}>

Since 1.3.14

Validation

check :: (Monad m, RenderMessage (HandlerSite m) msg) => (a -> Either msg a) -> Field m a -> Field m a Source #

checkBool :: (Monad m, RenderMessage (HandlerSite m) msg) => (a -> Bool) -> msg -> Field m a -> Field m a Source #

Return the given error message if the predicate is false.

checkM :: (Monad m, RenderMessage (HandlerSite m) msg) => (a -> m (Either msg a)) -> Field m a -> Field m a Source #

checkMMap :: (Monad m, RenderMessage (HandlerSite m) msg) => (a -> m (Either msg b)) -> (b -> a) -> Field m a -> Field m b Source #

Same as checkM, but modifies the datatype.

In order to make this work, you must provide a function to convert back from the new datatype to the old one (the second argument to this function).

Since 1.1.2

customErrorMessage :: Monad m => SomeMessage (HandlerSite m) -> Field m a -> Field m a Source #

Allows you to overwrite the error message on parse error.

Utilities

fieldSettingsLabel :: RenderMessage site msg => msg -> FieldSettings site Source #

Generate a FieldSettings from the given label.

parseHelper :: (Monad m, RenderMessage site FormMessage) => (Text -> Either FormMessage a) -> [Text] -> [FileInfo] -> m (Either (SomeMessage site) (Maybe a)) Source #

A helper function for creating custom fields.

This is intended to help with the common case where a single input value is required, such as when parsing a text field.

Since 1.1

parseHelperGen :: (Monad m, RenderMessage site msg) => (Text -> Either msg a) -> [Text] -> [FileInfo] -> m (Either (SomeMessage site) (Maybe a)) Source #

A generalized version of parseHelper, allowing any type for the message indicating a bad parse.

Since 1.3.6

convertField :: Functor m => (a -> b) -> (b -> a) -> Field m a -> Field m b Source #

Since a Field cannot be a Functor, it is not obvious how to "reuse" a Field on a newtype or otherwise equivalent type. This function allows you to convert a Field m a to a Field m b assuming you provide a bidirectional conversion between the two, through the first two functions.

A simple example:

import Data.Monoid
sumField :: (Functor m, Monad m, RenderMessage (HandlerSite m) FormMessage) => Field m (Sum Int)
sumField = convertField Sum getSum intField

Another example, not using a newtype, but instead creating a Lazy Text field:

import qualified Data.Text.Lazy as TL
TextField :: (Functor m, Monad m, RenderMessage (HandlerSite m) FormMessage) => Field m TL.Text
lazyTextField = convertField TL.fromStrict TL.toStrict textField

Since 1.3.16