digestive-functors-0.7.1.5: A practical formlet library

Safe HaskellSafe-Inferred
LanguageHaskell98

Text.Digestive.Form

Contents

Description

End-user interface - provides the main functionality for form creation and validation. For an interface for front-end implementation, see View.

Synopsis

Documentation

type Formlet v m a = Maybe a -> Form v m a Source

A Form with a set, optional default value

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 this m should be an instance of MonadIO.
  • a: the type of the value returned by the form, used for its Applicative instance.

data SomeForm v m Source

Value-agnostic Form

Constructors

forall a . SomeForm (FormTree Identity v m a) 

Instances

Show (SomeForm v m) 

(.:) :: 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 :: Formlet v m Text Source

Returns a Formlet which may optionally take a default text

string :: Monad m => Formlet v m String Source

Identical to "text" but takes a String

stringRead :: (Monad m, 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) => [(a, v)] -> Formlet v m a Source

Returns a Formlet for a value restricted to the provided list of value-message tuples

choice' :: Monad m => [(a, v)] -> Maybe Int -> Form v m a Source

Sometimes there is no good Eq instance for choice. In this case, you can use this function, which takes an index in the list as default.

choiceWith :: (Eq a, Monad m) => [(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 => [(Text, (a, v))] -> Maybe Int -> Form v m a Source

A version of choiceWith for when there is no good Eq instance.

groupedChoice :: (Eq a, Monad m) => [(Text, [(a, v)])] -> Formlet v m a Source

Returns a Formlet for named groups of choices.

groupedChoice' :: Monad m => [(Text, [(a, v)])] -> Maybe Int -> Form v m a Source

Sometimes there is no good Eq instance for choice. In this case, you can use this function, which takes an index in the list as default.

groupedChoiceWith :: (Eq a, Monad m) => [(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 => [(Text, [(Text, (a, v))])] -> Maybe Int -> Form v m a Source

Low-level support for grouped choice.

bool :: Formlet v m Bool Source

Returns a Formlet for binary choices

file :: Form v m (Maybe FilePath) Source

Returns a Formlet for file selection

Optional forms

optionalText :: Monad m => 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 => Maybe String -> Form v m (Maybe String) Source

Identical to optionalText, but uses Strings

optionalStringRead :: (Monad m, Read a, Show a) => v -> Maybe a -> Form v m (Maybe a) Source

Identical to optionalText for parseable and serializable values.

Date/time forms

utcTimeFormlet Source

Arguments

:: Monad m 
=> String

Date format string

-> String

Time format string

-> TimeZone 
-> Formlet Text m UTCTime 

localTimeFormlet Source

Arguments

:: Monad m 
=> String

Date format string

-> String

Time format string

-> Formlet Text m LocalTime 

dateFormlet Source

Arguments

:: Monad m 
=> String

Format string

-> Formlet Text m Day 

timeFormlet Source

Arguments

:: Monad m 
=> String

Format string

-> Formlet Text m TimeOfDay 

optionalUtcTimeFormlet Source

Arguments

:: Monad m 
=> String

Date format string

-> String

Time format string

-> TimeZone 
-> Maybe UTCTime 
-> Form Text m (Maybe UTCTime) 

optionalLocalTimeFormlet Source

Arguments

:: Monad m 
=> String

Date format string

-> String

Time format string

-> Maybe LocalTime 
-> Form Text m (Maybe LocalTime) 

optionalDateFormlet Source

Arguments

:: Monad m 
=> String

Format string

-> Maybe Day 
-> Form Text m (Maybe Day) 

optionalTimeFormlet Source

Arguments

:: Monad m 
=> String

Format string

-> Maybe TimeOfDay 
-> Form Text m (Maybe TimeOfDay) 

Validation and transformation

check Source

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 a Source

Version of check which allows monadic validations

validate :: Monad m => (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 => (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 => (a -> m (Result v b)) -> Form v m a -> Form v m b Source

Version of validate which allows monadic validations

conditions Source

Arguments

:: [a -> Result e b]

Any Success result of a validation function is provably guaranteed to be discarded. Only Error results are used.

-> a

If all validation functions pass, parameter will be re-wrapped with a Success.

-> 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)

.

disable :: Form v m a -> Form v m a Source

Disables a form

Lifting forms

monadic :: m (Form v m a) -> Form v m a Source

Hide a monadic wrapper

Dynamic list forms

listOf :: Monad m => Formlet v m a -> Formlet v m [a] Source

Dynamic lists