Skip to content

Commit 30e8104

Browse files
committed
Allow using different Cabal library versions for cabal-install tests with custom setup.
The idea here is to pass a `--package-db` flag to `cabal-install` which contains just `Cabal` and `Cabal-syntax` of the specific version. This allows `cabal-install` tests to use the in-tree `Cabal` version, something which you can easily run into and get very confused about when writing tests. There are a few options which can be passed to `cabal-tests` executable to control which Cabal library you will test against. 1. --boot-cabal-lib specifies to use the Cabal library bundled with the test compiler, this is the default and existing behaviour of the testsuite. 2. --intree-cabal-lib=<root_dir> specifies to use Cabal and Cabal-syntax from a specific directory, and `--test-tmp` indicates where to put the package database they are built with. 3. --specific-cabal-lib=<VERSION> specifies to use a specific Cabal version from hackage (ie 3.10.2.0) and installs the package database into --test-tmp=<DIR> The end result is that changes in the Cabal library can be tested with cabal-install tests in the testsuite. There have been a number of confusing issues with people writing tests for changes in the Cabal library which never ran because of cabal-install tests always used the boot Cabal library (see #9425 for one). Fixes #9681
1 parent 1907b12 commit 30e8104

File tree

21 files changed

+142
-61
lines changed

21 files changed

+142
-61
lines changed

cabal-testsuite/PackageTests/CustomDep/cabal.test.hs

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,5 @@
11
import Test.Cabal.Prelude
22
main = cabalTest $ do
3-
-- NB: This variant seems to use the bootstrapped Cabal?
4-
skipUnless "no Cabal for GHC" =<< hasCabalForGhc
53
-- implicit setup-depends conflict with GHC >= 8.2; c.f. #415
64
skipUnlessGhcVersion "< 8.2"
75
-- This test depends heavily on what packages are in the global
Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,4 @@
11
import Test.Cabal.Prelude
22
main = setupTest $ do
3-
skipUnless "no Cabal for GHC" =<< hasCabalForGhc
43
setup' "configure" [] >>= assertOutputContains "ThisIsCustomYeah"
54
setup' "build" [] >>= assertOutputContains "ThisIsCustomYeah"

cabal-testsuite/PackageTests/CustomPreProcess/cabal.test.hs

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,8 +1,6 @@
11
import Test.Cabal.Prelude
22
-- Test internal custom preprocessor
33
main = cabalTest $ do
4-
skipUnless "no Cabal for GHC" =<< hasCabalForGhc
5-
64
-- old Cabal's ./Setup.hs output is difficult to normalise
75
recordMode DoNotRecord $
86
cabal "v2-build" []
Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,6 @@
11
import Test.Cabal.Prelude
22
-- Test internal custom preprocessor
33
main = setupTest $ do
4-
skipUnless "no Cabal for GHC" =<< hasCabalForGhc
54
setup_build []
65
runExe' "hello-world" []
76
>>= assertOutputContains "hello from A"
Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
import Test.Cabal.Prelude
22
main = setupTest $ do
3+
skipIfGhcVersion "== 7.8.4"
34
recordMode DoNotRecord $ do
4-
skipUnless "no Cabal for GHC" =<< hasCabalForGhc
55
setup' "configure" ["--enable-tests", "--enable-coverage"] >>= assertOutputContains "ThisIsCustomYeah"
66
setup' "build" []
77
setup' "test" [] >>= assertOutputContains "Package coverage report written to"

cabal-testsuite/PackageTests/DuplicateModuleName/setup.test.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,7 @@ import Test.Cabal.Prelude
22
-- Test that if two components have the same module name, they do not
33
-- clobber each other.
44
main = setupAndCabalTest $ do
5-
skipUnless "no Cabal for GHC" =<< hasCabalForGhc -- use of library test suite
5+
skipIfCabalVersion "< 2.2"
66
setup_build ["--enable-tests"]
77
r1 <- fails $ setup' "test" ["foo"]
88
assertOutputContains "test B" r1
Lines changed: 0 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -1,11 +0,0 @@
1-
# cabal v2-update
2-
Downloading the latest package list from test-local-repo
3-
# cabal v2-repl
4-
Resolving dependencies...
5-
Error: [Cabal-7107]
6-
Could not resolve dependencies:
7-
[__0] trying: pkg-a-0 (user goal)
8-
[__1] next goal: pkg-a:setup.Cabal (dependency of pkg-a)
9-
[__1] rejecting: pkg-a:setup.Cabal-<VERSION>/installed-<HASH>, pkg-a:setup.Cabal-3.8.0.0 (constraint from --enable-multi-repl requires >=3.11)
10-
[__1] fail (backjumping, conflict set: pkg-a, pkg-a:setup.Cabal)
11-
After searching the rest of the dependency tree exhaustively, these were the goals I've had most trouble fulfilling: pkg-a:setup.Cabal (3), pkg-a (2)
Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,7 @@
11
import Test.Cabal.Prelude
22

3-
main = cabalTest $ withRepo "repo" $ do
3+
main = cabalTest $ recordMode DoNotRecord . withRepo "repo" $ do
4+
-- For the multi-repl command
45
skipUnlessGhcVersion ">= 9.4"
5-
void $ fails $ cabalWithStdin "v2-repl" ["--keep-temp-files","--enable-multi-repl","pkg-a", "pkg-b"] ""
6+
res <- fails $ cabalWithStdin "v2-repl" ["--keep-temp-files","--enable-multi-repl","pkg-a", "pkg-b"] ""
7+
assertOutputContains "constraint from --enable-multi-repl requires >=3.11" res
Lines changed: 0 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -1,9 +0,0 @@
1-
# cabal v2-repl
2-
Resolving dependencies...
3-
Error: [Cabal-7107]
4-
Could not resolve dependencies:
5-
[__0] trying: pkg-b-0 (user goal)
6-
[__1] next goal: pkg-b:setup.Cabal (dependency of pkg-b)
7-
[__1] rejecting: pkg-b:setup.Cabal-<VERSION>/installed-<HASH> (constraint from --enable-multi-repl requires >=3.11)
8-
[__1] fail (backjumping, conflict set: pkg-b, pkg-b:setup.Cabal)
9-
After searching the rest of the dependency tree exhaustively, these were the goals I've had most trouble fulfilling: pkg-b (2), pkg-b:setup.Cabal (2)

cabal-testsuite/PackageTests/MultiRepl/EnabledBadClosure/cabal.test.hs

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,8 @@
11
import Test.Cabal.Prelude
22

33
main = do
4-
cabalTest $ do
5-
-- MP: TODO: This should query Cabal library version
6-
skipIfGhcVersion ">= 9.10"
4+
cabalTest $ recordMode DoNotRecord $ do
5+
skipIfCabalVersion "<= 3.10"
76
-- Note: only the last package is interactive.
87
-- this test should load pkg-b too.
98
res <- fails $ cabalWithStdin "v2-repl" ["--enable-multi-repl","pkg-c", "pkg-a"] "Quu.quu"
Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,6 @@
11
import Test.Cabal.Prelude
22
main = cabalTest $ do
3-
withPackageDb $ do
3+
noCabalPackageDb . withPackageDb $ do
44
withDirectory "p-no-package-dbs" $ do
55
res <- fails $ cabal' "v2-build" []
66
assertOutputContains "No package databases have been specified." res

cabal-testsuite/PackageTests/Regression/T4270/setup.test.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -3,9 +3,9 @@ import Test.Cabal.Prelude
33
-- when linked dynamically
44
-- See https://github.com/haskell/cabal/issues/4270
55
main = setupAndCabalTest $ do
6+
skipIfCabalVersion "< 2.2"
67
skipUnless "no shared libs" =<< hasSharedLibraries
78
skipUnless "no shared Cabal" =<< hasCabalShared
8-
skipUnless "no Cabal for GHC" =<< hasCabalForGhc
99
ghc <- isGhcVersion "== 8.0.2"
1010
osx <- isOSX
1111
expectBrokenIf (osx && ghc) 8028 $ do

cabal-testsuite/PackageTests/TestNameCollision/setup.test.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,7 @@ import Test.Cabal.Prelude
33
-- which is in the database, we can still use the test case (they
44
-- should NOT shadow).
55
main = setupAndCabalTest $ do
6-
skipUnless "cabal for ghc" =<< hasCabalForGhc -- use of library test suite
6+
skipIfCabalVersion "< 2.2"
77
withPackageDb $ do
88
withDirectory "parent" $ setup_install []
99
withDirectory "child" $ do
Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,5 @@
11
import Test.Cabal.Prelude
22
main = setupAndCabalTest $ do
3-
skipUnless "no Cabal for GHC" =<< hasCabalForGhc
3+
skipIfCabalVersion "< 2.2"
44
setup_build ["--enable-tests"]
55
fails $ setup "test" []
Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,5 @@
11
import Test.Cabal.Prelude
22
-- Test if detailed-0.9 builds correctly
33
main = setupAndCabalTest $ do
4-
skipUnless "no Cabal for GHC" =<< hasCabalForGhc
4+
skipIfCabalVersion "< 1.20"
55
setup_build ["--enable-tests"]

cabal-testsuite/README.md

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -165,8 +165,7 @@ and stderr.
165165
**How do I skip running a test in some environments?** Use the
166166
`skipIf` and `skipUnless` combinators. Useful parameters to test
167167
these with include `hasSharedLibraries`, `hasProfiledLibraries`,
168-
`hasCabalShared`, `isGhcVersion`, `isWindows`, `isLinux`, `isOSX`
169-
and `hasCabalForGhc`.
168+
`hasCabalShared`, `isGhcVersion`, `isWindows`, `isLinux`, `isOSX`.
170169

171170
**I programmatically modified a file in my test suite, but Cabal/GHC
172171
doesn't seem to be picking it up.** You need to sleep sufficiently

cabal-testsuite/cabal-testsuite.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -104,6 +104,7 @@ executable cabal-tests
104104
, transformers
105105
-- dependencies specific to exe:cabal-tests
106106
, clock ^>= 0.7.2 || ^>=0.8
107+
, directory
107108

108109
build-tool-depends: cabal-testsuite:setup
109110
default-extensions: TypeOperators

cabal-testsuite/main/cabal-tests.hs

Lines changed: 83 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -11,6 +11,7 @@ import Test.Cabal.TestCode
1111

1212
import Distribution.Verbosity (normal, verbose, Verbosity)
1313
import Distribution.Simple.Utils (getDirectoryContentsRecursive)
14+
import Distribution.Simple.Program
1415

1516
import Options.Applicative
1617
import Control.Concurrent.MVar
@@ -26,6 +27,9 @@ import System.IO
2627
import System.FilePath
2728
import System.Exit
2829
import System.Process (callProcess, showCommandForUser)
30+
import System.Directory
31+
import Distribution.Pretty
32+
import Data.Maybe
2933

3034
#if !MIN_VERSION_base(4,12,0)
3135
import Data.Monoid ((<>))
@@ -71,9 +75,22 @@ data MainArgs = MainArgs {
7175
mainArgVerbose :: Bool,
7276
mainArgQuiet :: Bool,
7377
mainArgDistDir :: Maybe FilePath,
78+
mainArgCabalSpec :: Maybe CabalLibSpec,
7479
mainCommonArgs :: CommonArgs
7580
}
7681

82+
data CabalLibSpec = BootCabalLib | InTreeCabalLib FilePath FilePath | SpecificCabalLib String FilePath
83+
84+
cabalLibSpecParser :: Parser CabalLibSpec
85+
cabalLibSpecParser = bootParser <|> intreeParser <|> specificParser
86+
where
87+
bootParser = flag' BootCabalLib (long "boot-cabal-lib")
88+
intreeParser = InTreeCabalLib <$> strOption (long "intree-cabal-lib" <> metavar "ROOT")
89+
<*> option str ( help "Test TMP" <> long "test-tmp" )
90+
specificParser = SpecificCabalLib <$> strOption (long "specific-cabal-lib" <> metavar "VERSION")
91+
<*> option str ( help "Test TMP" <> long "test-tmp" )
92+
93+
7794
-- | optparse-applicative parser for 'MainArgs'
7895
mainArgParser :: Parser MainArgs
7996
mainArgParser = MainArgs
@@ -102,8 +119,52 @@ mainArgParser = MainArgs
102119
( help "Dist directory we were built with"
103120
<> long "builddir"
104121
<> metavar "DIR"))
122+
<*> optional cabalLibSpecParser
105123
<*> commonArgParser
106124

