avoid using Assistant.WebApp.Bootstrap3 when building with current yesod
Only use that when building with ancient yesod, which does not include it. This also let me remove ifdefs in the file to support building with the new version of yesod.
This commit is contained in:
parent
55c7eb78ee
commit
dd667844b6
3 changed files with 4 additions and 26 deletions
|
@ -1,7 +1,6 @@
|
|||
{-# LANGUAGE QuasiQuotes #-}
|
||||
{-# LANGUAGE TypeFamilies #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE CPP #-}
|
||||
-- | Helper functions for creating forms when using Bootstrap v3.
|
||||
-- This is a copy of the Yesod.Form.Bootstrap3 module that has been slightly
|
||||
-- modified to be compatible with Yesod 1.0.1
|
||||
|
@ -149,20 +148,13 @@ data BootstrapFormLayout =
|
|||
-- > ^{bootstrapSubmit MsgSubmit}
|
||||
--
|
||||
-- Since: yesod-form 1.3.8
|
||||
#if MIN_VERSION_yesod(1,2,0)
|
||||
renderBootstrap3 :: Monad m => BootstrapFormLayout -> FormRender m a
|
||||
#else
|
||||
renderBootstrap3 :: BootstrapFormLayout -> FormRender sub master a
|
||||
#endif
|
||||
renderBootstrap3 formLayout aform fragment = do
|
||||
(res, views') <- aFormToForm aform
|
||||
let views = views' []
|
||||
has (Just _) = True
|
||||
has Nothing = False
|
||||
widget = [whamlet|
|
||||
#if MIN_VERSION_yesod(1,2,0)
|
||||
$newline never
|
||||
#endif
|
||||
#{fragment}
|
||||
$forall view <- views
|
||||
<div .form-group :fvRequired view:.required :not $ fvRequired view:.optional :has $ fvErrors view:.has-error>
|
||||
|
@ -193,11 +185,7 @@ renderBootstrap3 formLayout aform fragment = do
|
|||
nequals a b = a /= b -- work around older hamlet versions not liking /=
|
||||
|
||||
-- | (Internal) Render a help widget for tooltips and errors.
|
||||
#if MIN_VERSION_yesod(1,2,0)
|
||||
helpWidget :: FieldView site -> WidgetT site IO ()
|
||||
#else
|
||||
helpWidget :: FieldView sub master -> GWidget sub master ()
|
||||
#endif
|
||||
helpWidget view = [whamlet|
|
||||
$maybe tt <- fvTooltip view
|
||||
<span .help-block>#{tt}
|
||||
|
@ -242,13 +230,7 @@ instance IsString msg => IsString (BootstrapSubmit msg) where
|
|||
-- layout.
|
||||
--
|
||||
-- Since: yesod-form 1.3.8
|
||||
#if MIN_VERSION_yesod(1,2,0)
|
||||
bootstrapSubmit
|
||||
:: (RenderMessage site msg, HandlerSite m ~ site, MonadHandler m)
|
||||
=> BootstrapSubmit msg -> AForm m ()
|
||||
#else
|
||||
bootstrapSubmit :: (RenderMessage master msg) => BootstrapSubmit msg -> AForm sub master ()
|
||||
#endif
|
||||
bootstrapSubmit = formToAForm . liftM (second return) . mbootstrapSubmit
|
||||
|
||||
|
||||
|
@ -257,13 +239,7 @@ bootstrapSubmit = formToAForm . liftM (second return) . mbootstrapSubmit
|
|||
-- anyway.
|
||||
--
|
||||
-- Since: yesod-form 1.3.8
|
||||
#if MIN_VERSION_yesod(1,2,0)
|
||||
mbootstrapSubmit
|
||||
:: (RenderMessage site msg, HandlerSite m ~ site, MonadHandler m)
|
||||
=> BootstrapSubmit msg -> MForm m (FormResult (), FieldView site)
|
||||
#else
|
||||
mbootstrapSubmit :: (RenderMessage master msg) => BootstrapSubmit msg -> MForm sub master (FormResult (), FieldView sub master)
|
||||
#endif
|
||||
mbootstrapSubmit (BootstrapSubmit msg classes attrs) =
|
||||
let res = FormSuccess ()
|
||||
widget = [whamlet|<button class="btn #{classes}" type=submit *{attrs}>_{msg}|]
|
||||
|
|
|
@ -18,15 +18,16 @@ import Assistant.Gpg
|
|||
#if MIN_VERSION_yesod(1,2,0)
|
||||
import Yesod hiding (textField, passwordField)
|
||||
import Yesod.Form.Fields as F
|
||||
import Yesod.Form.Bootstrap3 hiding (bfs)
|
||||
#else
|
||||
import Yesod hiding (textField, passwordField, selectField, selectFieldList)
|
||||
import Yesod.Form.Fields as F hiding (selectField, selectFieldList)
|
||||
import Data.String (IsString (..))
|
||||
import Control.Monad (unless)
|
||||
import Data.Maybe (listToMaybe)
|
||||
import Assistant.WebApp.Bootstrap3 hiding (bfs)
|
||||
#endif
|
||||
import Data.Text (Text)
|
||||
import Assistant.WebApp.Bootstrap3 hiding (bfs)
|
||||
|
||||
{- Yesod's textField sets the required attribute for required fields.
|
||||
- We don't want this, because many of the forms used in this webapp
|
||||
|
|
|
@ -25,10 +25,11 @@ module Utility.Yesod
|
|||
|
||||
#if MIN_VERSION_yesod(1,2,0)
|
||||
import Yesod as Y
|
||||
import Yesod.Form.Bootstrap3 as Y hiding (bfs)
|
||||
#else
|
||||
import Yesod as Y hiding (Html)
|
||||
#endif
|
||||
import Assistant.WebApp.Bootstrap3 as Y hiding (bfs)
|
||||
#endif
|
||||
#ifndef __NO_TH__
|
||||
import Yesod.Default.Util
|
||||
import Language.Haskell.TH.Syntax (Q, Exp)
|
||||
|
|
Loading…
Reference in a new issue