simpler use of MIN_VERSION checks
This commit is contained in:
parent
27078cca95
commit
56830af8d8
4 changed files with 8 additions and 26 deletions
|
@ -7,12 +7,6 @@
|
|||
|
||||
{-# LANGUAGE CPP, TypeFamilies, QuasiQuotes, MultiParamTypeClasses, TemplateHaskell, OverloadedStrings, RankNTypes #-}
|
||||
|
||||
#if defined VERSION_yesod_form
|
||||
#if ! MIN_VERSION_yesod_form(1,2,0)
|
||||
#define WITH_OLD_YESOD
|
||||
#endif
|
||||
#endif
|
||||
|
||||
module Assistant.WebApp.Configurators.Local where
|
||||
|
||||
import Assistant.WebApp.Common
|
||||
|
@ -52,15 +46,13 @@ data RepositoryPath = RepositoryPath Text
|
|||
- to use as a repository. -}
|
||||
repositoryPathField :: forall sub. Bool -> Field sub WebApp Text
|
||||
repositoryPathField autofocus = Field
|
||||
#ifdef WITH_OLD_YESOD
|
||||
#if ! MIN_VERSION_yesod_form(1,2,0)
|
||||
{ fieldParse = parse
|
||||
#else
|
||||
{ fieldParse = \l _ -> parse l
|
||||
#endif
|
||||
, fieldView = view
|
||||
#ifndef WITH_OLD_YESOD
|
||||
, fieldEnctype = UrlEncoded
|
||||
#endif
|
||||
, fieldView = view
|
||||
}
|
||||
where
|
||||
view idAttr nameAttr attrs val isReq =
|
||||
|
|
|
@ -7,12 +7,6 @@
|
|||
|
||||
{-# LANGUAGE ScopedTypeVariables, CPP #-}
|
||||
|
||||
#if defined VERSION_http_conduit
|
||||
#if ! MIN_VERSION_http_conduit(1,9,0)
|
||||
#define WITH_OLD_HTTP_CONDUIT
|
||||
#endif
|
||||
#endif
|
||||
|
||||
module Remote.WebDAV (remote, davCreds, setCredsEnv) where
|
||||
|
||||
import Network.Protocol.HTTP.DAV
|
||||
|
@ -234,7 +228,7 @@ davUrlExists :: DavUrl -> DavUser -> DavPass -> IO (Either String Bool)
|
|||
davUrlExists url user pass = decode <$> catchHttp (getProps url user pass)
|
||||
where
|
||||
decode (Right _) = Right True
|
||||
#ifdef WITH_OLD_HTTP_CONDUIT
|
||||
#if ! MIN_VERSION_http_conduit(1,9,0)
|
||||
decode (Left (Left (StatusCodeException status _)))
|
||||
#else
|
||||
decode (Left (Left (StatusCodeException status _ _)))
|
||||
|
@ -285,7 +279,7 @@ catchHttp a = (Right <$> a) `E.catches`
|
|||
type EitherException = Either HttpException E.IOException
|
||||
|
||||
showEitherException :: EitherException -> String
|
||||
#ifdef WITH_OLD_HTTP_CONDUIT
|
||||
#if ! MIN_VERSION_http_conduit(1,9,0)
|
||||
showEitherException (Left (StatusCodeException status _)) =
|
||||
#else
|
||||
showEitherException (Left (StatusCodeException status _ _)) =
|
||||
|
|
|
@ -59,6 +59,7 @@ runWebApp app observer = do
|
|||
void $ forkIO $ runSettingsSocket webAppSettings sock app
|
||||
observer =<< getSocketName sock
|
||||
|
||||
webAppSettings :: Settings
|
||||
webAppSettings = defaultSettings
|
||||
-- disable buggy sloworis attack prevention code
|
||||
{ settingsTimeout = 30 * 60
|
||||
|
@ -140,6 +141,7 @@ webAppSessionBackend _ = do
|
|||
Right (s, _) -> case CS.initKey s of
|
||||
Left e -> error $ "failed to initialize key: " ++ show e
|
||||
Right key -> return $ Just $
|
||||
|
||||
Yesod.clientSessionBackend key 120
|
||||
|
||||
{- Generates a random sha512 string, suitable to be used for an
|
||||
|
|
|
@ -7,23 +7,17 @@
|
|||
|
||||
{-# LANGUAGE CPP #-}
|
||||
|
||||
#if defined VERSION_yesod_default
|
||||
#if ! MIN_VERSION_yesod_default(1,1,0)
|
||||
#define WITH_OLD_YESOD
|
||||
#endif
|
||||
#endif
|
||||
|
||||
module Utility.Yesod where
|
||||
|
||||
import Yesod.Default.Util
|
||||
import Language.Haskell.TH.Syntax
|
||||
#ifndef WITH_OLD_YESOD
|
||||
#if MIN_VERSION_yesod_default(1,1,0)
|
||||
import Data.Default (def)
|
||||
import Text.Hamlet
|
||||
#endif
|
||||
|
||||
widgetFile :: String -> Q Exp
|
||||
#ifdef WITH_OLD_YESOD
|
||||
#if ! MIN_VERSION_yesod_default(1,1,0)
|
||||
widgetFile = widgetFileNoReload
|
||||
#else
|
||||
widgetFile = widgetFileNoReload $ def
|
||||
|
|
Loading…
Reference in a new issue