{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE OverloadedStrings #-}
-- | Helper functions for creating forms when using <http://getbootstrap.com/ Bootstrap 3>.
--

module Yesod.Form.Bootstrap3
  ( -- * Example: Rendering a basic form
    -- $example

    -- * Example: Rendering a horizontal form
    -- $example2

    -- * Rendering forms
    renderBootstrap3
  , BootstrapFormLayout(..)
  , BootstrapGridOptions(..)
    -- * Field settings
    -- $fieldSettings
  , bfs
  , withPlaceholder
  , withAutofocus
  , withLargeInput
  , withSmallInput
    -- * Submit button
  , bootstrapSubmit
  , mbootstrapSubmit
  , BootstrapSubmit(..)
  ) where

import Control.Arrow (second)
import Control.Monad (liftM)
import Data.Text (Text)
import Data.String (IsString(..))
import qualified Text.Blaze.Internal as Blaze
import Yesod.Core
import Yesod.Form.Types
import Yesod.Form.Functions

-- | Create a new 'FieldSettings' with the @form-control@ class that is
-- required by Bootstrap v3.
--
-- Since: yesod-form 1.3.8
bfs :: RenderMessage site msg => msg -> FieldSettings site
bfs :: msg -> FieldSettings site
bfs msg
msg =
    SomeMessage site
-> Maybe (SomeMessage site)
-> Maybe Text
-> Maybe Text
-> [(Text, Text)]
-> FieldSettings site
forall master.
SomeMessage master
-> Maybe (SomeMessage master)
-> Maybe Text
-> Maybe Text
-> [(Text, Text)]
-> FieldSettings master
FieldSettings (msg -> SomeMessage site
forall master msg.
RenderMessage master msg =>
msg -> SomeMessage master
SomeMessage msg
msg) Maybe (SomeMessage site)
forall a. Maybe a
Nothing Maybe Text
forall a. Maybe a
Nothing Maybe Text
forall a. Maybe a
Nothing [(Text
"class", Text
"form-control")]


-- | 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
withPlaceholder :: Text -> FieldSettings site -> FieldSettings site
withPlaceholder :: Text -> FieldSettings site -> FieldSettings site
withPlaceholder Text
placeholder FieldSettings site
fs = FieldSettings site
fs { fsAttrs :: [(Text, Text)]
fsAttrs = [(Text, Text)]
newAttrs }
    where newAttrs :: [(Text, Text)]
newAttrs = (Text
"placeholder", Text
placeholder) (Text, Text) -> [(Text, Text)] -> [(Text, Text)]
forall a. a -> [a] -> [a]
: FieldSettings site -> [(Text, Text)]
forall master. FieldSettings master -> [(Text, Text)]
fsAttrs FieldSettings site
fs


-- | Add an autofocus attribute to a field.
--
-- Since: yesod-form 1.3.8
withAutofocus :: FieldSettings site -> FieldSettings site
withAutofocus :: FieldSettings site -> FieldSettings site
withAutofocus FieldSettings site
fs = FieldSettings site
fs { fsAttrs :: [(Text, Text)]
fsAttrs = [(Text, Text)]
newAttrs }
    where newAttrs :: [(Text, Text)]
newAttrs = (Text
"autofocus", Text
"autofocus") (Text, Text) -> [(Text, Text)] -> [(Text, Text)]
forall a. a -> [a] -> [a]
: FieldSettings site -> [(Text, Text)]
forall master. FieldSettings master -> [(Text, Text)]
fsAttrs FieldSettings site
fs


-- | Add the @input-lg@ CSS class to a field.
--
-- Since: yesod-form 1.3.8
withLargeInput :: FieldSettings site -> FieldSettings site
withLargeInput :: FieldSettings site -> FieldSettings site
withLargeInput FieldSettings site
fs = FieldSettings site
fs { fsAttrs :: [(Text, Text)]
fsAttrs = [(Text, Text)]
newAttrs }
    where newAttrs :: [(Text, Text)]
newAttrs = Text -> [(Text, Text)] -> [(Text, Text)]
addClass Text
"input-lg" (FieldSettings site -> [(Text, Text)]
forall master. FieldSettings master -> [(Text, Text)]
fsAttrs FieldSettings site
fs)


-- | Add the @input-sm@ CSS class to a field.
--
-- Since: yesod-form 1.3.8
withSmallInput :: FieldSettings site -> FieldSettings site
withSmallInput :: FieldSettings site -> FieldSettings site
withSmallInput FieldSettings site
fs = FieldSettings site
fs { fsAttrs :: [(Text, Text)]
fsAttrs = [(Text, Text)]
newAttrs }
    where newAttrs :: [(Text, Text)]
newAttrs = Text -> [(Text, Text)] -> [(Text, Text)]
addClass Text
"input-sm" (FieldSettings site -> [(Text, Text)]
forall master. FieldSettings master -> [(Text, Text)]
fsAttrs FieldSettings site
fs)


-- | How many bootstrap grid columns should be taken (see
-- 'BootstrapFormLayout').
--
-- Since: yesod-form 1.3.8
data BootstrapGridOptions =
    ColXs !Int
  | ColSm !Int
  | ColMd !Int
  | ColLg !Int
    deriving (BootstrapGridOptions -> BootstrapGridOptions -> Bool
(BootstrapGridOptions -> BootstrapGridOptions -> Bool)
-> (BootstrapGridOptions -> BootstrapGridOptions -> Bool)
-> Eq BootstrapGridOptions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BootstrapGridOptions -> BootstrapGridOptions -> Bool
$c/= :: BootstrapGridOptions -> BootstrapGridOptions -> Bool
== :: BootstrapGridOptions -> BootstrapGridOptions -> Bool
$c== :: BootstrapGridOptions -> BootstrapGridOptions -> Bool
Eq, Eq BootstrapGridOptions
Eq BootstrapGridOptions
-> (BootstrapGridOptions -> BootstrapGridOptions -> Ordering)
-> (BootstrapGridOptions -> BootstrapGridOptions -> Bool)
-> (BootstrapGridOptions -> BootstrapGridOptions -> Bool)
-> (BootstrapGridOptions -> BootstrapGridOptions -> Bool)
-> (BootstrapGridOptions -> BootstrapGridOptions -> Bool)
-> (BootstrapGridOptions
    -> BootstrapGridOptions -> BootstrapGridOptions)
-> (BootstrapGridOptions
    -> BootstrapGridOptions -> BootstrapGridOptions)
-> Ord BootstrapGridOptions
BootstrapGridOptions -> BootstrapGridOptions -> Bool
BootstrapGridOptions -> BootstrapGridOptions -> Ordering
BootstrapGridOptions
-> BootstrapGridOptions -> BootstrapGridOptions
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: BootstrapGridOptions
-> BootstrapGridOptions -> BootstrapGridOptions
$cmin :: BootstrapGridOptions
-> BootstrapGridOptions -> BootstrapGridOptions
max :: BootstrapGridOptions
-> BootstrapGridOptions -> BootstrapGridOptions
$cmax :: BootstrapGridOptions
-> BootstrapGridOptions -> BootstrapGridOptions
>= :: BootstrapGridOptions -> BootstrapGridOptions -> Bool
$c>= :: BootstrapGridOptions -> BootstrapGridOptions -> Bool
> :: BootstrapGridOptions -> BootstrapGridOptions -> Bool
$c> :: BootstrapGridOptions -> BootstrapGridOptions -> Bool
<= :: BootstrapGridOptions -> BootstrapGridOptions -> Bool
$c<= :: BootstrapGridOptions -> BootstrapGridOptions -> Bool
< :: BootstrapGridOptions -> BootstrapGridOptions -> Bool
$c< :: BootstrapGridOptions -> BootstrapGridOptions -> Bool
compare :: BootstrapGridOptions -> BootstrapGridOptions -> Ordering
$ccompare :: BootstrapGridOptions -> BootstrapGridOptions -> Ordering
$cp1Ord :: Eq BootstrapGridOptions
Ord, Int -> BootstrapGridOptions -> ShowS
[BootstrapGridOptions] -> ShowS
BootstrapGridOptions -> String
(Int -> BootstrapGridOptions -> ShowS)
-> (BootstrapGridOptions -> String)
-> ([BootstrapGridOptions] -> ShowS)
-> Show BootstrapGridOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BootstrapGridOptions] -> ShowS
$cshowList :: [BootstrapGridOptions] -> ShowS
show :: BootstrapGridOptions -> String
$cshow :: BootstrapGridOptions -> String
showsPrec :: Int -> BootstrapGridOptions -> ShowS
$cshowsPrec :: Int -> BootstrapGridOptions -> ShowS
Show)

