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

Ditto.Types

Description

Types relevant to forms and their validation.

Synopsis

FormId

data FormId Source #

An ID used to identify forms

Constructors

FormId 

Fields

  • !Text

    Global prefix for the form

  • !(NonEmpty Int)

    Stack indicating field. Head is most specific to this item

FormIdName 

Fields

  • !Text

    Local name of the input

  • !Int

    Index of the input

Instances

Instances details
Eq FormId Source # 
Instance details

Defined in Ditto.Types

Methods

(==) :: FormId -> FormId -> Bool #

(/=) :: FormId -> FormId -> Bool #

Ord FormId Source # 
Instance details

Defined in Ditto.Types

Show FormId Source # 
Instance details

Defined in Ditto.Types

IsString FormId Source # 
Instance details

Defined in Ditto.Types

Methods

fromString :: String -> FormId #

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 #

data FormRange Source #

A range of ID's to specify a group of forms

Constructors

FormRange FormId FormId 

Instances

Instances details
Eq FormRange Source # 
Instance details

Defined in Ditto.Types

Show FormRange Source # 
Instance details

Defined in Ditto.Types

encodeFormId :: FormId -> Text Source #

Encoding a FormId: use this instead of show for the name of the input / query string parameter

formIdentifier :: FormId -> Int Source #

get the head Int from a FormId

Form result types

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 

Instances

Instances details
Functor Value Source # 
Instance details

Defined in Ditto.Types

Methods

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

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

Applicative Value Source # 
Instance details

Defined in Ditto.Types

Methods

pure :: a -> Value a #

(<*>) :: Value (a -> b) -> Value a -> Value b #

liftA2 :: (a -> b -> c) -> Value a -> Value b -> Value c #

(*>) :: Value a -> Value b -> Value b #

(<*) :: Value a -> Value b -> Value a #

Foldable Value Source # 
Instance details

Defined in Ditto.Types

Methods

fold :: Monoid m => Value m -> m #

foldMap :: Monoid m => (a -> m) -> Value a -> m #

foldMap' :: Monoid m => (a -> m) -> Value a -> m #

foldr :: (a -> b -> b) -> b -> Value a -> b #

foldr' :: (a -> b -> b) -> b -> Value a -> b #

foldl :: (b -> a -> b) -> b -> Value a -> b #

foldl' :: (b -> a -> b) -> b -> Value a -> b #

foldr1 :: (a -> a -> a) -> Value a -> a #

foldl1 :: (a -> a -> a) -> Value a -> a #

toList :: Value a -> [a] #

null :: Value a -> Bool #

length :: Value a -> Int #

elem :: Eq a => a -> Value a -> Bool #

maximum :: Ord a => Value a -> a #

minimum :: Ord a => Value a -> a #

sum :: Num a => Value a -> a #

product :: Num a => Value a -> a #

Traversable Value Source # 
Instance details

Defined in Ditto.Types

Methods

traverse :: Applicative f => (a -> f b) -> Value a -> f (Value b) #

sequenceA :: Applicative f => Value (f a) -> f (Value a) #

mapM :: Monad m => (a -> m b) -> Value a -> m (Value b) #

sequence :: Monad m => Value (m a) -> m (Value a) #

Alternative Value Source # 
Instance details

Defined in Ditto.Types

Methods

empty :: Value a #

(<|>) :: Value a -> Value a -> Value a #

some :: Value a -> Value [a] #

many :: Value a -> Value [a] #

Eq a => Eq (Value a) Source # 
Instance details

Defined in Ditto.Types

Methods

(==) :: Value a -> Value a -> Bool #

(/=) :: Value a -> Value a -> Bool #

Show a => Show (Value a) Source # 
Instance details

Defined in Ditto.Types

Methods

showsPrec :: Int -> Value a -> ShowS #

show :: Value a -> String #

showList :: [Value a] -> ShowS #

Semigroup a => Semigroup (Value a) Source # 
Instance details

Defined in Ditto.Types

Methods

(<>) :: Value a -> Value a -> Value a #

sconcat :: NonEmpty (Value a) -> Value a #

stimes :: Integral b => b -> Value a -> Value a #

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 #

newtype View err v Source #

views, values as a result of the environment, etc.

Function which creates the form view

Constructors

View 

Fields

Instances

Instances details
Functor (View err) Source # 
Instance details

Defined in Ditto.Types

Methods

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

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

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

Defined in Ditto.Types

Methods

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

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

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

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

Defined in Ditto.Types

Methods

mempty :: View err v #

mappend :: View err v -> View err v -> View err v #

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

data Proved a Source #

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

Constructors

