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

Yesod.Form.Types

Contents

Synopsis

Helpers

data Enctype Source

The encoding type required by a form. The ToHtml instance produces values that can be inserted directly into HTML.

Constructors

UrlEncoded 
Multipart 

data FormResult a Source

A form can produce three different results: there was no data available, the data was invalid, or there was a successful parse.

The Applicative instance will concatenate the failure messages in two FormResults.

type Env = [(Text, Text)]Source

data Ints Source

Constructors

IntCons Int Ints 
IntSingle Int 

Instances

Form

type Form master m a = RWST (Maybe (Env, FileEnv), master, [Text]) Enctype Ints m aSource

newtype AForm xml master m a Source

Constructors

AForm 

Fields

unAForm :: (master, [Text]) -> Maybe (Env, FileEnv) -> Ints -> m (FormResult a, xml, Ints, Enctype)
 

Instances

Monoid xml => MonadTrans (AForm xml msg) 
Monad m => Functor (AForm xml msg m) 
(Monad m, Monoid xml) => Applicative (AForm xml msg m) 
(Monad m, Monoid xml, Monoid a) => Monoid (AForm xml msg m a) 

Build forms

data Field xml msg a Source

Constructors

Field 

Fields

fieldParse :: Maybe Text -> Either msg (Maybe a)
 
fieldRender :: a -> Text
 
fieldView :: Text -> Text -> Text -> Bool -> xml

ID, name, value, required

data FieldSettings msg Source

Constructors

FieldSettings 

Fields

fsLabel :: msg
 
fsTooltip :: Maybe msg
 
fsId :: Maybe Text
 
fsName :: Maybe Text
 

Instances

data FieldView xml Source

Constructors

FieldView