toColumn :: BootstrapGridOptions -> String
toColumn :: BootstrapGridOptions -> String
toColumn (ColXs Int
0) = String
""
toColumn (ColSm Int
0) = String
""
toColumn (ColMd Int
0) = String
""
toColumn (ColLg Int
0) = String
""
toColumn (ColXs Int
columns) = String
"col-xs-" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
columns
toColumn (ColSm Int
columns) = String
"col-sm-" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
columns
toColumn (ColMd Int
columns) = String
"col-md-" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
columns
toColumn (ColLg Int
columns) = String
"col-lg-" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
columns

toOffset :: BootstrapGridOptions -> String
toOffset :: BootstrapGridOptions -> String
toOffset (ColXs Int
0) = String
""
toOffset (ColSm Int
0) = String
""
toOffset (ColMd Int
0) = String
""
toOffset (ColLg Int
0) = String
""
toOffset (ColXs Int
columns) = String
"col-xs-offset-" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
columns
toOffset (ColSm Int
columns) = String
"col-sm-offset-" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
columns
toOffset (ColMd Int
columns) = String
"col-md-offset-" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
columns
toOffset (ColLg Int
columns) = String
"col-lg-offset-" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
columns

addGO :: BootstrapGridOptions -> BootstrapGridOptions -> BootstrapGridOptions
addGO :: BootstrapGridOptions
-> BootstrapGridOptions -> BootstrapGridOptions
addGO (ColXs Int
a) (ColXs Int
b) = Int -> BootstrapGridOptions
ColXs (Int
aInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
b)
addGO (ColSm Int
a) (ColSm Int
b) = Int -> BootstrapGridOptions
ColSm (Int
aInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
b)
addGO (ColMd Int
a) (ColMd Int
b) = Int -> BootstrapGridOptions
ColMd (Int
aInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
b)
addGO (ColLg Int
a) (ColLg Int
b) = Int -> BootstrapGridOptions
ColLg (Int
aInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
b)
addGO BootstrapGridOptions
a BootstrapGridOptions
b     | BootstrapGridOptions
a BootstrapGridOptions -> BootstrapGridOptions -> Bool
forall a. Ord a => a -> a -> Bool
> BootstrapGridOptions
b = BootstrapGridOptions
-> BootstrapGridOptions -> BootstrapGridOptions
addGO BootstrapGridOptions
b BootstrapGridOptions
a
addGO (ColXs Int
a) BootstrapGridOptions
other = BootstrapGridOptions
-> BootstrapGridOptions -> BootstrapGridOptions
addGO (Int -> BootstrapGridOptions
ColSm Int
a) BootstrapGridOptions
other
addGO (ColSm Int
a) BootstrapGridOptions
other = BootstrapGridOptions
-> BootstrapGridOptions -> BootstrapGridOptions
addGO (Int -> BootstrapGridOptions
ColMd Int
a) BootstrapGridOptions
other
addGO (ColMd Int
a) BootstrapGridOptions
other = BootstrapGridOptions
-> BootstrapGridOptions -> BootstrapGridOptions
addGO (Int -> BootstrapGridOptions
ColLg Int
a) BootstrapGridOptions
other
addGO (ColLg Int
_) BootstrapGridOptions
_     = String -> BootstrapGridOptions
forall a. HasCallStack => String -> a
error String
"Yesod.Form.Bootstrap.addGO: never here"


