Skip to content
Snippets Groups Projects
Commit 61f97e07 authored by ttuegel's avatar ttuegel
Browse files

PackageTests: set dist prefix

Some package tests run multiple tests on the same package, causing the
build directory to be overwritten. For debugging, it is important to
keep the build directory contents, so in this case we run each test
with a different build directory.
parent 3974e36a
No related branches found
No related tags found
No related merge requests found
Showing
with 100 additions and 23 deletions
/dist/
/tests/PackageTests/TestSuiteExeV10/dist-*
...@@ -140,6 +140,7 @@ main = do ...@@ -140,6 +140,7 @@ main = do
, configOpts = [ "--package-db=" ++ dbFile , configOpts = [ "--package-db=" ++ dbFile
, "--constraint=Cabal == " ++ display cabalVersion , "--constraint=Cabal == " ++ display cabalVersion
] ]
, distPref = Nothing
} }
putStrLn $ "Cabal test suite - testing cabal version " ++ putStrLn $ "Cabal test suite - testing cabal version " ++
display cabalVersion display cabalVersion
......
...@@ -11,6 +11,6 @@ dir = "PackageTests" </> "BenchmarkExeV10" ...@@ -11,6 +11,6 @@ dir = "PackageTests" </> "BenchmarkExeV10"
checkBenchmark :: FilePath -> Test checkBenchmark :: FilePath -> Test
checkBenchmark ghcPath = TestCase $ do checkBenchmark ghcPath = TestCase $ do
let spec = PackageSpec dir ["--enable-benchmarks"] let spec = PackageSpec dir Nothing ["--enable-benchmarks"]
buildResult <- cabal_build spec ghcPath buildResult <- cabal_build spec ghcPath
assertBuildSucceeded buildResult assertBuildSucceeded buildResult
...@@ -6,8 +6,11 @@ import Test.HUnit ...@@ -6,8 +6,11 @@ import Test.HUnit
suite :: FilePath -> Test suite :: FilePath -> Test
suite ghcPath = TestCase $ do suite ghcPath = TestCase $ do
let spec = PackageSpec ("PackageTests" </> "BenchmarkOptions") let spec = PackageSpec
["--enable-benchmarks"] { directory = "PackageTests" </> "BenchmarkOptions"
, configOpts = ["--enable-benchmarks"]
, distPref = Nothing
}
_ <- cabal_build spec ghcPath _ <- cabal_build spec ghcPath
result <- cabal_bench spec ["--benchmark-options=1 2 3"] ghcPath result <- cabal_bench spec ["--benchmark-options=1 2 3"] ghcPath
let message = "\"cabal bench\" did not pass the correct options to the " let message = "\"cabal bench\" did not pass the correct options to the "
......
...@@ -26,7 +26,7 @@ suite :: FilePath -> Test ...@@ -26,7 +26,7 @@ suite :: FilePath -> Test
suite ghcPath = TestCase $ do suite ghcPath = TestCase $ do
let dir = "PackageTests" </> "BenchmarkStanza" let dir = "PackageTests" </> "BenchmarkStanza"
pdFile = dir </> "my" <.> "cabal" pdFile = dir </> "my" <.> "cabal"
spec = PackageSpec dir [] spec = PackageSpec { directory = dir, configOpts = [], distPref = Nothing }
result <- cabal_configure spec ghcPath result <- cabal_configure spec ghcPath
assertOutputDoesNotContain "unknown section type" result assertOutputDoesNotContain "unknown section type" result
genPD <- readPackageDescription silent pdFile genPD <- readPackageDescription silent pdFile
......
...@@ -9,7 +9,11 @@ import Test.HUnit ...@@ -9,7 +9,11 @@ import Test.HUnit
suite :: Version -> FilePath -> Test suite :: Version -> FilePath -> Test
suite cabalVersion ghcPath = TestCase $ do suite cabalVersion ghcPath = TestCase $ do
let spec = PackageSpec ("PackageTests" </> "BuildDeps" </> "InternalLibrary0") [] let spec = PackageSpec
{ directory = "PackageTests" </> "BuildDeps" </> "InternalLibrary0"
, configOpts = []
, distPref = Nothing
}
result <- cabal_build spec ghcPath result <- cabal_build spec ghcPath
assertBuildFailed result assertBuildFailed result
when (cabalVersion >= Version [1, 7] []) $ do when (cabalVersion >= Version [1, 7] []) $ do
......
...@@ -7,6 +7,10 @@ import Test.HUnit ...@@ -7,6 +7,10 @@ import Test.HUnit
suite :: FilePath -> Test suite :: FilePath -> Test
suite ghcPath = TestCase $ do suite ghcPath = TestCase $ do
let spec = PackageSpec ("PackageTests" </> "BuildDeps" </> "InternalLibrary1") [] let spec = PackageSpec
{ directory = "PackageTests" </> "BuildDeps" </> "InternalLibrary1"
, configOpts = []
, distPref = Nothing
}
result <- cabal_build spec ghcPath result <- cabal_build spec ghcPath
assertBuildSucceeded result assertBuildSucceeded result
...@@ -8,8 +8,16 @@ import Test.HUnit ...@@ -8,8 +8,16 @@ import Test.HUnit
suite :: FilePath -> FilePath -> Test suite :: FilePath -> FilePath -> Test
suite ghcPath ghcPkgPath = TestCase $ do suite ghcPath ghcPkgPath = TestCase $ do
let spec = PackageSpec ("PackageTests" </> "BuildDeps" </> "InternalLibrary2") [] let spec = PackageSpec
let specTI = PackageSpec (directory spec </> "to-install") [] { directory = "PackageTests" </> "BuildDeps" </> "InternalLibrary2"
, configOpts = []
, distPref = Nothing
}
let specTI = PackageSpec
{ directory = directory spec </> "to-install"
, configOpts = []
, distPref = Nothing
}
unregister "InternalLibrary2" ghcPkgPath unregister "InternalLibrary2" ghcPkgPath
iResult <- cabal_install specTI ghcPath iResult <- cabal_install specTI ghcPath
......
...@@ -8,8 +8,16 @@ import Test.HUnit ...@@ -8,8 +8,16 @@ import Test.HUnit
suite :: FilePath -> FilePath -> Test suite :: FilePath -> FilePath -> Test
suite ghcPath ghcPkgPath = TestCase $ do suite ghcPath ghcPkgPath = TestCase $ do
let spec = PackageSpec ("PackageTests" </> "BuildDeps" </> "InternalLibrary3") [] let spec = PackageSpec
let specTI = PackageSpec (directory spec </> "to-install") [] { directory = "PackageTests" </> "BuildDeps" </> "InternalLibrary3"
, configOpts = []
, distPref = Nothing
}
let specTI = PackageSpec
{ directory = directory spec </> "to-install"
, configOpts = []
, distPref = Nothing
}
unregister "InternalLibrary3" ghcPkgPath unregister "InternalLibrary3" ghcPkgPath
iResult <- cabal_install specTI ghcPath iResult <- cabal_install specTI ghcPath
......
...@@ -8,8 +8,16 @@ import Test.HUnit ...@@ -8,8 +8,16 @@ import Test.HUnit
suite :: FilePath -> FilePath -> Test suite :: FilePath -> FilePath -> Test
suite ghcPath ghcPkgPath = TestCase $ do suite ghcPath ghcPkgPath = TestCase $ do
let spec = PackageSpec ("PackageTests" </> "BuildDeps" </> "InternalLibrary4") [] let spec = PackageSpec
let specTI = PackageSpec (directory spec </> "to-install") [] { directory = "PackageTests" </> "BuildDeps" </> "InternalLibrary4"
, configOpts = []
, distPref = Nothing
}
let specTI = PackageSpec
{ directory = directory spec </> "to-install"
, configOpts = []
, distPref = Nothing
}
unregister "InternalLibrary4" ghcPkgPath unregister "InternalLibrary4" ghcPkgPath
iResult <- cabal_install specTI ghcPath iResult <- cabal_install specTI ghcPath
......
...@@ -8,7 +8,11 @@ import qualified Control.Exception as E ...@@ -8,7 +8,11 @@ import qualified Control.Exception as E
suite :: FilePath -> Test suite :: FilePath -> Test
suite ghcPath = TestCase $ do suite ghcPath = TestCase $ do
let spec = PackageSpec ("PackageTests" </> "BuildDeps" </> "SameDepsAllRound") [] let spec = PackageSpec
{ directory = "PackageTests" </> "BuildDeps" </> "SameDepsAllRound"
, configOpts = []
, distPref = Nothing
}
result <- cabal_build spec ghcPath result <- cabal_build spec ghcPath
do do
assertEqual "cabal build should succeed - see test-log.txt" True (successful result) assertEqual "cabal build should succeed - see test-log.txt" True (successful result)
......
...@@ -10,7 +10,11 @@ import Text.Regex.Posix ...@@ -10,7 +10,11 @@ import Text.Regex.Posix
suite :: FilePath -> Test suite :: FilePath -> Test
suite ghcPath = TestCase $ do suite ghcPath = TestCase $ do
let spec = PackageSpec ("PackageTests" </> "BuildDeps" </> "TargetSpecificDeps1") [] let spec = PackageSpec
{ directory = "PackageTests" </> "BuildDeps" </> "TargetSpecificDeps1"
, configOpts = []
, distPref = Nothing
}
result <- cabal_build spec ghcPath result <- cabal_build spec ghcPath
do do
assertEqual "cabal build should fail - see test-log.txt" False (successful result) assertEqual "cabal build should fail - see test-log.txt" False (successful result)
......
...@@ -8,7 +8,11 @@ import qualified Control.Exception as E ...@@ -8,7 +8,11 @@ import qualified Control.Exception as E
suite :: FilePath -> Test suite :: FilePath -> Test
suite ghcPath = TestCase $ do suite ghcPath = TestCase $ do
let spec = PackageSpec ("PackageTests" </> "BuildDeps" </> "TargetSpecificDeps2") [] let spec = PackageSpec
{ directory = "PackageTests" </> "BuildDeps" </> "TargetSpecificDeps2"
, configOpts = []
, distPref = Nothing
}
result <- cabal_build spec ghcPath result <- cabal_build spec ghcPath
do do
assertEqual "cabal build should succeed - see test-log.txt" True (successful result) assertEqual "cabal build should succeed - see test-log.txt" True (successful result)
......
...@@ -10,7 +10,11 @@ import Text.Regex.Posix ...@@ -10,7 +10,11 @@ import Text.Regex.Posix
suite :: FilePath -> Test suite :: FilePath -> Test
suite ghcPath = TestCase $ do suite ghcPath = TestCase $ do
let spec = PackageSpec ("PackageTests" </> "BuildDeps" </> "TargetSpecificDeps3") [] let spec = PackageSpec
{ directory = "PackageTests" </> "BuildDeps" </> "TargetSpecificDeps3"
, configOpts = []
, distPref = Nothing
}
result <- cabal_build spec ghcPath result <- cabal_build spec ghcPath
do do
assertEqual "cabal build should fail - see test-log.txt" False (successful result) assertEqual "cabal build should fail - see test-log.txt" False (successful result)
......
...@@ -11,6 +11,10 @@ dir = "PackageTests" </> "CMain" ...@@ -11,6 +11,10 @@ dir = "PackageTests" </> "CMain"
checkBuild :: FilePath -> Test checkBuild :: FilePath -> Test
checkBuild ghcPath = TestCase $ do checkBuild ghcPath = TestCase $ do
let spec = PackageSpec dir [] let spec = PackageSpec
{ directory = dir
, distPref = Nothing
, configOpts = []
}
buildResult <- cabal_build spec ghcPath buildResult <- cabal_build spec ghcPath
assertBuildSucceeded buildResult assertBuildSucceeded buildResult
...@@ -51,7 +51,11 @@ this = "DeterministicAr" ...@@ -51,7 +51,11 @@ this = "DeterministicAr"
suite :: FilePath -> FilePath -> Test suite :: FilePath -> FilePath -> Test
suite ghcPath ghcPkgPath = TestCase $ do suite ghcPath ghcPkgPath = TestCase $ do
let dir = "PackageTests" </> this let dir = "PackageTests" </> this
let spec = PackageSpec dir [] let spec = PackageSpec
{ directory = dir
, configOpts = []
, distPref = Nothing
}
unregister this ghcPkgPath unregister this ghcPkgPath
iResult <- cabal_install spec ghcPath iResult <- cabal_install spec ghcPath
......
...@@ -7,7 +7,10 @@ import Test.HUnit ...@@ -7,7 +7,10 @@ import Test.HUnit
-- See https://github.com/haskell/cabal/issues/1241 -- See https://github.com/haskell/cabal/issues/1241
emptyLib :: FilePath -> Test emptyLib :: FilePath -> Test
emptyLib ghcPath = TestCase $ do emptyLib ghcPath = TestCase $ do
let spec = PackageSpec ("PackageTests" </> "EmptyLib" let spec = PackageSpec
</> "empty") [] { directory = "PackageTests" </> "EmptyLib" </> "empty"
, configOpts = []
, distPref = Nothing
}
result <- cabal_build spec ghcPath result <- cabal_build spec ghcPath
assertBuildSucceeded result assertBuildSucceeded result
...@@ -18,7 +18,11 @@ suite :: FilePath -> Test ...@@ -18,7 +18,11 @@ suite :: FilePath -> Test
suite ghcPath = TestCase $ do suite ghcPath = TestCase $ do
let dir = "PackageTests" </> this let dir = "PackageTests" </> this
haddocksDir = dir </> "dist" </> "doc" </> "html" </> "Haddock" haddocksDir = dir </> "dist" </> "doc" </> "html" </> "Haddock"
spec = PackageSpec dir [] spec = PackageSpec
{ directory = dir
, configOpts = []
, distPref = Nothing
}
haddocksDirExists <- doesDirectoryExist haddocksDir haddocksDirExists <- doesDirectoryExist haddocksDir
when haddocksDirExists (removeDirectoryRecursive haddocksDir) when haddocksDirExists (removeDirectoryRecursive haddocksDir)
......
...@@ -11,7 +11,11 @@ import Prelude hiding (catch) ...@@ -11,7 +11,11 @@ import Prelude hiding (catch)
suite :: FilePath -> Test suite :: FilePath -> Test
suite ghcPath = TestCase $ do suite ghcPath = TestCase $ do
let spec = PackageSpec ("PackageTests" </> "OrderFlags") [] let spec = PackageSpec
{ directory = "PackageTests" </> "OrderFlags"
, configOpts = []
, distPref = Nothing
}
result <- cabal_build spec ghcPath result <- cabal_build spec ghcPath
do do
assertEqual "cabal build should succeed - see test-log.txt" True (successful result) assertEqual "cabal build should succeed - see test-log.txt" True (successful result)
......
...@@ -51,6 +51,7 @@ import Distribution.Verbosity (Verbosity, flagToVerbosity, normal) ...@@ -51,6 +51,7 @@ import Distribution.Verbosity (Verbosity, flagToVerbosity, normal)
data PackageSpec = PackageSpec data PackageSpec = PackageSpec
{ directory :: FilePath { directory :: FilePath
, distPref :: Maybe FilePath
, configOpts :: [String] , configOpts :: [String]
} }
...@@ -180,7 +181,10 @@ compileSetup packageDir ghcPath = do ...@@ -180,7 +181,10 @@ compileSetup packageDir ghcPath = do
-- | Returns the command that was issued, the return code, and the output text. -- | 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 :: PackageSpec -> [(String, Maybe String)] -> [String] -> FilePath -> IO (String, ExitCode, String)
cabal spec envOverrides cabalArgs ghcPath = do cabal spec envOverrides cabalArgs_ ghcPath = do
let cabalArgs = case distPref spec of
Nothing -> cabalArgs_
Just dist -> ("--builddir=" ++ dist) : cabalArgs_
customSetup <- doesFileExist (directory spec </> "Setup.hs") customSetup <- doesFileExist (directory spec </> "Setup.hs")
if customSetup if customSetup
then do then do
......
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