125+
-- Unpack and build a specific released version of Cabal and Cabal-syntax libraries
126+
buildCabalLibsProject :: String -> Verbosity -> Maybe FilePath -> FilePath -> IO FilePath
127+
buildCabalLibsProject projString verb mbGhc dir = do
128+
let prog_db = userSpecifyPaths [("ghc", path) | Just path <- [mbGhc] ] defaultProgramDb
129+
(cabal, _) <- requireProgram verb (simpleProgram "cabal") prog_db
130+
(ghc, _) <- requireProgram verb ghcProgram prog_db
131+
132+
let pv = fromMaybe (error "no ghc version") (programVersion ghc)
133+
let final_package_db = dir </> "dist-newstyle" </> "packagedb" </> "ghc-" ++ prettyShow pv
134+
createDirectoryIfMissing True dir
135+
writeFile (dir </> "cabal.project-test") projString
136+
137+
runProgramInvocation verb
138+
((programInvocation cabal
139+
["--store-dir", dir </> "store"
140+
, "--project-file=" ++ dir </> "cabal.project-test"
141+
, "build"
142+
, "-w", programPath ghc
143+
, "Cabal", "Cabal-syntax"] ) { progInvokeCwd = Just dir })
144+
return final_package_db
145+
146+
147+
buildCabalLibsSpecific :: String -> Verbosity -> Maybe FilePath -> FilePath -> IO FilePath
148+
buildCabalLibsSpecific ver verb mbGhc builddir_rel = do
149+
let prog_db = userSpecifyPaths [("ghc", path) | Just path <- [mbGhc] ] defaultProgramDb
150+
(cabal, _) <- requireProgram verb (simpleProgram "cabal") prog_db
151+
dir <- canonicalizePath (builddir_rel </> "specific" </> ver)
152+
cgot <- doesDirectoryExist (dir </> "Cabal-" ++ ver)
153+
unless cgot $
154+
runProgramInvocation verb ((programInvocation cabal ["get", "Cabal-" ++ ver]) { progInvokeCwd = Just dir })
155+
csgot <- doesDirectoryExist (dir </> "Cabal-syntax-" ++ ver)
156+
unless csgot $
157+
runProgramInvocation verb ((programInvocation cabal ["get", "Cabal-syntax-" ++ ver]) { progInvokeCwd = Just dir })
158+
159+
buildCabalLibsProject ("packages: Cabal-" ++ ver ++ " Cabal-syntax-" ++ ver) verb mbGhc dir
160+
161+
162+
buildCabalLibsIntree :: String -> Verbosity -> Maybe FilePath -> FilePath -> IO FilePath
163+
buildCabalLibsIntree root verb mbGhc builddir_rel = do
164+
dir <- canonicalizePath (builddir_rel </> "intree")
165+
buildCabalLibsProject ("packages: " ++ root </> "Cabal" ++ " " ++ root </> "Cabal-syntax") verb mbGhc dir
166+
167+
107168
main :: IO ()
108169
main = do
109170
-- By default, stderr is not buffered. This isn't really necessary
@@ -115,6 +176,27 @@ main = do
115176
args <- execParser $ info (mainArgParser <**> helper) mempty
116177
let verbosity = if mainArgVerbose args then verbose else normal
117178