Proved 

Fields

Instances

Instances details
Functor Proved Source # 
Instance details

Defined in Ditto.Types

Methods

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

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

Foldable Proved Source # 
Instance details

Defined in Ditto.Types

Methods

fold :: Monoid m => Proved m -> m #

foldMap :: Monoid m => (a -> m) -> Proved a -> m #

foldMap' :: Monoid m => (a -> m) -> Proved a -> m #

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

foldr' :: (a -> b -> b) -> b -> Proved a -> b #

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

foldl' :: (b -> a -> b) -> b -> Proved a -> b #

foldr1 :: (a -> a -> a) -> Proved a -> a #

foldl1 :: (a -> a -> a) -> Proved a -> a #

toList :: Proved a -> [a] #

null :: Proved a -> Bool #

length :: Proved a -> Int #

elem :: Eq a => a -> Proved a -> Bool #

maximum :: Ord a => Proved a -> a #

minimum :: Ord a => Proved a -> a #

sum :: Num a => Proved a -> a #

product :: Num a => Proved a -> a #

Traversable Proved Source # 
Instance details

Defined in Ditto.Types

Methods

traverse :: Applicative f => (a -> f b) -> Proved a -> f (Proved b) #

sequenceA :: Applicative f => Proved (f a) -> f (Proved a) #

mapM :: Monad m => (a -> m b) -> Proved a -> m (Proved b) #

sequence :: Monad m => Proved (m a) -> m (Proved a) #

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

Defined in Ditto.Types

Methods

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

show :: Proved a -> String #

showList :: [Proved a] -> ShowS #

newtype Result e ok Source #

Type for failing computations Similar to Either but with an accumilating Applicative instance

Constructors

Result 

Fields

Bundled Patterns

pattern Error :: forall e ok. [(FormRange, e)] -> Result e ok 
pattern Ok :: forall e ok. ok -> Result e ok 

Instances

Instances details
Monad (Result e) Source # 
Instance details

Defined in Ditto.Types

Methods

(>>=) :: Result e a -> (a -> Result e b) -> Result e b #

(>>) :: Result e a -> Result e b -> Result e b #

return :: a -> Result e a #

Functor (Result e) Source # 
Instance details

Defined in Ditto.Types

Methods

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

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

Applicative (Result e) Source # 
Instance details

Defined in Ditto.Types

Methods

pure :: a -> Result e a #

(<*>) :: Result e (a -> b) -> Result e a -> Result e b #

liftA2 :: (a -> b -> c) -> Result e a -> Result e b -> Result e c #

(*>) :: Result e a -> Result e b -> Result e b #

(<*) :: Result e a -> Result e b -> Result e a #

Foldable (Result e) Source # 
Instance details

Defined in Ditto.Types

Methods

fold :: Monoid m => Result e m -> m #

foldMap :: Monoid m => (a -> m) -> Result e a -> m #

foldMap' :: Monoid m => (a -> m) -> Result e a -> m #

foldr :: (a -> b -> b) -> b -> Result e a -> b #

foldr' :: (a -> b -> b) -> b -> Result e a -> b #

foldl :: (b -> a -> b) -> b -> Result e a -> b #

foldl' :: (b -> a -> b) -> b -> Result e a -> b #

foldr1 :: (a -> a -> a) -> Result e a -> a #

foldl1 :: (a -> a -> a) -> Result e a -> a #

toList :: Result e a -> [a] #

null :: Result e a -> Bool #

length :: Result e a -> Int #

elem :: Eq a => a -> Result e a -> Bool #

maximum :: Ord a => Result e a -> a #

minimum :: Ord a => Result e a -> a #

sum :: Num a => Result e a -> a #

product :: Num a => Result e a -> a #

Traversable (Result e) Source # 
Instance details

Defined in Ditto.Types

Methods

traverse :: Applicative f => (a -> f b) -> Result e a -> f (Result e b) #

sequenceA :: Applicative f => Result e (f a) -> f (Result e a) #

mapM :: Monad m => (a -> m b) -> Result e a -> m (Result e b) #

sequence :: Monad m => Result e (m a) -> m (Result e a) #

(Eq e, Eq ok) => Eq (Result e ok) Source # 
Instance details

Defined in Ditto.Types

Methods

(==) :: Result e ok -> Result e ok -> Bool #

(/=) :: Result e ok -> Result e ok -> Bool #

(Show e, Show ok) => Show (Result e ok) Source # 
Instance details

Defined in Ditto.Types

Methods

showsPrec :: Int -> Result e ok -> ShowS #

show :: Result e ok -> String #

showList :: [Result e ok] -> ShowS #