ditto-0.4.1: ditto is a type-safe HTML form generation and validation library
Safe HaskellNone
LanguageHaskell2010

Ditto.Core

Description

The core module for ditto.

This module provides the Form type and helper functions for constructing typesafe forms inside arbitrary "views" / web frameworks. ditto is meant to be a generalized formlet library used to write formlet libraries specific to a web / gui framework

Synopsis

Form types

The representation of formlets

type FormState m = StateT FormRange m Source #

The Form's state is just the range of identifiers so far

data Form m input err view a Source #

ditto's representation of a formlet

It's reccommended to use ApplicativeDo where possible when constructing forms

Constructors

Form 

Fields

Instances

Instances details
Functor m => Bifunctor (Form m input err) Source # 
Instance details

Defined in Ditto.Core

Methods

bimap :: (a -> b) -> (c -> d) -> Form m input err a c -> Form m input err b d #

first :: (a -> b) -> Form m input err a c -> Form m input err b c #

second :: (b -> c) -> Form m input err a b -> Form m input err a c #

(Environment m input, Monoid view, FormError input err) => Monad (Form m input err view) Source # 
Instance details

Defined in Ditto.Core

Methods

(>>=) :: Form m input err view a -> (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 b #

return :: a -> Form m input err view a #

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

Defined in Ditto.Core

Methods

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

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

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

Defined in Ditto.Core

Methods

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, FormError input err, Environment m input) => Alternative (Form m input err view) Source # 
Instance details

Defined in Ditto.Core

Methods

empty :: Form m input err view a #

(<|>) :: Form m input err view a -> Form m input err view a -> Form m input err view a #

some :: Form m input err view a -> Form m input err view [a] #

many :: Form m input err view a -> Form m input err view [a] #

(Monad m, Monoid view, Semigroup a) => Semigroup (Form m input err view a) Source # 
Instance details

Defined in Ditto.Core

Methods

(<>) :: Form m input err view a -> Form m input err view a -> Form m input err view a #

sconcat :: NonEmpty (Form m input err view a) -> Form m input err view a #

stimes :: Integral b => b -> Form m input err view a -> Form m input err view a #

(Monad m, Monoid view, Monoid a) => Monoid (Form m input err view a) Source # 
Instance details

Defined in Ditto.Core

Methods

mempty :: Form m input err view a #

mappend :: Form m input err view a -> Form m input err view a -> Form m input err view a #

mconcat :: [Form m input err view a] -> Form m input err view a #

Environment

The interface to a given web framework

class Monad m => Environment m input | m -> input where Source #

The environment typeclass: the interface between ditto and a given framework

Methods

environment :: FormId -> m (Value input) Source #

Instances

Instances details
Monad m => Environment (WithEnvironment input m) input Source # 
Instance details

Defined in Ditto.Core

Methods

environment :: FormId -> WithEnvironment input m (Value input) Source #

Monad m => Environment (NoEnvironment input m) input Source # 
Instance details

Defined in Ditto.Core

Methods

environment :: FormId -> NoEnvironment input m (Value input) Source #

newtype NoEnvironment input m a Source #

Run the form, but always return the initial value

Constructors

NoEnvironment 

Fields

Instances

Instances details
Monad m => Monad (NoEnvironment input m) Source # 
Instance details

Defined in Ditto.Core

Methods

(>>=) :: NoEnvironment input m a -> (a -> NoEnvironment input m b) -> NoEnvironment input m b #

(>>) :: NoEnvironment input m a -> NoEnvironment input m b -> NoEnvironment input m b #

return :: a -> NoEnvironment input m a #

Functor m => Functor (NoEnvironment input m) Source # 
Instance details

Defined in Ditto.Core

Methods

fmap :: (a -> b) -> NoEnvironment input m a -> NoEnvironment input m b #

(<$) :: a -> NoEnvironment input m b -> NoEnvironment input m a #

Applicative m => Applicative (NoEnvironment input m) Source # 
Instance details

Defined in Ditto.Core

Methods

pure :: a -> NoEnvironment input m a #

(<*>) :: NoEnvironment input m (a -> b) -> NoEnvironment input m a -> NoEnvironment input m b #

liftA2 :: (a -> b -> c) -> NoEnvironment input m a -> NoEnvironment input m b -> NoEnvironment input m c #

(*>) :: NoEnvironment input m a -> NoEnvironment input m b -> NoEnvironment input m b #

(<*) :: NoEnvironment input m a -> NoEnvironment input m b -> NoEnvironment input m a #

Monad m => Environment (NoEnvironment input m) input Source # 
Instance details

Defined in Ditto.Core

Methods

environment :: FormId -> NoEnvironment input m (Value input) Source #

newtype WithEnvironment input m a Source #

Run the form, but with a given environment function

Constructors

WithEnvironment 

Fields

Instances

Instances details
MonadTrans (WithEnvironment input) Source # 
Instance details

Defined in Ditto.Core

Methods

