Skip to content
Snippets Groups Projects
Unverified Commit 9f4b6b80 authored by Herbert Valerio Riedel's avatar Herbert Valerio Riedel :man_dancing: Committed by GitHub
Browse files

Merge pull request #5177

Implement ghc/cabal compatiblity matrix (#415)

(backported #5165)
parents c66a118d 8947db49
No related branches found
No related tags found
No related merge requests found
...@@ -949,18 +949,7 @@ planPackages verbosity comp platform solver SolverSettings{..} ...@@ -949,18 +949,7 @@ planPackages verbosity comp platform solver SolverSettings{..}
. PD.packageDescription . PD.packageDescription
. packageDescription) . packageDescription)
. addSetupCabalMinVersionConstraint (mkVersion [1,20]) . addSetupCabalMinVersionConstraint setupMinCabalVersionConstraint
-- While we can talk to older Cabal versions (we need to be able to
-- do so for custom Setup scripts that require older Cabal lib
-- versions), we have problems talking to some older versions that
-- don't support certain features.
--
-- For example, Cabal-1.16 and older do not know about build targets.
-- Even worse, 1.18 and older only supported the --constraint flag
-- with source package ids, not --dependency with installed package
-- ids. That is bad because we cannot reliably select the right
-- dependencies in the presence of multiple instances (i.e. the
-- store). See issue #3932. So we require Cabal 1.20 as a minimum.
. addPreferences . addPreferences
-- preferences from the config file or command line -- preferences from the config file or command line
...@@ -1029,6 +1018,47 @@ planPackages verbosity comp platform solver SolverSettings{..} ...@@ -1029,6 +1018,47 @@ planPackages verbosity comp platform solver SolverSettings{..}
installedPkgIndex sourcePkgDb installedPkgIndex sourcePkgDb
localPackages localPackages
-- While we can talk to older Cabal versions (we need to be able to
-- do so for custom Setup scripts that require older Cabal lib
-- versions), we have problems talking to some older versions that
-- don't support certain features.
--
-- For example, Cabal-1.16 and older do not know about build targets.
-- Even worse, 1.18 and older only supported the --constraint flag
-- with source package ids, not --dependency with installed package
-- ids. That is bad because we cannot reliably select the right
-- dependencies in the presence of multiple instances (i.e. the
-- store). See issue #3932. So we require Cabal 1.20 as a minimum.
--
-- Moreover, lib:Cabal generally only supports the interface of
-- current and past compilers; in fact recent lib:Cabal versions
-- will warn when they encounter a too new or unknown GHC compiler
-- version (c.f. #415). To avoid running into unsupported
-- configurations we encode the compatiblity matrix as lower
-- bounds on lib:Cabal here (effectively corresponding to the
-- respective major Cabal version bundled with the respective GHC
-- release).
--
-- GHC 8.4 needs Cabal >= 2.1 (GHC 8.4.1-rc1 has Cabal-2.1)
-- GHC 8.2 needs Cabal >= 2.0
-- GHC 8.0 needs Cabal >= 1.24
-- GHC 7.10 needs Cabal >= 1.22
--
-- (NB: we don't need to consider older GHCs as Cabal >= 1.20 is
-- the absolute lower bound)
--
-- TODO: long-term, this compatibility matrix should be
-- stored as a field inside 'Distribution.Compiler.Compiler'
setupMinCabalVersionConstraint
| isGHC, compVer >= mkVersion [8,4] = mkVersion [2,1]
| isGHC, compVer >= mkVersion [8,2] = mkVersion [2,0]
| isGHC, compVer >= mkVersion [8,0] = mkVersion [1,24]
| isGHC, compVer >= mkVersion [7,10] = mkVersion [1,22]
| otherwise = mkVersion [1,20]
where
isGHC = compFlav `elem` [GHC,GHCJS]
compFlav = compilerFlavor comp
compVer = compilerVersion comp
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
-- * Install plan post-processing -- * Install plan post-processing
......
...@@ -1347,14 +1347,16 @@ testSetupScriptStyles config reportSubCase = do ...@@ -1347,14 +1347,16 @@ testSetupScriptStyles config reportSubCase = do
marker1 @?= "ok" marker1 @?= "ok"
removeFile (basedir </> testdir1 </> "marker") removeFile (basedir </> testdir1 </> "marker")
reportSubCase (show SetupCustomImplicitDeps) -- implicit deps implies 'Cabal < 2' which conflicts w/ GHC 8.2 or later
(plan2, res2) <- executePlan =<< planProject testdir2 config when (compilerVersion (pkgConfigCompiler sharedConfig) < mkVersion [8,2]) $ do
(pkg2, _) <- expectPackageInstalled plan2 res2 pkgidA reportSubCase (show SetupCustomImplicitDeps)
elabSetupScriptStyle pkg2 @?= SetupCustomImplicitDeps (plan2, res2) <- executePlan =<< planProject testdir2 config
hasDefaultSetupDeps pkg2 @?= Just True (pkg2, _) <- expectPackageInstalled plan2 res2 pkgidA
marker2 <- readFile (basedir </> testdir2 </> "marker") elabSetupScriptStyle pkg2 @?= SetupCustomImplicitDeps
marker2 @?= "ok" hasDefaultSetupDeps pkg2 @?= Just True
removeFile (basedir </> testdir2 </> "marker") marker2 <- readFile (basedir </> testdir2 </> "marker")
marker2 @?= "ok"
removeFile (basedir </> testdir2 </> "marker")
reportSubCase (show SetupNonCustomInternalLib) reportSubCase (show SetupNonCustomInternalLib)
(plan3, res3) <- executePlan =<< planProject testdir3 config (plan3, res3) <- executePlan =<< planProject testdir3 config
......
...@@ -2,6 +2,8 @@ import Test.Cabal.Prelude ...@@ -2,6 +2,8 @@ import Test.Cabal.Prelude
main = cabalTest $ do main = cabalTest $ do
-- NB: This variant seems to use the bootstrapped Cabal? -- NB: This variant seems to use the bootstrapped Cabal?
skipUnless =<< hasCabalForGhc skipUnless =<< hasCabalForGhc
-- implicit setup-depends conflict with GHC >= 8.2; c.f. #415
skipIf =<< (ghcVersionIs (>= mkVersion [8,2]))
-- This test depends heavily on what packages are in the global -- This test depends heavily on what packages are in the global
-- database, don't record the output -- database, don't record the output
recordMode DoNotRecord $ do recordMode DoNotRecord $ do
......
import Test.Cabal.Prelude import Test.Cabal.Prelude
main = cabalTest $ do main = cabalTest $ do
-- implicit setup-depends conflict with GHC >= 8.2; c.f. #415
skipIf =<< (ghcVersionIs (>= mkVersion [8,2]))
-- Regression test for #4393 -- Regression test for #4393
recordMode DoNotRecord $ do recordMode DoNotRecord $ do
-- TODO: Hack; see also CustomDep/cabal.test.hs -- TODO: Hack; see also CustomDep/cabal.test.hs
......
...@@ -5,8 +5,11 @@ main = cabalTest $ ...@@ -5,8 +5,11 @@ main = cabalTest $
-- extra constraint that setup Cabal must be 1.20. If we don't -- extra constraint that setup Cabal must be 1.20. If we don't
-- have a choice like this available, the unsatisfied constraint -- have a choice like this available, the unsatisfied constraint
-- won't be reported. -- won't be reported.
--
-- Due to #415, the lower bound may be even higher based on GHC
-- version
withRepo "repo" $ do withRepo "repo" $ do
-- Don't record because output wobbles based on installed database. -- Don't record because output wobbles based on installed database.
recordMode DoNotRecord $ do recordMode DoNotRecord $ do
fails (cabal' "new-build" []) >>= fails (cabal' "new-build" []) >>=
assertOutputContains "Setup.hs requires >=1.20" assertOutputContains "Setup.hs requires >="
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment