module Distribution.Simple.Hpc
( enableCoverage
, htmlDir
, tixDir
, tixFilePath
, markupPackage
, markupTest
) where
import Control.Monad ( when )
import Distribution.Compiler ( CompilerFlavor(..) )
import Distribution.ModuleName ( main )
import Distribution.PackageDescription
( BuildInfo(..)
, Library(..)
, PackageDescription(..)
, TestSuite(..)
, testModules
)
import Distribution.Simple.LocalBuildInfo ( LocalBuildInfo(..) )
import Distribution.Simple.Program ( hpcProgram, requireProgram )
import Distribution.Simple.Program.Hpc ( markup, union )
import Distribution.Simple.Utils ( notice )
import Distribution.Text
import Distribution.Verbosity ( Verbosity() )
import System.Directory ( createDirectoryIfMissing, doesFileExist )
import System.FilePath
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", mixDir 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
hpcDir distPref = distPref </> "hpc"
mixDir :: FilePath
-> FilePath
-> FilePath
mixDir distPref name = hpcDir distPref </> "mix" </> name
tixDir :: FilePath
-> FilePath
-> FilePath
tixDir distPref name = hpcDir distPref </> "tix" </> name
tixFilePath :: FilePath
-> FilePath
-> FilePath
tixFilePath distPref name = tixDir distPref name </> name <.> "tix"
htmlDir :: FilePath
-> FilePath
-> FilePath
htmlDir distPref name = hpcDir distPref </> "html" </> name
markupTest :: Verbosity
-> LocalBuildInfo
-> FilePath
-> String
-> TestSuite
-> IO ()
markupTest verbosity lbi distPref libName suite = do
tixFileExists <- doesFileExist $ tixFilePath distPref $ testName suite
when tixFileExists $ do
(hpc, _) <- requireProgram verbosity hpcProgram $ withPrograms lbi
markup hpc verbosity (tixFilePath distPref $ testName suite)
(mixDir distPref libName)
(htmlDir distPref $ testName suite)
(testModules suite ++ [ main ])
notice verbosity $ "Test coverage report written to "
++ htmlDir distPref (testName suite)
</> "hpc_index" <.> "html"
markupPackage :: Verbosity
-> LocalBuildInfo
-> FilePath
-> String
-> [TestSuite]
-> IO ()
markupPackage verbosity lbi distPref libName suites = do
let tixFiles = map (tixFilePath distPref . testName) suites
tixFilesExist <- mapM doesFileExist tixFiles
when (and tixFilesExist) $ do
(hpc, _) <- requireProgram verbosity hpcProgram $ withPrograms lbi
let outFile = tixFilePath distPref libName
mixDir' = mixDir distPref libName
htmlDir' = htmlDir distPref libName
excluded = concatMap testModules suites ++ [ main ]
createDirectoryIfMissing True $ takeDirectory outFile
union hpc verbosity tixFiles outFile excluded
markup hpc verbosity outFile mixDir' htmlDir' excluded
notice verbosity $ "Package coverage report written to "
++ htmlDir' </> "hpc_index.html"