-- | The layout used for the bootstrap form.
--
-- Since: yesod-form 1.3.8
data BootstrapFormLayout =
    BootstrapBasicForm -- ^ A form with labels and inputs listed vertically. See <http://getbootstrap.com/css/#forms-example>
  | BootstrapInlineForm -- ^ A form whose @\<inputs>@ are laid out horizontally (displayed as @inline-block@). For this layout, @\<label>@s are still added to the HTML, but are hidden from display. When using this layout, you must add the @form-inline@ class to your form tag. See <http://getbootstrap.com/css/#forms-inline>
  | BootstrapHorizontalForm
      { BootstrapFormLayout -> BootstrapGridOptions
bflLabelOffset :: !BootstrapGridOptions -- ^ The left <http://getbootstrap.com/css/#grid-offsetting offset> of the @\<label>@.
      , BootstrapFormLayout -> BootstrapGridOptions
bflLabelSize   :: !BootstrapGridOptions -- ^ The number of grid columns the @\<label>@ should use.
      , BootstrapFormLayout -> BootstrapGridOptions
bflInputOffset :: !BootstrapGridOptions -- ^ The left <http://getbootstrap.com/css/#grid-offsetting offset> of the @\<input>@ from its @\<label>@.
      , BootstrapFormLayout -> BootstrapGridOptions
bflInputSize   :: !BootstrapGridOptions -- ^ The number of grid columns the @\<input>@ should use.
      } -- ^ A form laid out using the Bootstrap grid, with labels in the left column and inputs on the right. When using this layout, you must add the @form-horizontal@ class to your form tag. Bootstrap requires additional markup for the submit button for horizontal forms; you can use 'bootstrapSubmit' in your form or write the markup manually. See <http://getbootstrap.com/css/#forms-horizontal>
    deriving (Int -> BootstrapFormLayout -> ShowS
[BootstrapFormLayout] -> ShowS
BootstrapFormLayout -> String
(Int -> BootstrapFormLayout -> ShowS)
-> (BootstrapFormLayout -> String)
-> ([BootstrapFormLayout] -> ShowS)
-> Show BootstrapFormLayout
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BootstrapFormLayout] -> ShowS
$cshowList :: [BootstrapFormLayout] -> ShowS
show :: BootstrapFormLayout -> String
$cshow :: BootstrapFormLayout -> String
showsPrec :: Int -> BootstrapFormLayout -> ShowS
$cshowsPrec :: Int -> BootstrapFormLayout -> ShowS
Show)


