Safe Haskell | Safe |
---|---|
Language | Haskell98 |
This module mostly meant for internal usage, and might change between minor releases.
Synopsis
- type Form v m a = FormTree m v m a
- data FormTree t v m a where
- Ref :: Ref -> FormTree t v m a -> FormTree t v m a
- Pure :: Field v a -> FormTree t v m a
- App :: FormTree t v m (b -> a) -> FormTree t v m b -> FormTree t v m a
- Map :: (b -> m (Result v a)) -> FormTree t v m b -> FormTree t v m a
- Monadic :: t (FormTree t v m a) -> FormTree t v m a
- List :: DefaultList (FormTree t v m a) -> FormTree t v m [Int] -> FormTree t v m [a]
- Metadata :: [Metadata] -> FormTree t v m a -> FormTree t v m a
- data SomeForm v m = SomeForm (FormTree Identity v m a)
- type Ref = Text
- data Metadata = Disabled
- transform :: (Monad m, Monoid v) => (a -> m (Result v b)) -> FormTree t v m a -> FormTree t v m b
- monadic :: m (Form v m a) -> Form v m a
- toFormTree :: Monad m => Form v m a -> m (FormTree Identity v m a)
- children :: FormTree Identity v m a -> [SomeForm v m]
- (.:) :: Monad m => Text -> Form v m a -> Form v m a
- getRef :: FormTree Identity v m a -> Maybe Ref
- lookupForm :: Path -> FormTree Identity v m a -> [SomeForm v m]
- lookupFormMetadata :: Path -> FormTree Identity v m a -> [(SomeForm v m, [Metadata])]
- lookupList :: Path -> FormTree Identity v m a -> SomeForm v m
- toField :: FormTree Identity v m a -> Maybe (SomeField v)
- queryField :: Path -> FormTree Identity v m a -> (forall b. Field v b -> c) -> c
- eval :: Monad m => Method -> Env m -> FormTree Identity v m a -> m (Result [(Path, v)] a, [(Path, FormInput)])
- formMapView :: Monad m => (v -> w) -> FormTree Identity v m a -> FormTree Identity w m a
- forOptional :: (a -> Result v b) -> Maybe a -> Result v (Maybe b)
- debugFormPaths :: (Monad m, Monoid v) => FormTree Identity v m a -> [Path]
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.
data FormTree t v m a where Source #
Embedded tree structure for forms - the basis for deferred evaluation and the applicative interface.
Ref :: Ref -> FormTree t v m a -> FormTree t v m a | |
Pure :: Field v a -> FormTree t v m a | |
App :: FormTree t v m (b -> a) -> FormTree t v m b -> FormTree t v m a | |
Map :: (b -> m (Result v a)) -> FormTree t v m b -> FormTree t v m a | |
Monadic :: t (FormTree t v m a) -> FormTree t v m a | |
List :: DefaultList (FormTree t v m a) -> FormTree t v m [Int] -> FormTree t v m [a] | |
Metadata :: [Metadata] -> FormTree t v m a -> FormTree t v m a |
Instances
(Monad m, Monoid v) => Functor (FormTree t v m) Source # | |
(Monad m, Monoid v) => Applicative (FormTree t v m) Source # | |
Defined in Text.Digestive.Form.Internal pure :: a -> FormTree t v m a # (<*>) :: FormTree t v m (a -> b) -> FormTree t v m a -> FormTree t v m b # liftA2 :: (a -> b -> c) -> FormTree t v m a -> FormTree t v m b -> FormTree t v m c # (*>) :: FormTree t v m a -> FormTree t v m b -> FormTree t v m b # (<*) :: FormTree t v m a -> FormTree t v m b -> FormTree t v m a # | |
Show (FormTree Identity v m a) Source # | |
Value-agnostic Form
transform :: (Monad m, Monoid v) => (a -> m (Result v b)) -> FormTree t v m a -> FormTree t v m b Source #
Map on the value type
toFormTree :: Monad m => Form v m a -> m (FormTree Identity v m a) Source #
Normalize a Form to allow operations on the contents
children :: FormTree Identity v m a -> [SomeForm v m] Source #
Returns the topmost applicative or index trees if either exists otherwise returns an empty list
(.:) :: Monad m => Text -> Form v m a -> Form v m a infixr 5 Source #
Operator to set a name for a subform.
lookupForm :: Path -> FormTree Identity v m a -> [SomeForm v m] Source #
Retrieve the form(s) at the given path
lookupFormMetadata :: Path -> FormTree Identity v m a -> [(SomeForm v m, [Metadata])] Source #
A variant of lookupForm
which also returns all metadata associated with
the form.
lookupList :: Path -> FormTree Identity v m a -> SomeForm v m Source #
Always returns a List - fails if path does not directly reference a list
toField :: FormTree Identity v m a -> Maybe (SomeField v) Source #
Returns the topmost untransformed single field, if one exists
queryField :: Path -> FormTree Identity v m a -> (forall b. Field v b -> c) -> c Source #
Retrieve the field at the given path of the tree and apply the evaluation. Used in field evaluation functions in View.
eval :: Monad m => Method -> Env m -> FormTree Identity v m a -> m (Result [(Path, v)] a, [(Path, FormInput)]) Source #
Evaluate a formtree with a given method and environment. Incrementally builds the path based on the set labels and evaluates recursively - applying transformations and applications with a bottom-up strategy.
formMapView :: Monad m => (v -> w) -> FormTree Identity v m a -> FormTree Identity w m a Source #
Map on the error type of a FormTree - used to define the Functor instance of View.View
forOptional :: (a -> Result v b) -> Maybe a -> Result v (Maybe b) Source #
Combinator that lifts input and output of valiation function used by validate
to from (a -> Result v b) to (Maybe a -> Result v (Maybe b)).