Skip to content
Snippets Groups Projects
Commit 3de2d9a4 authored by ttuegel's avatar ttuegel
Browse files

Fix BuildTestSuiteDetailedV09 on GHC <7.6

parent d5687127
No related merge requests found
...@@ -9,7 +9,8 @@ module Main where ...@@ -9,7 +9,8 @@ module Main where
import Data.Version (Version(Version)) import Data.Version (Version(Version))
import Distribution.Simple.Utils (cabalVersion) import Distribution.Simple.Utils (cabalVersion)
import Distribution.Text (display) import Distribution.Text (display)
import System.Directory (setCurrentDirectory) import System.Directory (getCurrentDirectory, setCurrentDirectory)
import System.FilePath ((</>))
import Test.Framework (Test, TestName, defaultMain, testGroup) import Test.Framework (Test, TestName, defaultMain, testGroup)
import Test.Framework.Providers.HUnit (hUnitTestToTests) import Test.Framework.Providers.HUnit (hUnitTestToTests)
import qualified Test.HUnit as HUnit import qualified Test.HUnit as HUnit
...@@ -29,7 +30,7 @@ import PackageTests.BuildDeps.TargetSpecificDeps1.Check ...@@ -29,7 +30,7 @@ import PackageTests.BuildDeps.TargetSpecificDeps1.Check
import PackageTests.BuildDeps.TargetSpecificDeps2.Check import PackageTests.BuildDeps.TargetSpecificDeps2.Check
import PackageTests.BuildDeps.TargetSpecificDeps3.Check import PackageTests.BuildDeps.TargetSpecificDeps3.Check
import PackageTests.BuildTestSuiteDetailedV09.Check import PackageTests.BuildTestSuiteDetailedV09.Check
import PackageTests.PackageTester (compileSetup) import PackageTests.PackageTester (PackageSpec(..), compileSetup)
import PackageTests.PathsModule.Executable.Check import PackageTests.PathsModule.Executable.Check
import PackageTests.PathsModule.Library.Check import PackageTests.PathsModule.Library.Check
import PackageTests.PreProcess.Check import PackageTests.PreProcess.Check
...@@ -43,8 +44,8 @@ import PackageTests.TestSuiteExeV10.Check ...@@ -43,8 +44,8 @@ import PackageTests.TestSuiteExeV10.Check
hunit :: TestName -> HUnit.Test -> Test hunit :: TestName -> HUnit.Test -> Test
hunit name test = testGroup name $ hUnitTestToTests test hunit name test = testGroup name $ hUnitTestToTests test
tests :: Version -> [Test] tests :: Version -> PackageSpec -> [Test]
tests version = tests version inplaceSpec =
[ hunit "BuildDeps/SameDepsAllRound" [ hunit "BuildDeps/SameDepsAllRound"
PackageTests.BuildDeps.SameDepsAllRound.Check.suite PackageTests.BuildDeps.SameDepsAllRound.Check.suite
-- The two following tests were disabled by Johan Tibell as -- The two following tests were disabled by Johan Tibell as
...@@ -79,7 +80,7 @@ tests version = ...@@ -79,7 +80,7 @@ tests version =
, hunit "EmptyLib/emptyLib" , hunit "EmptyLib/emptyLib"
PackageTests.EmptyLib.Check.emptyLib PackageTests.EmptyLib.Check.emptyLib
, hunit "BuildTestSuiteDetailedV09" , hunit "BuildTestSuiteDetailedV09"
PackageTests.BuildTestSuiteDetailedV09.Check.suite $ PackageTests.BuildTestSuiteDetailedV09.Check.suite inplaceSpec
] ++ ] ++
-- These tests are only required to pass on cabal version >= 1.7 -- These tests are only required to pass on cabal version >= 1.7
(if version >= Version [1, 7] [] (if version >= Version [1, 7] []
...@@ -104,9 +105,17 @@ tests version = ...@@ -104,9 +105,17 @@ tests version =
main :: IO () main :: IO ()
main = do main = do
wd <- getCurrentDirectory
let dbFile = wd </> "dist/package.conf.inplace"
inplaceSpec = PackageSpec
{ directory = []
, configOpts = [ "--package-db=" ++ dbFile
, "--constraint=Cabal == " ++ display cabalVersion
]
}
putStrLn $ "Cabal test suite - testing cabal version " ++ putStrLn $ "Cabal test suite - testing cabal version " ++
display cabalVersion display cabalVersion
setCurrentDirectory "tests" setCurrentDirectory "tests"
-- Create a shared Setup executable to speed up Simple tests -- Create a shared Setup executable to speed up Simple tests
compileSetup "." compileSetup "."
defaultMain (tests cabalVersion) defaultMain (tests cabalVersion inplaceSpec)
...@@ -5,10 +5,13 @@ import System.FilePath ((</>)) ...@@ -5,10 +5,13 @@ import System.FilePath ((</>))
import PackageTests.PackageTester import PackageTests.PackageTester
suite :: Test suite :: PackageSpec -> Test
suite = TestCase $ do suite inplaceSpec = TestCase $ do
let dir = "PackageTests" </> "BuildTestSuiteDetailedV09" let dir = "PackageTests" </> "BuildTestSuiteDetailedV09"
spec = PackageSpec dir ["--enable-tests"] spec = inplaceSpec
{ directory = dir
, configOpts = "--enable-tests" : configOpts inplaceSpec
}
confResult <- cabal_configure spec confResult <- cabal_configure spec
assertEqual "configure failed!" (successful confResult) True assertEqual "configure failed!" (successful confResult) True
buildResult <- cabal_build spec buildResult <- cabal_build spec
......
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