-- | Render the given form using Bootstrap v3 conventions.
--
-- Since: yesod-form 1.3.8
renderBootstrap3 :: Monad m => BootstrapFormLayout -> FormRender m a
renderBootstrap3 :: BootstrapFormLayout -> FormRender m a
renderBootstrap3 BootstrapFormLayout
formLayout AForm m a
aform Markup
fragment = do
    (FormResult a
res, [FieldView (HandlerSite m)] -> [FieldView (HandlerSite m)]
views') <- AForm m a
-> MForm
     m
     (FormResult a,
      [FieldView (HandlerSite m)] -> [FieldView (HandlerSite m)])
forall (m :: * -> *) site a.
(Monad m, HandlerSite m ~ site) =>
AForm m a
-> MForm m (FormResult a, [FieldView site] -> [FieldView site])
aFormToForm AForm m a
aform
    let views :: [FieldView (HandlerSite m)]
views = [FieldView (HandlerSite m)] -> [FieldView (HandlerSite m)]
views' []
        has :: Maybe a -> Bool
has (Just a
_) = Bool
True
        has Maybe a
Nothing  = Bool
False
        widget :: WidgetFor (HandlerSite m) ()
widget = [whamlet|
            $newline never
            #{fragment}
            $forall view <- views
              <div .form-group :fvRequired view:.required :not $ fvRequired view:.optional :has $ fvErrors view:.has-error>
                $case formLayout
                  $of BootstrapBasicForm
                    $if fvId view /= bootstrapSubmitId
                      <label :Blaze.null (fvLabel view):.sr-only for=#{fvId view}>#{fvLabel view}
                    ^{fvInput view}
                    ^{helpWidget view}
                  $of BootstrapInlineForm
                    $if fvId view /= bootstrapSubmitId
                      <label .sr-only for=#{fvId view}>#{fvLabel view}
                    ^{fvInput view}
                    ^{helpWidget view}
                  $of BootstrapHorizontalForm labelOffset labelSize inputOffset inputSize
                    $if fvId view /= bootstrapSubmitId
                      <label :Blaze.null (fvLabel view):.sr-only .control-label .#{toOffset labelOffset} .#{toColumn labelSize} for=#{fvId view}>#{fvLabel view}
                      <div .#{toOffset inputOffset} .#{toColumn inputSize}>
                        ^{fvInput view}
                        ^{helpWidget view}
                    $else
                      <div .#{toOffset (addGO inputOffset (addGO labelOffset labelSize))} .#{toColumn inputSize}>
                        ^{fvInput view}
                        ^{helpWidget view}
                |]
    (FormResult a, WidgetFor (HandlerSite m) ())
-> MForm m (FormResult a, WidgetFor (HandlerSite m) ())
forall (m :: * -> *) a. Monad m => a -> m a
return (FormResult a
res, WidgetFor (HandlerSite m) ()
widget)


-- | (Internal) Render a help widget for tooltips and errors.
helpWidget :: FieldView site -> WidgetFor site ()
helpWidget :: FieldView site -> WidgetFor site ()
helpWidget FieldView site
view = [whamlet|
    $maybe tt <- fvTooltip view
      <span .help-block>#{tt}
    $maybe err <- fvErrors view
      <span .help-block .error-block>#{err}
|]


-- | How the 'bootstrapSubmit' button should be rendered.
--
-- Since: yesod-form 1.3.8
data BootstrapSubmit msg =
    BootstrapSubmit
        { BootstrapSubmit msg -> msg
bsValue   :: msg
          -- ^ The text of the submit button.
        , BootstrapSubmit msg -> Text
bsClasses :: Text
          -- ^ Classes added to the @\<button>@.
        , BootstrapSubmit msg -> [(Text, Text)]
bsAttrs   :: [(Text, Text)]
          -- ^ Attributes added to the @\<button>@.
        } deriving (Int -> BootstrapSubmit msg -> ShowS
[BootstrapSubmit msg] -> ShowS
BootstrapSubmit msg -> String
(Int -> BootstrapSubmit msg -> ShowS)
-> (BootstrapSubmit msg -> String)
-> ([BootstrapSubmit msg] -> ShowS)
-> Show (BootstrapSubmit msg)
forall msg. Show msg => Int -> BootstrapSubmit msg -> ShowS
forall msg. Show msg => [BootstrapSubmit msg] -> ShowS
forall msg. Show msg => BootstrapSubmit msg -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BootstrapSubmit msg] -> ShowS
$cshowList :: forall msg. Show msg => [BootstrapSubmit msg] -> ShowS
show :: BootstrapSubmit msg -> String
$cshow :: forall msg. Show msg => BootstrapSubmit msg -> String
showsPrec :: Int -> BootstrapSubmit msg -> ShowS
$cshowsPrec :: forall msg. Show msg => Int -> BootstrapSubmit msg -> ShowS
Show)

