unbreak android build
This reverts commitdd667844b6
and commite6eff0e951
. Those commits were fine, except the android autobuilder currently has a bit of a mess of yesod versions and broke. Better to wait on this.
This commit is contained in:
parent
4d681ae38b
commit
7bfc4a5442
5 changed files with 29 additions and 13 deletions
|
@ -1,6 +1,7 @@
|
||||||
{-# LANGUAGE QuasiQuotes #-}
|
{-# LANGUAGE QuasiQuotes #-}
|
||||||
{-# LANGUAGE TypeFamilies #-}
|
{-# LANGUAGE TypeFamilies #-}
|
||||||
{-# LANGUAGE OverloadedStrings #-}
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
|
{-# LANGUAGE CPP #-}
|
||||||
-- | Helper functions for creating forms when using Bootstrap v3.
|
-- | Helper functions for creating forms when using Bootstrap v3.
|
||||||
-- This is a copy of the Yesod.Form.Bootstrap3 module that has been slightly
|
-- This is a copy of the Yesod.Form.Bootstrap3 module that has been slightly
|
||||||
-- modified to be compatible with Yesod 1.0.1
|
-- modified to be compatible with Yesod 1.0.1
|
||||||
|
@ -148,13 +149,20 @@ data BootstrapFormLayout =
|
||||||
-- > ^{bootstrapSubmit MsgSubmit}
|
-- > ^{bootstrapSubmit MsgSubmit}
|
||||||
--
|
--
|
||||||
-- Since: yesod-form 1.3.8
|
-- 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
|
renderBootstrap3 :: BootstrapFormLayout -> FormRender sub master a
|
||||||
|
#endif
|
||||||
renderBootstrap3 formLayout aform fragment = do
|
renderBootstrap3 formLayout aform fragment = do
|
||||||
(res, views') <- aFormToForm aform
|
(res, views') <- aFormToForm aform
|
||||||
let views = views' []
|
let views = views' []
|
||||||
has (Just _) = True
|
has (Just _) = True
|
||||||
has Nothing = False
|
has Nothing = False
|
||||||
widget = [whamlet|
|
widget = [whamlet|
|
||||||
|
#if MIN_VERSION_yesod(1,2,0)
|
||||||
|
$newline never
|
||||||
|
#endif
|
||||||
#{fragment}
|
#{fragment}
|
||||||
$forall view <- views
|
$forall view <- views
|
||||||
<div .form-group :fvRequired view:.required :not $ fvRequired view:.optional :has $ fvErrors view:.has-error>
|
<div .form-group :fvRequired view:.required :not $ fvRequired view:.optional :has $ fvErrors view:.has-error>
|
||||||
|
@ -185,7 +193,11 @@ renderBootstrap3 formLayout aform fragment = do
|
||||||
nequals a b = a /= b -- work around older hamlet versions not liking /=
|
nequals a b = a /= b -- work around older hamlet versions not liking /=
|
||||||
|
|
||||||
-- | (Internal) Render a help widget for tooltips and errors.
|
-- | (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 ()
|
helpWidget :: FieldView sub master -> GWidget sub master ()
|
||||||
|
#endif
|
||||||
helpWidget view = [whamlet|
|
helpWidget view = [whamlet|
|
||||||
$maybe tt <- fvTooltip view
|
$maybe tt <- fvTooltip view
|
||||||
<span .help-block>#{tt}
|
<span .help-block>#{tt}
|
||||||
|
@ -230,7 +242,13 @@ instance IsString msg => IsString (BootstrapSubmit msg) where
|
||||||
-- layout.
|
-- layout.
|
||||||
--
|
--
|
||||||
-- Since: yesod-form 1.3.8
|
-- 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 ()
|
bootstrapSubmit :: (RenderMessage master msg) => BootstrapSubmit msg -> AForm sub master ()
|
||||||
|
#endif
|
||||||
bootstrapSubmit = formToAForm . liftM (second return) . mbootstrapSubmit
|
bootstrapSubmit = formToAForm . liftM (second return) . mbootstrapSubmit
|
||||||
|
|
||||||
|
|
||||||
|
@ -239,7 +257,13 @@ bootstrapSubmit = formToAForm . liftM (second return) . mbootstrapSubmit
|
||||||
-- anyway.
|
-- anyway.
|
||||||
--
|
--
|
||||||
-- Since: yesod-form 1.3.8
|
-- 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)
|
mbootstrapSubmit :: (RenderMessage master msg) => BootstrapSubmit msg -> MForm sub master (FormResult (), FieldView sub master)
|
||||||
|
#endif
|
||||||
mbootstrapSubmit (BootstrapSubmit msg classes attrs) =
|
mbootstrapSubmit (BootstrapSubmit msg classes attrs) =
|
||||||
let res = FormSuccess ()
|
let res = FormSuccess ()
|
||||||
widget = [whamlet|<button class="btn #{classes}" type=submit *{attrs}>_{msg}|]
|
widget = [whamlet|<button class="btn #{classes}" type=submit *{attrs}>_{msg}|]
|
||||||
|
|
|
@ -25,12 +25,8 @@ import Data.String (IsString (..))
|
||||||
import Control.Monad (unless)
|
import Control.Monad (unless)
|
||||||
import Data.Maybe (listToMaybe)
|
import Data.Maybe (listToMaybe)
|
||||||
#endif
|
#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 Data.Text (Text)
|
||||||
|
import Assistant.WebApp.Bootstrap3 hiding (bfs)
|
||||||
|
|
||||||
{- Yesod's textField sets the required attribute for required fields.
|
{- Yesod's textField sets the required attribute for required fields.
|
||||||
- We don't want this, because many of the forms used in this webapp
|
- We don't want this, because many of the forms used in this webapp
|
||||||
|
|
|
@ -194,11 +194,11 @@ tryScan r
|
||||||
| Git.repoIsUrl r = return Nothing
|
| Git.repoIsUrl r = return Nothing
|
||||||
| otherwise = liftIO $ safely $ Git.Config.read r
|
| otherwise = liftIO $ safely $ Git.Config.read r
|
||||||
where
|
where
|
||||||
pipedconfig cmd params = liftIO $ safely $
|
pipedconfig c params = liftIO $ safely $
|
||||||
withHandle StdoutHandle createProcessSuccess p $
|
withHandle StdoutHandle createProcessSuccess p $
|
||||||
Git.Config.hRead r
|
Git.Config.hRead r
|
||||||
where
|
where
|
||||||
p = proc cmd $ toCommand params
|
p = proc c $ toCommand params
|
||||||
|
|
||||||
configlist = Ssh.onRemote r (pipedconfig, return Nothing) "configlist" [] []
|
configlist = Ssh.onRemote r (pipedconfig, return Nothing) "configlist" [] []
|
||||||
manualconfiglist = do
|
manualconfiglist = do
|
||||||
|
|
|
@ -24,11 +24,11 @@ seek :: CommandSeek
|
||||||
seek = trustCommand "trust" Trusted
|
seek = trustCommand "trust" Trusted
|
||||||
|
|
||||||
trustCommand :: String -> TrustLevel -> CommandSeek
|
trustCommand :: String -> TrustLevel -> CommandSeek
|
||||||
trustCommand cmd level = withWords start
|
trustCommand cmdname level = withWords start
|
||||||
where
|
where
|
||||||
start ws = do
|
start ws = do
|
||||||
let name = unwords ws
|
let name = unwords ws
|
||||||
showStart cmd name
|
showStart cmdname name
|
||||||
u <- Remote.nameToUUID name
|
u <- Remote.nameToUUID name
|
||||||
next $ perform u
|
next $ perform u
|
||||||
perform uuid = do
|
perform uuid = do
|
||||||
|
|
|
@ -28,11 +28,7 @@ import Yesod as Y
|
||||||
#else
|
#else
|
||||||
import Yesod as Y hiding (Html)
|
import Yesod as Y hiding (Html)
|
||||||
#endif
|
#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)
|
import Assistant.WebApp.Bootstrap3 as Y hiding (bfs)
|
||||||
#endif
|
|
||||||
#ifndef __NO_TH__
|
#ifndef __NO_TH__
|
||||||
import Yesod.Default.Util
|
import Yesod.Default.Util
|
||||||
import Language.Haskell.TH.Syntax (Q, Exp)
|
import Language.Haskell.TH.Syntax (Q, Exp)
|
||||||
|
|
Loading…
Reference in a new issue