Pass the buildDir as first argument to test suite.

Allows test suite to work with cabal sandboxes.
Previously we hard-coded the build directory.
This commit is contained in:
John MacFarlane 2013-10-20 12:36:26 -07:00
parent 1ce875a010
commit 9d6bca06ee
3 changed files with 18 additions and 7 deletions

View file

@ -3,13 +3,15 @@
import Distribution.Simple import Distribution.Simple
import Distribution.Simple.PreProcess import Distribution.Simple.PreProcess
import Distribution.Simple.Setup import Distribution.Simple.Setup
(copyDest, copyVerbosity, fromFlag, installVerbosity, BuildFlags(..)) (copyDest, copyVerbosity, fromFlag, installVerbosity, BuildFlags(..),
TestFlags(..))
import Distribution.PackageDescription (PackageDescription(..), Executable(..)) import Distribution.PackageDescription (PackageDescription(..), Executable(..))
import Distribution.Simple.LocalBuildInfo import Distribution.Simple.LocalBuildInfo
(LocalBuildInfo(..), absoluteInstallDirs) (LocalBuildInfo(..), absoluteInstallDirs)
import Distribution.Verbosity ( Verbosity, silent ) import Distribution.Verbosity ( Verbosity, silent )
import Distribution.Simple.InstallDirs (mandir, CopyDest (NoCopyDest)) import Distribution.Simple.InstallDirs (mandir, CopyDest (NoCopyDest), toPathTemplate)
import Distribution.Simple.Utils (installOrdinaryFiles, info) import Distribution.Simple.Utils (installOrdinaryFiles, info)
import Distribution.Simple.Test (test)
import Prelude hiding (catch) import Prelude hiding (catch)
import System.Process ( rawSystem ) import System.Process ( rawSystem )
import System.FilePath ( (</>) ) import System.FilePath ( (</>) )
@ -20,6 +22,10 @@ main :: IO ()
main = do main = do
defaultMainWithHooks $ simpleUserHooks { defaultMainWithHooks $ simpleUserHooks {
postBuild = makeManPages postBuild = makeManPages
, testHook = \pkg lbi _ flags ->
-- pass build directory as first argument to test program
test pkg lbi flags{ testOptions =
toPathTemplate (buildDir lbi) : testOptions flags }
, postCopy = \ _ flags pkg lbi -> , postCopy = \ _ flags pkg lbi ->
installManpages pkg lbi (fromFlag $ copyVerbosity flags) installManpages pkg lbi (fromFlag $ copyVerbosity flags)
(fromFlag $ copyDest flags) (fromFlag $ copyDest flags)

View file

@ -3,7 +3,7 @@ module Tests.Old (tests) where
import Test.Framework (testGroup, Test ) import Test.Framework (testGroup, Test )
import Test.Framework.Providers.HUnit import Test.Framework.Providers.HUnit
import Test.HUnit ( assertBool ) import Test.HUnit ( assertBool )
import System.Environment ( getArgs )
import System.IO ( openTempFile, stderr ) import System.IO ( openTempFile, stderr )
import System.Process ( runProcess, waitForProcess ) import System.Process ( runProcess, waitForProcess )
import System.FilePath ( (</>), (<.>) ) import System.FilePath ( (</>), (<.>) )
@ -22,9 +22,6 @@ import Text.Printf
readFileUTF8 :: FilePath -> IO String readFileUTF8 :: FilePath -> IO String
readFileUTF8 f = B.readFile f >>= return . toStringLazy readFileUTF8 f = B.readFile f >>= return . toStringLazy
pandocPath :: FilePath
pandocPath = ".." </> "dist" </> "build" </> "pandoc" </> "pandoc"
data TestResult = TestPassed data TestResult = TestPassed
| TestError ExitCode | TestError ExitCode
| TestFailed String FilePath [Diff String] | TestFailed String FilePath [Diff String]
@ -209,6 +206,11 @@ testWithNormalize :: (String -> String) -- ^ Normalize function for output
-> FilePath -- ^ Norm (for test results) filepath -> FilePath -- ^ Norm (for test results) filepath
-> Test -> Test
testWithNormalize normalizer testname opts inp norm = testCase testname $ do testWithNormalize normalizer testname opts inp norm = testCase testname $ do
args <- getArgs
let buildDir = case args of
(x:_) -> ".." </> x
_ -> error "test-pandoc: missing buildDir argument"
let pandocPath = buildDir </> "pandoc" </> "pandoc"
(outputPath, hOut) <- openTempFile "" "pandoc-test" (outputPath, hOut) <- openTempFile "" "pandoc-test"
let inpPath = inp let inpPath = inp
let normPath = norm let normPath = norm

View file

@ -38,4 +38,7 @@ tests = [ testGroup "Old" Tests.Old.tests
main :: IO () main :: IO ()
main = do main = do
setLocaleEncoding utf8 setLocaleEncoding utf8
inDirectory "tests" $ defaultMain tests -- we ignore command-line arguments, since we're having cabal pass
-- the build directory as first argument, and we don't want test-framework
-- to choke on that.
inDirectory "tests" $ defaultMainWithArgs tests []