Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module provides helper functions for HTML input elements. These helper functions are not specific to any particular web framework or html library.
For unnamed (enumerated) formlets, see Ditto.Generalized.Unnamed
Synopsis
- data Choice lbl a = Choice {
- choiceFormId :: FormId
- choiceLabel :: lbl
- choiceIsSelected :: Bool
- choiceVal :: a
- input :: (Environment m input, FormError input err) => Text -> (input -> Either err a) -> (FormId -> a -> view) -> a -> Form m input err view a
- inputMaybe :: (Environment m input, FormError input err) => Text -> (input -> Either err a) -> (FormId -> Maybe a -> view) -> Maybe a -> Form m input err view (Maybe a)
- inputNoData :: Environment m input => Text -> (FormId -> view) -> Form m input err view ()
- inputFile :: forall m input err view ft. (Environment m input, FormInput input, FormError input err, ft ~ FileType input, Monoid ft) => Text -> (FormId -> view) -> Form m input err view (FileType input)
- inputMulti :: forall m input err view a lbl. (FormError input err, FormInput input, Environment m input, Eq a) => Text -> [(a, lbl)] -> (input -> Either err [a]) -> (FormId -> [Choice lbl a] -> view) -> (a -> Bool) -> Form m input err view [a]
- inputChoice :: forall a m err input lbl view. (FormError input err, FormInput input, Environment m input, Eq a, Monoid view) => Text -> (a -> Bool) -> NonEmpty (a, lbl) -> (input -> Either err a) -> (FormId -> [Choice lbl a] -> view) -> Form m input err view a
- inputList :: forall m input err a view. (Monad m, FormError input err, Environment m input) => Text -> (input -> m (Either err [a])) -> ([view] -> view) -> [a] -> view -> (a -> Form m input err view a) -> Form m input err view [a]
- label :: Environment m input => Text -> (FormId -> view) -> Form m input err view ()
- errors :: Environment m input => ([err] -> view) -> Form m input err view ()
- childErrors :: Environment m input => ([err] -> view) -> Form m input err view ()
- withErrors :: Environment m input => (view -> [err] -> view) -> Form m input err view a -> Form m input err view a
- withChildErrors :: Monad m => (view -> [err] -> view) -> Form m input err view a -> Form m input err view a
- ireq :: forall m input view err a. (Monoid view, Environment m input, FormError input err) => Text -> (input -> Either err a) -> a -> Form m input err view a
- iopt :: forall m input view err a. (Monoid view, Environment m input, FormError input err) => Text -> (input -> Either err a) -> Maybe a -> Form m input err view (Maybe a)
Documentation
a choice for inputChoice
Choice | |
|
input :: (Environment m input, FormError input err) => Text -> (input -> Either err a) -> (FormId -> a -> view) -> a -> Form m input err view a Source #
used for constructing elements like <input type="text">
, which pure a single input value.
inputMaybe :: (Environment m input, FormError input err) => Text -> (input -> Either err a) -> (FormId -> Maybe a -> view) -> Maybe a -> Form m input err view (Maybe a) Source #
used for elements like <input type="submit">
which are not always present in the form submission data.
inputNoData :: Environment m input => Text -> (FormId -> view) -> Form m input err view () Source #
used for elements like <input type="reset">
which take a value, but are never present in the form data set.
inputFile :: forall m input err view ft. (Environment m input, FormInput input, FormError input err, ft ~ FileType input, Monoid ft) => Text -> (FormId -> view) -> Form m input err view (FileType input) Source #
used for <input type="file">
:: forall m input err view a lbl. (FormError input err, FormInput input, Environment m input, Eq a) | |
=> Text | |
-> [(a, lbl)] | value, label, initially checked |
-> (input -> Either err [a]) | |
-> (FormId -> [Choice lbl a] -> view) | function which generates the view |
-> (a -> Bool) | isChecked/isSelected initially |
-> Form m input err view [a] |
used for groups of checkboxes, <select multiple="multiple">
boxes
:: forall a m err input lbl view. (FormError input err, FormInput input, Environment m input, Eq a, Monoid view) | |
=> Text | |
-> (a -> Bool) | is default |
-> NonEmpty (a, lbl) | value, label |
-> (input -> Either err a) | |
-> (FormId -> [Choice lbl a] -> view) | function which generates the view |
-> Form m input err view a |
radio buttons, single <select>
boxes
:: forall m input err a view. (Monad m, FormError input err, Environment m input) | |
=> Text | |
-> (input -> m (Either err [a])) | decoding function for the list |
-> ([view] -> view) | how to concatenate views |
-> [a] | initial values |
-> view | view to generate in the fail case |
-> (a -> Form m input err view a) | |
-> Form m input err view [a] |
this is necessary in order to basically map over the decoding function
label :: Environment m input => Text -> (FormId -> view) -> Form m input err view () Source #
used to create <label>
elements
:: Environment m input | |
=> ([err] -> view) | function to convert the err messages into a view |
-> Form m input err view () |
childErrors :: Environment m input => ([err] -> view) -> Form m input err view () Source #
similar to errors
but includes err messages from children of the form as well.
withErrors :: Environment m input => (view -> [err] -> view) -> Form m input err view a -> Form m input err view a Source #
modify the view of a form based on its errors
withChildErrors :: Monad m => (view -> [err] -> view) -> Form m input err view a -> Form m input err view a Source #
modify the view of a form based on its child errors