{-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE TypeFamilies #-} -- | this program based on Yesod.Form.Bootstrap3 of yesod-form -- yesod-form under MIT license, author is Michael Snoyman module Yesod.Form.Bootstrap4 ( renderBootstrap4 , BootstrapFormLayout(..) , BootstrapGridOptions(..) , bfs , withPlaceholder , withAutofocus , withLargeInput , withSmallInput , bootstrapSubmit , mbootstrapSubmit , BootstrapSubmit(..) ) where import ClassyPrelude.Yesod import Yesod.Form bfs :: RenderMessage site msg => msg -> FieldSettings site bfs msg = FieldSettings (SomeMessage msg) Nothing Nothing Nothing [("class", "form-control")] 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. 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. withLargeInput :: FieldSettings site -> FieldSettings site withLargeInput fs = fs { fsAttrs = newAttrs } where newAttrs = addClass "form-control-lg" (fsAttrs fs) -- | Add the @input-sm@ CSS class to a field. withSmallInput :: FieldSettings site -> FieldSettings site withSmallInput fs = fs { fsAttrs = newAttrs } where newAttrs = addClass "form-control-sm" (fsAttrs fs) addClass :: Text -> [(Text, Text)] -> [(Text, Text)] addClass klass [] = [("class", klass)] addClass klass (("class", old):rest) = ("class", concat [old, " ", klass]) : rest addClass klass (other :rest) = other : addClass klass rest data BootstrapGridOptions = ColXs !Int | ColSm !Int | ColMd !Int | ColLg !Int | ColXl !Int deriving (Eq, Ord, Show, Read) toColumn :: BootstrapGridOptions -> String 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 toColumn (ColXl columns) = "col-xl-" ++ show columns toOffset :: BootstrapGridOptions -> String 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 toOffset (ColXl columns) = "col-Xl-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 _ _ = error "Yesod.Form.Bootstrap.addGO: never here" -- | The layout used for the bootstrap form. data BootstrapFormLayout = BootstrapBasicForm | BootstrapInlineForm | BootstrapHorizontalForm { bflLabelOffset :: !BootstrapGridOptions , bflLabelSize :: !BootstrapGridOptions , bflInputOffset :: !BootstrapGridOptions , bflInputSize :: !BootstrapGridOptions } deriving (Eq, Ord, Show, Read) -- | Render the given form using Bootstrap v3 conventions. renderBootstrap4 :: Monad m => BootstrapFormLayout -> FormRender m a renderBootstrap4 formLayout aform fragment = do (res, views') <- aFormToForm aform let views = views' [] widget = [whamlet| #{fragment} $forall view <- views
$case formLayout $of BootstrapBasicForm $if fvId view /= bootstrapSubmitId