reform-0.2.7.3: reform is a type-safe HTML form generation and validation library

Safe HaskellNone
LanguageHaskell98

Text.Reform.Core

Contents

Description

This module defines the Form type, its instances, core manipulation functions, and a bunch of helper utilities.

Synopsis

Proved

data Proved proofs a Source #

Proved records a value, the location that value came from, and something that was proved about the value.

Constructors

Proved 

Fields

Instances
Functor (Proved ()) Source # 
Instance details

Defined in Text.Reform.Core

Methods

fmap :: (a -> b) -> Proved () a -> Proved () b #

(<$) :: a -> Proved () b -> Proved () a #

(Show proofs, Show a) => Show (Proved proofs a) Source # 
Instance details

Defined in Text.Reform.Core

Methods

showsPrec :: Int -> Proved proofs a -> ShowS #

show :: Proved proofs a -> String #

showList :: [Proved proofs a] -> ShowS #

unitProved :: FormId -> Proved () () Source #

Utility Function: trivially prove nothing about ()

FormState

type FormState m input = ReaderT (Environment m input) (StateT FormRange m) Source #

inner state used by Form.

data Value a Source #

used to represent whether a value was found in the form submission data, missing from the form submission data, or expected that the default value should be used

Constructors

Default 
Missing 
Found a 

getFormInput :: Monad m => FormState m input (Value input) Source #

Utility function: Get the current input

getFormInput' :: Monad m => FormId -> FormState m input (Value input) Source #

Utility function: Gets the input of an arbitrary FormId.

getFormRange :: Monad m => FormState m i FormRange Source #

Utility function: Get the current range

data Environment m input Source #

The environment is where you get the actual input per form.

The NoEnvironment constructor is typically used when generating a view for a GET request, where no data has yet been submitted. This will cause the input elements to use their supplied default values.

Note that NoEnviroment is different than supplying an empty environment.

Constructors

Environment (FormId -> m (Value input)) 
NoEnvironment 
Instances
(Semigroup input, Monad m) => Semigroup (Environment m input) Source # 
Instance details

Defined in Text.Reform.Core

Methods

(<>) :: Environment m input -> Environment m input -> Environment m input #

sconcat :: NonEmpty (Environment m input) -> Environment m input #

stimes :: Integral b => b -> Environment m input -> Environment m input #

(Semigroup input, Monad m) => Monoid (Environment m input) Source #

Not quite sure when this is useful and so hard to say if the rules for combining things with Missing/Default are correct

Instance details

Defined in Text.Reform.Core

Methods

mempty :: Environment m input #

mappend :: Environment m input -> Environment m input -> Environment m input #

mconcat :: [Environment m input] -> Environment m input #

getFormId :: Monad m => FormState m i FormId Source #

Utility function: returns the current FormId. This will only make sense if the form is not composed

incFormId :: Monad m => FormState m i () Source #

Utility function: increment the current FormId.

newtype View error v Source #

A view represents a visual representation of a form. It is composed of a function which takes a list of all errors and then produces a new view

Constructors

View 

Fields

Instances
Functor (View e) Source # 
Instance details

Defined in Text.Reform.Core

Methods

fmap :: (a -> b) -> View e a -> View e b #

(<$) :: a -> View e b -> View e a #

Semigroup v => Semigroup (View error v) Source # 
Instance details

Defined in Text.Reform.Core

Methods

(<>) :: View error v -> View error v -> View error v #

sconcat :: NonEmpty (View error v) -> View error v #

stimes :: Integral b => b -> View error v -> View error v #

Monoid v => Monoid (View error v) Source # 
Instance details

Defined in Text.Reform.Core

Methods

mempty :: View error v #

mappend :: View error v -> View error v -> View error v #

mconcat :: [View error v] -> View error v #

Form

newtype Form m input error view proof a Source #

a Form contains a View combined with a validation function which will attempt to extract a value from submitted form data.

It is highly parameterized, allowing it work in a wide variety of different configurations. You will likely want to make a type alias that is specific to your application to make type signatures more manageable.

