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 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
- getNamedFormId :: Monad m => String -> FormState m i FormId
- incFormId :: Monad m => FormState m i ()
- newtype View err v = View {}
- newtype Form m input err view a = Form {}
- bracketState :: Monad m => FormState m input a -> FormState m input a
- newtype MForm m input err view a = MForm {}
- runAsMForm :: Monad m => Environment m input -> Text -> Form m input err view a -> m (View err view, m (Result err (Proved a)))
- runForm :: Monad m => Environment m input -> Text -> Form m input err view a -> m (View err view, m (Result err (Proved a)))
- runForm' :: Monad m => Environment m input -> Text -> Form m input err view a -> m (view, Maybe a)
- viewForm :: Monad m => Text -> Form m input err view a -> m view
- eitherForm :: Monad m => Environment m input -> Text -> Form m input err view a -> m (Either view a)
- view :: Monad m => view -> Form m input err view ()
- (++>) :: (Monad m, Semigroup view) => Form m input err view z -> Form m input err view a -> Form m input err view a
- (<++) :: (Monad m, Semigroup view) => Form m input err view a -> Form m input err view z -> Form m input err view a
- mapView :: Functor m => (view -> view') -> Form m input err view a -> Form m input err view' a
- (@$) :: Monad m => (view -> view) -> Form m input err view a -> Form m input err view a
- mkOk :: Monad m => FormId -> view -> a -> FormState m input (View err view, m (Result err (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 Ditto.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 Ditto.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 err view 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
err
- A application specific type for err 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 pure value.
()
means nothing has been proved. a
- Value pure 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
Functor m => Bifunctor (Form m input err) Source # | |
Functor m => Functor (Form m input err view) Source # | |
(Functor m, Monoid view, Monad m) => Applicative (Form m input err view) Source # | |
Defined in Ditto.Core pure :: a -> Form m input err view a # (<*>) :: Form m input err view (a -> b) -> Form m input err view a -> Form m input err view b # liftA2 :: (a -> b -> c) -> Form m input err view a -> Form m input err view b -> Form m input err view c # (*>) :: Form m input err view a -> Form m input err view b -> Form m input err view b # (<*) :: Form m input err view a -> Form m input err view b -> Form m input err view a # | |
(Monad m, Monoid view) => Alternative (Form m input err view) Source # | |
(Monad m, Monoid view, Semigroup a) => Semigroup (Form m input err view a) Source # | |
(Monoid view, Monad m, Semigroup a) => Monoid (Form m input err view a) Source # | |
newtype MForm m input err view a Source #
This provides a Monad instance which will stop rendering on err.
This instance isn't a part of Form
because of its undesirable behavior.
-XApplicativeDo
is generally preferred
Instances
Functor m => Bifunctor (MForm m input err) Source # | |
(Monad m, Monoid view) => Monad (MForm m input err view) Source # | |
Functor m => Functor (MForm m input err view) Source # | |
(Monoid view, Monad m) => Applicative (MForm m input err view) Source # | |
Defined in Ditto.Core pure :: a -> MForm m input err view a # (<*>) :: MForm m input err view (a -> b) -> MForm m input err view a -> MForm m input err view b # liftA2 :: (a -> b -> c) -> MForm m input err view a -> MForm m input err view b -> MForm m input err view c # (*>) :: MForm m input err view a -> MForm m input err view b -> MForm m input err view b # (<*) :: MForm m input err view a -> MForm m input err view b -> MForm m input err view a # | |
(Monad m, Monoid view) => Alternative (MForm m input err view) Source # | |
runAsMForm :: Monad m => Environment m input -> Text -> Form m input err view a -> m (View err view, m (Result err (Proved a))) Source #
Ways to evaluate a Form
runForm :: Monad m => Environment m input -> Text -> Form m input err view a -> m (View err view, m (Result err (Proved a))) Source #
Run a form
runForm' :: Monad m => Environment m input -> Text -> Form m input err view 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 err view 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, Semigroup view) => Form m input err view z -> Form m input err view a -> Form m input err view a infixl 6 Source #
Append a unit form to the left. This is useful for adding labels or err 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, Semigroup view) => Form m input err view a -> Form m input err view z -> Form m input err view a infixr 5 Source #
Append a unit form to the right. See ++>
.
:: Functor m | |
=> (view -> view') | Manipulator |
-> Form m input err view a | Initial form |
-> Form m input err view' 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.