simpler use of MIN_VERSION checks

This commit is contained in:
Joey Hess 2013-03-10 15:43:10 -04:00
parent 27078cca95
commit 56830af8d8
4 changed files with 8 additions and 26 deletions

View file

@ -7,12 +7,6 @@
{-# LANGUAGE CPP, TypeFamilies, QuasiQuotes, MultiParamTypeClasses, TemplateHaskell, OverloadedStrings, RankNTypes #-} {-# 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 module Assistant.WebApp.Configurators.Local where
import Assistant.WebApp.Common import Assistant.WebApp.Common
@ -52,15 +46,13 @@ data RepositoryPath = RepositoryPath Text
- to use as a repository. -} - to use as a repository. -}
repositoryPathField :: forall sub. Bool -> Field sub WebApp Text repositoryPathField :: forall sub. Bool -> Field sub WebApp Text
repositoryPathField autofocus = Field repositoryPathField autofocus = Field
#ifdef WITH_OLD_YESOD #if ! MIN_VERSION_yesod_form(1,2,0)
{ fieldParse = parse { fieldParse = parse
#else #else
{ fieldParse = \l _ -> parse l { fieldParse = \l _ -> parse l
#endif
, fieldView = view
#ifndef WITH_OLD_YESOD
, fieldEnctype = UrlEncoded , fieldEnctype = UrlEncoded
#endif #endif
, fieldView = view
} }
where where
view idAttr nameAttr attrs val isReq = view idAttr nameAttr attrs val isReq =

View file

@ -7,12 +7,6 @@
{-# LANGUAGE ScopedTypeVariables, CPP #-} {-# 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 module Remote.WebDAV (remote, davCreds, setCredsEnv) where
import Network.Protocol.HTTP.DAV 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) davUrlExists url user pass = decode <$> catchHttp (getProps url user pass)
where where
decode (Right _) = Right True decode (Right _) = Right True
#ifdef WITH_OLD_HTTP_CONDUIT #if ! MIN_VERSION_http_conduit(1,9,0)
decode (Left (Left (StatusCodeException status _))) decode (Left (Left (StatusCodeException status _)))
#else #else
decode (Left (Left (StatusCodeException status _ _))) decode (Left (Left (StatusCodeException status _ _)))
@ -285,7 +279,7 @@ catchHttp a = (Right <$> a) `E.catches`
type EitherException = Either HttpException E.IOException type EitherException = Either HttpException E.IOException
showEitherException :: EitherException -> String showEitherException :: EitherException -> String
#ifdef WITH_OLD_HTTP_CONDUIT #if ! MIN_VERSION_http_conduit(1,9,0)
showEitherException (Left (StatusCodeException status _)) = showEitherException (Left (StatusCodeException status _)) =
#else #else
showEitherException (Left (StatusCodeException status _ _)) = showEitherException (Left (StatusCodeException status _ _)) =

View file

@ -59,6 +59,7 @@ runWebApp app observer = do
void $ forkIO $ runSettingsSocket webAppSettings sock app void $ forkIO $ runSettingsSocket webAppSettings sock app
observer =<< getSocketName sock observer =<< getSocketName sock
webAppSettings :: Settings
webAppSettings = defaultSettings webAppSettings = defaultSettings
-- disable buggy sloworis attack prevention code -- disable buggy sloworis attack prevention code
{ settingsTimeout = 30 * 60 { settingsTimeout = 30 * 60
@ -140,6 +141,7 @@ webAppSessionBackend _ = do
Right (s, _) -> case CS.initKey s of Right (s, _) -> case CS.initKey s of
Left e -> error $ "failed to initialize key: " ++ show e Left e -> error $ "failed to initialize key: " ++ show e
Right key -> return $ Just $ Right key -> return $ Just $
Yesod.clientSessionBackend key 120 Yesod.clientSessionBackend key 120
{- Generates a random sha512 string, suitable to be used for an {- Generates a random sha512 string, suitable to be used for an

View file

@ -7,23 +7,17 @@
{-# LANGUAGE CPP #-} {-# 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 module Utility.Yesod where
import Yesod.Default.Util import Yesod.Default.Util
import Language.Haskell.TH.Syntax import Language.Haskell.TH.Syntax
#ifndef WITH_OLD_YESOD #if MIN_VERSION_yesod_default(1,1,0)
import Data.Default (def) import Data.Default (def)
import Text.Hamlet import Text.Hamlet
#endif #endif
widgetFile :: String -> Q Exp widgetFile :: String -> Q Exp
#ifdef WITH_OLD_YESOD #if ! MIN_VERSION_yesod_default(1,1,0)
widgetFile = widgetFileNoReload widgetFile = widgetFileNoReload
#else #else
widgetFile = widgetFileNoReload $ def widgetFile = widgetFileNoReload $ def