revert reversion

This reverts commit 7bfc4a5442.

Android build is going to have consistent versions again.
This commit is contained in:
Joey Hess 2014-10-15 11:49:13 -04:00
parent 6b08fdc818
commit 9c8abb761f
5 changed files with 13 additions and 29 deletions

View file

@ -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}|]

View file

@ -25,8 +25,12 @@ import Data.String (IsString (..))
import Control.Monad (unless)
import Data.Maybe (listToMaybe)
#endif
#if MIN_VERSION_yesod_form(1,3,8)
import Yesod.Form.Bootstrap3 as Y hiding (bfs)
#else
import Assistant.WebApp.Bootstrap3 as Y 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

View file

@ -194,11 +194,11 @@ tryScan r
| Git.repoIsUrl r = return Nothing
| otherwise = liftIO $ safely $ Git.Config.read r
where
pipedconfig c params = liftIO $ safely $
pipedconfig cmd params = liftIO $ safely $
withHandle StdoutHandle createProcessSuccess p $
Git.Config.hRead r
where
p = proc c $ toCommand params
p = proc cmd $ toCommand params
configlist = Ssh.onRemote r (pipedconfig, return Nothing) "configlist" [] []
manualconfiglist = do

View file

@ -24,11 +24,11 @@ seek :: CommandSeek
seek = trustCommand "trust" Trusted
trustCommand :: String -> TrustLevel -> CommandSeek
trustCommand cmdname level = withWords start
trustCommand cmd level = withWords start
where
start ws = do
let name = unwords ws
showStart cmdname name
showStart cmd name
u <- Remote.nameToUUID name
next $ perform u
perform uuid = do

View file

@ -28,7 +28,11 @@ import Yesod as Y
#else
import Yesod as Y hiding (Html)
#endif
#if MIN_VERSION_yesod_form(1,3,8)
import Yesod.Form.Bootstrap3 as Y hiding (bfs)
#else
import Assistant.WebApp.Bootstrap3 as Y hiding (bfs)
#endif
#ifndef __NO_TH__
import Yesod.Default.Util
import Language.Haskell.TH.Syntax (Q, Exp)