m
A monad which can be used by the validator
input
A framework specific type for representing the raw key/value pairs from the form data
error
A application specific type for error messages
view
The type of data being generated for the view (HSP, Blaze Html, Heist, etc)
proof
A type which names what has been proved about the return value. () means nothing has been proved.
a
Value return by form when it is successfully decoded, validated, etc.

This type is very similar to the Form type from digestive-functors <= 0.2. If proof is (), then Form is an applicative functor and can be used almost exactly like digestive-functors <= 0.2.

Constructors

Form 

Fields

Instances
(Monoid view, Monad m) => IndexedApplicative (Form m input error view) Source # 
Instance details

Defined in Text.Reform.Core

Methods

ipure :: x -> a -> Form m input error view x a Source #

(<<*>>) :: Form m input error view (x -> y) (a -> b) -> Form m input error view x a -> Form m input error view y b Source #

(*>>) :: Form m input error view x a -> Form m input error view y b -> Form m input error view y b Source #

(<<*) :: Form m input error view x a -> Form m input error view y b -> Form m input error view x a Source #

Monad m => IndexedFunctor (Form m input view error) Source # 
Instance details

Defined in Text.Reform.Core

Methods

imap :: (x -> y) -> (a -> b) -> Form m input view error x a -> Form m input view error y b Source #

Functor m => Functor (Form m input error view ()) Source # 
Instance details

Defined in Text.Reform.Core

Methods

fmap :: (a -> b) -> Form m input error view () a -> Form m input error view () b #

(<$) :: a -> Form m input error view () b -> Form m input error view () a #

(Functor m, Monoid view, Monad m) => Applicative (Form m input error view ()) Source # 
Instance details

Defined in Text.Reform.Core

Methods

pure :: a -> Form m input error view () a #

(<*>) :: Form m input error view () (a -> b) -> Form m input error view () a -> Form m input error view () b #

liftA2 :: (a -> b -> c) -> Form m input error view () a -> Form m input error view () b -> Form m input error view () c #

(*>) :: Form m input error view () a -> Form m input error view () b -> Form m input error view () b #

(<*) :: Form m input error view () a -> Form m input error view () b -> Form m input error view () a #

bracketState :: Monad m => FormState m input a -> FormState m input a Source #

Ways to evaluate a Form

runForm :: Monad m => Environment m input -> Text -> Form m input error view proof a -> m (View error view, m (Result error (Proved proof a))) Source #

Run a form

runForm' :: Monad m => Environment m input -> Text -> Form m input error view proof a -> m (view, Maybe a) Source #

Run a form

viewForm Source #

Arguments

:: Monad m 
=> Text

form prefix

-> Form m input error view proof a

form to view

-> m view 

Just evaluate the form to a view. This usually maps to a GET request in the browser.

eitherForm Source #

Arguments

:: Monad m 
=> Environment m input

Input environment

-> Text

Identifier for the form

-> Form m input error view proof a

Form to run

-> m (Either view a)

Result

Evaluate a form

Returns:

Left view
on failure. The view will have already been applied to the errors.
Right a
on success.

view Source #

Arguments

:: Monad m 
=> view

View to insert

-> Form m input error view () ()

Resulting form

create a Form from some view.

This is typically used to turn markup like <br> into a Form.

(++>) :: (Monad m, Monoid view) => Form m input error view () () -> Form m input error view proof a -> Form m input error view proof a infixl 6 Source #

Append a unit form to the left. This is useful for adding labels or error fields.

The Forms on the left and right hand side will share the same FormId. This is useful for elements like <label for="someid">, which need to refer to the id of another element.

(<++) :: (Monad m, Monoid view) => Form m input error view proof a -> Form m input error view () () -> Form m input error view proof a infixr 5 Source #

Append a unit form to the right. See ++>.

mapView Source #

Arguments

:: (Monad m, Functor m) 
=> (view -> view')

Manipulator

-> Form m input error view proof a

Initial form

-> Form m input error view' proof a

Resulting form

Change the view of a form using a simple function

This is useful for wrapping a form inside of a <fieldset> or other markup element.

mkOk :: Monad m => FormId -> view -> a -> FormState m input (View error view, m (Result error (Proved () a))) Source #

Utility Function: turn a view and return value into a successful FormState