instance IsString msg => IsString (BootstrapSubmit msg) where
    fromString :: String -> BootstrapSubmit msg
fromString String
msg = msg -> Text -> [(Text, Text)] -> BootstrapSubmit msg
forall msg. msg -> Text -> [(Text, Text)] -> BootstrapSubmit msg
BootstrapSubmit (String -> msg
forall a. IsString a => String -> a
fromString String
msg) Text
" btn-default " []


-- | 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
bootstrapSubmit
    :: (RenderMessage site msg, HandlerSite m ~ site, MonadHandler m)
    => BootstrapSubmit msg -> AForm m ()
bootstrapSubmit :: BootstrapSubmit msg -> AForm m ()
bootstrapSubmit = RWST
  (Maybe (Map Text [Text], Map Text [FileInfo]), site, [Text])
  Enctype
  Ints
  m
  (FormResult (), [FieldView site])
-> AForm m ()
forall (m :: * -> *) site a.
(HandlerSite m ~ site, Monad m) =>
MForm m (FormResult a, [FieldView site]) -> AForm m a
formToAForm (RWST
   (Maybe (Map Text [Text], Map Text [FileInfo]), site, [Text])
   Enctype
   Ints
   m
   (FormResult (), [FieldView site])
 -> AForm m ())
-> (BootstrapSubmit msg
    -> RWST
         (Maybe (Map Text [Text], Map Text [FileInfo]), site, [Text])
         Enctype
         Ints
         m
         (FormResult (), [FieldView site]))
-> BootstrapSubmit msg
-> AForm m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((FormResult (), FieldView site)
 -> (FormResult (), [FieldView site]))
