| Safe Haskell | None | 
|---|
SimpleForm.Digestive.Combined
Contents
Description
SimpleForm implementation that works along with digestive-functors
The Combined module both renders to Html and also parses input.
- data SimpleForm r a
- type SimpleForm' m a = SimpleForm a (Form Html m a)
- postSimpleForm :: Monad m => Renderer -> m (Env m) -> SimpleForm' m a -> m (Html, Maybe a)
- getSimpleForm :: Monad m => Renderer -> Maybe a -> SimpleForm' m a -> m Html
- simpleForm' :: ToMarkup v => Renderer -> (View v, Maybe a) -> SimpleForm a r -> (r, Html)
- input :: (Eq a, Monad m) => Text -> (r -> Maybe a) -> (Widget a, Validation a) -> InputOptions -> SimpleForm r (Form Html m a)
- input_ :: (DefaultWidget a, DefaultValidation a, Eq a, Monad m) => Text -> (r -> Maybe a) -> SimpleForm r (Form Html m a)
- toForm :: ToMarkup h => h -> SimpleForm a ()
- withFields :: Monad m => Text -> (r' -> r) -> SimpleForm r (Form Html m a) -> SimpleForm r' (Form Html m a)
- withFields' :: Maybe Text -> (r' -> r) -> SimpleForm r a -> SimpleForm r' a
- wrap :: (Html -> Html) -> SimpleForm r a -> SimpleForm r a
- fieldset :: Monad m => Text -> (r' -> r) -> SimpleForm r (Form Html m a) -> SimpleForm r' (Form Html m a)
Documentation
data SimpleForm r a Source
A form for producing something of type r
Instances
| Monad (SimpleForm r) | |
| Functor (SimpleForm r) | |
| MonadFix (SimpleForm r) | |
| Applicative (SimpleForm r) | |
| Monoid a => Monoid (SimpleForm r a) | 
type SimpleForm' m a = SimpleForm a (Form Html m a)Source
Convenience type synonym for combined forms
Arguments
| :: Monad m | |
| => Renderer | |
| -> m (Env m) | The digestive-functors input environment | 
| -> SimpleForm' m a | The simple form to render | 
| -> m (Html, Maybe a) | 
Render a SimpleForm to Html in the presence of input
This also parses the input to the correct datatype.
The Html is the contents of the form, but you must still wrap it in
 the actual <form> element.
Arguments
| :: Monad m | |
| => Renderer | |
| -> Maybe a | Default values for the form | 
| -> SimpleForm' m a | The simple form to render | 
| -> m Html | 
Render a SimpleForm to Html
This produces the contents of the form, but you must still wrap it in the actual <form> element.
Arguments
| :: ToMarkup v | |
| => Renderer | |
| -> (View v, Maybe a) | Results of running a digestive-functors  | 
| -> SimpleForm a r | The simple form to render | 
| -> (r, Html) | 
Render a SimpleForm to Html and get the return value
This produces the contents of the form, but you must still wrap it in the actual <form> element.
Create forms
Arguments
| :: (Eq a, Monad m) | |
| => Text | Form element name | 
| -> (r -> Maybe a) | Get value from parsed data | 
| -> (Widget a, Validation a) | Widget and validation to use | 
| -> InputOptions | Other options | 
| -> SimpleForm r (Form Html m a) | 
Create an input element for a SimpleForm
input "username" (Just . username) (wdef,vdef) mempty
Arguments
| :: (DefaultWidget a, DefaultValidation a, Eq a, Monad m) | |
| => Text | Form element name | 
| -> (r -> Maybe a) | Get value from parsed data | 
| -> SimpleForm r (Form Html m a) | 
Same as input, but just use the default options
toForm :: ToMarkup h => h -> SimpleForm a ()Source
Add some raw markup to a SimpleForm
Subforms
Arguments
| :: Monad m | |
| => Text | Subview name | 
| -> (r' -> r) | Projection function | 
| -> SimpleForm r (Form Html m a) | |
| -> SimpleForm r' (Form Html m a) | 
Project out some part of the parsed data and name the subview
Arguments
| :: Maybe Text | Optional subview name | 
| -> (r' -> r) | Projection function | 
| -> SimpleForm r a | |
| -> SimpleForm r' a | 
Project out some part of the parsed data (does not add name to subview)
wrap :: (Html -> Html) -> SimpleForm r a -> SimpleForm r aSource
Wrap a SimpleForm in an Html tag
fieldset :: Monad m => Text -> (r' -> r) -> SimpleForm r (Form Html m a) -> SimpleForm r' (Form Html m a)Source
Like withFields, but also wrap in fieldset tag