{-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE OverloadedStrings #-} -- | Helper functions for creating forms when using . -- 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 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 (SomeMessage msg) Nothing Nothing Nothing [("class", "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 placeholder fs = fs { fsAttrs = newAttrs } where newAttrs = ("placeholder", placeholder) : fsAttrs fs -- | Add an autofocus attribute to a field. -- -- Since: yesod-form 1.3.8 withAutofocus :: FieldSettings site -> FieldSettings site withAutofocus fs = fs { fsAttrs = newAttrs } where newAttrs = ("autofocus", "autofocus") : fsAttrs fs -- | Add the @input-lg@ CSS class to a field. -- -- Since: yesod-form 1.3.8 withLargeInput :: FieldSettings site -> FieldSettings site withLargeInput fs = fs { fsAttrs = newAttrs } where newAttrs = addClass "input-lg" (fsAttrs fs) -- | Add the @input-sm@ CSS class to a field. -- -- Since: yesod-form 1.3.8 withSmallInput :: FieldSettings site -> FieldSettings site withSmallInput fs = fs { fsAttrs = newAttrs } where newAttrs = addClass "input-sm" (fsAttrs 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 (Eq, Ord, Show) toColumn :: BootstrapGridOptions -> String toColumn (ColXs 0) = "" toColumn (ColSm 0) = "" toColumn (ColMd 0) = "" toColumn (ColLg 0) = "" toColumn (ColXs columns) = "col-xs-" ++ show columns toColumn (ColSm columns) = "col-sm-" ++ show columns toColumn (ColMd columns) = "col-md-" ++ show columns toColumn (ColLg columns) = "col-lg-" ++ show columns toOffset :: BootstrapGridOptions -> String toOffset (ColXs 0) = "" toOffset (ColSm 0) = "" toOffset (ColMd 0) = "" toOffset (ColLg 0) = "" toOffset (ColXs columns) = "col-xs-offset-" ++ show columns toOffset (ColSm columns) = "col-sm-offset-" ++ show columns toOffset (ColMd columns) = "col-md-offset-" ++ show columns toOffset (ColLg columns) = "col-lg-offset-" ++ show columns addGO :: BootstrapGridOptions -> BootstrapGridOptions -> BootstrapGridOptions addGO (ColXs a) (ColXs b) = ColXs (a+b) addGO (ColSm a) (ColSm b) = ColSm (a+b) addGO (ColMd a) (ColMd b) = ColMd (a+b) addGO (ColLg a) (ColLg b) = ColLg (a+b) addGO a b | a > b = addGO b a addGO (ColXs a) other = addGO (ColSm a) other addGO (ColSm a) other = addGO (ColMd a) other addGO (ColMd a) other = addGO (ColLg a) other addGO (ColLg _) _ = error "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 | BootstrapInlineForm -- ^ A form whose @\@ are laid out horizontally (displayed as @inline-block@). For this layout, @\