Safe Haskell | Safe |
---|---|
Language | Haskell98 |
End-user interface - provides the main functionality for form creation and validation. For an interface for front-end implementation, see View.
Synopsis
- type Formlet v m a = Maybe a -> Form v m a
- type Form v m a = FormTree m v m a
- data SomeForm v m = SomeForm (FormTree Identity v m a)
- (.:) :: Monad m => Text -> Form v m a -> Form v m a
- text :: (Monad m, Monoid v) => Formlet v m Text
- string :: (Monad m, Monoid v) => Formlet v m String
- stringRead :: (Monad m, Monoid v, Read a, Show a) => v -> Formlet v m a
- choice :: (Eq a, Monad m, Monoid v) => [(a, v)] -> Formlet v m a
- choice' :: (Monad m, Monoid v) => [(a, v)] -> Maybe Int -> Form v m a
- choiceWith :: (Eq a, Monad m, Monoid v) => [(Text, (a, v))] -> Formlet v m a
- choiceWith' :: (Monad m, Monoid v) => [(Text, (a, v))] -> Maybe Int -> Form v m a
- choiceMultiple :: (Eq a, Monad m, Monoid v) => [(a, v)] -> Formlet v m [a]
- choiceMultiple' :: (Monad m, Monoid v) => [(a, v)] -> Maybe [Int] -> Form v m [a]
- choiceWithMultiple :: (Eq a, Monad m, Monoid v) => [(Text, (a, v))] -> Formlet v m [a]
- choiceWithMultiple' :: (Monad m, Monoid v) => [(Text, (a, v))] -> Maybe [Int] -> Form v m [a]
- groupedChoice :: (Eq a, Monad m, Monoid v) => [(Text, [(a, v)])] -> Formlet v m a
- groupedChoice' :: (Monad m, Monoid v) => [(Text, [(a, v)])] -> Maybe Int -> Form v m a
- groupedChoiceWith :: (Eq a, Monad m, Monoid v) => [(Text, [(Text, (a, v))])] -> Formlet v m a
- groupedChoiceWith' :: (Monad m, Monoid v) => [(Text, [(Text, (a, v))])] -> Maybe Int -> Form v m a
- groupedChoiceMultiple :: (Eq a, Monad m, Monoid v) => [(Text, [(a, v)])] -> Formlet v m [a]
- groupedChoiceMultiple' :: (Monad m, Monoid v) => [(Text, [(a, v)])] -> Maybe [Int] -> Form v m [a]
- groupedChoiceWithMultiple :: (Eq a, Monad m, Monoid v) => [(Text, [(Text, (a, v))])] -> Formlet v m [a]
- groupedChoiceWithMultiple' :: (Monad m, Monoid v) => [(Text, [(Text, (a, v))])] -> Maybe [Int] -> Form v m [a]
- bool :: (Monad m, Monoid v) => Formlet v m Bool
- file :: (Monad m, Monoid v) => Form v m (Maybe FilePath)
- fileMultiple :: (Monad m, Monoid v) => Form v m [FilePath]
- optionalText :: (Monad m, Monoid v) => Maybe Text -> Form v m (Maybe Text)
- optionalString :: (Monad m, Monoid v) => Maybe String -> Form v m (Maybe String)
- optionalStringRead :: (Monad m, Monoid v, Read a, Show a) => v -> Maybe a -> Form v m (Maybe a)
- utcTimeFormlet :: Monad m => String -> String -> TimeZone -> Formlet Text m UTCTime
- localTimeFormlet :: Monad m => String -> String -> Formlet Text m LocalTime
- dateFormlet :: Monad m => String -> Formlet Text m Day
- timeFormlet :: Monad m => String -> Formlet Text m TimeOfDay
- optionalUtcTimeFormlet :: Monad m => String -> String -> TimeZone -> Maybe UTCTime -> Form Text m (Maybe UTCTime)
- optionalLocalTimeFormlet :: Monad m => String -> String -> Maybe LocalTime -> Form Text m (Maybe LocalTime)
- optionalDateFormlet :: Monad m => String -> Maybe Day -> Form Text m (Maybe Day)
- optionalTimeFormlet :: Monad m => String -> Maybe TimeOfDay -> Form Text m (Maybe TimeOfDay)
- check :: (Monad m, Monoid v) => v -> (a -> Bool) -> Form v m a -> Form v m a
- checkM :: (Monad m, Monoid v) => v -> (a -> m Bool) -> Form v m a -> Form v m a
- validate :: (Monad m, Monoid v) => (a -> Result v b) -> Form v m a -> Form v m b
- validateOptional :: (Monad m, Monoid v) => (a -> Result v b) -> Form v m (Maybe a) -> Form v m (Maybe b)
- validateM :: (Monad m, Monoid v) => (a -> m (Result v b)) -> Form v m a -> Form v m b
- conditions :: [a -> Result e b] -> a -> Result [e] a
- disable :: Form v m a -> Form v m a
- monadic :: m (Form v m a) -> Form v m a
- listOf :: (Monad m, Monoid v) => (Maybe a -> Form v m b) -> Maybe [a] -> Form v m [b]
Documentation
type Form v m a = FormTree m v m a Source #
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.v
stands for "view".m
: the monad in which validators operate. The classical example is when validating input requires access to a database, in which case thism
should be an instance ofMonadIO
.a
: the type of the value returned by the form, used for its Applicative instance.
Value-agnostic Form
(.:) :: Monad m => Text -> Form v m a -> Form v m a infixr 5 Source #
Operator to set a name for a subform.
Basic forms
text :: (Monad m, Monoid v) => Formlet v m Text Source #
Returns a Formlet
which may optionally take a default text
stringRead :: (Monad m, Monoid v, Read a, Show a) => v -> Formlet v m a Source #
Returns a Formlet
for a parseable and serializable value type
choice :: (Eq a, Monad m, Monoid v) => [(a, v)] -> Formlet v m a Source #
Returns a Formlet
for a value restricted to a single value from
the provided list of value-message tuples
choiceWith :: (Eq a, Monad m, Monoid v) => [(Text, (a, v))] -> Formlet v m a Source #
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, Monoid v) => [(Text, (a, v))] -> Maybe Int -> Form v m a Source #
A version of choiceWith
for when there is no good Eq
instance.
choiceMultiple :: (Eq a, Monad m, Monoid v) => [(a, v)] -> Formlet v m [a] Source #
Returns a Formlet
for a value restricted to multiple values from
the provided list of value-message tuples. Intended for use with the
multiple
attribute for select elements. Allows for an empty result.
choiceWithMultiple :: (Eq a, Monad m, Monoid v) => [(Text, (a, v))] -> Formlet v m [a] Source #
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...
choiceWithMultiple' :: (Monad m, Monoid v) => [(Text, (a, v))] -> Maybe [Int] -> Form v m [a] Source #
A version of choiceWithMultiple
for when there is no good Eq
instance.
groupedChoice :: (Eq a, Monad m, Monoid v) => [(Text, [(a, v)])] -> Formlet v m a Source #
Returns a Formlet
for a single value from named groups of choices.
groupedChoiceWith :: (Eq a, Monad m, Monoid v) => [(Text, [(Text, (a, v))])] -> Formlet v m a Source #
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...
groupedChoiceWith' :: (Monad m, Monoid v) => [(Text, [(Text, (a, v))])] -> Maybe Int -> Form v m a Source #
Low-level support for grouped choice.
groupedChoiceMultiple :: (Eq a, Monad m, Monoid v) => [(Text, [(a, v)])] -> Formlet v m [a] Source #
Returns a Formlet
for multiple values from named groups of choices.
Intended for use with the multiple
attribute for select elements that
have optgroups. Allows for an empty result.
groupedChoiceMultiple' :: (Monad m, Monoid v) => [(Text, [(a, v)])] -> Maybe [Int] -> Form v m [a] Source #
groupedChoiceWithMultiple :: (Eq a, Monad m, Monoid v) => [(Text, [(Text, (a, v))])] -> Formlet v m [a] Source #
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...
groupedChoiceWithMultiple' :: (Monad m, Monoid v) => [(Text, [(Text, (a, v))])] -> Maybe [Int] -> Form v m [a] Source #
Low-level support for grouped choice.
file :: (Monad m, Monoid v) => Form v m (Maybe FilePath) Source #
Returns a Formlet
for file selection
fileMultiple :: (Monad m, Monoid v) => Form v m [FilePath] Source #
Returns a Formlet
for multiple file selection. Intended for use with
the multiple
attribute, which allows for multiple files to be uploaded
with a single input element.
Optional forms
optionalText :: (Monad m, Monoid v) => Maybe Text -> Form v m (Maybe Text) Source #
Create a text form with an optional default text which returns nothing if no optional text was set, and no input was retrieved.
optionalString :: (Monad m, Monoid v) => Maybe String -> Form v m (Maybe String) Source #
Identical to optionalText
, but uses Strings
optionalStringRead :: (Monad m, Monoid v, Read a, Show a) => v -> Maybe a -> Form v m (Maybe a) Source #
Identical to optionalText
for parseable and serializable values.
Date/time forms
Validation and transformation
:: (Monad m, Monoid v) | |
=> 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, Monoid v) => v -> (a -> m Bool) -> Form v m a -> Form v m a Source #
Version of check
which allows monadic validations
validate :: (Monad m, Monoid v) => (a -> Result v b) -> Form v m a -> Form v m b Source #
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)
validateOptional :: (Monad m, Monoid v) => (a -> Result v b) -> Form v m (Maybe a) -> Form v m (Maybe b) Source #
Same as validate
, but works with forms of the form:
Form v m (Maybe a)
.
Example: taking the first character of an optional input string
head' :: String -> Result String Char head' [] = Error "Is empty" head' (x : _) = Success x char :: Monad m => Form m String (Maybe Char) char = validateOptional head' (optionalString Nothing)
validateM :: (Monad m, Monoid v) => (a -> m (Result v b)) -> Form v m a -> Form v m b Source #
Version of validate
which allows monadic validations
:: [a -> Result e b] | Any |
-> a | If all validation functions pass, parameter will be re-wrapped with a |
-> Result [e] a | List of errors is guaranteed to be in the same order as inputed validations functions. So, conditions [even, greaterThan 0] -1 is specified to return Error ["must be even", "must be greater than 0"] and not Error ["must be greater than 0", "must be even"] . |
Allows for the composition of independent validation functions.
For example, let's validate an even integer between 0 and 100:
form :: Monad m => Form Text m FormData ... -- some fields <*> "smallEvenInteger" .: validate (notEmpty >=> integer >=> even >=> greaterThan 0 >=> lessThanOrEq 100) (text Nothing) ... -- more fields
where
notEmpty :: IsString v => Text -> Result v Text integer :: (Integral a, IsString v) => Text -> Result v a greaterThan 0 :: (Num a, Ord a, Show a) => a -> Result Text a lessThanOrEq 0 :: (Num a, Ord a, Show a) => a -> Result Text a even :: Integer -> Result Text Integer
.
This will validate our smallEvenInteger correctly, but there is a problem. If a user enters an odd number greater than 100, only
"number must be even"
will be returned. It would make for a better user experience if
["number must be even", "number must be less than 100"]
was returned instead. This can be accomplished by rewriting our form to be:
form :: Monad m => Form [Text] m FormData ... -- some fields <*> "smallEvenInteger" .: validate (notEmpty >=> integer >=> conditions [even, greaterThan 0, lessThanOrEq 100]) (text Nothing) ... -- more fields
.
If we want to collapse our list of errors into a single Text
, we can do something like:
form :: Monad m => Form Text m FormData ... -- some fields <*> "smallEvenInteger" .: validate (notEmpty >=> integer >=> commaSeperated . conditions [even, greaterThan 0, lessThanOrEq 100]) (text Nothing) ... -- more fields
where
commaSeperated :: (Result [Text] a) -> (Result Text a)
.