From 2af1c1d56d25ae1b64f97c5a2e9d80a364b4697d Mon Sep 17 00:00:00 2001 From: Thomas Tuegel <ttuegel@gmail.com> Date: Sat, 20 Jun 2015 17:53:59 -0500 Subject: [PATCH] Fix tests when CABAL_BUILDDIR is set --- Cabal/tests/PackageTests.hs | 115 ++++++++++-------- .../PackageTests/BenchmarkExeV10/Check.hs | 6 +- .../PackageTests/BenchmarkOptions/Check.hs | 18 +-- .../PackageTests/BenchmarkStanza/Check.hs | 6 +- .../BuildDeps/InternalLibrary0/Check.hs | 6 +- .../BuildDeps/InternalLibrary1/Check.hs | 6 +- .../BuildDeps/InternalLibrary2/Check.hs | 12 +- .../BuildDeps/InternalLibrary3/Check.hs | 12 +- .../BuildDeps/InternalLibrary4/Check.hs | 12 +- .../BuildDeps/SameDepsAllRound/Check.hs | 6 +- .../BuildDeps/TargetSpecificDeps1/Check.hs | 6 +- .../BuildDeps/TargetSpecificDeps2/Check.hs | 6 +- .../BuildDeps/TargetSpecificDeps3/Check.hs | 6 +- .../BuildTestSuiteDetailedV09/Check.hs | 12 +- Cabal/tests/PackageTests/CMain/Check.hs | 6 +- .../PackageTests/DeterministicAr/Check.hs | 24 ++-- Cabal/tests/PackageTests/EmptyLib/Check.hs | 6 +- Cabal/tests/PackageTests/Haddock/Check.hs | 8 +- Cabal/tests/PackageTests/OrderFlags/Check.hs | 6 +- Cabal/tests/PackageTests/PackageTester.hs | 102 +++++++++------- .../PathsModule/Executable/Check.hs | 8 +- .../PackageTests/PathsModule/Library/Check.hs | 8 +- Cabal/tests/PackageTests/PreProcess/Check.hs | 8 +- .../PreProcessExtraSources/Check.hs | 8 +- .../PackageTests/ReexportedModules/Check.hs | 8 +- .../PackageTests/TemplateHaskell/Check.hs | 18 +-- Cabal/tests/PackageTests/TestOptions/Check.hs | 18 +-- Cabal/tests/PackageTests/TestStanza/Check.hs | 6 +- .../PackageTests/TestSuiteExeV10/Check.hs | 48 ++++---- cabal-install/tests/PackageTests.hs | 9 +- .../Distribution/Client/UserConfig.hs | 10 +- 31 files changed, 279 insertions(+), 251 deletions(-) diff --git a/Cabal/tests/PackageTests.hs b/Cabal/tests/PackageTests.hs index 13e09b02d4..55dacf5c99 100644 --- a/Cabal/tests/PackageTests.hs +++ b/Cabal/tests/PackageTests.hs @@ -21,7 +21,7 @@ import PackageTests.BuildDeps.TargetSpecificDeps1.Check import PackageTests.BuildDeps.TargetSpecificDeps2.Check import PackageTests.BuildDeps.TargetSpecificDeps3.Check import PackageTests.BuildTestSuiteDetailedV09.Check -import PackageTests.PackageTester (PackageSpec(..), compileSetup) +import PackageTests.PackageTester (PackageSpec(..), SuiteConfig(..), compileSetup) import PackageTests.PathsModule.Executable.Check import PackageTests.PathsModule.Library.Check import PackageTests.PreProcess.Check @@ -38,29 +38,31 @@ import PackageTests.OrderFlags.Check import PackageTests.ReexportedModules.Check import Distribution.Simple.Configure - ( ConfigStateFileError(..), getConfigStateFile ) + ( ConfigStateFileError(..), findDistPrefOrDefault, getConfigStateFile ) import Distribution.Simple.LocalBuildInfo (LocalBuildInfo(..)) import Distribution.Simple.Program.Types (programPath) import Distribution.Simple.Program.Builtin ( ghcProgram, ghcPkgProgram, haddockProgram ) import Distribution.Simple.Program.Db (requireProgram) +import Distribution.Simple.Setup (Flag(..)) import Distribution.Simple.Utils (cabalVersion) import Distribution.Text (display) import Distribution.Verbosity (normal) import Distribution.Version (Version(Version)) import Control.Exception (try, throw) +import Distribution.Compat.Environment ( setEnv ) import System.Directory - ( getCurrentDirectory, setCurrentDirectory ) + ( canonicalizePath, setCurrentDirectory ) import System.FilePath ((</>)) import Test.Tasty import Test.Tasty.HUnit -tests :: Version -> PackageSpec -> FilePath -> FilePath -> [TestTree] -tests version inplaceSpec ghcPath ghcPkgPath = +tests :: SuiteConfig -> Version -> [TestTree] +tests config version = [ testCase "BuildDeps/SameDepsAllRound" - (PackageTests.BuildDeps.SameDepsAllRound.Check.suite ghcPath) + (PackageTests.BuildDeps.SameDepsAllRound.Check.suite config) -- The two following tests were disabled by Johan Tibell as -- they have been failing for a long time: -- , testCase "BuildDeps/GlobalBuildDepsNotAdditive1/" @@ -68,91 +70,98 @@ tests version inplaceSpec ghcPath ghcPkgPath = -- , testCase "BuildDeps/GlobalBuildDepsNotAdditive2/" -- (PackageTests.BuildDeps.GlobalBuildDepsNotAdditive2.Check.suite ghcPath) , testCase "BuildDeps/InternalLibrary0" - (PackageTests.BuildDeps.InternalLibrary0.Check.suite version ghcPath) - , testCase "PreProcess" (PackageTests.PreProcess.Check.suite ghcPath) + (PackageTests.BuildDeps.InternalLibrary0.Check.suite config version) + , testCase "PreProcess" (PackageTests.PreProcess.Check.suite config) , testCase "PreProcessExtraSources" - (PackageTests.PreProcessExtraSources.Check.suite ghcPath) - , testCase "TestStanza" (PackageTests.TestStanza.Check.suite ghcPath) + (PackageTests.PreProcessExtraSources.Check.suite config) + , testCase "TestStanza" (PackageTests.TestStanza.Check.suite config) -- ^ The Test stanza test will eventually be required -- only for higher versions. - , testGroup "TestSuiteExeV10" (PackageTests.TestSuiteExeV10.Check.checks ghcPath) - , testCase "TestOptions" (PackageTests.TestOptions.Check.suite ghcPath) - , testCase "BenchmarkStanza" (PackageTests.BenchmarkStanza.Check.suite ghcPath) + , testGroup "TestSuiteExeV10" (PackageTests.TestSuiteExeV10.Check.checks config) + , testCase "TestOptions" (PackageTests.TestOptions.Check.suite config) + , testCase "BenchmarkStanza" (PackageTests.BenchmarkStanza.Check.suite config) -- ^ The benchmark stanza test will eventually be required -- only for higher versions. , testCase "BenchmarkExeV10/Test" - (PackageTests.BenchmarkExeV10.Check.checkBenchmark ghcPath) - , testCase "BenchmarkOptions" (PackageTests.BenchmarkOptions.Check.suite ghcPath) + (PackageTests.BenchmarkExeV10.Check.checkBenchmark config) + , testCase "BenchmarkOptions" (PackageTests.BenchmarkOptions.Check.suite config) , testCase "TemplateHaskell/vanilla" - (PackageTests.TemplateHaskell.Check.vanilla ghcPath) + (PackageTests.TemplateHaskell.Check.vanilla config) , testCase "TemplateHaskell/profiling" - (PackageTests.TemplateHaskell.Check.profiling ghcPath) + (PackageTests.TemplateHaskell.Check.profiling config) , testCase "PathsModule/Executable" - (PackageTests.PathsModule.Executable.Check.suite ghcPath) - , testCase "PathsModule/Library" (PackageTests.PathsModule.Library.Check.suite ghcPath) + (PackageTests.PathsModule.Executable.Check.suite config) + , testCase "PathsModule/Library" + (PackageTests.PathsModule.Library.Check.suite config) , testCase "DeterministicAr" - (PackageTests.DeterministicAr.Check.suite ghcPath ghcPkgPath) + (PackageTests.DeterministicAr.Check.suite config) , testCase "EmptyLib/emptyLib" - (PackageTests.EmptyLib.Check.emptyLib ghcPath) - , testCase "Haddock" (PackageTests.Haddock.Check.suite ghcPath) + (PackageTests.EmptyLib.Check.emptyLib config) + , testCase "Haddock" (PackageTests.Haddock.Check.suite config) , testCase "BuildTestSuiteDetailedV09" - (PackageTests.BuildTestSuiteDetailedV09.Check.suite inplaceSpec ghcPath) + (PackageTests.BuildTestSuiteDetailedV09.Check.suite config) , testCase "OrderFlags" - (PackageTests.OrderFlags.Check.suite ghcPath) + (PackageTests.OrderFlags.Check.suite config) , testCase "TemplateHaskell/dynamic" - (PackageTests.TemplateHaskell.Check.dynamic ghcPath) + (PackageTests.TemplateHaskell.Check.dynamic config) , testCase "ReexportedModules" - (PackageTests.ReexportedModules.Check.suite ghcPath) + (PackageTests.ReexportedModules.Check.suite config) ] ++ -- These tests are only required to pass on cabal version >= 1.7 (if version >= Version [1, 7] [] then [ testCase "BuildDeps/TargetSpecificDeps1" - (PackageTests.BuildDeps.TargetSpecificDeps1.Check.suite ghcPath) + (PackageTests.BuildDeps.TargetSpecificDeps1.Check.suite config) , testCase "BuildDeps/TargetSpecificDeps2" - (PackageTests.BuildDeps.TargetSpecificDeps2.Check.suite ghcPath) + (PackageTests.BuildDeps.TargetSpecificDeps2.Check.suite config) , testCase "BuildDeps/TargetSpecificDeps3" - (PackageTests.BuildDeps.TargetSpecificDeps3.Check.suite ghcPath) + (PackageTests.BuildDeps.TargetSpecificDeps3.Check.suite config) , testCase "BuildDeps/InternalLibrary1" - (PackageTests.BuildDeps.InternalLibrary1.Check.suite ghcPath) + (PackageTests.BuildDeps.InternalLibrary1.Check.suite config) , testCase "BuildDeps/InternalLibrary2" - (PackageTests.BuildDeps.InternalLibrary2.Check.suite ghcPath ghcPkgPath) + (PackageTests.BuildDeps.InternalLibrary2.Check.suite config) , testCase "BuildDeps/InternalLibrary3" - (PackageTests.BuildDeps.InternalLibrary3.Check.suite ghcPath ghcPkgPath) + (PackageTests.BuildDeps.InternalLibrary3.Check.suite config) , testCase "BuildDeps/InternalLibrary4" - (PackageTests.BuildDeps.InternalLibrary4.Check.suite ghcPath ghcPkgPath) + (PackageTests.BuildDeps.InternalLibrary4.Check.suite config) , testCase "PackageTests/CMain" - (PackageTests.CMain.Check.checkBuild ghcPath) + (PackageTests.CMain.Check.checkBuild config) ] else []) main :: IO () main = do - wd <- getCurrentDirectory - let dbFile = wd </> "dist/package.conf.inplace" - inplaceSpec = PackageSpec - { directory = [] - , configOpts = [ "--package-db=" ++ dbFile - , "--constraint=Cabal == " ++ display cabalVersion - ] - , distPref = Nothing - } - putStrLn $ "Cabal test suite - testing cabal version " ++ - display cabalVersion - lbi <- getPersistBuildConfig_ ("dist" </> "setup-config") + -- Find the builddir used to build Cabal + distPref_ <- findDistPrefOrDefault NoFlag >>= canonicalizePath + -- Use the default builddir for all of the subsequent package tests + setEnv "CABAL_BUILDDIR" "dist" + lbi <- getPersistBuildConfig_ (distPref_ </> "setup-config") (ghc, _) <- requireProgram normal ghcProgram (withPrograms lbi) (ghcPkg, _) <- requireProgram normal ghcPkgProgram (withPrograms lbi) (haddock, _) <- requireProgram normal haddockProgram (withPrograms lbi) - let ghcPath = programPath ghc - ghcPkgPath = programPath ghcPkg - haddockPath = programPath haddock - putStrLn $ "Using ghc: " ++ ghcPath - putStrLn $ "Using ghc-pkg: " ++ ghcPkgPath + let haddockPath = programPath haddock + dbFile = distPref_ </> "package.conf.inplace" + config = SuiteConfig + { cabalDistPref = distPref_ + , ghcPath = programPath ghc + , ghcPkgPath = programPath ghcPkg + , inplaceSpec = PackageSpec + { directory = [] + , configOpts = + [ "--package-db=" ++ dbFile + , "--constraint=Cabal == " ++ display cabalVersion + ] + , distPref = Nothing + } + } + putStrLn $ "Cabal test suite - testing cabal version " ++ display cabalVersion + putStrLn $ "Using ghc: " ++ ghcPath config + putStrLn $ "Using ghc-pkg: " ++ ghcPkgPath config putStrLn $ "Using haddock: " ++ haddockPath setCurrentDirectory "tests" -- Create a shared Setup executable to speed up Simple tests - compileSetup "." ghcPath + compileSetup config "." defaultMain $ testGroup "Package Tests" - (tests cabalVersion inplaceSpec ghcPath ghcPkgPath) + (tests config cabalVersion) -- Like Distribution.Simple.Configure.getPersistBuildConfig but -- doesn't check that the Cabal version matches, which it doesn't when diff --git a/Cabal/tests/PackageTests/BenchmarkExeV10/Check.hs b/Cabal/tests/PackageTests/BenchmarkExeV10/Check.hs index 6316f972bd..83b123bed6 100644 --- a/Cabal/tests/PackageTests/BenchmarkExeV10/Check.hs +++ b/Cabal/tests/PackageTests/BenchmarkExeV10/Check.hs @@ -9,8 +9,8 @@ import Test.Tasty.HUnit dir :: FilePath dir = "PackageTests" </> "BenchmarkExeV10" -checkBenchmark :: FilePath -> Assertion -checkBenchmark ghcPath = do +checkBenchmark :: SuiteConfig -> Assertion +checkBenchmark config = do let spec = PackageSpec dir Nothing ["--enable-benchmarks"] - buildResult <- cabal_build spec ghcPath + buildResult <- cabal_build config spec assertBuildSucceeded buildResult diff --git a/Cabal/tests/PackageTests/BenchmarkOptions/Check.hs b/Cabal/tests/PackageTests/BenchmarkOptions/Check.hs index 41f363c8de..54396c1812 100644 --- a/Cabal/tests/PackageTests/BenchmarkOptions/Check.hs +++ b/Cabal/tests/PackageTests/BenchmarkOptions/Check.hs @@ -4,23 +4,23 @@ import PackageTests.PackageTester import System.FilePath import Test.Tasty.HUnit -suite :: FilePath -> Assertion -suite ghcPath = do +suite :: SuiteConfig -> Assertion +suite config = do let spec = PackageSpec { directory = "PackageTests" </> "BenchmarkOptions" , configOpts = ["--enable-benchmarks"] , distPref = Nothing } - _ <- cabal_build spec ghcPath - result <- cabal_bench spec ["--benchmark-options=1 2 3"] ghcPath + _ <- cabal_build config spec + result <- cabal_bench config spec ["--benchmark-options=1 2 3"] let message = "\"cabal bench\" did not pass the correct options to the " ++ "benchmark executable with \"--benchmark-options\"" assertEqual message True $ successful result - result' <- cabal_bench spec [ "--benchmark-option=1" - , "--benchmark-option=2" - , "--benchmark-option=3" - ] - ghcPath + result' <- cabal_bench config spec + [ "--benchmark-option=1" + , "--benchmark-option=2" + , "--benchmark-option=3" + ] let message' = "\"cabal bench\" did not pass the correct options to the " ++ "benchmark executable with \"--benchmark-option\"" assertEqual message' True $ successful result' diff --git a/Cabal/tests/PackageTests/BenchmarkStanza/Check.hs b/Cabal/tests/PackageTests/BenchmarkStanza/Check.hs index 5ffdb4083c..c9088c5245 100644 --- a/Cabal/tests/PackageTests/BenchmarkStanza/Check.hs +++ b/Cabal/tests/PackageTests/BenchmarkStanza/Check.hs @@ -22,12 +22,12 @@ import Distribution.Compiler ( CompilerId(..), CompilerFlavor(..), unknownCompilerInfo, AbiTag(..) ) import Distribution.Text -suite :: FilePath -> Assertion -suite ghcPath = do +suite :: SuiteConfig -> Assertion +suite config = do let dir = "PackageTests" </> "BenchmarkStanza" pdFile = dir </> "my" <.> "cabal" spec = PackageSpec { directory = dir, configOpts = [], distPref = Nothing } - result <- cabal_configure spec ghcPath + result <- cabal_configure config spec assertOutputDoesNotContain "unknown section type" result genPD <- readPackageDescription silent pdFile let compiler = unknownCompilerInfo (CompilerId GHC $ Version [6, 12, 2] []) NoAbiTag diff --git a/Cabal/tests/PackageTests/BuildDeps/InternalLibrary0/Check.hs b/Cabal/tests/PackageTests/BuildDeps/InternalLibrary0/Check.hs index 910ef703d5..e7ef5de96a 100644 --- a/Cabal/tests/PackageTests/BuildDeps/InternalLibrary0/Check.hs +++ b/Cabal/tests/PackageTests/BuildDeps/InternalLibrary0/Check.hs @@ -7,14 +7,14 @@ import System.FilePath import Test.Tasty.HUnit -suite :: Version -> FilePath -> Assertion -suite cabalVersion ghcPath = do +suite :: SuiteConfig -> Version -> Assertion +suite config cabalVersion = do let spec = PackageSpec { directory = "PackageTests" </> "BuildDeps" </> "InternalLibrary0" , configOpts = [] , distPref = Nothing } - result <- cabal_build spec ghcPath + result <- cabal_build config spec assertBuildFailed result when (cabalVersion >= Version [1, 7] []) $ do let sb = "library which is defined within the same package." diff --git a/Cabal/tests/PackageTests/BuildDeps/InternalLibrary1/Check.hs b/Cabal/tests/PackageTests/BuildDeps/InternalLibrary1/Check.hs index a7d0c47d0c..5e0f9f3ba0 100644 --- a/Cabal/tests/PackageTests/BuildDeps/InternalLibrary1/Check.hs +++ b/Cabal/tests/PackageTests/BuildDeps/InternalLibrary1/Check.hs @@ -5,12 +5,12 @@ import System.FilePath import Test.Tasty.HUnit -suite :: FilePath -> Assertion -suite ghcPath = do +suite :: SuiteConfig -> Assertion +suite config = do let spec = PackageSpec { directory = "PackageTests" </> "BuildDeps" </> "InternalLibrary1" , configOpts = [] , distPref = Nothing } - result <- cabal_build spec ghcPath + result <- cabal_build config spec assertBuildSucceeded result diff --git a/Cabal/tests/PackageTests/BuildDeps/InternalLibrary2/Check.hs b/Cabal/tests/PackageTests/BuildDeps/InternalLibrary2/Check.hs index dae1c884f7..b35882685f 100644 --- a/Cabal/tests/PackageTests/BuildDeps/InternalLibrary2/Check.hs +++ b/Cabal/tests/PackageTests/BuildDeps/InternalLibrary2/Check.hs @@ -6,8 +6,8 @@ import System.FilePath import Test.Tasty.HUnit -suite :: FilePath -> FilePath -> Assertion -suite ghcPath ghcPkgPath = do +suite :: SuiteConfig -> Assertion +suite config = do let spec = PackageSpec { directory = "PackageTests" </> "BuildDeps" </> "InternalLibrary2" , configOpts = [] @@ -19,12 +19,12 @@ suite ghcPath ghcPkgPath = do , distPref = Nothing } - unregister "InternalLibrary2" ghcPkgPath - iResult <- cabal_install specTI ghcPath + unregister config "InternalLibrary2" + iResult <- cabal_install config specTI assertInstallSucceeded iResult - bResult <- cabal_build spec ghcPath + bResult <- cabal_build config spec assertBuildSucceeded bResult - unregister "InternalLibrary2" ghcPkgPath + unregister config "InternalLibrary2" (_, _, output) <- run (Just $ directory spec) (directory spec </> "dist" </> "build" </> "lemon" </> "lemon") [] [] C.appendFile (directory spec </> "test-log.txt") (C.pack $ "\ndist/build/lemon/lemon\n"++output) diff --git a/Cabal/tests/PackageTests/BuildDeps/InternalLibrary3/Check.hs b/Cabal/tests/PackageTests/BuildDeps/InternalLibrary3/Check.hs index d39160bc9c..9edfa55cbc 100644 --- a/Cabal/tests/PackageTests/BuildDeps/InternalLibrary3/Check.hs +++ b/Cabal/tests/PackageTests/BuildDeps/InternalLibrary3/Check.hs @@ -6,8 +6,8 @@ import System.FilePath import Test.Tasty.HUnit -suite :: FilePath -> FilePath -> Assertion -suite ghcPath ghcPkgPath = do +suite :: SuiteConfig -> Assertion +suite config = do let spec = PackageSpec { directory = "PackageTests" </> "BuildDeps" </> "InternalLibrary3" , configOpts = [] @@ -19,12 +19,12 @@ suite ghcPath ghcPkgPath = do , distPref = Nothing } - unregister "InternalLibrary3" ghcPkgPath - iResult <- cabal_install specTI ghcPath + unregister config "InternalLibrary3" + iResult <- cabal_install config specTI assertInstallSucceeded iResult - bResult <- cabal_build spec ghcPath + bResult <- cabal_build config spec assertBuildSucceeded bResult - unregister "InternalLibrary3"ghcPkgPath + unregister config "InternalLibrary3" (_, _, output) <- run (Just $ directory spec) (directory spec </> "dist" </> "build" </> "lemon" </> "lemon") [] [] C.appendFile (directory spec </> "test-log.txt") (C.pack $ "\ndist/build/lemon/lemon\n"++output) diff --git a/Cabal/tests/PackageTests/BuildDeps/InternalLibrary4/Check.hs b/Cabal/tests/PackageTests/BuildDeps/InternalLibrary4/Check.hs index 7a890e6a01..6ccc0a9e04 100644 --- a/Cabal/tests/PackageTests/BuildDeps/InternalLibrary4/Check.hs +++ b/Cabal/tests/PackageTests/BuildDeps/InternalLibrary4/Check.hs @@ -6,8 +6,8 @@ import System.FilePath import Test.Tasty.HUnit -suite :: FilePath -> FilePath -> Assertion -suite ghcPath ghcPkgPath = do +suite :: SuiteConfig -> Assertion +suite config = do let spec = PackageSpec { directory = "PackageTests" </> "BuildDeps" </> "InternalLibrary4" , configOpts = [] @@ -19,12 +19,12 @@ suite ghcPath ghcPkgPath = do , distPref = Nothing } - unregister "InternalLibrary4" ghcPkgPath - iResult <- cabal_install specTI ghcPath + unregister config "InternalLibrary4" + iResult <- cabal_install config specTI assertInstallSucceeded iResult - bResult <- cabal_build spec ghcPath + bResult <- cabal_build config spec assertBuildSucceeded bResult - unregister "InternalLibrary4" ghcPkgPath + unregister config "InternalLibrary4" (_, _, output) <- run (Just $ directory spec) (directory spec </> "dist" </> "build" </> "lemon" </> "lemon") [] [] C.appendFile (directory spec </> "test-log.txt") (C.pack $ "\ndist/build/lemon/lemon\n"++output) diff --git a/Cabal/tests/PackageTests/BuildDeps/SameDepsAllRound/Check.hs b/Cabal/tests/PackageTests/BuildDeps/SameDepsAllRound/Check.hs index adc3cdf647..80d4d34076 100644 --- a/Cabal/tests/PackageTests/BuildDeps/SameDepsAllRound/Check.hs +++ b/Cabal/tests/PackageTests/BuildDeps/SameDepsAllRound/Check.hs @@ -6,14 +6,14 @@ import System.FilePath import qualified Control.Exception as E -suite :: FilePath -> Assertion -suite ghcPath = do +suite :: SuiteConfig -> Assertion +suite config = do let spec = PackageSpec { directory = "PackageTests" </> "BuildDeps" </> "SameDepsAllRound" , configOpts = [] , distPref = Nothing } - result <- cabal_build spec ghcPath + result <- cabal_build config spec do assertEqual "cabal build should succeed - see test-log.txt" True (successful result) `E.catch` \exc -> do diff --git a/Cabal/tests/PackageTests/BuildDeps/TargetSpecificDeps1/Check.hs b/Cabal/tests/PackageTests/BuildDeps/TargetSpecificDeps1/Check.hs index 454cdd37ac..e10fbd5d1b 100644 --- a/Cabal/tests/PackageTests/BuildDeps/TargetSpecificDeps1/Check.hs +++ b/Cabal/tests/PackageTests/BuildDeps/TargetSpecificDeps1/Check.hs @@ -8,14 +8,14 @@ import qualified Control.Exception as E import Text.Regex.Posix -suite :: FilePath -> Assertion -suite ghcPath = do +suite :: SuiteConfig -> Assertion +suite config = do let spec = PackageSpec { directory = "PackageTests" </> "BuildDeps" </> "TargetSpecificDeps1" , configOpts = [] , distPref = Nothing } - result <- cabal_build spec ghcPath + result <- cabal_build config spec do assertEqual "cabal build should fail - see test-log.txt" False (successful result) assertBool "error should be in MyLibrary.hs" $ diff --git a/Cabal/tests/PackageTests/BuildDeps/TargetSpecificDeps2/Check.hs b/Cabal/tests/PackageTests/BuildDeps/TargetSpecificDeps2/Check.hs index c6adc1f5b9..55513ba9fb 100644 --- a/Cabal/tests/PackageTests/BuildDeps/TargetSpecificDeps2/Check.hs +++ b/Cabal/tests/PackageTests/BuildDeps/TargetSpecificDeps2/Check.hs @@ -6,14 +6,14 @@ import System.FilePath import qualified Control.Exception as E -suite :: FilePath -> Assertion -suite ghcPath = do +suite :: SuiteConfig -> Assertion +suite config = do let spec = PackageSpec { directory = "PackageTests" </> "BuildDeps" </> "TargetSpecificDeps2" , configOpts = [] , distPref = Nothing } - result <- cabal_build spec ghcPath + result <- cabal_build config spec do assertEqual "cabal build should succeed - see test-log.txt" True (successful result) `E.catch` \exc -> do diff --git a/Cabal/tests/PackageTests/BuildDeps/TargetSpecificDeps3/Check.hs b/Cabal/tests/PackageTests/BuildDeps/TargetSpecificDeps3/Check.hs index 6b4b91dd4c..2beecbefca 100644 --- a/Cabal/tests/PackageTests/BuildDeps/TargetSpecificDeps3/Check.hs +++ b/Cabal/tests/PackageTests/BuildDeps/TargetSpecificDeps3/Check.hs @@ -8,14 +8,14 @@ import qualified Control.Exception as E import Text.Regex.Posix -suite :: FilePath -> Assertion -suite ghcPath = do +suite :: SuiteConfig -> Assertion +suite config = do let spec = PackageSpec { directory = "PackageTests" </> "BuildDeps" </> "TargetSpecificDeps3" , configOpts = [] , distPref = Nothing } - result <- cabal_build spec ghcPath + result <- cabal_build config spec do assertEqual "cabal build should fail - see test-log.txt" False (successful result) assertBool "error should be in lemon.hs" $ diff --git a/Cabal/tests/PackageTests/BuildTestSuiteDetailedV09/Check.hs b/Cabal/tests/PackageTests/BuildTestSuiteDetailedV09/Check.hs index d7a75b20c4..17c16edaac 100644 --- a/Cabal/tests/PackageTests/BuildTestSuiteDetailedV09/Check.hs +++ b/Cabal/tests/PackageTests/BuildTestSuiteDetailedV09/Check.hs @@ -5,14 +5,14 @@ import System.FilePath ((</>)) import PackageTests.PackageTester -suite :: PackageSpec -> FilePath -> Assertion -suite inplaceSpec ghcPath = do +suite :: SuiteConfig -> Assertion +suite config = do let dir = "PackageTests" </> "BuildTestSuiteDetailedV09" - spec = inplaceSpec + spec = (inplaceSpec config) { directory = dir - , configOpts = "--enable-tests" : configOpts inplaceSpec + , configOpts = "--enable-tests" : configOpts (inplaceSpec config) } - confResult <- cabal_configure spec ghcPath + confResult <- cabal_configure config spec assertConfigureSucceeded confResult - buildResult <- cabal_build spec ghcPath + buildResult <- cabal_build config spec assertBuildSucceeded buildResult diff --git a/Cabal/tests/PackageTests/CMain/Check.hs b/Cabal/tests/PackageTests/CMain/Check.hs index 4f3c0d95da..c1c46d4686 100644 --- a/Cabal/tests/PackageTests/CMain/Check.hs +++ b/Cabal/tests/PackageTests/CMain/Check.hs @@ -9,12 +9,12 @@ import PackageTests.PackageTester dir :: FilePath dir = "PackageTests" </> "CMain" -checkBuild :: FilePath -> Assertion -checkBuild ghcPath = do +checkBuild :: SuiteConfig -> Assertion +checkBuild config = do let spec = PackageSpec { directory = dir , distPref = Nothing , configOpts = [] } - buildResult <- cabal_build spec ghcPath + buildResult <- cabal_build config spec assertBuildSucceeded buildResult diff --git a/Cabal/tests/PackageTests/DeterministicAr/Check.hs b/Cabal/tests/PackageTests/DeterministicAr/Check.hs index df231836f3..891aa350ae 100644 --- a/Cabal/tests/PackageTests/DeterministicAr/Check.hs +++ b/Cabal/tests/PackageTests/DeterministicAr/Check.hs @@ -30,9 +30,9 @@ import Distribution.Simple.LocalBuildInfo (LocalBuildInfo, compiler, pkgKey) assertFailure' :: String -> IO a assertFailure' msg = assertFailure msg >> return {-unpossible!-}undefined -ghcPkg_field :: String -> String -> FilePath -> IO [FilePath] -ghcPkg_field libraryName fieldName ghcPkgPath = do - (cmd, exitCode, raw) <- run Nothing ghcPkgPath [] +ghcPkg_field :: SuiteConfig -> String -> String -> IO [FilePath] +ghcPkg_field config libraryName fieldName = do + (cmd, exitCode, raw) <- run Nothing (ghcPkgPath config) [] ["--user", "field", libraryName, fieldName] let output = filter ('\r' /=) raw -- Windows -- copypasta of PackageTester.requireSuccess @@ -45,9 +45,9 @@ ghcPkg_field libraryName fieldName ghcPkgPath = do ++ show prefix ++ " prefix on every line.\noutput: " ++ output Just fields -> return fields -ghcPkg_field1 :: String -> String -> FilePath -> IO FilePath -ghcPkg_field1 libraryName fieldName ghcPkgPath = do - fields <- ghcPkg_field libraryName fieldName ghcPkgPath +ghcPkg_field1 :: SuiteConfig -> String -> String -> IO FilePath +ghcPkg_field1 config libraryName fieldName = do + fields <- ghcPkg_field config libraryName fieldName case fields of [field] -> return field _ -> assertFailure' $ "Command ghc-pkg field failed: " @@ -58,8 +58,8 @@ ghcPkg_field1 libraryName fieldName ghcPkgPath = do this :: String this = "DeterministicAr" -suite :: FilePath -> FilePath -> Assertion -suite ghcPath ghcPkgPath = do +suite :: SuiteConfig -> Assertion +suite config = do let dir = "PackageTests" </> this let spec = PackageSpec { directory = dir @@ -67,15 +67,15 @@ suite ghcPath ghcPkgPath = do , distPref = Nothing } - unregister this ghcPkgPath - iResult <- cabal_install spec ghcPath + unregister config this + iResult <- cabal_install config spec assertInstallSucceeded iResult let distBuild = dir </> "dist" </> "build" - libdir <- ghcPkg_field1 this "library-dirs" ghcPkgPath + libdir <- ghcPkg_field1 config this "library-dirs" lbi <- getPersistBuildConfig (dir </> "dist") mapM_ (checkMetadata lbi) [distBuild, libdir] - unregister this ghcPkgPath + unregister config this -- Almost a copypasta of Distribution.Simple.Program.Ar.wipeMetadata checkMetadata :: LocalBuildInfo -> FilePath -> Assertion diff --git a/Cabal/tests/PackageTests/EmptyLib/Check.hs b/Cabal/tests/PackageTests/EmptyLib/Check.hs index 68d35f17cb..aa4b9307bc 100644 --- a/Cabal/tests/PackageTests/EmptyLib/Check.hs +++ b/Cabal/tests/PackageTests/EmptyLib/Check.hs @@ -5,12 +5,12 @@ import System.FilePath import Test.Tasty.HUnit -- See https://github.com/haskell/cabal/issues/1241 -emptyLib :: FilePath -> Assertion -emptyLib ghcPath = do +emptyLib :: SuiteConfig -> Assertion +emptyLib config = do let spec = PackageSpec { directory = "PackageTests" </> "EmptyLib" </> "empty" , configOpts = [] , distPref = Nothing } - result <- cabal_build spec ghcPath + result <- cabal_build config spec assertBuildSucceeded result diff --git a/Cabal/tests/PackageTests/Haddock/Check.hs b/Cabal/tests/PackageTests/Haddock/Check.hs index 720ec35d3c..5064936cd7 100644 --- a/Cabal/tests/PackageTests/Haddock/Check.hs +++ b/Cabal/tests/PackageTests/Haddock/Check.hs @@ -9,13 +9,13 @@ import Test.Tasty.HUnit (Assertion, assertFailure) import Distribution.Simple.Utils (withFileContents) import PackageTests.PackageTester - (PackageSpec(..), assertHaddockSucceeded, cabal_haddock) + (PackageSpec(..), SuiteConfig, assertHaddockSucceeded, cabal_haddock) this :: String this = "Haddock" -suite :: FilePath -> Assertion -suite ghcPath = do +suite :: SuiteConfig -> Assertion +suite config = do let dir = "PackageTests" </> this haddocksDir = dir </> "dist" </> "doc" </> "html" </> "Haddock" spec = PackageSpec @@ -26,7 +26,7 @@ suite ghcPath = do haddocksDirExists <- doesDirectoryExist haddocksDir when haddocksDirExists (removeDirectoryRecursive haddocksDir) - hResult <- cabal_haddock spec [] ghcPath + hResult <- cabal_haddock config spec [] assertHaddockSucceeded hResult let docFiles = map (haddocksDir </>) diff --git a/Cabal/tests/PackageTests/OrderFlags/Check.hs b/Cabal/tests/PackageTests/OrderFlags/Check.hs index fac126a116..a90d374508 100644 --- a/Cabal/tests/PackageTests/OrderFlags/Check.hs +++ b/Cabal/tests/PackageTests/OrderFlags/Check.hs @@ -9,14 +9,14 @@ import Control.Exception import Prelude hiding (catch) #endif -suite :: FilePath -> Assertion -suite ghcPath = do +suite :: SuiteConfig -> Assertion +suite config = do let spec = PackageSpec { directory = "PackageTests" </> "OrderFlags" , configOpts = [] , distPref = Nothing } - result <- cabal_build spec ghcPath + result <- cabal_build config spec do assertEqual "cabal build should succeed - see test-log.txt" True (successful result) `catch` \exc -> do diff --git a/Cabal/tests/PackageTests/PackageTester.hs b/Cabal/tests/PackageTests/PackageTester.hs index b2531893ab..17be641e23 100644 --- a/Cabal/tests/PackageTests/PackageTester.hs +++ b/Cabal/tests/PackageTests/PackageTester.hs @@ -4,6 +4,7 @@ -- the verbosity of the output generated by this module. module PackageTests.PackageTester ( PackageSpec(..) + , SuiteConfig(..) , Success(..) , Result(..) @@ -34,7 +35,7 @@ import Control.Monad import qualified Data.ByteString.Char8 as C import Data.List import Data.Maybe -import System.Directory (canonicalizePath, doesFileExist, getCurrentDirectory) +import System.Directory (canonicalizePath, doesFileExist) import System.Environment (getEnv) import System.Exit (ExitCode(ExitSuccess)) import System.FilePath @@ -56,6 +57,13 @@ data PackageSpec = PackageSpec , configOpts :: [String] } +data SuiteConfig = SuiteConfig + { ghcPath :: FilePath + , ghcPkgPath :: FilePath + , cabalDistPref :: FilePath + , inplaceSpec :: PackageSpec + } + data Success = Failure | ConfigureSuccess | BuildSuccess @@ -87,109 +95,113 @@ recordRun (cmd, exitCode, exeOutput) thisSucc res = cmd ++ "\n" ++ exeOutput } -cabal_configure :: PackageSpec -> FilePath -> IO Result -cabal_configure spec ghcPath = do - res <- doCabalConfigure spec ghcPath +cabal_configure :: SuiteConfig -> PackageSpec -> IO Result +cabal_configure config spec = do + res <- doCabalConfigure config spec record spec res return res -doCabalConfigure :: PackageSpec -> FilePath -> IO Result -doCabalConfigure spec ghcPath = do - cleanResult@(_, _, _) <- cabal spec [] ["clean"] ghcPath +doCabalConfigure :: SuiteConfig -> PackageSpec -> IO Result +doCabalConfigure config spec = do + cleanResult@(_, _, _) <- cabal config spec [] ["clean"] requireSuccess cleanResult - res <- cabal spec [] - (["configure", "--user", "-w", ghcPath] ++ configOpts spec) - ghcPath + res <- cabal config spec [] + (["configure", "--user", "-w", ghcPath config] ++ configOpts spec) return $ recordRun res ConfigureSuccess nullResult -doCabalBuild :: PackageSpec -> FilePath -> IO Result -doCabalBuild spec ghcPath = do - configResult <- doCabalConfigure spec ghcPath +doCabalBuild :: SuiteConfig -> PackageSpec -> IO Result +doCabalBuild config spec = do + configResult <- doCabalConfigure config spec if successful configResult then do - res <- cabal spec [] ["build", "-v"] ghcPath + res <- cabal config spec [] ["build", "-v"] return $ recordRun res BuildSuccess configResult else return configResult -cabal_build :: PackageSpec -> FilePath -> IO Result -cabal_build spec ghcPath = do - res <- doCabalBuild spec ghcPath +cabal_build :: SuiteConfig -> PackageSpec -> IO Result +cabal_build config spec = do + res <- doCabalBuild config spec record spec res return res -cabal_haddock :: PackageSpec -> [String] -> FilePath -> IO Result -cabal_haddock spec extraArgs ghcPath = do - res <- doCabalHaddock spec extraArgs ghcPath +cabal_haddock :: SuiteConfig -> PackageSpec -> [String] -> IO Result +cabal_haddock config spec extraArgs = do + res <- doCabalHaddock config spec extraArgs record spec res return res -doCabalHaddock :: PackageSpec -> [String] -> FilePath -> IO Result -doCabalHaddock spec extraArgs ghcPath = do - configResult <- doCabalConfigure spec ghcPath +doCabalHaddock :: SuiteConfig -> PackageSpec -> [String] -> IO Result +doCabalHaddock config spec extraArgs = do + configResult <- doCabalConfigure config spec if successful configResult then do - res <- cabal spec [] ("haddock" : extraArgs) ghcPath + res <- cabal config spec [] ("haddock" : extraArgs) return $ recordRun res HaddockSuccess configResult else return configResult -unregister :: String -> FilePath -> IO () -unregister libraryName ghcPkgPath = do - res@(_, _, output) <- run Nothing ghcPkgPath [] ["unregister", "--user", libraryName] +unregister :: SuiteConfig -> String -> IO () +unregister config libraryName = do + res@(_, _, output) <- run Nothing (ghcPkgPath config) [] + ["unregister", "--user", libraryName] if "cannot find package" `isInfixOf` output then return () else requireSuccess res -- | Install this library in the user area -cabal_install :: PackageSpec -> FilePath -> IO Result -cabal_install spec ghcPath = do - buildResult <- doCabalBuild spec ghcPath +cabal_install :: SuiteConfig -> PackageSpec -> IO Result +cabal_install config spec = do + buildResult <- doCabalBuild config spec res <- if successful buildResult then do - res <- cabal spec [] ["install"] ghcPath + res <- cabal config spec [] ["install"] return $ recordRun res InstallSuccess buildResult else return buildResult record spec res return res -cabal_test :: PackageSpec -> [(String, Maybe String)] -> [String] -> FilePath -> IO Result -cabal_test spec envOverrides extraArgs ghcPath = do - res <- cabal spec envOverrides ("test" : extraArgs) ghcPath +cabal_test :: SuiteConfig -> PackageSpec -> [(String, Maybe String)] + -> [String] -> IO Result +cabal_test config spec envOverrides extraArgs = do + res <- cabal config spec envOverrides ("test" : extraArgs) let r = recordRun res TestSuccess nullResult record spec r return r -cabal_bench :: PackageSpec -> [String] -> FilePath -> IO Result -cabal_bench spec extraArgs ghcPath = do - res <- cabal spec [] ("bench" : extraArgs) ghcPath +cabal_bench :: SuiteConfig -> PackageSpec -> [String] -> IO Result +cabal_bench config spec extraArgs = do + res <- cabal config spec [] ("bench" : extraArgs) let r = recordRun res BenchSuccess nullResult record spec r return r -compileSetup :: FilePath -> FilePath -> IO () -compileSetup packageDir ghcPath = do - wd <- getCurrentDirectory - r <- run (Just $ packageDir) ghcPath [] +compileSetup :: SuiteConfig -> FilePath -> IO () +compileSetup config packageDir = do + r <- run (Just $ packageDir) (ghcPath config) [] [ "--make" -- HPC causes trouble -- see #1012 -- , "-fhpc" - , "-package-conf " ++ wd </> "../dist/package.conf.inplace" + , "-package-conf " ++ (cabalDistPref config) </> "package.conf.inplace" , "Setup.hs" ] requireSuccess r -- | Returns the command that was issued, the return code, and the output text. -cabal :: PackageSpec -> [(String, Maybe String)] -> [String] -> FilePath -> IO (String, ExitCode, String) -cabal spec envOverrides cabalArgs_ ghcPath = do +cabal :: SuiteConfig + -> PackageSpec + -> [(String, Maybe String)] -- ^ environment variable overrides + -> [String] -- ^ extra arguments + -> IO (String, ExitCode, String) +cabal config spec envOverrides cabalArgs_ = do let cabalArgs = case distPref spec of Nothing -> cabalArgs_ Just dist -> ("--builddir=" ++ dist) : cabalArgs_ customSetup <- doesFileExist (directory spec </> "Setup.hs") if customSetup then do - compileSetup (directory spec) ghcPath + compileSetup config (directory spec) path <- canonicalizePath $ directory spec </> "Setup" run (Just $ directory spec) path envOverrides cabalArgs else do diff --git a/Cabal/tests/PackageTests/PathsModule/Executable/Check.hs b/Cabal/tests/PackageTests/PathsModule/Executable/Check.hs index 79f1362c0e..4b8d7f27c7 100644 --- a/Cabal/tests/PackageTests/PathsModule/Executable/Check.hs +++ b/Cabal/tests/PackageTests/PathsModule/Executable/Check.hs @@ -1,16 +1,16 @@ module PackageTests.PathsModule.Executable.Check (suite) where import PackageTests.PackageTester - (PackageSpec(..), assertBuildSucceeded, cabal_build) + (PackageSpec(..), SuiteConfig, assertBuildSucceeded, cabal_build) import System.FilePath import Test.Tasty.HUnit -suite :: FilePath -> Assertion -suite ghcPath = do +suite :: SuiteConfig -> Assertion +suite config = do let spec = PackageSpec { directory = "PackageTests" </> "PathsModule" </> "Executable" , distPref = Nothing , configOpts = [] } - result <- cabal_build spec ghcPath + result <- cabal_build config spec assertBuildSucceeded result diff --git a/Cabal/tests/PackageTests/PathsModule/Library/Check.hs b/Cabal/tests/PackageTests/PathsModule/Library/Check.hs index 1218b2478d..30b2453019 100644 --- a/Cabal/tests/PackageTests/PathsModule/Library/Check.hs +++ b/Cabal/tests/PackageTests/PathsModule/Library/Check.hs @@ -1,16 +1,16 @@ module PackageTests.PathsModule.Library.Check (suite) where import PackageTests.PackageTester - (PackageSpec(..), assertBuildSucceeded, cabal_build) + (PackageSpec(..), SuiteConfig, assertBuildSucceeded, cabal_build) import System.FilePath import Test.Tasty.HUnit -suite :: FilePath -> Assertion -suite ghcPath = do +suite :: SuiteConfig -> Assertion +suite config = do let spec = PackageSpec { directory = "PackageTests" </> "PathsModule" </> "Library" , distPref = Nothing , configOpts = [] } - result <- cabal_build spec ghcPath + result <- cabal_build config spec assertBuildSucceeded result diff --git a/Cabal/tests/PackageTests/PreProcess/Check.hs b/Cabal/tests/PackageTests/PreProcess/Check.hs index 97facb4b29..0e5a6ae3eb 100644 --- a/Cabal/tests/PackageTests/PreProcess/Check.hs +++ b/Cabal/tests/PackageTests/PreProcess/Check.hs @@ -1,16 +1,16 @@ module PackageTests.PreProcess.Check (suite) where import PackageTests.PackageTester - (PackageSpec(..), assertBuildSucceeded, cabal_build) + (PackageSpec(..), SuiteConfig, assertBuildSucceeded, cabal_build) import System.FilePath import Test.Tasty.HUnit -suite :: FilePath -> Assertion -suite ghcPath = do +suite :: SuiteConfig -> Assertion +suite config = do let spec = PackageSpec { directory = "PackageTests" </> "PreProcess" , distPref = Nothing , configOpts = ["--enable-tests", "--enable-benchmarks"] } - result <- cabal_build spec ghcPath + result <- cabal_build config spec assertBuildSucceeded result diff --git a/Cabal/tests/PackageTests/PreProcessExtraSources/Check.hs b/Cabal/tests/PackageTests/PreProcessExtraSources/Check.hs index d1b2cf1dce..9bede5d877 100644 --- a/Cabal/tests/PackageTests/PreProcessExtraSources/Check.hs +++ b/Cabal/tests/PackageTests/PreProcessExtraSources/Check.hs @@ -1,16 +1,16 @@ module PackageTests.PreProcessExtraSources.Check (suite) where import PackageTests.PackageTester - (PackageSpec(..), assertBuildSucceeded, cabal_build) + (PackageSpec(..), SuiteConfig, assertBuildSucceeded, cabal_build) import System.FilePath import Test.Tasty.HUnit -suite :: FilePath -> Assertion -suite ghcPath = do +suite :: SuiteConfig -> Assertion +suite config = do let spec = PackageSpec { directory = "PackageTests" </> "PreProcessExtraSources" , distPref = Nothing , configOpts = ["--enable-tests", "--enable-benchmarks"] } - result <- cabal_build spec ghcPath + result <- cabal_build config spec assertBuildSucceeded result diff --git a/Cabal/tests/PackageTests/ReexportedModules/Check.hs b/Cabal/tests/PackageTests/ReexportedModules/Check.hs index c24cf4ff4d..af2d8c168b 100644 --- a/Cabal/tests/PackageTests/ReexportedModules/Check.hs +++ b/Cabal/tests/PackageTests/ReexportedModules/Check.hs @@ -18,10 +18,10 @@ orFail err r = case find (all isSpace . snd) r of find' :: (a -> Bool) -> [a] -> Maybe a find' = find -suite :: FilePath -> Assertion -suite ghcPath = do +suite :: SuiteConfig -> Assertion +suite config = do -- ToDo: Turn this into a utility function - (_, _, xs) <- run Nothing ghcPath [] ["--info"] + (_, _, xs) <- run Nothing (ghcPath config) [] ["--info"] let compat = (>= Version [7,9] []) . orFail "could not parse version" . readP_to_S parseVersion @@ -37,5 +37,5 @@ suite ghcPath = do , configOpts = [] , distPref = Nothing } - result <- cabal_build spec ghcPath + result <- cabal_build config spec assertBuildSucceeded result diff --git a/Cabal/tests/PackageTests/TemplateHaskell/Check.hs b/Cabal/tests/PackageTests/TemplateHaskell/Check.hs index 531d6157af..1f61af038a 100644 --- a/Cabal/tests/PackageTests/TemplateHaskell/Check.hs +++ b/Cabal/tests/PackageTests/TemplateHaskell/Check.hs @@ -4,18 +4,18 @@ import PackageTests.PackageTester import System.FilePath import Test.Tasty.HUnit -vanilla :: FilePath -> Assertion -vanilla ghcPath = do +vanilla :: SuiteConfig -> Assertion +vanilla config = do let spec = PackageSpec { directory = "PackageTests" </> "TemplateHaskell" </> "vanilla" , configOpts = [] , distPref = Nothing } - result <- cabal_build spec ghcPath + result <- cabal_build config spec assertBuildSucceeded result -profiling :: FilePath -> Assertion -profiling ghcPath = do +profiling :: SuiteConfig -> Assertion +profiling config = do let flags = ["--enable-library-profiling" -- ,"--disable-library-vanilla" ,"--enable-profiling"] @@ -24,11 +24,11 @@ profiling ghcPath = do , configOpts = flags , distPref = Nothing } - result <- cabal_build spec ghcPath + result <- cabal_build config spec assertBuildSucceeded result -dynamic :: FilePath -> Assertion -dynamic ghcPath = do +dynamic :: SuiteConfig -> Assertion +dynamic config = do let flags = ["--enable-shared" -- ,"--disable-library-vanilla" ,"--enable-executable-dynamic"] @@ -37,5 +37,5 @@ dynamic ghcPath = do , configOpts = flags , distPref = Nothing } - result <- cabal_build spec ghcPath + result <- cabal_build config spec assertBuildSucceeded result diff --git a/Cabal/tests/PackageTests/TestOptions/Check.hs b/Cabal/tests/PackageTests/TestOptions/Check.hs index d3a2721470..c0640f8ac1 100644 --- a/Cabal/tests/PackageTests/TestOptions/Check.hs +++ b/Cabal/tests/PackageTests/TestOptions/Check.hs @@ -4,23 +4,23 @@ import PackageTests.PackageTester import System.FilePath import Test.Tasty.HUnit -suite :: FilePath -> Assertion -suite ghcPath = do +suite :: SuiteConfig -> Assertion +suite config = do let spec = PackageSpec { directory = "PackageTests" </> "TestOptions" , configOpts = ["--enable-tests"] , distPref = Nothing } - _ <- cabal_build spec ghcPath - result <- cabal_test spec [] ["--test-options=1 2 3"] ghcPath + _ <- cabal_build config spec + result <- cabal_test config spec [] ["--test-options=1 2 3"] let message = "\"cabal test\" did not pass the correct options to the " ++ "test executable with \"--test-options\"" assertEqual message True $ successful result - result' <- cabal_test spec [] [ "--test-option=1" - , "--test-option=2" - , "--test-option=3" - ] - ghcPath + result' <- cabal_test config spec [] + [ "--test-option=1" + , "--test-option=2" + , "--test-option=3" + ] let message' = "\"cabal test\" did not pass the correct options to the " ++ "test executable with \"--test-option\"" assertEqual message' True $ successful result' diff --git a/Cabal/tests/PackageTests/TestStanza/Check.hs b/Cabal/tests/PackageTests/TestStanza/Check.hs index e7877de1ff..70bada38f6 100644 --- a/Cabal/tests/PackageTests/TestStanza/Check.hs +++ b/Cabal/tests/PackageTests/TestStanza/Check.hs @@ -19,8 +19,8 @@ import Distribution.Compiler ( CompilerId(..), CompilerFlavor(..), unknownCompilerInfo, AbiTag(..) ) import Distribution.Text -suite :: FilePath -> Assertion -suite ghcPath = do +suite :: SuiteConfig -> Assertion +suite config = do let dir = "PackageTests" </> "TestStanza" pdFile = dir </> "my" <.> "cabal" spec = PackageSpec @@ -28,7 +28,7 @@ suite ghcPath = do , configOpts = [] , distPref = Nothing } - result <- cabal_configure spec ghcPath + result <- cabal_configure config spec assertOutputDoesNotContain "unknown section type" result genPD <- readPackageDescription silent pdFile let compiler = unknownCompilerInfo (CompilerId GHC $ Version [6, 12, 2] []) NoAbiTag diff --git a/Cabal/tests/PackageTests/TestSuiteExeV10/Check.hs b/Cabal/tests/PackageTests/TestSuiteExeV10/Check.hs index 40fcfe9a09..a8e53e060f 100644 --- a/Cabal/tests/PackageTests/TestSuiteExeV10/Check.hs +++ b/Cabal/tests/PackageTests/TestSuiteExeV10/Check.hs @@ -23,16 +23,16 @@ import Distribution.Version (Version(..), orLaterVersion) import PackageTests.PackageTester -checks :: FilePath -> [TestTree] -checks ghcPath = - [ testCase "Test" $ checkTest ghcPath ] - ++ hpcTestMatrix ghcPath ++ - [ testCase "TestNoHpc/NoTix" $ checkTestNoHpcNoTix ghcPath - , testCase "TestNoHpc/NoMarkup" $ checkTestNoHpcNoMarkup ghcPath +checks :: SuiteConfig -> [TestTree] +checks config = + [ testCase "Test" $ checkTest config ] + ++ hpcTestMatrix config ++ + [ testCase "TestNoHpc/NoTix" $ checkTestNoHpcNoTix config + , testCase "TestNoHpc/NoMarkup" $ checkTestNoHpcNoMarkup config ] -hpcTestMatrix :: FilePath -> [TestTree] -hpcTestMatrix ghcPath = do +hpcTestMatrix :: SuiteConfig -> [TestTree] +hpcTestMatrix config = do libProf <- [True, False] exeProf <- [True, False] exeDyn <- [True, False] @@ -53,13 +53,13 @@ hpcTestMatrix ghcPath = do , enable exeDyn "executable-dynamic" , enable shared "shared" ] - return $ testCase name $ checkTestWithHpc ghcPath name opts + return $ testCase name $ checkTestWithHpc config name opts dir :: FilePath dir = "PackageTests" </> "TestSuiteExeV10" -checkTest :: FilePath -> Assertion -checkTest ghcPath = buildAndTest ghcPath "Default" [] [] +checkTest :: SuiteConfig -> Assertion +checkTest config = buildAndTest config "Default" [] [] shouldExist :: FilePath -> Assertion shouldExist path = doesFileExist path >>= assertBool (path ++ " should exist") @@ -69,12 +69,12 @@ shouldNotExist path = doesFileExist path >>= assertBool (path ++ " should exist") . not -- | Ensure that both .tix file and markup are generated if coverage is enabled. -checkTestWithHpc :: FilePath -> String -> [String] -> Assertion -checkTestWithHpc ghcPath name extraOpts = do +checkTestWithHpc :: SuiteConfig -> String -> [String] -> Assertion +checkTestWithHpc config name extraOpts = do isCorrectVersion <- correctHpcVersion when isCorrectVersion $ do let distPref' = dir </> "dist-" ++ name - buildAndTest ghcPath name [] ("--enable-coverage" : extraOpts) + buildAndTest config name [] ("--enable-coverage" : extraOpts) lbi <- getPersistBuildConfig distPref' let way = guessWay lbi CompilerId comp version = compilerId (compiler lbi) @@ -90,9 +90,9 @@ checkTestWithHpc ghcPath name extraOpts = do ] -- | Ensures that even if -fhpc is manually provided no .tix file is output. -checkTestNoHpcNoTix :: FilePath -> Assertion -checkTestNoHpcNoTix ghcPath = do - buildAndTest ghcPath "NoHpcNoTix" [] +checkTestNoHpcNoTix :: SuiteConfig -> Assertion +checkTestNoHpcNoTix config = do + buildAndTest config "NoHpcNoTix" [] [ "--ghc-option=-fhpc" , "--ghc-option=-hpcdir" , "--ghc-option=dist-NoHpcNoTix/hpc/vanilla" ] @@ -102,10 +102,10 @@ checkTestNoHpcNoTix ghcPath = do -- | Ensures that even if a .tix file happens to be left around -- markup isn't generated. -checkTestNoHpcNoMarkup :: FilePath -> Assertion -checkTestNoHpcNoMarkup ghcPath = do +checkTestNoHpcNoMarkup :: SuiteConfig -> Assertion +checkTestNoHpcNoMarkup config = do let tixFile = tixFilePath "dist-NoHpcNoMarkup" Vanilla "test-Foo" - buildAndTest ghcPath "NoHpcNoMarkup" + buildAndTest config "NoHpcNoMarkup" [("HPCTIXFILE", Just tixFile)] [ "--ghc-option=-fhpc" , "--ghc-option=-hpcdir" @@ -115,16 +115,16 @@ checkTestNoHpcNoMarkup ghcPath = do -- | Build and test a package and ensure that both were successful. -- -- The flag "--enable-tests" is provided in addition to the given flags. -buildAndTest :: FilePath -> String -> [(String, Maybe String)] -> [String] -> IO () -buildAndTest ghcPath name envOverrides flags = do +buildAndTest :: SuiteConfig -> String -> [(String, Maybe String)] -> [String] -> IO () +buildAndTest config name envOverrides flags = do let spec = PackageSpec { directory = dir , distPref = Just $ "dist-" ++ name , configOpts = "--enable-tests" : flags } - buildResult <- cabal_build spec ghcPath + buildResult <- cabal_build config spec assertBuildSucceeded buildResult - testResult <- cabal_test spec envOverrides [] ghcPath + testResult <- cabal_test config spec envOverrides [] assertTestSucceeded testResult -- | Checks for a suitable HPC version for testing. diff --git a/cabal-install/tests/PackageTests.hs b/cabal-install/tests/PackageTests.hs index f4d10ef0cf..481a2a7eee 100644 --- a/cabal-install/tests/PackageTests.hs +++ b/cabal-install/tests/PackageTests.hs @@ -7,6 +7,7 @@ module Main where -- Modules from Cabal. +import Distribution.Simple.Configure (findDistPrefOrDefault) import Distribution.Simple.Program.Builtin (ghcPkgProgram) import Distribution.Simple.Program.Db (defaultProgramDb, requireProgram, setProgramSearchPath) @@ -14,11 +15,13 @@ import Distribution.Simple.Program.Find (ProgramSearchPathEntry(ProgramSearchPathDir), defaultProgramSearchPath) import Distribution.Simple.Program.Types ( Program(..), simpleProgram, programPath) +import Distribution.Simple.Setup ( Flag(..) ) import Distribution.Simple.Utils ( findProgramVersion ) import Distribution.Verbosity (normal) -- Third party modules. import qualified Control.Exception.Extensible as E +import Distribution.Compat.Environment ( setEnv ) import System.Directory ( canonicalizePath, getCurrentDirectory, setCurrentDirectory , removeFile, doesFileExist ) @@ -53,7 +56,11 @@ cabalProgram = (simpleProgram "cabal") { main :: IO () main = do - buildDir <- canonicalizePath "dist/build/cabal" + -- Find the builddir used to build Cabal + distPref <- findDistPrefOrDefault NoFlag + -- Use the default builddir for all of the subsequent package tests + setEnv "CABAL_BUILDDIR" "dist" + buildDir <- canonicalizePath (distPref </> "build/cabal") let programSearchPath = ProgramSearchPathDir buildDir : defaultProgramSearchPath (cabal, _) <- requireProgram normal cabalProgram (setProgramSearchPath programSearchPath defaultProgramDb) diff --git a/cabal-install/tests/UnitTests/Distribution/Client/UserConfig.hs b/cabal-install/tests/UnitTests/Distribution/Client/UserConfig.hs index 8df77576c0..d0cf738724 100644 --- a/cabal-install/tests/UnitTests/Distribution/Client/UserConfig.hs +++ b/cabal-install/tests/UnitTests/Distribution/Client/UserConfig.hs @@ -31,7 +31,7 @@ tests = [ testCase "nullDiffOnCreate" nullDiffOnCreateTest nullDiffOnCreateTest :: Assertion nullDiffOnCreateTest = bracketTest . const $ do -- Create a new default config file in our test directory. - _ <- loadConfig silent mempty mempty + _ <- loadConfig silent mempty -- Now we read it in and compare it against the default. diff <- userConfigDiff mempty assertBool (unlines $ "Following diff should be empty:" : diff) $ null diff @@ -40,7 +40,7 @@ nullDiffOnCreateTest = bracketTest . const $ do canDetectDifference :: Assertion canDetectDifference = bracketTest . const $ do -- Create a new default config file in our test directory. - _ <- loadConfig silent mempty mempty + _ <- loadConfig silent mempty cabalFile <- defaultConfigFile appendFile cabalFile "verbose: 0\n" diff <- userConfigDiff mempty @@ -57,7 +57,7 @@ canUpdateConfig = bracketTest . const $ do -- Update the config file. userConfigUpdate silent mempty -- Load it again. - updated <- loadConfig silent mempty mempty + updated <- loadConfig silent mempty assertBool ("Field 'tests' should be True") $ fromFlag (configTests $ savedConfigureFlags updated) @@ -65,12 +65,12 @@ canUpdateConfig = bracketTest . const $ do doubleUpdateConfig :: Assertion doubleUpdateConfig = bracketTest . const $ do -- Create a new default config file in our test directory. - _ <- loadConfig silent mempty mempty + _ <- loadConfig silent mempty -- Update it. userConfigUpdate silent mempty userConfigUpdate silent mempty -- Load it again. - updated <- loadConfig silent mempty mempty + updated <- loadConfig silent mempty assertBool ("Field 'remote-repo' doesn't contain duplicates") $ listUnique (map show . fromNubList . globalRemoteRepos $ savedGlobalFlags updated) -- GitLab