module Distribution.Simple.Hpc
( hpcDir
, enableCoverage
, tixDir
, tixFilePath
, doHpcMarkup
, findTixFiles
) where
import Control.Exception ( bracket )
import Control.Monad ( unless, when )
import Distribution.Compiler ( CompilerFlavor(..) )
import Distribution.ModuleName ( main )
import Distribution.PackageDescription
( BuildInfo(..)
, Library(..)
, PackageDescription(..)
, TestSuite(..)
, testModules
)
import Distribution.Simple.Utils ( die, notice )
import Distribution.Text
import Distribution.Verbosity ( Verbosity() )
import System.Directory ( doesFileExist, getDirectoryContents, removeFile )
import System.Exit ( ExitCode(..) )
import System.FilePath
import System.IO ( hClose, IOMode(..), openFile, openTempFile )
import System.Process ( runProcess, waitForProcess )
enableCoverage :: Bool
-> String
-> PackageDescription
-> PackageDescription
enableCoverage False _ x = x
enableCoverage True distPref p =
p { library = fmap enableLibCoverage (library p)
, testSuites = map enableTestCoverage (testSuites p)
}
where
enableBICoverage name oldBI =
let oldOptions = options oldBI
oldGHCOpts = lookup GHC oldOptions
newGHCOpts = case oldGHCOpts of
Just xs -> (GHC, hpcOpts ++ xs)
_ -> (GHC, hpcOpts)
newOptions = (:) newGHCOpts $ filter ((== GHC) . fst) oldOptions
hpcOpts = ["-fhpc", "-hpcdir", hpcDir distPref name]
in oldBI { options = newOptions }
enableLibCoverage l =
l { libBuildInfo = enableBICoverage (display $ package p)
(libBuildInfo l)
}
enableTestCoverage t =
t { testBuildInfo = enableBICoverage (testName t) (testBuildInfo t) }
hpcDir :: FilePath
-> FilePath
-> FilePath
hpcDir distPref name = distPref </> "hpc" </> name
tixDir :: FilePath
-> TestSuite
-> FilePath
tixDir distPref suite = distPref </> "test" </> testName suite
tixFilePath :: FilePath
-> TestSuite
-> FilePath
tixFilePath distPref suite = tixDir distPref suite </> testName suite <.> "tix"
findTixFiles :: FilePath
-> TestSuite
-> IO [FilePath]
findTixFiles distPref suite = do
files <- getDirectoryContents $ tixDir distPref suite
let tixFiles = flip filter files $ \x -> takeExtension x == ".tix"
return $ map (tixDir distPref suite </>) tixFiles
doHpcMarkup :: Verbosity
-> FilePath
-> String
-> TestSuite
-> IO ()
doHpcMarkup verbosity distPref libName suite = do
tixFiles <- findTixFiles distPref suite
when (not $ null tixFiles) $ do
let hpcOptions = map (\x -> "--exclude=" ++ display x) excluded
unionOptions = [ "sum"
, "--union"
, "--output=" ++ tixFilePath distPref suite
]
++ hpcOptions ++ tixFiles
markupOptions = [ "markup"
, tixFilePath distPref suite
, "--hpcdir=" ++ hpcDir distPref libName
, "--destdir=" ++ tixDir distPref suite
]
++ hpcOptions
excluded = testModules suite ++ [ main ]
runHpc opts h = runProcess "hpc" opts Nothing Nothing Nothing
(Just h) (Just h)
bracket (openHpcTemp $ tixDir distPref suite) deleteIfExists
$ \hpcOut -> do
hUnion <- openFile hpcOut AppendMode
procUnion <- runHpc unionOptions hUnion
exitUnion <- waitForProcess procUnion
success <- case exitUnion of
ExitSuccess -> do
hMarkup <- openFile hpcOut AppendMode
procMarkup <- runHpc markupOptions hMarkup
exitMarkup <- waitForProcess procMarkup
case exitMarkup of
ExitSuccess -> return True
_ -> return False
_ -> return False
unless success $ do
errs <- readFile hpcOut
die $ "HPC failed:\n" ++ errs
when success $ notice verbosity
$ "Test coverage report written to "
++ tixDir distPref suite </> "hpc_index"
<.> "html"
return ()
where openHpcTemp dir = do
(f, h) <- openTempFile dir $ "cabal-test-hpc-" <.> "log"
hClose h >> return f
deleteIfExists path = do
exists <- doesFileExist path
when exists $ removeFile path