| Safe Haskell | Safe-Infered | 
|---|
Text.Digestive.Form
- type Formlet m v a = Maybe a -> Form m v a
- type Form v m a = FormTree m v m a
- data SomeForm v m = forall a . SomeForm (FormTree Identity v m a)
- (.:) :: Monad m => Text -> Form v m a -> Form v m a
- text :: Formlet v m Text
- string :: Monad m => Formlet v m String
- stringRead :: (Monad m, Read a, Show a) => v -> Formlet v m a
- choice :: (Eq a, Monad m) => [(a, v)] -> Formlet v m a
- choice' :: Monad m => [(a, v)] -> Maybe Int -> Form v m a
- choiceWith :: (Eq a, Monad m) => [(Text, (a, v))] -> Formlet v m a
- choiceWith' :: Monad m => [(Text, (a, v))] -> Maybe Int -> Form v m a
- bool :: Formlet v m Bool
- file :: Form v m (Maybe FilePath)
- optionalText :: Monad m => Maybe Text -> Form v m (Maybe Text)
- optionalString :: Monad m => Maybe String -> Form v m (Maybe String)
- optionalStringRead :: (Monad m, Read a, Show a) => v -> Maybe a -> Form v m (Maybe a)
- check :: Monad m => v -> (a -> Bool) -> Form v m a -> Form v m a
- checkM :: Monad m => v -> (a -> m Bool) -> Form v m a -> Form v m a
- validate :: Monad m => (a -> Result v b) -> Form v m a -> Form v m b
- validateM :: Monad m => (a -> m (Result v b)) -> Form v m a -> Form v m b
- monadic :: m (Form v m a) -> Form v m a
Documentation
type Form v m a = FormTree m v m aSource
Base type for a form.
The three type parameters are:
-  v: the type for textual information, displayed to the user. For example, error messages are of this type.vstands for view.
-  m: the monad in which validators operate. The classical example is when validating input requires access to a database, in which case thismshould be an instance ofMonadIO.
-  a: the type of the value returned by the form, used for its Applicative instance.
Basic forms
choiceWith :: (Eq a, Monad m) => [(Text, (a, v))] -> Formlet v m aSource
Allows you to assign your own values: these values will be used in the
 resulting HTML instead of the default [0 ..]. This fixes some race
 conditions that might otherwise appear, e.g. if new choice items are added to
 some database while a user views and submits the form...
choiceWith' :: Monad m => [(Text, (a, v))] -> Maybe Int -> Form v m aSource
A version of choiceWith for when you have no good Eq instance.
Optional forms
Validation
Arguments
| :: Monad m | |
| => v | Error message (if fail) | 
| -> (a -> Bool) | Validating predicate | 
| -> Form v m a | Form to validate | 
| -> Form v m a | Resulting form | 
Validate the results of a form with a simple predicate
Example:
check "Can't be empty" (not . null) (string Nothing)
checkM :: Monad m => v -> (a -> m Bool) -> Form v m a -> Form v m aSource
Version of check which allows monadic validations
validate :: Monad m => (a -> Result v b) -> Form v m a -> Form v m bSource
This is an extension of check that can be used to apply transformations
 that optionally fail
Example: taking the first character of an input string
head' :: String -> Result String Char head' [] = Error "Is empty" head' (x : _) = Success x char :: Monad m => Form m String Char char = validate head' (string Nothing)
validateM :: Monad m => (a -> m (Result v b)) -> Form v m a -> Form v m bSource
Version of validate which allows monadic validations