-> RWST
     (Maybe (Map Text [Text], Map Text [FileInfo]), site, [Text])
     Enctype
     Ints
     m
     (FormResult (), FieldView site)
-> RWST
     (Maybe (Map Text [Text], Map Text [FileInfo]), site, [Text])
     Enctype
     Ints
     m
     (FormResult (), [FieldView site])
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM ((FieldView site -> [FieldView site])
-> (FormResult (), FieldView site)
-> (FormResult (), [FieldView site])
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
second FieldView site -> [FieldView site]
forall (m :: * -> *) a. Monad m => a -> m a
return) (RWST
   (Maybe (Map Text [Text], Map Text [FileInfo]), site, [Text])
   Enctype
   Ints
   m
   (FormResult (), FieldView site)
 -> RWST
      (Maybe (Map Text [Text], Map Text [FileInfo]), site, [Text])
      Enctype
      Ints
      m
      (FormResult (), [FieldView site]))
-> (BootstrapSubmit msg
    -> RWST
         (Maybe (Map Text [Text], Map Text [FileInfo]), site, [Text])
         Enctype
         Ints
         m
         (FormResult (), FieldView site))
-> BootstrapSubmit msg
-> RWST
     (Maybe (Map Text [Text], Map Text [FileInfo]), site, [Text])
     Enctype
     Ints
     m
     (FormResult (), [FieldView site])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BootstrapSubmit msg
-> RWST
     (Maybe (Map Text [Text], Map Text [FileInfo]), site, [Text])
     Enctype
     Ints
     m
     (FormResult (), FieldView site)
forall site msg (m :: * -> *).
(RenderMessage site msg, HandlerSite m ~ site, MonadHandler m) =>
BootstrapSubmit msg -> MForm m (FormResult (), FieldView site)
mbootstrapSubmit


-- | 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
mbootstrapSubmit
    :: (RenderMessage site msg, HandlerSite m ~ site, MonadHandler m)
    => BootstrapSubmit msg -> MForm m (FormResult (), FieldView site)
mbootstrapSubmit :: BootstrapSubmit msg -> MForm m (FormResult (), FieldView site)
mbootstrapSubmit (BootstrapSubmit msg
msg Text
classes [(Text, Text)]
attrs) =
    let res :: FormResult ()
res = () -> FormResult ()
forall a. a -> FormResult a
FormSuccess ()
        widget :: WidgetFor site ()
widget = [whamlet|<button class="btn #{classes}" type=submit *{attrs}>_{msg}|]
        fv :: FieldView site
fv  = FieldView :: forall site.
Markup
-> Maybe Markup
-> Text
-> WidgetFor site ()
-> Maybe Markup
-> Bool
-> FieldView site
FieldView { fvLabel :: Markup
fvLabel    = Markup
""
                        , fvTooltip :: Maybe Markup
fvTooltip  = Maybe Markup
forall a. Maybe a
Nothing
                        , fvId :: Text
fvId       = Text
bootstrapSubmitId
                        , fvInput :: WidgetFor site ()
fvInput    = WidgetFor site ()
widget
                        , fvErrors :: Maybe Markup
fvErrors   = Maybe Markup
forall a. Maybe a
Nothing
                        , fvRequired :: Bool
fvRequired = Bool
False }
    in (FormResult (), FieldView site)
-> RWST
     (Maybe (Map Text [Text], Map Text [FileInfo]), site, [Text])
     Enctype
     Ints
     m
     (FormResult (), FieldView site)
forall (m :: * -> *) a. Monad m => a -> m a
return (FormResult ()
res, FieldView site
fv)


-- | A royal hack.  Magic id used to identify whether a field
-- should have no label.  A valid HTML4 id which is probably not
-- going to clash with any other id should someone use
-- 'bootstrapSubmit' outside 'renderBootstrap3'.
bootstrapSubmitId :: Text
bootstrapSubmitId :: Text
bootstrapSubmitId = Text
"b:ootstrap___unique__:::::::::::::::::submit-id"

-- $example
-- @\<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

-- $example2
-- Yesod.Form.Bootstrap3 also supports <http://getbootstrap.com/css/#forms-horizontal 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}

-- $fieldSettings
-- 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))