module Distribution.Simple.Test
( test
, runTests
, writeSimpleTestStub
, stubFilePath
, stubName
, PackageLog(..)
, TestSuiteLog(..)
, Case(..)
, suitePassed, suiteFailed, suiteError
) where
import Distribution.Compat.TempFile ( openTempFile )
import Distribution.ModuleName ( ModuleName )
import Distribution.Package
( PackageId )
import qualified Distribution.PackageDescription as PD
( PackageDescription(..), BuildInfo(buildable)
, TestSuite(..)
, TestSuiteInterface(..), testType, hasTests )
import Distribution.Simple.Build.PathsModule ( pkgPathEnvVar )
import Distribution.Simple.BuildPaths ( exeExtension )
import Distribution.Simple.Compiler ( Compiler(..), CompilerId )
import Distribution.Simple.Hpc
( markupPackage, markupTest, tixDir, tixFilePath )
import Distribution.Simple.InstallDirs
( fromPathTemplate, initialPathTemplateEnv, PathTemplateVariable(..)
, substPathTemplate , toPathTemplate, PathTemplate )
import qualified Distribution.Simple.LocalBuildInfo as LBI
( LocalBuildInfo(..) )
import Distribution.Simple.Setup ( TestFlags(..), TestShowDetails(..), fromFlag )
import Distribution.Simple.Utils ( die, notice )
import qualified Distribution.TestSuite as TestSuite
( Test, Result(..), ImpureTestable(..), TestOptions(..), Options(..) )
import Distribution.Text
import Distribution.Verbosity ( normal, Verbosity )
import Distribution.System ( buildPlatform, Platform )
import Control.Exception ( bracket )
import Control.Monad ( when, liftM, unless, filterM )
import Data.Char ( toUpper )
import Data.Monoid ( mempty )
import System.Directory
( createDirectoryIfMissing, doesDirectoryExist, doesFileExist
, getCurrentDirectory, getDirectoryContents, removeDirectoryRecursive
, removeFile )
import System.Environment ( getEnvironment )
import System.Exit ( ExitCode(..), exitFailure, exitWith )
import System.FilePath ( (</>), (<.>) )
import System.IO ( hClose, IOMode(..), openFile )
import System.Process ( runProcess, waitForProcess )
data PackageLog = PackageLog
{ package :: PackageId
, compiler :: CompilerId
, platform :: Platform
, testSuites :: [TestSuiteLog]
}
deriving (Read, Show, Eq)
localPackageLog :: PD.PackageDescription -> LBI.LocalBuildInfo -> PackageLog
localPackageLog pkg_descr lbi = PackageLog
{ package = PD.package pkg_descr
, compiler = compilerId $ LBI.compiler lbi
, platform = buildPlatform
, testSuites = []
}
data TestSuiteLog = TestSuiteLog
{ name :: String
, cases :: [Case]
, logFile :: FilePath
}
deriving (Read, Show, Eq)
data Case = Case
{ caseName :: String
, caseOptions :: TestSuite.Options
, caseResult :: TestSuite.Result
}
deriving (Read, Show, Eq)
getTestOptions :: TestSuite.Test -> TestSuiteLog -> IO TestSuite.Options
getTestOptions t l =
case filter ((== TestSuite.name t) . caseName) (cases l) of
(x:_) -> return $ caseOptions x
_ -> TestSuite.defaultOptions t
suitePassed :: TestSuiteLog -> Bool
suitePassed = all (== TestSuite.Pass) . map caseResult . cases
suiteFailed :: TestSuiteLog -> Bool
suiteFailed = any isFail . map caseResult . cases
where isFail (TestSuite.Fail _) = True
isFail _ = False
suiteError :: TestSuiteLog -> Bool
suiteError = any isError . map caseResult . cases
where isError (TestSuite.Error _) = True
isError _ = False
testController :: TestFlags
-> PD.PackageDescription
-> LBI.LocalBuildInfo
-> PD.TestSuite
-> (FilePath -> String)
-> FilePath
-> (ExitCode -> String -> TestSuiteLog)
-> (TestSuiteLog -> FilePath)
-> IO TestSuiteLog
testController flags pkg_descr lbi suite preTest cmd postTest logNamer = do
let distPref = fromFlag $ testDistPref flags
verbosity = fromFlag $ testVerbosity flags
testLogDir = distPref </> "test"
options = map (testOption pkg_descr lbi suite) $ testOptions flags
pwd <- getCurrentDirectory
existingEnv <- getEnvironment
let dataDirPath = pwd </> PD.dataDir pkg_descr
shellEnv = Just $ (pkgPathEnvVar pkg_descr "datadir", dataDirPath)
: ("HPCTIXFILE", (</>) pwd
$ tixFilePath distPref $ PD.testName suite)
: existingEnv
bracket (openCabalTemp testLogDir) deleteIfExists $ \tempLog ->
bracket (openCabalTemp testLogDir) deleteIfExists $ \tempInput -> do
exists <- doesFileExist cmd
unless exists $ die $ "Error: Could not find test program \"" ++ cmd
++ "\". Did you build the package first?"
unless (fromFlag $ testKeepTix flags) $ do
let tDir = tixDir distPref $ PD.testName suite
exists <- doesDirectoryExist tDir
when exists $ removeDirectoryRecursive tDir
createDirectoryIfMissing True $ tixDir distPref $ PD.testName suite
notice verbosity $ summarizeSuiteStart $ PD.testName suite
appendFile tempInput $ preTest tempInput
exit <- do
hLog <- openFile tempLog AppendMode
hIn <- openFile tempInput ReadMode
proc <- runProcess cmd options Nothing shellEnv
(Just hIn) (Just hLog) (Just hLog)
waitForProcess proc
suiteLog <- fmap (postTest exit $!) $ readFile tempInput
let finalLogName = testLogDir </> logNamer suiteLog
suiteLog' = suiteLog { logFile = finalLogName }
appendFile (logFile suiteLog') $ summarizeSuiteStart $ PD.testName suite
readFile tempLog >>= appendFile (logFile suiteLog')
appendFile (logFile suiteLog') $ summarizeSuiteFinish suiteLog'
let details = fromFlag $ testShowDetails flags
whenPrinting = when $ (details > Never)
&& (not (suitePassed suiteLog) || details == Always)
&& verbosity >= normal
whenPrinting $ readFile tempLog >>=
putStr . unlines . lines
notice verbosity $ summarizeSuiteFinish suiteLog'
markupTest verbosity lbi distPref
(display $ PD.package pkg_descr) suite
return suiteLog'
where
deleteIfExists file = do
exists <- doesFileExist file
when exists $ removeFile file
openCabalTemp testLogDir = do
(f, h) <- openTempFile testLogDir $ "cabal-test-" <.> "log"
hClose h >> return f
test :: PD.PackageDescription
-> LBI.LocalBuildInfo
-> TestFlags
-> IO ()
test pkg_descr lbi flags = do
let verbosity = fromFlag $ testVerbosity flags
humanTemplate = fromFlag $ testHumanLog flags
machineTemplate = fromFlag $ testMachineLog flags
distPref = fromFlag $ testDistPref flags
testLogDir = distPref </> "test"
testNames = fromFlag $ testList flags
pkgTests = PD.testSuites pkg_descr
enabledTests = [ t | t <- pkgTests
, PD.testEnabled t
, PD.buildable (PD.testBuildInfo t) ]
doTest :: (PD.TestSuite, Maybe TestSuiteLog) -> IO TestSuiteLog
doTest (suite, mLog) = do
let testLogPath = testSuiteLogPath humanTemplate pkg_descr lbi
go pre cmd post = testController flags pkg_descr lbi suite
pre cmd post testLogPath
case PD.testInterface suite of
PD.TestSuiteExeV10 _ _ -> do
let cmd = LBI.buildDir lbi </> PD.testName suite
</> PD.testName suite <.> exeExtension
preTest _ = ""
postTest exit _ =
let r = case exit of
ExitSuccess -> TestSuite.Pass
ExitFailure c -> TestSuite.Fail
$ "exit code: " ++ show c
in TestSuiteLog
{ name = PD.testName suite
, cases = [Case (PD.testName suite) mempty r]
, logFile = ""
}
go preTest cmd postTest
PD.TestSuiteLibV09 _ _ -> do
let cmd = LBI.buildDir lbi </> stubName suite
</> stubName suite <.> exeExtension
oldLog = case mLog of
Nothing -> TestSuiteLog
{ name = PD.testName suite
, cases = []
, logFile = []
}
Just l -> l
preTest f = show $ oldLog { logFile = f }
postTest _ = read
go preTest cmd postTest
_ -> return TestSuiteLog
{ name = PD.testName suite
, cases = [Case (PD.testName suite) mempty
$ TestSuite.Error $ "No support for running "
++ "test suite type: "
++ show (disp $ PD.testType suite)]
, logFile = ""
}
when (not $ PD.hasTests pkg_descr) $ do
notice verbosity "Package has no test suites."
exitWith ExitSuccess
when (PD.hasTests pkg_descr && null enabledTests) $
die $ "No test suites enabled. Did you remember to configure with "
++ "\'--enable-tests\'?"
testsToRun <- case testNames of
[] -> return $ zip enabledTests $ repeat Nothing
names -> flip mapM names $ \tName ->
let testMap = zip enabledNames enabledTests
enabledNames = map PD.testName enabledTests
allNames = map PD.testName pkgTests
in case lookup tName testMap of
Just t -> return (t, Nothing)
_ | tName `elem` allNames ->
die $ "Package configured with test suite "
++ tName ++ " disabled."
| otherwise -> die $ "no such test: " ++ tName
createDirectoryIfMissing True testLogDir
getDirectoryContents testLogDir
>>= filterM doesFileExist . map (testLogDir </>)
>>= mapM_ removeFile
let totalSuites = length testsToRun
notice verbosity $ "Running " ++ show totalSuites ++ " test suites..."
suites <- mapM doTest testsToRun
let packageLog = (localPackageLog pkg_descr lbi) { testSuites = suites }
packageLogFile = (</>) testLogDir
$ packageLogPath machineTemplate pkg_descr lbi
allOk <- summarizePackage verbosity packageLog
writeFile packageLogFile $ show packageLog
markupPackage verbosity lbi distPref (display $ PD.package pkg_descr)
$ map fst testsToRun
unless allOk exitFailure
summarizePackage :: Verbosity -> PackageLog -> IO Bool
summarizePackage verbosity packageLog = do
let cases' = map caseResult $ concatMap cases $ testSuites packageLog
passedCases = length $ filter (== TestSuite.Pass) cases'
totalCases = length cases'
passedSuites = length $ filter suitePassed $ testSuites packageLog
totalSuites = length $ testSuites packageLog
notice verbosity $ show passedSuites ++ " of " ++ show totalSuites
++ " test suites (" ++ show passedCases ++ " of "
++ show totalCases ++ " test cases) passed."
return $! passedSuites == totalSuites
summarizeCase :: Verbosity -> TestShowDetails -> Case -> IO ()
summarizeCase verbosity details t =
when shouldPrint $ notice verbosity $ "Test case " ++ caseName t
++ ": " ++ show (caseResult t)
where shouldPrint = (details > Never) && (notPassed || details == Always)
notPassed = caseResult t /= TestSuite.Pass
summarizeSuiteFinish :: TestSuiteLog -> String
summarizeSuiteFinish testLog = unlines
[ "Test suite " ++ name testLog ++ ": " ++ resStr
, "Test suite logged to: " ++ logFile testLog
]
where resStr = map toUpper (resultString testLog)
summarizeSuiteStart :: String -> String
summarizeSuiteStart n = "Test suite " ++ n ++ ": RUNNING...\n"
resultString :: TestSuiteLog -> String
resultString l | suiteError l = "error"
| suiteFailed l = "fail"
| otherwise = "pass"
testSuiteLogPath :: PathTemplate
-> PD.PackageDescription
-> LBI.LocalBuildInfo
-> TestSuiteLog
-> FilePath
testSuiteLogPath template pkg_descr lbi testLog =
fromPathTemplate $ substPathTemplate env template
where
env = initialPathTemplateEnv
(PD.package pkg_descr) (compilerId $ LBI.compiler lbi)
++ [ (TestSuiteNameVar, toPathTemplate $ name testLog)
, (TestSuiteResultVar, result)
]
result = toPathTemplate $ resultString testLog
testOption :: PD.PackageDescription
-> LBI.LocalBuildInfo
-> PD.TestSuite
-> PathTemplate
-> String
testOption pkg_descr lbi suite template =
fromPathTemplate $ substPathTemplate env template
where
env = initialPathTemplateEnv
(PD.package pkg_descr) (compilerId $ LBI.compiler lbi) ++
[(TestSuiteNameVar, toPathTemplate $ PD.testName suite)]
packageLogPath :: PathTemplate
-> PD.PackageDescription
-> LBI.LocalBuildInfo
-> FilePath
packageLogPath template pkg_descr lbi =
fromPathTemplate $ substPathTemplate env template
where
env = initialPathTemplateEnv
(PD.package pkg_descr) (compilerId $ LBI.compiler lbi)
stubFilePath :: PD.TestSuite -> FilePath
stubFilePath t = stubName t <.> "hs"
stubName :: PD.TestSuite -> FilePath
stubName t = PD.testName t ++ "Stub"
writeSimpleTestStub :: PD.TestSuite
-> FilePath
-> IO ()
writeSimpleTestStub t dir = do
createDirectoryIfMissing True dir
let filename = dir </> stubFilePath t
PD.TestSuiteLibV09 _ m = PD.testInterface t
writeFile filename $ simpleTestStub m
simpleTestStub :: ModuleName -> String
simpleTestStub m = unlines
[ "module Main ( main ) where"
, "import Control.Monad ( liftM )"
, "import Distribution.Simple.Test ( runTests )"
, "import " ++ show (disp m) ++ " ( tests )"
, "main :: IO ()"
, "main = runTests tests"
]
runTests :: [TestSuite.Test] -> IO ()
runTests tests = do
testLogIn <- liftM read getContents
let go :: TestSuite.Test -> IO Case
go t = do
o <- getTestOptions t testLogIn
r <- TestSuite.runM t o
let ret = Case
{ caseName = TestSuite.name t
, caseOptions = o
, caseResult = r
}
summarizeCase normal Always ret
return ret
cases' <- mapM go tests
let testLog = testLogIn { cases = cases'}
writeFile (logFile testLog) $ show testLog
when (suiteError testLog) $ exitWith $ ExitFailure 2
when (suiteFailed testLog) $ exitWith $ ExitFailure 1
exitWith ExitSuccess