diff options
author | Daniel Gröber <dxld@darkboxed.org> | 2017-06-12 03:08:56 +0200 |
---|---|---|
committer | Daniel Gröber <dxld@darkboxed.org> | 2017-06-12 03:08:56 +0200 |
commit | c8f7ac80ee152d737220c75a4d9b10211a37ace8 (patch) | |
tree | 0098798db293d9f52960d9f6ed35a998caa415f9 /CabalHelper | |
parent | eddd7e4dcbd014030b6c28bc97adf47f7cfad2fb (diff) |
Update and fix support for Cabal HEAD
Diffstat (limited to 'CabalHelper')
-rw-r--r-- | CabalHelper/Compat/Version.hs | 25 | ||||
-rw-r--r-- | CabalHelper/Compile.hs | 22 | ||||
-rw-r--r-- | CabalHelper/Licenses.hs | 18 | ||||
-rw-r--r-- | CabalHelper/Main.hs | 87 | ||||
-rw-r--r-- | CabalHelper/Wrapper.hs | 4 |
5 files changed, 110 insertions, 46 deletions
diff --git a/CabalHelper/Compat/Version.hs b/CabalHelper/Compat/Version.hs new file mode 100644 index 0000000..d2389aa --- /dev/null +++ b/CabalHelper/Compat/Version.hs @@ -0,0 +1,25 @@ +{-# LANGUAGE CPP #-} +module CabalHelper.Compat.Version + ( DataVersion + , toDataVersion + , fromDataVersion + , Data.Version.showVersion + ) where + +import qualified Data.Version +import qualified Distribution.Version (Version) +#if MIN_VERSION_Cabal(2,0,0) +import qualified Distribution.Version (versionNumbers, mkVersion) +#endif + +type DataVersion = Data.Version.Version + +toDataVersion :: Distribution.Version.Version -> Data.Version.Version +fromDataVersion :: Data.Version.Version -> Distribution.Version.Version +#if MIN_VERSION_Cabal(2,0,0) +toDataVersion v = Data.Version.Version (Distribution.Version.versionNumbers v) [] +fromDataVersion (Data.Version.Version vs _) = Distribution.Version.mkVersion vs +#else +toDataVersion = id +fromDataVersion = id +#endif diff --git a/CabalHelper/Compile.hs b/CabalHelper/Compile.hs index 0f1942a..66cd96b 100644 --- a/CabalHelper/Compile.hs +++ b/CabalHelper/Compile.hs @@ -152,7 +152,8 @@ compile distdir opts@Options {..} Compile {..} = do cCabalSourceDir <- canonicalizePath `traverse` compCabalSourceDir appdir <- appDataDir - let outdir' = maybe appdir (const $ distdir </> "cabal-helper") cCabalSourceDir + let outdir' = + maybe appdir (const $ distdir </> "cabal-helper") cCabalSourceDir createDirectoryIfMissing True outdir' outdir <- canonicalizePath outdir' @@ -164,16 +165,17 @@ compile distdir opts@Options {..} Compile {..} = do vLog opts $ "outdir: " ++ outdir vLog opts $ "exedir: " ++ exedir - let (mj:mi:_) = case compCabalVersion of - Left _commitid -> [1, 10000] - Right (Version vs _) -> vs - let ghc_opts = - concat [ + let (mj1:mj2:mi:_) = case compCabalVersion of + Left _commitid -> [1, 10000, 0] + Right (Version vs _) -> vs + let ghc_opts = concat [ [ "-outputdir", outdir , "-o", exe , "-optP-DCABAL_HELPER=1" - , "-optP-DCABAL_MAJOR=" ++ show mj - , "-optP-DCABAL_MINOR=" ++ show mi + , "-optP-DCH_MIN_VERSION_Cabal(major1,major2,minor)=(\ + \ (major1) < "++show mj1++" \ + \|| (major1) == "++show mj1++" && (major2) < "++show mj2++"\ + \|| (major1) == "++show mj1++" && (major2) == "++show mj2++" && (minor) < "++show mi++")" ], maybeToList $ ("-package-conf="++) <$> compPackageDb, map ("-i"++) $ nub $ ".":maybeToList cCabalSourceDir, @@ -289,9 +291,7 @@ cabalInstall opts db e_ver_msrcdir = do , case e_ver_msrcdir of Right ver -> - [ "install", "Cabal" - , "--constraint", "Cabal == " ++ showVersion ver - ] + [ "install", "Cabal-"++showVersion ver ] Left srcdir -> [ "install", srcdir ] ] diff --git a/CabalHelper/Licenses.hs b/CabalHelper/Licenses.hs index 10a0e7c..55a1600 100644 --- a/CabalHelper/Licenses.hs +++ b/CabalHelper/Licenses.hs @@ -1,4 +1,10 @@ {-# LANGUAGE CPP #-} + +#ifdef MIN_VERSION_Cabal +#undef CH_MIN_VERSION_Cabal +#define CH_MIN_VERSION_Cabal MIN_VERSION_Cabal +#endif + module CabalHelper.Licenses ( displayDependencyLicenseList , groupByLicense @@ -32,21 +38,21 @@ import Distribution.Version (Version) -#if CABAL_MAJOR == 1 && CABAL_MINOR > 22 +#if CH_MIN_VERSION_Cabal(1,23,0) +-- CPP > 1.22 type CPackageIndex a = PackageIndex (InstalledPackageInfo) -#elif CABAL_MAJOR == 1 && CABAL_MINOR >= 22 +#elif CH_MIN_VERSION_Cabal(1,22,0) +-- CPP >= 1.22 type CPackageIndex a = PackageIndex (InstalledPackageInfo_ a) #else type CPackageIndex a = PackageIndex #endif -#if CABAL_MAJOR == 1 && CABAL_MINOR >= 23 +#if CH_MIN_VERSION_Cabal(1,23,0) +-- CPP >= 1.23 type CInstalledPackageId = UnitId lookupInstalledPackageId' :: PackageIndex a -> UnitId -> Maybe a lookupInstalledPackageId' = lookupUnitId -#elif CABAL_MAJOR == 1 && CABAL_MINOR > 22 -type CInstalledPackageId = ComponentId -lookupInstalledPackageId' = lookupComponentId #else type CInstalledPackageId = InstalledPackageId lookupInstalledPackageId' = lookupInstalledPackageId diff --git a/CabalHelper/Main.hs b/CabalHelper/Main.hs index abdeef8..dcf87c5 100644 --- a/CabalHelper/Main.hs +++ b/CabalHelper/Main.hs @@ -16,6 +16,12 @@ {-# LANGUAGE CPP, BangPatterns, RecordWildCards, RankNTypes, ViewPatterns #-} {-# OPTIONS_GHC -fno-warn-deprecations #-} + +#ifdef MIN_VERSION_Cabal +#undef CH_MIN_VERSION_Cabal +#define CH_MIN_VERSION_Cabal MIN_VERSION_Cabal +#endif> + import Distribution.Simple.Utils (cabalVersion) import Distribution.Simple.Configure @@ -34,7 +40,8 @@ import Distribution.PackageDescription (PackageDescription, TestSuiteInterface(..), BenchmarkInterface(..), withLib) -#if CABAL_MAJOR == 1 && CABAL_MINOR >= 25 +#if CH_MIN_VERSION_Cabal(1,25,0) +-- CPP CABAL_MAJOR == 1 && CABAL_MINOR >= 25 import Distribution.PackageDescription (unFlagName, mkFlagName) #endif import Distribution.PackageDescription.Parse (readPackageDescription) @@ -51,9 +58,11 @@ import Distribution.Simple.LocalBuildInfo (LocalBuildInfo(..), externalPackageDeps, withComponentsLBI, withLibLBI) -#if CABAL_MAJOR == 1 && CABAL_MINOR >= 23 +#if CH_MIN_VERSION_Cabal(1,23,0) +-- >= 1.23 import Distribution.Simple.LocalBuildInfo (localUnitId) -#elif CABAL_MAJOR == 1 && CABAL_MINOR <= 22 +#else +-- <= 1.22 import Distribution.Simple.LocalBuildInfo (inplacePackageId) #endif @@ -70,17 +79,29 @@ import Distribution.ModuleName (components) import qualified Distribution.ModuleName as C (ModuleName) import Distribution.Text (display) import Distribution.Verbosity (Verbosity, silent, deafening, normal) -import Distribution.Version (Version, mkVersion, versionNumbers) -#if CABAL_MAJOR == 1 && CABAL_MINOR >= 22 +import Distribution.Version (Version) +#if CH_MIN_VERSION_Cabal(2,0,0) +-- CPP >= 2.0 +import Distribution.Version (versionNumbers, mkVersion) +#endif + +#if CH_MIN_VERSION_Cabal(1,22,0) +-- CPP >= 1.22 import Distribution.Utils.NubList #endif -#if CABAL_MAJOR == 1 && CABAL_MINOR >= 25 +#if CH_MIN_VERSION_Cabal(1,25,0) +-- CPP >= 1.25 import Distribution.Types.ForeignLib (ForeignLib(..)) import Distribution.Types.UnqualComponentName (unUnqualComponentName) #endif +#if CH_MIN_VERSION_Cabal(2,1,0) +import Distribution.Types.UnitId (UnitId) +import Distribution.Types.MungedPackageId (MungedPackageId) +#endif + import Control.Applicative ((<$>)) import Control.Arrow (first, second, (&&&)) import Control.Monad @@ -310,16 +331,21 @@ main = do flagName' = unFlagName . flagName -#if CABAL_MAJOR == 1 && CABAL_MINOR < 25 +#if !CH_MIN_VERSION_Cabal(1,25,0) +-- CPP < 1.25 unFlagName (FlagName n) = n mkFlagName n = FlagName n #endif toDataVersion :: Version -> DataVersion.Version -toDataVersion v = DataVersion.Version (versionNumbers v) [] - --fromDataVersion :: DataVersion.Version -> Version +#if CH_MIN_VERSION_Cabal(2,0,0) +toDataVersion v = DataVersion.Version (versionNumbers v) [] --fromDataVersion (DataVersion.Version vs _) = mkVersion vs +#else +toDataVersion = id +fromDataVersion = id +#endif getLibrary :: PackageDescription -> Library getLibrary pd = unsafePerformIO $ do @@ -378,7 +404,8 @@ componentOptions (lbi, v, distdir) inplaceFlag flags f = componentOptions' (lbi, v, distdir) inplaceFlag flags renderGhcOptions' f componentNameToCh CLibName = ChLibName -#if CABAL_MAJOR == 1 && CABAL_MINOR >= 25 +#if CH_MIN_VERSION_Cabal(1,25,0) +-- CPP >= 1.25 componentNameToCh (CSubLibName n) = ChSubLibName $ unUnqualComponentName' n componentNameToCh (CFLibName n) = ChFLibName $ unUnqualComponentName' n #endif @@ -386,15 +413,18 @@ componentNameToCh (CExeName n) = ChExeName $ unUnqualComponentName' n componentNameToCh (CTestName n) = ChTestName $ unUnqualComponentName' n componentNameToCh (CBenchName n) = ChBenchName $ unUnqualComponentName' n -#if CABAL_MAJOR == 1 && CABAL_MINOR >= 25 +#if CH_MIN_VERSION_Cabal(1,25,0) +-- CPP >= 1.25 unUnqualComponentName' = unUnqualComponentName #else unUnqualComponentName' = id #endif -#if CABAL_MAJOR == 1 && CABAL_MINOR < 25 +#if !CH_MIN_VERSION_Cabal(1,25,0) +-- CPP < 1.25 componentNameFromComponent (CLib Library {}) = CLibName -#elif CABAL_MAJOR == 1 && CABAL_MINOR >= 25 +#elif CH_MIN_VERSION_Cabal(1,25,0) +-- CPP >= 1.25 (redundant) componentNameFromComponent (CLib Library { libName = Nothing }) = CLibName componentNameFromComponent (CLib Library { libName = Just n }) = CSubLibName n componentNameFromComponent (CFLib ForeignLib {..}) = CFLibName foreignLibName @@ -458,10 +488,6 @@ removeInplaceDeps v lbi pd clbi = let in (componentGhcOptions normal lbi libbi libclbi liboutdir) { ghcOptPackageDBs = [] -#if CABAL_MAJOR == 1 && CABAL_MINOR > 22 && CABAL_MINOR < 23 - , ghcOptComponentId = NoFlag -#endif - } _ -> mempty clbi' = clbi { componentPackageDeps = deps } @@ -469,16 +495,22 @@ removeInplaceDeps v lbi pd clbi = let in (clbi', libopts) where +#if CH_MIN_VERSION_Cabal(2,1,0) + isInplaceDep :: (UnitId, MungedPackageId) -> Bool + isInplaceDep (mpid, pid) = localUnitId lbi == mpid +#else isInplaceDep :: (InstalledPackageId, PackageId) -> Bool -#if CABAL_MAJOR == 1 && CABAL_MINOR >= 23 +# if CH_MIN_VERSION_Cabal(1,23,0) +-- CPP >= 1.23 isInplaceDep (ipid, pid) = localUnitId lbi == ipid -#elif CABAL_MAJOR == 1 && CABAL_MINOR <= 22 +# else +-- CPP <= 1.22 isInplaceDep (ipid, pid) = inplacePackageId pid == ipid - +# endif #endif - -#if CABAL_MAJOR == 1 && CABAL_MINOR >= 22 +#if CH_MIN_VERSION_Cabal(1,22,0) +-- CPP >= 1.22 -- >= 1.22 uses NubListR nubPackageFlags opts = opts #else @@ -490,15 +522,16 @@ renderGhcOptions' :: LocalBuildInfo -> GhcOptions -> IO [String] renderGhcOptions' lbi v opts = do -#if CABAL_MAJOR == 1 && CABAL_MINOR < 20 +#if !CH_MIN_VERSION_Cabal(1,20,0) +-- CPP < 1.20 (ghcProg, _) <- requireProgram v ghcProgram (withPrograms lbi) let Just ghcVer = programVersion ghcProg return $ renderGhcOptions ghcVer opts -#elif CABAL_MAJOR == 1 && CABAL_MINOR >= 20 && CABAL_MINOR < 24 --- && CABAL_MINOR < 24 +#elif CH_MIN_VERSION_Cabal(1,20,0) && !CH_MIN_VERSION_Cabal(1,24,0) +-- CPP >= 1.20 && < 1.24 return $ renderGhcOptions (compiler lbi) opts -#elif CABAL_MAJOR == 1 && CABAL_MINOR >= 24 --- CABAL_MAJOR == 1 && CABAL_MINOR >= 24 +#else +-- CPP >= 1.24 return $ renderGhcOptions (compiler lbi) (hostPlatform lbi) opts #endif diff --git a/CabalHelper/Wrapper.hs b/CabalHelper/Wrapper.hs index 1987e6c..5805f3f 100644 --- a/CabalHelper/Wrapper.hs +++ b/CabalHelper/Wrapper.hs @@ -22,7 +22,6 @@ import Data.Char import Data.List import Data.Maybe import Data.String -import Data.Version import Text.Printf import System.Console.GetOpt import System.Environment @@ -44,6 +43,7 @@ import CabalHelper.Common import CabalHelper.GuessGhc import CabalHelper.Compile import CabalHelper.Types +import CabalHelper.Compat.Version usage :: IO () usage = do @@ -126,7 +126,7 @@ main = handlePanic $ do [cfile] <- filter isCabalFile <$> getDirectoryContents projdir gpd <- readPackageDescription v (projdir </> cfile) putStrLn $ show $ - [Just $ ChResponseVersion (display (packageName gpd)) (packageVersion gpd)] + [Just $ ChResponseVersion (display (packageName gpd)) (toDataVersion $ packageVersion gpd)] projdir:distdir:args' -> do cfgf <- canonicalizePath (distdir </> "setup-config") |