Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Helper functions for creating forms when using Bootstrap 3.
Synopsis
- renderBootstrap3 :: Monad m => BootstrapFormLayout -> FormRender m a
- data BootstrapFormLayout
- data BootstrapGridOptions
- bfs :: RenderMessage site msg => msg -> FieldSettings site
- withPlaceholder :: Text -> FieldSettings site -> FieldSettings site
- withAutofocus :: FieldSettings site -> FieldSettings site
- withLargeInput :: FieldSettings site -> FieldSettings site
- withSmallInput :: FieldSettings site -> FieldSettings site
- bootstrapSubmit :: (RenderMessage site msg, HandlerSite m ~ site, MonadHandler m) => BootstrapSubmit msg -> AForm m ()
- mbootstrapSubmit :: (RenderMessage site msg, HandlerSite m ~ site, MonadHandler m) => BootstrapSubmit msg -> MForm m (FormResult (), FieldView site)
- data BootstrapSubmit msg = BootstrapSubmit {}
Example: Rendering a basic form
<input>
tags in Bootstrap 3 require the form-control
class,
and so they need modified FieldSettings
to display correctly.
When creating your forms, use the bfs
function to add this class:
personForm :: AForm Handler Person personForm = Person <$> areq textField (bfs ("Name" :: Text)) Nothing <*> areq textField (bfs ("Surname" :: Text)) Nothing
That form can then be rendered into a widget using the renderBootstrap3
function. Here, the form is laid out vertically using BootstrapBasicForm
:
(formWidget, formEnctype) <- generateFormPost $ renderBootstrap3 BootstrapBasicForm personForm
And then used in Hamlet:
<form role=form method=post action=@{ActionR} enctype=#{formEnctype}> ^{formWidget} <button type="submit" .btn .btn-default>Submit
Example: Rendering a horizontal form
Yesod.Form.Bootstrap3 also supports horizontal, grid based forms.
These forms require additional markup for the submit tag, which is provided by the bootstrapSubmit
function:
personForm :: AForm Handler Person personForm = Person <$> areq textField MsgName Nothing <*> areq textField MsgSurname Nothing <* bootstrapSubmit (BootstrapSubmit MsgSubmit "btn-default" [("attribute-name","attribute-value")]) -- Note: bootstrapSubmit works with all BootstrapFormLayouts, but provides the additional markup required for Bootstrap's horizontal forms.
That form can be rendered with specific grid spacing:
(formWidget, formEnctype) <- generateFormPost $ renderBootstrap3 (BootstrapHorizontalForm (ColSm 0) (ColSm 4) (ColSm 0) (ColSm 6)) personForm
And then used in Hamlet. Note the additional form-horizontal
class on the form, and that a manual submit tag isn't required:
<form .form-horizontal role=form method=post action=@{ActionR} enctype=#{formEnctype}> ^{formWidget}
Rendering forms
renderBootstrap3 :: Monad m => BootstrapFormLayout -> FormRender m a Source #
Render the given form using Bootstrap v3 conventions.
Since: yesod-form 1.3.8
data BootstrapFormLayout Source #
The layout used for the bootstrap form.
Since: yesod-form 1.3.8
BootstrapBasicForm | A form with labels and inputs listed vertically. See http://getbootstrap.com/css/#forms-example |
BootstrapInlineForm | A form whose |
BootstrapHorizontalForm | |
|
Instances
Show BootstrapFormLayout Source # | |
Defined in Yesod.Form.Bootstrap3 showsPrec :: Int -> BootstrapFormLayout -> ShowS # show :: BootstrapFormLayout -> String # showList :: [BootstrapFormLayout] -> ShowS # |
data BootstrapGridOptions Source #
How many bootstrap grid columns should be taken (see
BootstrapFormLayout
).
Since: yesod-form 1.3.8
Instances
Show BootstrapGridOptions Source # | |
Defined in Yesod.Form.Bootstrap3 showsPrec :: Int -> BootstrapGridOptions -> ShowS # show :: BootstrapGridOptions -> String # showList :: [BootstrapGridOptions] -> ShowS # | |
Eq BootstrapGridOptions Source # | |
Defined in Yesod.Form.Bootstrap3 (==) :: BootstrapGridOptions -> BootstrapGridOptions -> Bool # (/=) :: BootstrapGridOptions -> BootstrapGridOptions -> Bool # | |
Ord BootstrapGridOptions Source # | |
Defined in Yesod.Form.Bootstrap3 compare :: BootstrapGridOptions -> BootstrapGridOptions -> Ordering # (<) :: BootstrapGridOptions -> BootstrapGridOptions -> Bool # (<=) :: BootstrapGridOptions -> BootstrapGridOptions -> Bool # (>) :: BootstrapGridOptions -> BootstrapGridOptions -> Bool # (>=) :: BootstrapGridOptions -> BootstrapGridOptions -> Bool # max :: BootstrapGridOptions -> BootstrapGridOptions -> BootstrapGridOptions # min :: BootstrapGridOptions -> BootstrapGridOptions -> BootstrapGridOptions # |
Field settings
This module comes with several methods to help customize your Bootstrap 3 <input>
s.
These functions can be chained together to apply several properties to an input:
userForm :: AForm Handler UserForm userForm = UserForm <$> areq textField nameSettings Nothing where nameSettings = withAutofocus $ withPlaceholder "First name" $ (bfs ("Name" :: Text))
bfs :: RenderMessage site msg => msg -> FieldSettings site Source #
Create a new FieldSettings
with the form-control
class that is
required by Bootstrap v3.
Since: yesod-form 1.3.8
withPlaceholder :: Text -> FieldSettings site -> FieldSettings site Source #
Add a placeholder attribute to a field. If you need i18n
for the placeholder, currently you'll need to do a hack and
use getMessageRender
manually.
Since: yesod-form 1.3.8
withAutofocus :: FieldSettings site -> FieldSettings site Source #
Add an autofocus attribute to a field.
Since: yesod-form 1.3.8
withLargeInput :: FieldSettings site -> FieldSettings site Source #
Add the input-lg
CSS class to a field.
Since: yesod-form 1.3.8
withSmallInput :: FieldSettings site -> FieldSettings site Source #
Add the input-sm
CSS class to a field.
Since: yesod-form 1.3.8
Submit button
bootstrapSubmit :: (RenderMessage site msg, HandlerSite m ~ site, MonadHandler m) => BootstrapSubmit msg -> AForm m () Source #
A Bootstrap v3 submit button disguised as a field for convenience. For example, if your form currently is:
Person <$> areq textField "Name" Nothing <*> areq textField "Surname" Nothing
Then just change it to:
Person <$> areq textField "Name" Nothing <*> areq textField "Surname" Nothing <* bootstrapSubmit ("Register" :: BootstrapSubmit Text)
(Note that <*
is not a typo.)
Alternatively, you may also just create the submit button manually as well in order to have more control over its layout.
Since: yesod-form 1.3.8
mbootstrapSubmit :: (RenderMessage site msg, HandlerSite m ~ site, MonadHandler m) => BootstrapSubmit msg -> MForm m (FormResult (), FieldView site) Source #
Same as bootstrapSubmit
but for monadic forms. This isn't
as useful since you're not going to use renderBootstrap3
anyway.
Since: yesod-form 1.3.8
data BootstrapSubmit msg Source #
How the bootstrapSubmit
button should be rendered.
Since: yesod-form 1.3.8
Instances
IsString msg => IsString (BootstrapSubmit msg) Source # | |
Defined in Yesod.Form.Bootstrap3 fromString :: String -> BootstrapSubmit msg # | |
Show msg => Show (BootstrapSubmit msg) Source # | |
Defined in Yesod.Form.Bootstrap3 showsPrec :: Int -> BootstrapSubmit msg -> ShowS # show :: BootstrapSubmit msg -> String # showList :: [BootstrapSubmit msg] -> ShowS # |