{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RankNTypes #-}
module Distribution.Simple.Test.LibV09
( runTest
, simpleTestStub
, stubFilePath
, stubMain
, stubName
, stubWriteLog
, writeSimpleTestStub
) where
import Distribution.Compat.Prelude
import Distribution.Types.UnqualComponentName
import Prelude ()
import Distribution.Compat.Environment
import Distribution.Compat.Internal.TempFile
import Distribution.ModuleName
import qualified Distribution.PackageDescription as PD
import Distribution.Pretty
import Distribution.Simple.Build.PathsModule
import Distribution.Simple.BuildPaths
import Distribution.Simple.Compiler
import Distribution.Simple.Flag (Flag (Flag, NoFlag), fromFlag)
import Distribution.Simple.Hpc
import Distribution.Simple.InstallDirs
import qualified Distribution.Simple.LocalBuildInfo as LBI
import Distribution.Simple.Setup.Test
import Distribution.Simple.Test.Log
import Distribution.Simple.Utils
import Distribution.System
import Distribution.TestSuite
import qualified Distribution.Types.LocalBuildInfo as LBI
import Distribution.Verbosity
import qualified Control.Exception as CE
import qualified Data.ByteString.Lazy as LBS
import Distribution.Compat.Process (proc)
import Distribution.Simple.Errors
import System.Directory
( canonicalizePath
, createDirectoryIfMissing
, doesDirectoryExist
, doesFileExist
, getCurrentDirectory
, removeDirectoryRecursive
, removeFile
, setCurrentDirectory
)
import System.FilePath ((<.>), (</>))
import System.IO (hClose, hPutStr)
import qualified System.Process as Process
runTest
:: PD.PackageDescription
-> LBI.LocalBuildInfo
-> LBI.ComponentLocalBuildInfo
-> HPCMarkupInfo
-> TestFlags
-> PD.TestSuite
-> IO TestSuiteLog
runTest :: PackageDescription
-> LocalBuildInfo
-> ComponentLocalBuildInfo
-> HPCMarkupInfo
-> TestFlags
-> TestSuite
-> IO TestSuiteLog
runTest PackageDescription
pkg_descr LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi HPCMarkupInfo
hpcMarkupInfo TestFlags
flags TestSuite
suite = do
let isCoverageEnabled :: Bool
isCoverageEnabled = LocalBuildInfo -> Bool
LBI.testCoverage LocalBuildInfo
lbi
way :: Way
way = LocalBuildInfo -> Way
guessWay LocalBuildInfo
lbi
pwd <- IO FilePath
getCurrentDirectory
existingEnv <- getEnvironment
let cmd =
LocalBuildInfo -> FilePath
LBI.buildDir LocalBuildInfo
lbi
FilePath -> FilePath -> FilePath
</> TestSuite -> FilePath
stubName TestSuite
suite
FilePath -> FilePath -> FilePath
</> TestSuite -> FilePath
stubName TestSuite
suite FilePath -> FilePath -> FilePath
<.> Platform -> FilePath
exeExtension (LocalBuildInfo -> Platform
LBI.hostPlatform LocalBuildInfo
lbi)
exists <- doesFileExist cmd
unless exists $
dieWithException verbosity $
Couldn'tFindTestProgLibV09 cmd
unless (fromFlag $ testKeepTix flags) $ do
let tDir = FilePath -> Way -> FilePath
tixDir FilePath
distPref Way
way
exists' <- doesDirectoryExist tDir
when exists' $ removeDirectoryRecursive tDir
createDirectoryIfMissing True $ tixDir distPref way
notice verbosity $ summarizeSuiteStart testName'
suiteLog <- CE.bracket openCabalTemp deleteIfExists $ \FilePath
tempLog -> do
let opts :: [FilePath]
opts = (PathTemplate -> FilePath) -> [PathTemplate] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map (PackageDescription
-> LocalBuildInfo -> TestSuite -> PathTemplate -> FilePath
testOption PackageDescription
pkg_descr LocalBuildInfo
lbi TestSuite
suite) ([PathTemplate] -> [FilePath]) -> [PathTemplate] -> [FilePath]
forall a b. (a -> b) -> a -> b
$ TestFlags -> [PathTemplate]
testOptions TestFlags
flags
dataDirPath :: FilePath
dataDirPath = FilePath
pwd FilePath -> FilePath -> FilePath
</> PackageDescription -> FilePath
PD.dataDir PackageDescription
pkg_descr
tixFile :: FilePath
tixFile = FilePath
pwd FilePath -> FilePath -> FilePath
</> FilePath -> Way -> FilePath -> FilePath
tixFilePath FilePath
distPref Way
way FilePath
testName'
pkgPathEnv :: [(FilePath, FilePath)]
pkgPathEnv =
(PackageDescription -> FilePath -> FilePath
pkgPathEnvVar PackageDescription
pkg_descr FilePath
"datadir", FilePath
dataDirPath)
(FilePath, FilePath)
-> [(FilePath, FilePath)] -> [(FilePath, FilePath)]
forall a. a -> [a] -> [a]
: [(FilePath, FilePath)]
existingEnv
shellEnv :: [(FilePath, FilePath)]
shellEnv =
[(FilePath
"HPCTIXFILE", FilePath
tixFile) | Bool
isCoverageEnabled]
[(FilePath, FilePath)]
-> [(FilePath, FilePath)] -> [(FilePath, FilePath)]
forall a. [a] -> [a] -> [a]
++ [(FilePath, FilePath)]
pkgPathEnv
shellEnv' <-
if LocalBuildInfo -> Bool
LBI.withDynExe LocalBuildInfo
lbi
then do
let (Platform Arch
_ OS
os) = LocalBuildInfo -> Platform
LBI.hostPlatform LocalBuildInfo
lbi
paths <- Bool
-> Bool
-> LocalBuildInfo
-> ComponentLocalBuildInfo
-> IO [FilePath]
LBI.depLibraryPaths Bool
True Bool
False LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi
cpath <- canonicalizePath $ LBI.componentBuildDir lbi clbi
return (addLibraryPath os (cpath : paths) shellEnv)
else [(FilePath, FilePath)] -> IO [(FilePath, FilePath)]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [(FilePath, FilePath)]
shellEnv
let (cmd', opts') = case testWrapper flags of
Flag FilePath
path -> (FilePath
path, FilePath
cmd FilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
: [FilePath]
opts)
Flag FilePath
NoFlag -> (FilePath
cmd, [FilePath]
opts)
(rOut, wOut) <- Process.createPipe
(exitcode, logText) <- rawSystemProcAction
verbosity
(proc cmd' opts')
{ Process.env = Just shellEnv'
, Process.std_in = Process.CreatePipe
, Process.std_out = Process.UseHandle wOut
, Process.std_err = Process.UseHandle wOut
}
$ \Maybe Handle
mIn Maybe Handle
_ Maybe Handle
_ -> do
let wIn :: Handle
wIn = Maybe Handle -> Handle
fromCreatePipe Maybe Handle
mIn
Handle -> FilePath -> IO ()
hPutStr Handle
wIn (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ (FilePath, UnqualComponentName) -> FilePath
forall a. Show a => a -> FilePath
show (FilePath
tempLog, TestSuite -> UnqualComponentName
PD.testName TestSuite
suite)
Handle -> IO ()
hClose Handle
wIn
logText <- Handle -> IO ByteString
LBS.hGetContents Handle
rOut
_ <- evaluate (force logText)
return logText
unless (exitcode == ExitSuccess) $
debug verbosity $
cmd ++ " returned " ++ show exitcode
let finalLogName TestSuiteLog
l =
FilePath
testLogDir
FilePath -> FilePath -> FilePath
</> PathTemplate
-> PackageDescription
-> LocalBuildInfo
-> FilePath
-> TestLogs
-> FilePath
testSuiteLogPath
(Flag PathTemplate -> PathTemplate
forall a. WithCallStack (Flag a -> a)
fromFlag (Flag PathTemplate -> PathTemplate)
-> Flag PathTemplate -> PathTemplate
forall a b. (a -> b) -> a -> b
$ TestFlags -> Flag PathTemplate
testHumanLog TestFlags
flags)
PackageDescription
pkg_descr
LocalBuildInfo
lbi
(UnqualComponentName -> FilePath
unUnqualComponentName (UnqualComponentName -> FilePath)
-> UnqualComponentName -> FilePath
forall a b. (a -> b) -> a -> b
$ TestSuiteLog -> UnqualComponentName
testSuiteName TestSuiteLog
l)
(TestSuiteLog -> TestLogs
testLogs TestSuiteLog
l)
suiteLog <-
fmap
( \FilePath
s ->
(\TestSuiteLog
l -> TestSuiteLog
l{logFile = finalLogName l})
(TestSuiteLog -> TestSuiteLog)
-> (Maybe TestSuiteLog -> TestSuiteLog)
-> Maybe TestSuiteLog
-> TestSuiteLog
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TestSuiteLog -> Maybe TestSuiteLog -> TestSuiteLog
forall a. a -> Maybe a -> a
fromMaybe (FilePath -> TestSuiteLog
forall a. HasCallStack => FilePath -> a
error (FilePath -> TestSuiteLog) -> FilePath -> TestSuiteLog
forall a b. (a -> b) -> a -> b
$ FilePath
"panic! read @TestSuiteLog " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath -> FilePath
forall a. Show a => a -> FilePath
show FilePath
s)
(Maybe TestSuiteLog -> TestSuiteLog)
-> Maybe TestSuiteLog -> TestSuiteLog
forall a b. (a -> b) -> a -> b
$ FilePath -> Maybe TestSuiteLog
forall a. Read a => FilePath -> Maybe a
readMaybe FilePath
s
)
$ readFile tempLog
appendFile (logFile suiteLog) $ summarizeSuiteStart testName'
LBS.appendFile (logFile suiteLog) logText
appendFile (logFile suiteLog) $ summarizeSuiteFinish suiteLog
let details = Flag TestShowDetails -> TestShowDetails
forall a. WithCallStack (Flag a -> a)
fromFlag (Flag TestShowDetails -> TestShowDetails)
-> Flag TestShowDetails -> TestShowDetails
forall a b. (a -> b) -> a -> b
$ TestFlags -> Flag TestShowDetails
testShowDetails TestFlags
flags
whenPrinting =
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> IO () -> IO ()) -> Bool -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
(TestShowDetails
details TestShowDetails -> TestShowDetails -> Bool
forall a. Ord a => a -> a -> Bool
> TestShowDetails
Never)
Bool -> Bool -> Bool
&& (Bool -> Bool
not (TestLogs -> Bool
suitePassed (TestLogs -> Bool) -> TestLogs -> Bool
forall a b. (a -> b) -> a -> b
$ TestSuiteLog -> TestLogs
testLogs TestSuiteLog
suiteLog) Bool -> Bool -> Bool
|| TestShowDetails
details TestShowDetails -> TestShowDetails -> Bool
forall a. Eq a => a -> a -> Bool
== TestShowDetails
Always)
Bool -> Bool -> Bool
&& Verbosity
verbosity Verbosity -> Verbosity -> Bool
forall a. Ord a => a -> a -> Bool
>= Verbosity
normal
whenPrinting $ do
LBS.putStr logText
putChar '\n'
return suiteLog
notice verbosity $ summarizeSuiteFinish suiteLog
when isCoverageEnabled $ do
when (null $ PD.allLibraries pkg_descr) $
dieWithException verbosity TestCoverageSupport
markupPackage verbosity hpcMarkupInfo lbi distPref pkg_descr [suite]
return suiteLog
where
testName' :: FilePath
testName' = UnqualComponentName -> FilePath
unUnqualComponentName (UnqualComponentName -> FilePath)
-> UnqualComponentName -> FilePath
forall a b. (a -> b) -> a -> b
$ TestSuite -> UnqualComponentName
PD.testName TestSuite
suite
deleteIfExists :: FilePath -> IO ()
deleteIfExists FilePath
file = do
exists <- FilePath -> IO Bool
doesFileExist FilePath
file
when exists $ removeFile file
testLogDir :: FilePath
testLogDir = FilePath
distPref FilePath -> FilePath -> FilePath
</> FilePath
"test"
openCabalTemp :: IO FilePath
openCabalTemp = do
(f, h) <- FilePath -> FilePath -> IO (FilePath, Handle)
openTempFile FilePath
testLogDir (FilePath -> IO (FilePath, Handle))
-> FilePath -> IO (FilePath, Handle)
forall a b. (a -> b) -> a -> b
$ FilePath
"cabal-test-" FilePath -> FilePath -> FilePath
<.> FilePath
"log"
hClose h >> return f
distPref :: FilePath
distPref = Flag FilePath -> FilePath
forall a. WithCallStack (Flag a -> a)
fromFlag (Flag FilePath -> FilePath) -> Flag FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$ TestFlags -> Flag FilePath
testDistPref TestFlags
flags
verbosity :: Verbosity
verbosity = Flag Verbosity -> Verbosity
forall a. WithCallStack (Flag a -> a)
fromFlag (Flag Verbosity -> Verbosity) -> Flag Verbosity -> Verbosity
forall a b. (a -> b) -> a -> b
$ TestFlags -> Flag Verbosity
testVerbosity TestFlags
flags
testOption
:: PD.PackageDescription
-> LBI.LocalBuildInfo
-> PD.TestSuite
-> PathTemplate
-> String
testOption :: PackageDescription
-> LocalBuildInfo -> TestSuite -> PathTemplate -> FilePath
testOption PackageDescription
pkg_descr LocalBuildInfo
lbi TestSuite
suite PathTemplate
template =
PathTemplate -> FilePath
fromPathTemplate (PathTemplate -> FilePath) -> PathTemplate -> FilePath
forall a b. (a -> b) -> a -> b
$ PathTemplateEnv -> PathTemplate -> PathTemplate
substPathTemplate PathTemplateEnv
env PathTemplate
template
where
env :: PathTemplateEnv
env =
PackageIdentifier
-> UnitId -> CompilerInfo -> Platform -> PathTemplateEnv
initialPathTemplateEnv
(PackageDescription -> PackageIdentifier
PD.package PackageDescription
pkg_descr)
(LocalBuildInfo -> UnitId
LBI.localUnitId LocalBuildInfo
lbi)
(Compiler -> CompilerInfo
compilerInfo (Compiler -> CompilerInfo) -> Compiler -> CompilerInfo
forall a b. (a -> b) -> a -> b
$ LocalBuildInfo -> Compiler
LBI.compiler LocalBuildInfo
lbi)
(LocalBuildInfo -> Platform
LBI.hostPlatform LocalBuildInfo
lbi)
PathTemplateEnv -> PathTemplateEnv -> PathTemplateEnv
forall a. [a] -> [a] -> [a]
++ [(PathTemplateVariable
TestSuiteNameVar, FilePath -> PathTemplate
toPathTemplate (FilePath -> PathTemplate) -> FilePath -> PathTemplate
forall a b. (a -> b) -> a -> b
$ UnqualComponentName -> FilePath
unUnqualComponentName (UnqualComponentName -> FilePath)
-> UnqualComponentName -> FilePath
forall a b. (a -> b) -> a -> b
$ TestSuite -> UnqualComponentName
PD.testName TestSuite
suite)]
stubName :: PD.TestSuite -> FilePath
stubName :: TestSuite -> FilePath
stubName TestSuite
t = UnqualComponentName -> FilePath
unUnqualComponentName (TestSuite -> UnqualComponentName
PD.testName TestSuite
t) FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"Stub"
stubFilePath :: PD.TestSuite -> FilePath
stubFilePath :: TestSuite -> FilePath
stubFilePath TestSuite
t = TestSuite -> FilePath
stubName TestSuite
t FilePath -> FilePath -> FilePath
<.> FilePath
"hs"
writeSimpleTestStub
:: PD.TestSuite
-> FilePath
-> IO ()
writeSimpleTestStub :: TestSuite -> FilePath -> IO ()
writeSimpleTestStub TestSuite
t FilePath
dir = do
Bool -> FilePath -> IO ()
createDirectoryIfMissing Bool
True FilePath
dir
let filename :: FilePath
filename = FilePath
dir FilePath -> FilePath -> FilePath
</> TestSuite -> FilePath
stubFilePath TestSuite
t
m :: ModuleName
m = case TestSuite -> TestSuiteInterface
PD.testInterface TestSuite
t of
PD.TestSuiteLibV09 Version
_ ModuleName
m' -> ModuleName
m'
TestSuiteInterface
_ -> FilePath -> ModuleName
forall a. HasCallStack => FilePath -> a
error FilePath
"writeSimpleTestStub: invalid TestSuite passed"
FilePath -> FilePath -> IO ()
writeFile FilePath
filename (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ ModuleName -> FilePath
simpleTestStub ModuleName
m
simpleTestStub :: ModuleName -> String
simpleTestStub :: ModuleName -> FilePath
simpleTestStub ModuleName
m =
[FilePath] -> FilePath
unlines
[ FilePath
"module Main ( main ) where"
, FilePath
"import Distribution.Simple.Test.LibV09 ( stubMain )"
, FilePath
"import " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Doc -> FilePath
forall a. Show a => a -> FilePath
show (ModuleName -> Doc
forall a. Pretty a => a -> Doc
pretty ModuleName
m) FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" ( tests )"
, FilePath
"main :: IO ()"
, FilePath
"main = stubMain tests"
]
stubMain :: IO [Test] -> IO ()
stubMain :: IO [Test] -> IO ()
stubMain IO [Test]
tests = do
(f, n) <- (FilePath -> (FilePath, UnqualComponentName))
-> IO FilePath -> IO (FilePath, UnqualComponentName)
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\FilePath
s -> (FilePath, UnqualComponentName)
-> Maybe (FilePath, UnqualComponentName)
-> (FilePath, UnqualComponentName)
forall a. a -> Maybe a -> a
fromMaybe (FilePath -> (FilePath, UnqualComponentName)
forall a. HasCallStack => FilePath -> a
error (FilePath -> (FilePath, UnqualComponentName))
-> FilePath -> (FilePath, UnqualComponentName)
forall a b. (a -> b) -> a -> b
$ FilePath
"panic! read " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath -> FilePath
forall a. Show a => a -> FilePath
show FilePath
s) (Maybe (FilePath, UnqualComponentName)
-> (FilePath, UnqualComponentName))
-> Maybe (FilePath, UnqualComponentName)
-> (FilePath, UnqualComponentName)
forall a b. (a -> b) -> a -> b
$ FilePath -> Maybe (FilePath, UnqualComponentName)
forall a. Read a => FilePath -> Maybe a
readMaybe FilePath
s) IO FilePath
getContents
dir <- getCurrentDirectory
results <- (tests >>= stubRunTests) `CE.catch` errHandler
setCurrentDirectory dir
stubWriteLog f n results
where
errHandler :: CE.SomeException -> IO TestLogs
errHandler :: SomeException -> IO TestLogs
errHandler SomeException
e = case SomeException -> Maybe AsyncException
forall e. Exception e => SomeException -> Maybe e
CE.fromException SomeException
e of
Just AsyncException
CE.UserInterrupt -> SomeException -> IO TestLogs
forall e a. (HasCallStack, Exception e) => e -> IO a
CE.throwIO SomeException
e
Maybe AsyncException
_ ->
TestLogs -> IO TestLogs
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (TestLogs -> IO TestLogs) -> TestLogs -> IO TestLogs
forall a b. (a -> b) -> a -> b
$
TestLog
{ testName :: FilePath
testName = FilePath
"Cabal test suite exception"
, testOptionsReturned :: [(FilePath, FilePath)]
testOptionsReturned = []
, testResult :: Result
testResult = FilePath -> Result
Error (FilePath -> Result) -> FilePath -> Result
forall a b. (a -> b) -> a -> b
$ SomeException -> FilePath
forall a. Show a => a -> FilePath
show SomeException
e
}
stubRunTests :: [Test] -> IO TestLogs
stubRunTests :: [Test] -> IO TestLogs
stubRunTests [Test]
tests = do
logs <- (Test -> IO TestLogs) -> [Test] -> IO [TestLogs]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse Test -> IO TestLogs
stubRunTests' [Test]
tests
return $ GroupLogs "Default" logs
where
stubRunTests' :: Test -> IO TestLogs
stubRunTests' (Test TestInstance
t) = do
l <- TestInstance -> IO Progress
run TestInstance
t IO Progress -> (Progress -> IO TestLogs) -> IO TestLogs
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Progress -> IO TestLogs
finish
summarizeTest normal Always l
return l
where
finish :: Progress -> IO TestLogs
finish (Finished Result
result) =
TestLogs -> IO TestLogs
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return
TestLog
{ testName :: FilePath
testName = TestInstance -> FilePath
name TestInstance
t
, testOptionsReturned :: [(FilePath, FilePath)]
testOptionsReturned = TestInstance -> [(FilePath, FilePath)]
defaultOptions TestInstance
t
, testResult :: Result
testResult = Result
result
}
finish (Progress FilePath
_ IO Progress
next) = IO Progress
next IO Progress -> (Progress -> IO TestLogs) -> IO TestLogs
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Progress -> IO TestLogs
finish
stubRunTests' g :: Test
g@(Group{}) = do
logs <- (Test -> IO TestLogs) -> [Test] -> IO [TestLogs]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse Test -> IO TestLogs
stubRunTests' ([Test] -> IO [TestLogs]) -> [Test] -> IO [TestLogs]
forall a b. (a -> b) -> a -> b
$ Test -> [Test]
groupTests Test
g
return $ GroupLogs (groupName g) logs
stubRunTests' (ExtraOptions [OptionDescr]
_ Test
t) = Test -> IO TestLogs
stubRunTests' Test
t
maybeDefaultOption :: OptionDescr -> Maybe (FilePath, FilePath)
maybeDefaultOption OptionDescr
opt =
Maybe (FilePath, FilePath)
-> (FilePath -> Maybe (FilePath, FilePath))
-> Maybe FilePath
-> Maybe (FilePath, FilePath)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Maybe (FilePath, FilePath)
forall a. Maybe a
Nothing (\FilePath
d -> (FilePath, FilePath) -> Maybe (FilePath, FilePath)
forall a. a -> Maybe a
Just (OptionDescr -> FilePath
optionName OptionDescr
opt, FilePath
d)) (Maybe FilePath -> Maybe (FilePath, FilePath))
-> Maybe FilePath -> Maybe (FilePath, FilePath)
forall a b. (a -> b) -> a -> b
$ OptionDescr -> Maybe FilePath
optionDefault OptionDescr
opt
defaultOptions :: TestInstance -> [(FilePath, FilePath)]
defaultOptions TestInstance
testInst = (OptionDescr -> Maybe (FilePath, FilePath))
-> [OptionDescr] -> [(FilePath, FilePath)]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe OptionDescr -> Maybe (FilePath, FilePath)
maybeDefaultOption ([OptionDescr] -> [(FilePath, FilePath)])
-> [OptionDescr] -> [(FilePath, FilePath)]
forall a b. (a -> b) -> a -> b
$ TestInstance -> [OptionDescr]
options TestInstance
testInst
stubWriteLog :: FilePath -> UnqualComponentName -> TestLogs -> IO ()
stubWriteLog :: FilePath -> UnqualComponentName -> TestLogs -> IO ()
stubWriteLog FilePath
f UnqualComponentName
n TestLogs
logs = do
let testLog :: TestSuiteLog
testLog = TestSuiteLog{testSuiteName :: UnqualComponentName
testSuiteName = UnqualComponentName
n, testLogs :: TestLogs
testLogs = TestLogs
logs, logFile :: FilePath
logFile = FilePath
f}
FilePath -> FilePath -> IO ()
writeFile (TestSuiteLog -> FilePath
logFile TestSuiteLog
testLog) (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ TestSuiteLog -> FilePath
forall a. Show a => a -> FilePath
show TestSuiteLog
testLog
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (TestLogs -> Bool
suiteError TestLogs
logs) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ ExitCode -> IO ()
forall a. ExitCode -> IO a
exitWith (ExitCode -> IO ()) -> ExitCode -> IO ()
forall a b. (a -> b) -> a -> b
$ Int -> ExitCode
ExitFailure Int
2
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (TestLogs -> Bool
suiteFailed TestLogs
logs) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ ExitCode -> IO ()
forall a. ExitCode -> IO a
exitWith (ExitCode -> IO ()) -> ExitCode -> IO ()
forall a b. (a -> b) -> a -> b
$ Int -> ExitCode
ExitFailure Int
1
IO ()
forall a. IO a
exitSuccess