-----------------------------------------------------------------------------
-- |
-- Module      :  Distribution.Simple.Test
-- Copyright   :  Thomas Tuegel 2010
--
-- Maintainer  :  cabal-devel@haskell.org
-- Portability :  portable
--
-- This is the entry point into testing a built package. It performs the
-- \"@.\/setup test@\" action. It runs test suites designated in the package
-- description and reports on the results.

{- All rights reserved.

Redistribution and use in source and binary forms, with or without
modification, are permitted provided that the following conditions are
met:

    * Redistributions of source code must retain the above copyright
      notice, this list of conditions and the following disclaimer.

    * Redistributions in binary form must reproduce the above
      copyright notice, this list of conditions and the following
      disclaimer in the documentation and/or other materials provided
      with the distribution.

    * Neither the name of Isaac Jones nor the names of other
      contributors may be used to endorse or promote products derived
      from this software without specific prior written permission.

THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR
A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT
OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL,
SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT
LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE
OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -}

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 ( doHpcMarkup, findTixFiles, tixDir )
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, doesFileExist, getCurrentDirectory
    , removeFile, getDirectoryContents )
import System.Environment ( getEnvironment )
import System.Exit ( ExitCode(..), exitFailure, exitWith )
import System.FilePath ( (</>), (<.>) )
import System.IO ( hClose, IOMode(..), openFile )
import System.Process ( runProcess, waitForProcess )

