| Safe Haskell | None |
|---|
SimpleForm.Digestive.Combined
Contents
Description
SimpleForm implementation that works along with digestive-functors
- data SimpleForm r a
- getSimpleForm :: Monad m => Renderer -> Maybe a -> SimpleForm a (Form Html m a) -> m Html
- postSimpleForm :: Monad m => Renderer -> m (Env m) -> SimpleForm a (Form Html m a) -> m (Html, Maybe a)
- simpleForm :: ToMarkup v => Renderer -> (View v, Maybe a) -> SimpleForm a () -> 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 :: Maybe Text -> (r' -> r) -> SimpleForm r a -> SimpleForm r' a
- wrap :: (Html -> Html) -> SimpleForm r a -> SimpleForm r a
- fieldset :: Maybe Text -> (r' -> r) -> SimpleForm r a -> SimpleForm r' a
Documentation
data SimpleForm r a Source
The type of a form
Instances
| Monad (SimpleForm r) | |
| Functor (SimpleForm r) | |
| MonadFix (SimpleForm r) | |
| Applicative (SimpleForm r) | |
| Monoid a => Monoid (SimpleForm r a) |
Arguments
| :: Monad m | |
| => Renderer | |
| -> Maybe a | Default values for the form |
| -> SimpleForm a (Form Html 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
| :: Monad m | |
| => Renderer | |
| -> m (Env m) | |
| -> SimpleForm a (Form Html m a) | The simple form to render |
| -> m (Html, Maybe a) |
Render a SimpleForm to Html in the presence of input
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 () | The simple form to render |
| -> 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
| :: Maybe Text | Optional subview name |
| -> (r' -> r) | Projection function |
| -> SimpleForm r a | |
| -> SimpleForm r' a |
Project out some part of the parsed data
wrap :: (Html -> Html) -> SimpleForm r a -> SimpleForm r aSource
Wrap a SimpleForm in an Html tag
fieldset :: Maybe Text -> (r' -> r) -> SimpleForm r a -> SimpleForm r' aSource
Like withFields, but also wrap in fieldset tag