179+
mpkg_db <-
180+
-- Not path to cabal-install so we're not going to run cabal-install tests so we
181+
-- can skip setting up a Cabal library to use with cabal-install.
182+
case argCabalInstallPath (mainCommonArgs args) of
183+
Nothing -> do
184+
when (isJust $ mainArgCabalSpec args)
185+
(putStrLn "Ignoring Cabal library specification as cabal-install tests are not running")
186+
return Nothing
187+
-- Path to cabal-install is passed, so need to install the requested relevant version of Cabal
188+
-- library.
189+
Just {} ->
190+
case mainArgCabalSpec args of
191+
Nothing -> do
192+
putStrLn "No Cabal library specified, using boot Cabal library with cabal-install tests"
193+
return Nothing
194+
Just BootCabalLib -> return Nothing
195+
Just (InTreeCabalLib root build_dir) ->
196+
Just <$> buildCabalLibsIntree root verbosity (argGhcPath (mainCommonArgs args)) build_dir
197+
Just (SpecificCabalLib ver build_dir) ->
198+
Just <$> buildCabalLibsSpecific ver verbosity (argGhcPath (mainCommonArgs args)) build_dir
199+
118200
-- To run our test scripts, we need to be able to run Haskell code
119201
-- linked against the Cabal library under test. The most efficient
120202
-- way to get this information is by querying the *host* build
@@ -140,7 +222,7 @@ main = do
140222
-> IO result
141223
runTest runner path
142224
= runner Nothing [] path $
143-
["--builddir", dist_dir, path] ++ renderCommonArgs (mainCommonArgs args)
225+
["--builddir", dist_dir, path] ++ ["--extra-package-db=" ++ pkg_db | Just pkg_db <- [mpkg_db]] ++ renderCommonArgs (mainCommonArgs args)
144226

