Safe Haskell | None |
---|
- data Enctype
- = UrlEncoded
- | Multipart
- data FormResult a
- = FormMissing
- | FormFailure [Text]
- | FormSuccess a
- data FormMessage
- = MsgInvalidInteger Text
- | MsgInvalidNumber Text
- | MsgInvalidEntry Text
- | MsgInvalidUrl Text
- | MsgInvalidEmail Text
- | MsgInvalidTimeFormat
- | MsgInvalidHour Text
- | MsgInvalidMinute Text
- | MsgInvalidSecond Text
- | MsgInvalidDay
- | MsgCsrfWarning
- | MsgValueRequired
- | MsgInputNotFound Text
- | MsgSelectNone
- | MsgInvalidBool Text
- | MsgBoolYes
- | MsgBoolNo
- | MsgDelete
- type Env = Map Text [Text]
- type FileEnv = Map Text [FileInfo]
- data Ints
- type MForm m a = RWST (Maybe (Env, FileEnv), HandlerSite m, [Lang]) Enctype Ints m a
- newtype AForm m a = AForm {
- unAForm :: (HandlerSite m, [Text]) -> Maybe (Env, FileEnv) -> Ints -> m (FormResult a, [FieldView (HandlerSite m)] -> [FieldView (HandlerSite m)], Ints, Enctype)
- data Field m a = Field {
- fieldParse :: [Text] -> [FileInfo] -> m (Either (SomeMessage (HandlerSite m)) (Maybe a))
- fieldView :: FieldViewFunc m a
- fieldEnctype :: Enctype
- data FieldSettings master = FieldSettings {}
- data FieldView site = FieldView {}
- type FieldViewFunc m a = Text -> Text -> [(Text, Text)] -> Either Text a -> Bool -> WidgetT (HandlerSite m) IO ()
Helpers
The encoding type required by a form. The ToHtml
instance produces values
that can be inserted directly into HTML.
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
FormResult
s.
Functor FormResult | |
Applicative FormResult | |
Show a => Show (FormResult a) | |
Monoid m => Monoid (FormResult m) |
data FormMessage Source
Form
AForm | |
|
Build forms
Field | |
|
data FieldSettings master Source