module Distribution.Simple.Test
    ( test
    , stubMain
    , writeSimpleTestStub
    , stubFilePath
    , stubName
    , PackageLog(..)
    , TestSuiteLog(..)
    , TestLogs(..)
    , 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, rawSystemIOWithEnv )
import Distribution.TestSuite
    ( OptionDescr(..), Options, Progress(..), Result(..), TestInstance(..)
    , Test(..) )
import Distribution.Text
import Distribution.Verbosity ( normal, Verbosity )
import Distribution.System ( Platform )
import Control.Exception ( bracket )
import Control.Monad ( when, unless, filterM )
import Data.Char ( toUpper )
import Data.Maybe ( mapMaybe )
import System.Directory
    ( createDirectoryIfMissing, doesDirectoryExist, doesFileExist
    , getCurrentDirectory, getDirectoryContents, removeDirectoryRecursive
    , removeFile, setCurrentDirectory )
import Distribution.Compat.Environment ( getEnvironment )
import System.Exit ( ExitCode(..), exitFailure, exitWith )
import System.FilePath ( (</>), (<.>) )
import System.IO ( hClose, IOMode(..), openFile )
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 = LBI.hostPlatform lbi
    , testSuites = []
    }
data TestSuiteLog = TestSuiteLog
    { testSuiteName :: String
    , testLogs :: TestLogs
    , logFile :: FilePath    
    }
    deriving (Read, Show, Eq)
data TestLogs
    = TestLog
        { testName              :: String
        , testOptionsReturned   :: Options
        , testResult            :: Result
        }
    | GroupLogs String [TestLogs]
    deriving (Read, Show, Eq)
countTestResults :: TestLogs
                 -> (Int, Int, Int) 
                                    
countTestResults = go (0, 0, 0)
  where
    go (p, f, e) (TestLog { testResult = r }) =
        case r of
            Pass -> (p + 1, f, e)
            Fail _ -> (p, f + 1, e)
            Error _ -> (p, f, e + 1)
    go (p, f, e) (GroupLogs _ ts) = foldl go (p, f, e) ts
suitePassed :: TestSuiteLog -> Bool
suitePassed l =
    case countTestResults (testLogs l) of
        (_, 0, 0) -> True
        _ -> False
suiteFailed :: TestSuiteLog -> Bool
suiteFailed l =
    case countTestResults (testLogs l) of
        (_, 0, _) -> False
        _ -> True
suiteError :: TestSuiteLog -> Bool
suiteError l =
    case countTestResults (testLogs l) of
        (_, _, 0) -> False
        _ -> True
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"
        opts = map (testOption pkg_descr lbi suite) $ testOptions flags
    pwd <- getCurrentDirectory
    existingEnv <- getEnvironment
    let dataDirPath = pwd </> PD.dataDir pkg_descr
        shellEnv = (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
              
              rawSystemIOWithEnv verbosity cmd opts Nothing (Just shellEnv)
                                 (Just hIn) (Just hLog) (Just hLog)
            
            
            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, _) = 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 -> Pass
                                    ExitFailure c -> Fail
                                        $ "exit code: " ++ show c
                            in TestSuiteLog
                                { testSuiteName = PD.testName suite
                                , testLogs = TestLog
                                    { testName = PD.testName suite
                                    , testOptionsReturned = []
                                    , testResult = r
                                    }
                                , logFile = ""
                                }
                    go preTest cmd postTest
              PD.TestSuiteLibV09 _ _ -> do
                    let cmd = LBI.buildDir lbi </> stubName suite
                            </> stubName suite <.> exeExtension
                        preTest f = show ( f
                                         , PD.testName suite
                                         )
                        postTest _ = read
                    go preTest cmd postTest
              _ -> return TestSuiteLog
                            { testSuiteName = PD.testName suite
                            , testLogs = TestLog
                                { testName = PD.testName suite
                                , testOptionsReturned = []
                                , testResult = 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 counts = map (countTestResults . testLogs) $ testSuites packageLog
        (passed, failed, errors) = foldl1 addTriple counts
        totalCases = passed + failed + errors
        passedSuites = length $ filter suitePassed $ testSuites packageLog
        totalSuites = length $ testSuites packageLog
    notice verbosity $ show passedSuites ++ " of " ++ show totalSuites
        ++ " test suites (" ++ show passed ++ " of "
        ++ show totalCases ++ " test cases) passed."
    return $! passedSuites == totalSuites
  where
    addTriple (p1, f1, e1) (p2, f2, e2) = (p1 + p2, f1 + f2, e1 + e2)
summarizeTest :: Verbosity -> TestShowDetails -> TestLogs -> IO ()
summarizeTest _ _ (GroupLogs {}) = return ()
summarizeTest verbosity details t =
    when shouldPrint $ notice verbosity $ "Test case " ++ testName t
        ++ ": " ++ show (testResult t)
    where shouldPrint = (details > Never) && (notPassed || details == Always)
          notPassed = testResult t /= Pass
summarizeSuiteFinish :: TestSuiteLog -> String
summarizeSuiteFinish testLog = unlines
    [ "Test suite " ++ testSuiteName 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)
                (LBI.hostPlatform lbi)
                ++  [ (TestSuiteNameVar, toPathTemplate $ testSuiteName 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)
          (LBI.hostPlatform 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)
                (LBI.hostPlatform 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 Distribution.Simple.Test ( stubMain )"
    , "import " ++ show (disp m) ++ " ( tests )"
    , "main :: IO ()"
    , "main = stubMain tests"
    ]
stubMain :: IO [Test] -> IO ()
stubMain tests = do
    (f, n) <- fmap read getContents
    dir <- getCurrentDirectory
    results <- tests >>= stubRunTests
    setCurrentDirectory dir
    stubWriteLog f n results
stubRunTests :: [Test] -> IO TestLogs
stubRunTests tests = do
    logs <- mapM stubRunTests' tests
    return $ GroupLogs "Default" logs
  where
    stubRunTests' (Test t) = do
        l <- run t >>= finish
        summarizeTest normal Always l
        return l
      where
        finish (Finished result) =
            return TestLog
                { testName = name t
                , testOptionsReturned = defaultOptions t
                , testResult = result
                }
        finish (Progress _ next) = next >>= finish
    stubRunTests' g@(Group {}) = do
        logs <- mapM stubRunTests' $ groupTests g
        return $ GroupLogs (groupName g) logs
    stubRunTests' (ExtraOptions _ t) = stubRunTests' t
    maybeDefaultOption opt =
        maybe Nothing (\d -> Just (optionName opt, d)) $ optionDefault opt
    defaultOptions testInst = mapMaybe maybeDefaultOption $ options testInst
stubWriteLog :: FilePath -> String -> TestLogs -> IO ()
stubWriteLog f n logs = do
    let testLog = TestSuiteLog { testSuiteName = n, testLogs = logs, logFile = f }
    writeFile (logFile testLog) $ show testLog
    when (suiteError testLog) $ exitWith $ ExitFailure 2
    when (suiteFailed testLog) $ exitWith $ ExitFailure 1
    exitWith ExitSuccess