-- | Logs all test results for a package, broken down first by test suite and
-- then by test case.
data testSuites :: [TestSuiteLog]PackageLog = PackageLog
    { package :: PackageId
    , compiler :: CompilerId
    , platform :: Platform
    , testSuites :: [TestSuiteLog]
    }
    deriving (D:Read ::
  (Int -> ReadS a)
  -> ReadS [a]
  -> ReadPrec a
  -> ReadPrec [a]
  -> T:Read aRead, D:Show ::
  (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> T:Show aShow, D:Eq :: (a -> a -> Bool) -> (a -> a -> Bool) -> T:Eq aEq)

-- | A 'PackageLog' with package and platform information specified.
localPackageLog :: PD.PackageDescription -> LBI.LocalBuildInfo -> PackageLog
localPackageLog pkg_descr lbi = PackageLog
    { package = package :: PackageDescription -> PackageIdentifierPD.package pkg_descr :: PackageDescriptionpkg_descr
    , compiler = compilerId :: Compiler -> CompilerIdcompilerId ($) :: (a -> b) -> a -> b$ compiler :: LocalBuildInfo -> CompilerLBI.compiler lbi :: LocalBuildInfolbi
    , platform = buildPlatform :: PlatformbuildPlatform
    , testSuites = [] :: [a][]
    }

-- | Logs test suite results, itemized by test case.
data logFile :: FilePathTestSuiteLog = TestSuiteLog
    { name :: String
    , cases :: [Case]
    , logFile :: FilePath    -- path to human-readable log file
    }
    deriving (D:Read ::
  (Int -> ReadS a)
  -> ReadS [a]
  -> ReadPrec a
  -> ReadPrec [a]
  -> T:Read aRead, D:Show ::
  (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> T:Show aShow, D:Eq :: (a -> a -> Bool) -> (a -> a -> Bool) -> T:Eq aEq)

data caseOptions :: OptionsCase = Case
    { caseName :: String
    , caseOptions :: TestSuite.Options
    , caseResult :: TestSuite.Result
    }
    deriving (D:Read ::
  (Int -> ReadS a)
  -> ReadS [a]
  -> ReadPrec a
  -> ReadPrec [a]
  -> T:Read aRead, D:Show ::
  (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> T:Show aShow, D:Eq :: (a -> a -> Bool) -> (a -> a -> Bool) -> T:Eq aEq)

getTestOptions :: TestSuite.Test -> TestSuiteLog -> IO TestSuite.Options
getTestOptions t l =
    case filter :: (a -> Bool) -> [a] -> [a]filter (((==) :: Eq a => a -> a -> Bool== name :: TestOptions t => t -> StringTestSuite.name t :: TestSuitet) (.) :: (b -> c) -> (a -> b) -> a -> c. caseName :: Case -> StringcaseName) (cases :: TestSuiteLog -> [Case]cases l :: TestSuiteLogl) of
        (x:_) -> return :: Monad m => forall a. a -> m areturn ($) :: (a -> b) -> a -> b$ caseOptions :: Case -> OptionscaseOptions x :: Casex
        _ -> defaultOptions :: TestOptions t => t -> IO OptionsTestSuite.defaultOptions t :: TestSuitet

-- | From a 'TestSuiteLog', determine if the test suite passed.
suitePassed :: TestSuiteLog -> Bool
suitePassed = all :: (a -> Bool) -> [a] -> Boolall ((==) :: Eq a => a -> a -> Bool== Pass :: ResultTestSuite.Pass) (.) :: (b -> c) -> (a -> b) -> a -> c. map :: (a -> b) -> [a] -> [b]map caseResult :: Case -> ResultcaseResult (.) :: (b -> c) -> (a -> b) -> a -> c. cases :: TestSuiteLog -> [Case]cases

-- | From a 'TestSuiteLog', determine if the test suite failed.
suiteFailed :: TestSuiteLog -> Bool
suiteFailed = any :: (a -> Bool) -> [a] -> Boolany isFail :: Result -> BoolisFail (.) :: (b -> c) -> (a -> b) -> a -> c. map :: (a -> b) -> [a] -> [b]map caseResult :: Case -> ResultcaseResult (.) :: (b -> c) -> (a -> b) -> a -> c. cases :: TestSuiteLog -> [Case]cases
    where isFail (TestSuite.Fail _) = True :: BoolTrue
          isFail _ = False :: BoolFalse

-- | From a 'TestSuiteLog', determine if the test suite encountered errors.
suiteError :: TestSuiteLog -> Bool
suiteError = any :: (a -> Bool) -> [a] -> Boolany isError :: Result -> BoolisError (.) :: (b -> c) -> (a -> b) -> a -> c. map :: (a -> b) -> [a] -> [b]map caseResult :: Case -> ResultcaseResult (.) :: (b -> c) -> (a -> b) -> a -> c. cases :: TestSuiteLog -> [Case]cases
    where isError (TestSuite.Error _) = True :: BoolTrue
          isError _ = False :: BoolFalse

-- | Run a test executable, logging the output and generating the appropriate
-- summary messages.
testController :: TestFlags
               -- ^ flags Cabal was invoked with
               -> PD.PackageDescription
               -- ^ description of package the test suite belongs to
               -> LBI.LocalBuildInfo
               -- ^ information from the configure step
               -> PD.TestSuite
               -- ^ TestSuite being tested
               -> (FilePath -> String)
               -- ^ prepare standard input for test executable
               -> FilePath -- ^ executable name
               -> (ExitCode -> String -> TestSuiteLog)
               -- ^ generator for the TestSuiteLog
               -> (TestSuiteLog -> FilePath)
               -- ^ generator for final human-readable log filename
               -> IO TestSuiteLog
testController flags pkg_descr lbi suite preTest cmd postTest logNamer = do
    let distPref = fromFlag :: Flag a -> afromFlag ($) :: (a -> b) -> a -> b$ testDistPref :: TestFlags -> Flag FilePathtestDistPref flags :: TestFlagsflags
        verbosity = fromFlag :: Flag a -> afromFlag ($) :: (a -> b) -> a -> b$ testVerbosity :: TestFlags -> Flag VerbositytestVerbosity flags :: TestFlagsflags
        testLogDir = distPref :: FilePathdistPref (</>) :: FilePath -> FilePath -> FilePath</> "test"
        optionTemplates = fromFlag :: Flag a -> afromFlag ($) :: (a -> b) -> a -> b$ testOptions :: TestFlags -> Flag [PathTemplate]testOptions flags :: TestFlagsflags
        options = map :: (a -> b) -> [a] -> [b]map (testOption ::
  PackageDescription
  -> LocalBuildInfo
  -> TestSuite
  -> PathTemplate
  -> StringtestOption pkg_descr :: PackageDescriptionpkg_descr lbi :: LocalBuildInfolbi suite :: TestSuitesuite) optionTemplates :: [PathTemplate]optionTemplates

    pwd <- getCurrentDirectory :: IO FilePathgetCurrentDirectory
    existingEnv <- getEnvironment :: IO [(String, String)]getEnvironment
    let dataDirPath = pwd :: FilePathpwd (</>) :: FilePath -> FilePath -> FilePath</> dataDir :: PackageDescription -> FilePathPD.dataDir pkg_descr :: PackageDescriptionpkg_descr
        shellEnv = Just :: a -> Maybe aJust ($) :: (a -> b) -> a -> b$ (pkgPathEnvVar :: PackageDescription -> String -> StringpkgPathEnvVar pkg_descr :: PackageDescriptionpkg_descr "datadir", dataDirPath :: FilePathdataDirPath)
                        (:) :: a -> [a] -> [a]: ("HPCTIXDIR", pwd :: FilePathpwd (</>) :: FilePath -> FilePath -> FilePath</> tixDir :: FilePath -> TestSuite -> FilePathtixDir distPref :: FilePathdistPref suite :: TestSuitesuite)
                        (:) :: a -> [a] -> [a]: existingEnv :: [(String, String)]existingEnv

    bracket :: IO a -> (a -> IO b) -> (a -> IO c) -> IO cbracket (openCabalTemp :: FilePath -> IO FilePathopenCabalTemp testLogDir :: FilePathtestLogDir) deleteIfExists :: FilePath -> IO ()deleteIfExists ($) :: (a -> b) -> a -> b$ \tempLog ->
        bracket :: IO a -> (a -> IO b) -> (a -> IO c) -> IO cbracket (openCabalTemp :: FilePath -> IO FilePathopenCabalTemp testLogDir :: FilePathtestLogDir) deleteIfExists :: FilePath -> IO ()deleteIfExists ($) :: (a -> b) -> a -> b$ \tempInput -> do

            -- Create directory for HPC files.
            createDirectoryIfMissing :: Bool -> FilePath -> IO ()createDirectoryIfMissing True :: BoolTrue ($) :: (a -> b) -> a -> b$ tixDir :: FilePath -> TestSuite -> FilePathtixDir distPref :: FilePathdistPref suite :: TestSuitesuite

            -- Remove old .tix files if appropriate.
            tixFiles <- findTixFiles :: FilePath -> TestSuite -> IO [FilePath]findTixFiles distPref :: FilePathdistPref suite :: TestSuitesuite
            unless :: Monad m => Bool -> m () -> m ()unless (fromFlag :: Flag a -> afromFlag ($) :: (a -> b) -> a -> b$ testKeepTix :: TestFlags -> Flag BooltestKeepTix flags :: TestFlagsflags)
                ($) :: (a -> b) -> a -> b$ mapM_ :: Monad m => (a -> m b) -> [a] -> m ()mapM_ deleteIfExists :: FilePath -> IO ()deleteIfExists tixFiles :: [FilePath]tixFiles

            -- Write summary notices indicating start of test suite
            notice :: Verbosity -> String -> IO ()notice verbosity :: Verbosityverbosity ($) :: (a -> b) -> a -> b$ summarizeSuiteStart :: String -> StringsummarizeSuiteStart ($) :: (a -> b) -> a -> b$ testName :: TestSuite -> StringPD.testName suite :: TestSuitesuite
            appendFile :: FilePath -> String -> IO ()appendFile tempLog :: FilePathtempLog ($) :: (a -> b) -> a -> b$ summarizeSuiteStart :: String -> StringsummarizeSuiteStart ($) :: (a -> b) -> a -> b$ testName :: TestSuite -> StringPD.testName suite :: TestSuitesuite

            -- Prepare standard input for test executable
            appendFile :: FilePath -> String -> IO ()appendFile tempInput :: FilePathtempInput ($) :: (a -> b) -> a -> b$ preTest :: FilePath -> StringpreTest tempInput :: FilePathtempInput

            -- Run test executable
            exit <- do
              hLog <- openFile :: FilePath -> IOMode -> IO HandleopenFile tempLog :: FilePathtempLog AppendMode :: IOModeAppendMode
              hIn  <- openFile :: FilePath -> IOMode -> IO HandleopenFile tempInput :: FilePathtempInput ReadMode :: IOModeReadMode
              -- these handles get closed by runProcess
              proc <- runProcess ::
  FilePath
  -> [String]
  -> Maybe FilePath
  -> Maybe [(String, String)]
  -> Maybe Handle
  -> Maybe Handle
  -> Maybe Handle
  -> IO ProcessHandlerunProcess cmd :: FilePathcmd options :: [String]options Nothing :: Maybe aNothing shellEnv :: Maybe [(String, FilePath)]shellEnv
                        (Just :: a -> Maybe aJust hIn :: HandlehIn) (Just :: a -> Maybe aJust hLog :: HandlehLog) (Just :: a -> Maybe aJust hLog :: HandlehLog)
              waitForProcess :: ProcessHandle -> IO ExitCodewaitForProcess proc :: ProcessHandleproc

            -- Generate TestSuiteLog from executable exit code and a machine-
            -- readable test log
            suiteLog <- readFile :: FilePath -> IO StringreadFile tempInput :: FilePathtempInput (>>=) :: Monad m => forall a b. m a -> (a -> m b) -> m b>>= return :: Monad m => forall a. a -> m areturn (.) :: (b -> c) -> (a -> b) -> a -> c. postTest :: Read a => t -> String -> apostTest exit :: ExitCodeexit

            -- Generate final log file name
            let finalLogName = testLogDir :: FilePathtestLogDir (</>) :: FilePath -> FilePath -> FilePath</> logNamer :: TestSuiteLog -> FilePathlogNamer suiteLog :: TestSuiteLogsuiteLog
                suiteLog' = suiteLog :: TestSuiteLogsuiteLog { logFile = finalLogName :: FilePathfinalLogName }

            -- Write summary notice to log file indicating end of test suite
            appendFile :: FilePath -> String -> IO ()appendFile tempLog :: FilePathtempLog ($) :: (a -> b) -> a -> b$ summarizeSuiteFinish :: TestSuiteLog -> StringsummarizeSuiteFinish suiteLog' :: TestSuiteLogsuiteLog'

            -- Append contents of temporary log file to the final human-
            -- readable log file
            readFile :: FilePath -> IO StringreadFile tempLog :: FilePathtempLog (>>=) :: Monad m => forall a b. m a -> (a -> m b) -> m b>>= appendFile :: FilePath -> String -> IO ()appendFile (logFile :: TestSuiteLog -> FilePathlogFile suiteLog' :: TestSuiteLogsuiteLog')

            -- Show the contents of the human-readable log file on the terminal
            -- if there is a failure and/or detailed output is requested
            let details = fromFlag :: Flag a -> afromFlag ($) :: (a -> b) -> a -> b$ testShowDetails :: TestFlags -> Flag TestShowDetailstestShowDetails flags :: TestFlagsflags
                whenPrinting = when :: Monad m => Bool -> m () -> m ()when ($) :: (a -> b) -> a -> b$ (details :: TestShowDetailsdetails (>) :: Ord a => a -> a -> Bool> Never :: TestShowDetailsNever)
                    (&&) :: Bool -> Bool -> Bool&& (not :: Bool -> Boolnot (suitePassed :: TestSuiteLog -> BoolsuitePassed suiteLog :: TestSuiteLogsuiteLog) (||) :: Bool -> Bool -> Bool|| details :: TestShowDetailsdetails (==) :: Eq a => a -> a -> Bool== Always :: TestShowDetailsAlways)
                    (&&) :: Bool -> Bool -> Bool&& verbosity :: Verbosityverbosity (>=) :: Ord a => a -> a -> Bool>= normal :: Verbositynormal
            whenPrinting :: IO () -> IO ()whenPrinting ($) :: (a -> b) -> a -> b$ readFile :: FilePath -> IO StringreadFile (logFile :: TestSuiteLog -> FilePathlogFile suiteLog' :: TestSuiteLogsuiteLog') (>>=) :: Monad m => forall a b. m a -> (a -> m b) -> m b>>=
                putStr :: String -> IO ()putStr (.) :: (b -> c) -> (a -> b) -> a -> c. unlines :: [String] -> Stringunlines (.) :: (b -> c) -> (a -> b) -> a -> c. map :: (a -> b) -> [a] -> [b]map (">>> " (++) :: [a] -> [a] -> [a]++) (.) :: (b -> c) -> (a -> b) -> a -> c. lines :: String -> [String]lines

            -- Write summary notice to terminal indicating end of test suite
            notice :: Verbosity -> String -> IO ()notice verbosity :: Verbosityverbosity ($) :: (a -> b) -> a -> b$ summarizeSuiteFinish :: TestSuiteLog -> StringsummarizeSuiteFinish suiteLog' :: TestSuiteLogsuiteLog'

            doHpcMarkup ::
  Verbosity -> FilePath -> String -> TestSuite -> IO ()doHpcMarkup verbosity :: Verbosityverbosity distPref :: FilePathdistPref (display :: Text a => a -> Stringdisplay ($) :: (a -> b) -> a -> b$ package :: PackageDescription -> PackageIdentifierPD.package pkg_descr :: PackageDescriptionpkg_descr) suite :: TestSuitesuite

            return :: Monad m => forall a. a -> m areturn suiteLog' :: TestSuiteLogsuiteLog'
    where
        deleteIfExists file = do
            exists <- doesFileExist :: FilePath -> IO BooldoesFileExist file :: FilePathfile
            when :: Monad m => Bool -> m () -> m ()when exists :: Boolexists ($) :: (a -> b) -> a -> b$ removeFile :: FilePath -> IO ()removeFile file :: FilePathfile

        openCabalTemp testLogDir = do
            (f, h) <- openTempFile :: FilePath -> String -> IO (FilePath, Handle)openTempFile testLogDir :: FilePathtestLogDir ($) :: (a -> b) -> a -> b$ "cabal-test-" (<.>) :: FilePath -> String -> FilePath<.> "log"
            hClose :: Handle -> IO ()hClose h :: Handleh (>>) :: Monad m => forall a b. m a -> m b -> m b>> return :: Monad m => forall a. a -> m areturn f :: FilePathf


-- |Perform the \"@.\/setup test@\" action.
test :: PD.PackageDescription   -- ^information from the .cabal file
     -> LBI.LocalBuildInfo      -- ^information from the configure step
     -> TestFlags               -- ^flags sent to test
     -> IO ()
test pkg_descr lbi flags = do
    let verbosity = fromFlag :: Flag a -> afromFlag ($) :: (a -> b) -> a -> b$ testVerbosity :: TestFlags -> Flag VerbositytestVerbosity flags :: TestFlagsflags
        humanTemplate = fromFlag :: Flag a -> afromFlag ($) :: (a -> b) -> a -> b$ testHumanLog :: TestFlags -> Flag PathTemplatetestHumanLog flags :: TestFlagsflags
        machineTemplate = fromFlag :: Flag a -> afromFlag ($) :: (a -> b) -> a -> b$ testMachineLog :: TestFlags -> Flag PathTemplatetestMachineLog flags :: TestFlagsflags
        distPref = fromFlag :: Flag a -> afromFlag ($) :: (a -> b) -> a -> b$ testDistPref :: TestFlags -> Flag FilePathtestDistPref flags :: TestFlagsflags
        testLogDir = distPref :: FilePathdistPref (</>) :: FilePath -> FilePath -> FilePath</> "test"
        testNames = fromFlag :: Flag a -> afromFlag ($) :: (a -> b) -> a -> b$ testList :: TestFlags -> Flag [String]testList flags :: TestFlagsflags
        pkgTests = testSuites :: PackageDescription -> [TestSuite]PD.testSuites pkg_descr :: PackageDescriptionpkg_descr
        enabledTests = [ t :: TestSuitet | t <- pkgTests :: [TestSuite]pkgTests
                           , testEnabled :: TestSuite -> BoolPD.testEnabled t :: TestSuitet
                           , buildable :: BuildInfo -> BoolPD.buildable (testBuildInfo :: TestSuite -> BuildInfoPD.testBuildInfo t :: TestSuitet) ]

        doTest :: (PD.TestSuite, Maybe TestSuiteLog) -> IO TestSuiteLog
        doTest (suite, mLog) = do
            let testLogPath = testSuiteLogPath ::
  PathTemplate
  -> PackageDescription
  -> LocalBuildInfo
  -> TestSuiteLog
  -> FilePathtestSuiteLogPath humanTemplate :: PathTemplatehumanTemplate pkg_descr :: PackageDescriptionpkg_descr lbi :: LocalBuildInfolbi
                go pre cmd post = testController ::
  TestFlags
  -> PackageDescription
  -> LocalBuildInfo
  -> TestSuite
  -> (FilePath -> String)
  -> FilePath
  -> (ExitCode -> String -> TestSuiteLog)
  -> (TestSuiteLog -> FilePath)
  -> IO TestSuiteLogtestController flags :: TestFlagsflags pkg_descr :: PackageDescriptionpkg_descr lbi :: LocalBuildInfolbi suite :: TestSuitesuite
                                                 pre :: FilePath -> Stringpre cmd :: FilePathcmd post :: ExitCode -> String -> TestSuiteLogpost testLogPath :: TestSuiteLog -> FilePathtestLogPath
            case testInterface :: TestSuite -> TestSuiteInterfacePD.testInterface suite :: TestSuitesuite of
              PD.TestSuiteExeV10 _ _ -> do
                    let cmd = buildDir :: LocalBuildInfo -> FilePathLBI.buildDir lbi :: LocalBuildInfolbi (</>) :: FilePath -> FilePath -> FilePath</> testName :: TestSuite -> StringPD.testName suite :: TestSuitesuite
                            (</>) :: FilePath -> FilePath -> FilePath</> testName :: TestSuite -> StringPD.testName suite :: TestSuitesuite (<.>) :: FilePath -> String -> FilePath<.> exeExtension :: StringexeExtension
                        preTest _ = ""
                        postTest exit _ =
                            let r = case exit :: ExitCodeexit of
                                    ExitSuccess -> Pass :: ResultTestSuite.Pass
                                    ExitFailure c -> Fail :: String -> ResultTestSuite.Fail
                                        ($) :: (a -> b) -> a -> b$ "exit code: " (++) :: [a] -> [a] -> [a]++ show :: Show a => a -> Stringshow c :: Intc
                            in TestSuiteLog
                                { name = testName :: TestSuite -> StringPD.testName suite :: TestSuitesuite
                                , cases = [Case :: String -> Options -> Result -> CaseCase (testName :: TestSuite -> StringPD.testName suite :: TestSuitesuite) mempty :: Monoid a => amempty r :: Resultr]
                                , logFile = ""
                                }
                    go ::
  (FilePath -> String)
  -> FilePath
  -> (ExitCode -> String -> TestSuiteLog)
  -> IO TestSuiteLoggo preTest :: FilePath -> StringpreTest cmd :: FilePathcmd postTest :: Read a => t -> String -> apostTest

              PD.TestSuiteLibV09 _ _ -> do
                    let cmd = buildDir :: LocalBuildInfo -> FilePathLBI.buildDir lbi :: LocalBuildInfolbi (</>) :: FilePath -> FilePath -> FilePath</> stubName :: TestSuite -> FilePathstubName suite :: TestSuitesuite
                            (</>) :: FilePath -> FilePath -> FilePath</> stubName :: TestSuite -> FilePathstubName suite :: TestSuitesuite (<.>) :: FilePath -> String -> FilePath<.> exeExtension :: StringexeExtension
                        oldLog = case mLog :: Maybe TestSuiteLogmLog of
                            Nothing -> TestSuiteLog
                                { name = testName :: TestSuite -> StringPD.testName suite :: TestSuitesuite
                                , cases = [] :: [a][]
                                , logFile = [] :: [a][]
                                }
                            Just l -> l :: TestSuiteLogl
                        preTest f = show :: Show a => a -> Stringshow ($) :: (a -> b) -> a -> b$ oldLog :: TestSuiteLogoldLog { logFile = f :: FilePathf }
                        postTest _ = read :: Read a => String -> aread
                    go ::
  (FilePath -> String)
  -> FilePath
  -> (ExitCode -> String -> TestSuiteLog)
  -> IO TestSuiteLoggo preTest :: FilePath -> StringpreTest cmd :: FilePathcmd postTest :: Read a => t -> String -> apostTest

              _ -> return :: Monad m => forall a. a -> m areturn TestSuiteLog
                            { name = testName :: TestSuite -> StringPD.testName suite :: TestSuitesuite
                            , cases = [Case :: String -> Options -> Result -> CaseCase (testName :: TestSuite -> StringPD.testName suite :: TestSuitesuite) mempty :: Monoid a => amempty
                                ($) :: (a -> b) -> a -> b$ Error :: String -> ResultTestSuite.Error ($) :: (a -> b) -> a -> b$ "No support for running "
                                (++) :: [a] -> [a] -> [a]++ "test suite type: "
                                (++) :: [a] -> [a] -> [a]++ show :: Show a => a -> Stringshow (disp :: Text a => a -> Docdisp ($) :: (a -> b) -> a -> b$ testType :: TestSuite -> TestTypePD.testType suite :: TestSuitesuite)]
                            , logFile = ""
                            }

    when :: Monad m => Bool -> m () -> m ()when (not :: Bool -> Boolnot ($) :: (a -> b) -> a -> b$ hasTests :: PackageDescription -> BoolPD.hasTests pkg_descr :: PackageDescriptionpkg_descr) ($) :: (a -> b) -> a -> b$ do
        notice :: Verbosity -> String -> IO ()notice verbosity :: Verbosityverbosity "Package has no test suites."
        exitWith :: ExitCode -> IO aexitWith ExitSuccess :: ExitCodeExitSuccess

    when :: Monad m => Bool -> m () -> m ()when (hasTests :: PackageDescription -> BoolPD.hasTests pkg_descr :: PackageDescriptionpkg_descr (&&) :: Bool -> Bool -> Bool&& null :: [a] -> Boolnull enabledTests :: [TestSuite]enabledTests) ($) :: (a -> b) -> a -> b$
        die :: String -> IO adie ($) :: (a -> b) -> a -> b$ "No test suites enabled. Did you remember to configure with "
              (++) :: [a] -> [a] -> [a]++ "\'--enable-tests\'?"

    testsToRun <- case testNames :: [String]testNames of
            [] -> return :: Monad m => forall a. a -> m areturn ($) :: (a -> b) -> a -> b$ zip :: [a] -> [b] -> [(a, b)]zip enabledTests :: [TestSuite]enabledTests ($) :: (a -> b) -> a -> b$ repeat :: a -> [a]repeat Nothing :: Maybe aNothing
            names -> flip :: (a -> b -> c) -> b -> a -> cflip mapM :: Monad m => (a -> m b) -> [a] -> m [b]mapM names :: [String]names ($) :: (a -> b) -> a -> b$ \tName ->
                let testMap = zip :: [a] -> [b] -> [(a, b)]zip enabledNames :: [String]enabledNames enabledTests :: [TestSuite]enabledTests
                    enabledNames = map :: (a -> b) -> [a] -> [b]map testName :: TestSuite -> StringPD.testName enabledTests :: [TestSuite]enabledTests
                    allNames = map :: (a -> b) -> [a] -> [b]map testName :: TestSuite -> StringPD.testName pkgTests :: [TestSuite]pkgTests
                in case lookup :: Eq a => a -> [(a, b)] -> Maybe blookup tName :: StringtName testMap :: [(String, TestSuite)]testMap of
                    Just t -> return :: Monad m => forall a. a -> m areturn (t :: TestSuitet, Nothing :: Maybe aNothing)
                    _ | tName :: StringtName elem :: Eq a => a -> [a] -> Bool`elem` allNames :: [String]allNames ->
                          die :: String -> IO adie ($) :: (a -> b) -> a -> b$ "Package configured with test suite "
                                (++) :: [a] -> [a] -> [a]++ tName :: StringtName (++) :: [a] -> [a] -> [a]++ " disabled."
                      | otherwise :: Boolotherwise -> die :: String -> IO adie ($) :: (a -> b) -> a -> b$ "no such test: " (++) :: [a] -> [a] -> [a]++ tName :: StringtName

    createDirectoryIfMissing :: Bool -> FilePath -> IO ()createDirectoryIfMissing True :: BoolTrue testLogDir :: FilePathtestLogDir

    -- Delete ordinary files from test log directory.
    getDirectoryContents :: FilePath -> IO [FilePath]getDirectoryContents testLogDir :: FilePathtestLogDir
        (>>=) :: Monad m => forall a b. m a -> (a -> m b) -> m b>>= filterM :: Monad m => (a -> m Bool) -> [a] -> m [a]filterM doesFileExist :: FilePath -> IO BooldoesFileExist (.) :: (b -> c) -> (a -> b) -> a -> c. map :: (a -> b) -> [a] -> [b]map (testLogDir :: FilePathtestLogDir (</>) :: FilePath -> FilePath -> FilePath</>)
        (>>=) :: Monad m => forall a b. m a -> (a -> m b) -> m b>>= mapM_ :: Monad m => (a -> m b) -> [a] -> m ()mapM_ removeFile :: FilePath -> IO ()removeFile

    let totalSuites = length :: [a] -> Intlength testsToRun :: [(TestSuite, Maybe TestSuiteLog)]testsToRun
    notice :: Verbosity -> String -> IO ()notice verbosity :: Verbosityverbosity ($) :: (a -> b) -> a -> b$ "Running " (++) :: [a] -> [a] -> [a]++ show :: Show a => a -> Stringshow totalSuites :: InttotalSuites (++) :: [a] -> [a] -> [a]++ " test suites..."
    suites <- mapM :: Monad m => (a -> m b) -> [a] -> m [b]mapM doTest :: (TestSuite, Maybe TestSuiteLog) -> IO TestSuiteLogdoTest testsToRun :: [(TestSuite, Maybe TestSuiteLog)]testsToRun
    let packageLog = (localPackageLog ::
  PackageDescription -> LocalBuildInfo -> PackageLoglocalPackageLog pkg_descr :: PackageDescriptionpkg_descr lbi :: LocalBuildInfolbi) { testSuites = suites :: [TestSuiteLog]suites }
        packageLogFile = (</>) :: FilePath -> FilePath -> FilePath(</>) testLogDir :: FilePathtestLogDir
            ($) :: (a -> b) -> a -> b$ packageLogPath ::
  PathTemplate -> PackageDescription -> LocalBuildInfo -> FilePathpackageLogPath machineTemplate :: PathTemplatemachineTemplate pkg_descr :: PackageDescriptionpkg_descr lbi :: LocalBuildInfolbi
    allOk <- summarizePackage :: Verbosity -> PackageLog -> IO BoolsummarizePackage verbosity :: Verbosityverbosity packageLog :: PackageLogpackageLog
    writeFile :: FilePath -> String -> IO ()writeFile packageLogFile :: FilePathpackageLogFile ($) :: (a -> b) -> a -> b$ show :: Show a => a -> Stringshow packageLog :: PackageLogpackageLog
    unless :: Monad m => Bool -> m () -> m ()unless allOk :: BoolallOk exitFailure :: IO aexitFailure

-- | Print a summary to the console after all test suites have been run
-- indicating the number of successful test suites and cases.  Returns 'True' if
-- all test suites passed and 'False' otherwise.
summarizePackage :: Verbosity -> PackageLog -> IO Bool
summarizePackage verbosity packageLog = do
    let cases' = map :: (a -> b) -> [a] -> [b]map caseResult :: Case -> ResultcaseResult ($) :: (a -> b) -> a -> b$ concatMap :: (a -> [b]) -> [a] -> [b]concatMap cases :: TestSuiteLog -> [Case]cases ($) :: (a -> b) -> a -> b$ testSuites :: PackageLog -> [TestSuiteLog]testSuites packageLog :: PackageLogpackageLog
        passedCases = length :: [a] -> Intlength ($) :: (a -> b) -> a -> b$ filter :: (a -> Bool) -> [a] -> [a]filter ((==) :: Eq a => a -> a -> Bool== Pass :: ResultTestSuite.Pass) cases' :: [Case]cases'
        totalCases = length :: [a] -> Intlength cases' :: [Case]cases'
        passedSuites = length :: [a] -> Intlength ($) :: (a -> b) -> a -> b$ filter :: (a -> Bool) -> [a] -> [a]filter suitePassed :: TestSuiteLog -> BoolsuitePassed ($) :: (a -> b) -> a -> b$ testSuites :: PackageLog -> [TestSuiteLog]testSuites packageLog :: PackageLogpackageLog
        totalSuites = length :: [a] -> Intlength ($) :: (a -> b) -> a -> b$ testSuites :: PackageLog -> [TestSuiteLog]testSuites packageLog :: PackageLogpackageLog
    notice :: Verbosity -> String -> IO ()notice verbosity :: Verbosityverbosity ($) :: (a -> b) -> a -> b$ show :: Show a => a -> Stringshow passedSuites :: IntpassedSuites (++) :: [a] -> [a] -> [a]++ " of " (++) :: [a] -> [a] -> [a]++ show :: Show a => a -> Stringshow totalSuites :: InttotalSuites
        (++) :: [a] -> [a] -> [a]++ " test suites (" (++) :: [a] -> [a] -> [a]++ show :: Show a => a -> Stringshow passedCases :: IntpassedCases (++) :: [a] -> [a] -> [a]++ " of "
        (++) :: [a] -> [a] -> [a]++ show :: Show a => a -> Stringshow totalCases :: InttotalCases (++) :: [a] -> [a] -> [a]++ " test cases) passed."
    return :: Monad m => forall a. a -> m areturn ($!) :: (a -> b) -> a -> b$! passedSuites :: IntpassedSuites (==) :: Eq a => a -> a -> Bool== totalSuites :: InttotalSuites

-- | Print a summary of a single test case's result to the console, supressing
-- output for certain verbosity or test filter levels.
summarizeCase :: Verbosity -> TestShowDetails -> Case -> IO ()
summarizeCase verbosity details t =
    when :: Monad m => Bool -> m () -> m ()when shouldPrint :: BoolshouldPrint ($) :: (a -> b) -> a -> b$ notice :: Verbosity -> String -> IO ()notice verbosity :: Verbosityverbosity ($) :: (a -> b) -> a -> b$ "Test case " (++) :: [a] -> [a] -> [a]++ caseName :: Case -> StringcaseName t :: TestSuitet
        (++) :: [a] -> [a] -> [a]++ ": " (++) :: [a] -> [a] -> [a]++ show :: Show a => a -> Stringshow (caseResult :: Case -> ResultcaseResult t :: TestSuitet)
    where shouldPrint = (details :: TestShowDetailsdetails (>) :: Ord a => a -> a -> Bool> Never :: TestShowDetailsNever) (&&) :: Bool -> Bool -> Bool&& (notPassed :: BoolnotPassed (||) :: Bool -> Bool -> Bool|| details :: TestShowDetailsdetails (==) :: Eq a => a -> a -> Bool== Always :: TestShowDetailsAlways)
          notPassed = caseResult :: Case -> ResultcaseResult t :: TestSuitet (/=) :: Eq a => a -> a -> Bool/= Pass :: ResultTestSuite.Pass

-- | Print a summary of the test suite's results on the console, suppressing
-- output for certain verbosity or test filter levels.
summarizeSuiteFinish :: TestSuiteLog -> String
summarizeSuiteFinish testLog = unlines :: [String] -> Stringunlines
    [ "Test suite " (++) :: [a] -> [a] -> [a]++ name :: TestSuiteLog -> Stringname testLog :: TestSuiteLogtestLog (++) :: [a] -> [a] -> [a]++ ": " (++) :: [a] -> [a] -> [a]++ resStr :: [Char]resStr
    , "Test suite logged to: " (++) :: [a] -> [a] -> [a]++ logFile :: TestSuiteLog -> FilePathlogFile testLog :: TestSuiteLogtestLog
    ]
    where resStr = map :: (a -> b) -> [a] -> [b]map toUpper :: Char -> ChartoUpper (resultString :: TestSuiteLog -> StringresultString testLog :: TestSuiteLogtestLog)

summarizeSuiteStart :: String -> String
summarizeSuiteStart n = "Test suite " (++) :: [a] -> [a] -> [a]++ n :: Stringn (++) :: [a] -> [a] -> [a]++ ": RUNNING...\n"

resultString :: TestSuiteLog -> String
resultString l | suiteError :: TestSuiteLog -> BoolsuiteError l :: TestSuiteLogl = "error"
               | suiteFailed :: TestSuiteLog -> BoolsuiteFailed l :: TestSuiteLogl = "fail"
               | otherwise :: Boolotherwise = "pass"

testSuiteLogPath :: PathTemplate
                 -> PD.PackageDescription
                 -> LBI.LocalBuildInfo
                 -> TestSuiteLog
                 -> FilePath
testSuiteLogPath template pkg_descr lbi testLog =
    fromPathTemplate :: PathTemplate -> FilePathfromPathTemplate ($) :: (a -> b) -> a -> b$ substPathTemplate ::
  PathTemplateEnv -> PathTemplate -> PathTemplatesubstPathTemplate env :: [(PathTemplateVariable, PathTemplate)]env template :: PathTemplatetemplate
    where
        env = initialPathTemplateEnv ::
  PackageIdentifier -> CompilerId -> PathTemplateEnvinitialPathTemplateEnv
                (package :: PackageDescription -> PackageIdentifierPD.package pkg_descr :: PackageDescriptionpkg_descr) (compilerId :: Compiler -> CompilerIdcompilerId ($) :: (a -> b) -> a -> b$ compiler :: LocalBuildInfo -> CompilerLBI.compiler lbi :: LocalBuildInfolbi)
                (++) :: [a] -> [a] -> [a]++  [ (TestSuiteNameVar :: PathTemplateVariableTestSuiteNameVar, toPathTemplate :: FilePath -> PathTemplatetoPathTemplate ($) :: (a -> b) -> a -> b$ name :: TestSuiteLog -> Stringname testLog :: TestSuiteLogtestLog)
                    , (TestSuiteResultVar :: PathTemplateVariableTestSuiteResultVar, result :: PathTemplateresult)
                    ]
        result = toPathTemplate :: FilePath -> PathTemplatetoPathTemplate ($) :: (a -> b) -> a -> b$ resultString :: TestSuiteLog -> StringresultString testLog :: TestSuiteLogtestLog

-- TODO: This is abusing the notion of a 'PathTemplate'.  The result
-- isn't neccesarily a path.
testOption :: PD.PackageDescription
           -> LBI.LocalBuildInfo
           -> PD.TestSuite
           -> PathTemplate
           -> String
testOption pkg_descr lbi suite template =
    fromPathTemplate :: PathTemplate -> FilePathfromPathTemplate ($) :: (a -> b) -> a -> b$ substPathTemplate ::
  PathTemplateEnv -> PathTemplate -> PathTemplatesubstPathTemplate env :: [(PathTemplateVariable, PathTemplate)]env template :: PathTemplatetemplate
  where
    env = initialPathTemplateEnv ::
  PackageIdentifier -> CompilerId -> PathTemplateEnvinitialPathTemplateEnv
          (package :: PackageDescription -> PackageIdentifierPD.package pkg_descr :: PackageDescriptionpkg_descr) (compilerId :: Compiler -> CompilerIdcompilerId ($) :: (a -> b) -> a -> b$ compiler :: LocalBuildInfo -> CompilerLBI.compiler lbi :: LocalBuildInfolbi) (++) :: [a] -> [a] -> [a]++
          [(TestSuiteNameVar :: PathTemplateVariableTestSuiteNameVar, toPathTemplate :: FilePath -> PathTemplatetoPathTemplate ($) :: (a -> b) -> a -> b$ testName :: TestSuite -> StringPD.testName suite :: TestSuitesuite)]

packageLogPath :: PathTemplate
               -> PD.PackageDescription
               -> LBI.LocalBuildInfo
               -> FilePath
packageLogPath template pkg_descr lbi =
    fromPathTemplate :: PathTemplate -> FilePathfromPathTemplate ($) :: (a -> b) -> a -> b$ substPathTemplate ::
  PathTemplateEnv -> PathTemplate -> PathTemplatesubstPathTemplate env :: [(PathTemplateVariable, PathTemplate)]env template :: PathTemplatetemplate
    where
        env = initialPathTemplateEnv ::
  PackageIdentifier -> CompilerId -> PathTemplateEnvinitialPathTemplateEnv
                (package :: PackageDescription -> PackageIdentifierPD.package pkg_descr :: PackageDescriptionpkg_descr) (compilerId :: Compiler -> CompilerIdcompilerId ($) :: (a -> b) -> a -> b$ compiler :: LocalBuildInfo -> CompilerLBI.compiler lbi :: LocalBuildInfolbi)

-- | The filename of the source file for the stub executable associated with a
-- library 'TestSuite'.
stubFilePath :: PD.TestSuite -> FilePath
stubFilePath t = stubName :: TestSuite -> FilePathstubName t :: TestSuitet (<.>) :: FilePath -> String -> FilePath<.> "hs"

-- | The name of the stub executable associated with a library 'TestSuite'.
stubName :: PD.TestSuite -> FilePath
stubName t = testName :: TestSuite -> StringPD.testName t :: TestSuitet (++) :: [a] -> [a] -> [a]++ "Stub"

-- | Write the source file for a library 'TestSuite' stub executable.
writeSimpleTestStub :: PD.TestSuite -- ^ library 'TestSuite' for which a stub
                                    -- is being created
                    -> FilePath     -- ^ path to directory where stub source
                                    -- should be located
                    -> IO ()
writeSimpleTestStub t dir = do
    createDirectoryIfMissing :: Bool -> FilePath -> IO ()createDirectoryIfMissing True :: BoolTrue dir :: FilePathdir
    let filename = dir :: FilePathdir (</>) :: FilePath -> FilePath -> FilePath</> stubFilePath :: TestSuite -> FilePathstubFilePath t :: TestSuitet
        PD.TestSuiteLibV09 _ m = testInterface :: TestSuite -> TestSuiteInterfacePD.testInterface t :: TestSuitet
    writeFile :: FilePath -> String -> IO ()writeFile filename :: FilePathfilename ($) :: (a -> b) -> a -> b$ simpleTestStub :: ModuleName -> StringsimpleTestStub m :: ModuleNamem

-- | Source code for library test suite stub executable
simpleTestStub :: ModuleName -> String
simpleTestStub m = unlines :: [String] -> Stringunlines
    [ "module Main ( main ) where"
    , "import Control.Monad ( liftM )"
    , "import Distribution.Simple.Test ( runTests )"
    , "import " (++) :: [a] -> [a] -> [a]++ show :: Show a => a -> Stringshow (disp :: Text a => a -> Docdisp m :: ModuleNamem) (++) :: [a] -> [a] -> [a]++ " ( tests )"
    , "main :: IO ()"
    , "main = runTests tests"
    ]

-- | The test runner used in library "TestSuite" stub executables.  Runs a list
-- of 'Test's.  An executable calling this function is meant to be invoked as
-- the child of a Cabal process during @.\/setup test@.  A 'TestSuiteLog',
-- provided by Cabal, is read from the standard input; it supplies the name of
-- the test suite and the location of the machine-readable test suite log file.
-- Human-readable log information is written to the standard output for capture
-- by the calling Cabal process.
runTests :: [TestSuite.Test] -> IO ()
runTests tests = do
    testLogIn <- liftM :: Monad m => (a1 -> r) -> m a1 -> m rliftM read :: Read a => String -> aread getContents :: IO StringgetContents
    let go :: TestSuite.Test -> IO Case
        go t = do
            o <- getTestOptions :: Test -> TestSuiteLog -> IO OptionsgetTestOptions t :: TestSuitet testLogIn :: TestSuiteLogtestLogIn
            r <- runM :: ImpureTestable t => t -> Options -> IO ResultTestSuite.runM t :: TestSuitet o :: Optionso
            let ret = Case
                    { caseName = name :: TestOptions t => t -> StringTestSuite.name t :: TestSuitet
                    , caseOptions = o :: Optionso
                    , caseResult = r :: Resultr
                    }
            summarizeCase :: Verbosity -> TestShowDetails -> Case -> IO ()summarizeCase normal :: Verbositynormal Always :: TestShowDetailsAlways ret :: Caseret
            return :: Monad m => forall a. a -> m areturn ret :: Caseret
    cases' <- mapM :: Monad m => (a -> m b) -> [a] -> m [b]mapM go ::
  (FilePath -> String)
  -> FilePath
  -> (ExitCode -> String -> TestSuiteLog)
  -> IO TestSuiteLoggo tests :: [Test]tests
    let testLog = testLogIn :: TestSuiteLogtestLogIn { cases = cases' :: [Case]cases'}
    writeFile :: FilePath -> String -> IO ()writeFile (logFile :: TestSuiteLog -> FilePathlogFile testLog :: TestSuiteLogtestLog) ($) :: (a -> b) -> a -> b$ show :: Show a => a -> Stringshow testLog :: TestSuiteLogtestLog
    when :: Monad m => Bool -> m () -> m ()when (suiteError :: TestSuiteLog -> BoolsuiteError testLog :: TestSuiteLogtestLog) ($) :: (a -> b) -> a -> b$ exitWith :: ExitCode -> IO aexitWith ($) :: (a -> b) -> a -> b$ ExitFailure :: Int -> ExitCodeExitFailure 2
    when :: Monad m => Bool -> m () -> m ()when (suiteFailed :: TestSuiteLog -> BoolsuiteFailed testLog :: TestSuiteLogtestLog) ($) :: (a -> b) -> a -> b$ exitWith :: ExitCode -> IO aexitWith ($) :: (a -> b) -> a -> b$ ExitFailure :: Int -> ExitCodeExitFailure 1
    exitWith :: ExitCode -> IO aexitWith ExitSuccess :: ExitCodeExitSuccess