Safe Haskell | None |
---|---|
Language | Haskell98 |
This module defines the Form
type, its instances, core manipulation functions, and a bunch of helper utilities.
Synopsis
- data Proved proofs a = Proved {}
- unitProved :: FormId -> Proved () ()
- type FormState m input = ReaderT (Environment m input) (StateT FormRange m)
- data Value a
- getFormInput :: Monad m => FormState m input (Value input)
- getFormInput' :: Monad m => FormId -> FormState m input (Value input)
- getFormRange :: Monad m => FormState m i FormRange
- data Environment m input
- = Environment (FormId -> m (Value input))
- | NoEnvironment
- getFormId :: Monad m => FormState m i FormId
- incFormId :: Monad m => FormState m i ()
- newtype View error v = View {}
- newtype Form m input error view proof a = Form {}
- bracketState :: Monad m => FormState m input a -> FormState m input a
- runForm :: Monad m => Environment m input -> Text -> Form m input error view proof a -> m (View error view, m (Result error (Proved proof a)))
- runForm' :: Monad m => Environment m input -> Text -> Form m input error view proof a -> m (view, Maybe a)
- viewForm :: Monad m => Text -> Form m input error view proof a -> m view
- eitherForm :: Monad m => Environment m input -> Text -> Form m input error view proof a -> m (Either view a)
- view :: Monad m => view -> Form m input error view () ()
- (++>) :: (Monad m, Monoid view) => Form m input error view () () -> Form m input error view proof a -> Form m input error view proof a
- (<++) :: (Monad m, Monoid view) => Form m input error view proof a -> Form m input error view () () -> Form m input error view proof a
- mapView :: (Monad m, Functor m) => (view -> view') -> Form m input error view proof a -> Form m input error view' proof a
- mkOk :: Monad m => FormId -> view -> a -> FormState m input (View error view, m (Result error (Proved () a)))
Proved
Proved records a value, the location that value came from, and something that was proved about the value.
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
.
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
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
.
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.
Environment (FormId -> m (Value input)) | |
NoEnvironment |
Instances
(Semigroup input, Monad m) => Semigroup (Environment m input) Source # | |
Defined in Text.Reform.Core (<>) :: 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 |
Defined in Text.Reform.Core 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
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
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
.
Instances
(Monoid view, Monad m) => IndexedApplicative (Form m input error view) Source # | |
Defined in Text.Reform.Core 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 # | |
Functor m => Functor (Form m input error view ()) Source # | |
(Functor m, Monoid view, Monad m) => Applicative (Form m input error view ()) Source # | |
Defined in Text.Reform.Core 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 # |
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
Just evaluate the form to a view. This usually maps to a GET request in the browser.
:: 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.
(++>) :: (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 ++>
.