lift :: Monad m => m a -> WithEnvironment input m a #

Monad m => Monad (WithEnvironment input m) Source # 
Instance details

Defined in Ditto.Core

Methods

(>>=) :: WithEnvironment input m a -> (a -> WithEnvironment input m b) -> WithEnvironment input m b #

(>>) :: WithEnvironment input m a -> WithEnvironment input m b -> WithEnvironment input m b #

return :: a -> WithEnvironment input m a #

Functor m => Functor (WithEnvironment input m) Source # 
Instance details

Defined in Ditto.Core

Methods

fmap :: (a -> b) -> WithEnvironment input m a -> WithEnvironment input m b #

(<$) :: a -> WithEnvironment input m b -> WithEnvironment input m a #

Applicative m => Applicative (WithEnvironment input m) Source # 
Instance details

Defined in Ditto.Core

Methods

pure :: a -> WithEnvironment input m a #

(<*>) :: WithEnvironment input m (a -> b) -> WithEnvironment input m a -> WithEnvironment input m b #

liftA2 :: (a -> b -> c) -> WithEnvironment input m a -> WithEnvironment input m b -> WithEnvironment input m c #

(*>) :: WithEnvironment input m a -> WithEnvironment input m b -> WithEnvironment input m b #

(<*) :: WithEnvironment input m a -> WithEnvironment input m b -> WithEnvironment input m a #

Monad m => Environment (WithEnvironment input m) input Source # 
Instance details

Defined in Ditto.Core

Methods

environment :: FormId -> WithEnvironment input m (Value input) Source #

Monad m => MonadReader (FormId -> m (Value input)) (WithEnvironment input m) Source # 
Instance details

Defined in Ditto.Core

Methods

ask :: WithEnvironment input m (FormId -> m (Value input)) #

local :: ((FormId -> m (Value input)) -> FormId -> m (Value input)) -> WithEnvironment input m a -> WithEnvironment input m a #

reader :: ((FormId -> m (Value input)) -> a) -> WithEnvironment input m a #

noEnvironment :: Applicative m => FormId -> m (Value input) Source #

environment which will always return the initial value

Utility functions

(@$) :: Monad m => (view -> view') -> Form m input err view a -> Form m input err view' a infixr 0 Source #

infix mapView: succinctly mix the view dsl and the formlets dsl e.g. div_ [class_ "my cool form"] @$ do (_ :: Form m input err view' a).

catchFormError :: Monad m => ([err] -> a) -> Form m input err view a -> Form m input err view a Source #

Catch errors purely

catchFormErrorM :: Monad m => Form m input err view a -> ([err] -> Form m input err view a) -> Form m input err view a Source #

Catch errors inside Form / m

eitherForm Source #

Arguments

:: Monad m 
=> 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 be produced by a View err view, which can be modified with functions like withChildErrors for the sake of rendering errors.
Right a
on success.

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

Get a FormId from the FormState

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

Utility function: Get the current input

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

Utility function: Gets the input of an arbitrary FormId.

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

Utility function: Get the current range

getNamedFormId :: Monad m => Text -> FormState m FormId Source #

Get a FormIdName from the FormState

incrementFormId :: FormId -> FormId Source #

Increment a form ID

isInRange Source #

Arguments

:: FormId

Id to check for

-> FormRange

Range

-> Bool

If the range contains the id

Check if a FormId is contained in a FormRange

mapResult :: Monad m => (Result err (Proved a) -> Result err (Proved a)) -> (View err view -> View err view) -> Form m input err view a -> Form m input err view a Source #

Map over the Result and View of a form

mapView Source #

Arguments

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

Manipulator

-> Form m input err view a

Initial form

-> Form m input err view' a

Resulting form

Common operations on Forms

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 (View err view, Result err (Proved a)) Source #

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

retainChildErrors :: FormRange -> [(FormRange, e)] -> [e] Source #

Select the errors originating from this form or from any of the children of this form

retainErrors :: FormRange -> [(FormRange, e)] -> [e] Source #

Select the errors for a certain range

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

Run a form

runForm_ :: Monad m => Text -> Form m input err view a -> m (view, Maybe a) Source #

Run a form, and unwrap the result

successDecode :: Applicative m => a -> input -> m (Either err a) Source #

Always succeed decoding

unitRange :: FormId -> FormRange Source #

Turns a FormId into a FormRange by incrementing the base for the end Id

view :: Monad m => view -> Form m input err view () Source #

Make a form which renders a view, accepts no input and produces no output

viewForm Source #

Arguments

:: Monad m 
=> Text

form prefix

-> Form m input err view a

form to view

-> m view 

Run the form with no environment, return only the html. This means that the values will always be their defaults

pureRes :: (Monad m, Monoid view, FormError input err) => a -> Either err a -> Form m input err view a Source #

lift the result of a decoding to a Form

liftForm :: (Monad m, Monoid view) => m a -> Form m input err view a Source #

Form is a MonadTrans, but we can't have an instance of it because of the order and kind of its type variables