145227
case mainArgTestPaths args of
146228
[path] -> do

cabal-testsuite/src/Test/Cabal/Monad.hs

Lines changed: 9 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -144,6 +144,7 @@ renderCommonArgs args =
144144

145145
data TestArgs = TestArgs {
146146
testArgDistDir :: FilePath,
147+
testArgPackageDb :: Maybe FilePath,
147148
testArgScriptPath :: FilePath,
148149
testCommonArgs :: CommonArgs
149150
}
@@ -154,6 +155,10 @@ testArgParser = TestArgs
154155
( help "Build directory of cabal-testsuite"
155156
<> long "builddir"
156157
<> metavar "DIR")
158+
<*> optional (option str
159+
( help "Package DB which contains Cabal and Cabal-syntax"
160+
<> long "extra-package-db"
161+
<> metavar "DIR"))
157162
<*> argument str ( metavar "FILE")
158163
<*> commonArgParser
159164

@@ -303,6 +308,7 @@ runTestM mode m = withSystemTempDirectory "cabal-testsuite" $ \tmp_dir -> do
303308
testMtimeChangeDelay = Nothing,
304309
testScriptEnv = senv,
305310
testSetupPath = dist_dir </> "build" </> "setup" </> "setup",
311+
testPackageDbPath = testArgPackageDb args,
306312
testSkipSetupTests = argSkipSetupTests (testCommonArgs args),
307313
testHaveCabalShared = runnerWithSharedLib senv,
308314
testEnvironment =
@@ -484,6 +490,9 @@ data TestEnv = TestEnv
484490
, testScriptEnv :: ScriptEnv
485491
-- | Setup script path
486492
, testSetupPath :: FilePath
493+
-- | Setup package-db path which contains Cabal and Cabal-syntax for cabal-install to
494+
-- use when compiling custom setups.
495+
, testPackageDbPath :: Maybe FilePath
487496
-- | Skip Setup tests?
488497
, testSkipSetupTests :: Bool
489498
-- | Do we have shared libraries for the Cabal-under-tests?

0 commit comments

Comments
 (0)