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 :: PackageDescriptionx
enableCoverage True distPref p =
p :: PackageDescriptionp { library = fmap :: Functor f => forall a b. (a -> b) -> f a -> f bfmap enableLibCoverage :: Library -> LibraryenableLibCoverage (library :: PackageDescription -> Maybe Librarylibrary p :: PackageDescriptionp)
, testSuites = map :: (a -> b) -> [a] -> [b]map enableTestCoverage :: TestSuite -> TestSuiteenableTestCoverage (testSuites :: PackageDescription -> [TestSuite]testSuites p :: PackageDescriptionp)
}
where
enableBICoverage name oldBI =
let oldOptions = options :: BuildInfo -> [(CompilerFlavor, [String])]options oldBI :: BuildInfooldBI
oldGHCOpts = lookup :: Eq a => a -> [(a, b)] -> Maybe blookup GHC :: CompilerFlavorGHC oldOptions :: [(CompilerFlavor, [String])]oldOptions
newGHCOpts = case oldGHCOpts :: Maybe [String]oldGHCOpts of
Just xs -> (GHC :: CompilerFlavorGHC, hpcOpts :: [[Char]]hpcOpts (++) :: [a] -> [a] -> [a]++ xs :: [String]xs)
_ -> (GHC :: CompilerFlavorGHC, hpcOpts :: [[Char]]hpcOpts)
newOptions = (:) :: a -> [a] -> [a](:) newGHCOpts :: (CompilerFlavor, [[Char]])newGHCOpts ($) :: (a -> b) -> a -> b$ filter :: (a -> Bool) -> [a] -> [a]filter (((==) :: Eq a => a -> a -> Bool== GHC :: CompilerFlavorGHC) (.) :: (b -> c) -> (a -> b) -> a -> c. fst :: (a, b) -> afst) oldOptions :: [(CompilerFlavor, [String])]oldOptions
hpcOpts = ["-fhpc", "-hpcdir", hpcDir :: FilePath -> FilePath -> FilePathhpcDir distPref :: StringdistPref name :: FilePathname]
in oldBI :: BuildInfooldBI { options = newOptions :: [(CompilerFlavor, [[Char]])]newOptions }
enableLibCoverage l =
l :: Libraryl { libBuildInfo = enableBICoverage :: FilePath -> BuildInfo -> BuildInfoenableBICoverage (display :: Text a => a -> Stringdisplay ($) :: (a -> b) -> a -> b$ package :: PackageDescription -> PackageIdentifierpackage p :: PackageDescriptionp)
(libBuildInfo :: Library -> BuildInfolibBuildInfo l :: Libraryl)
}
enableTestCoverage t =
t :: TestSuitet { testBuildInfo = enableBICoverage :: FilePath -> BuildInfo -> BuildInfoenableBICoverage (testName :: TestSuite -> StringtestName t :: TestSuitet) (testBuildInfo :: TestSuite -> BuildInfotestBuildInfo t :: TestSuitet) }
hpcDir :: FilePath
-> FilePath
-> FilePath
hpcDir distPref name = distPref :: StringdistPref (</>) :: FilePath -> FilePath -> FilePath</> "hpc" (</>) :: FilePath -> FilePath -> FilePath</> name :: FilePathname
tixDir :: FilePath
-> TestSuite
-> FilePath
tixDir distPref suite = distPref :: StringdistPref (</>) :: FilePath -> FilePath -> FilePath</> "test" (</>) :: FilePath -> FilePath -> FilePath</> testName :: TestSuite -> StringtestName suite :: TestSuitesuite
tixFilePath :: FilePath
-> TestSuite
-> FilePath
tixFilePath distPref suite = tixDir :: FilePath -> TestSuite -> FilePathtixDir distPref :: StringdistPref suite :: TestSuitesuite (</>) :: FilePath -> FilePath -> FilePath</> testName :: TestSuite -> StringtestName suite :: TestSuitesuite (<.>) :: FilePath -> String -> FilePath<.> "tix"
findTixFiles :: FilePath
-> TestSuite
-> IO [FilePath]
findTixFiles distPref suite = do
files <- getDirectoryContents :: FilePath -> IO [FilePath]getDirectoryContents ($) :: (a -> b) -> a -> b$ tixDir :: FilePath -> TestSuite -> FilePathtixDir distPref :: StringdistPref suite :: TestSuitesuite
let tixFiles = flip :: (a -> b -> c) -> b -> a -> cflip filter :: (a -> Bool) -> [a] -> [a]filter files :: [FilePath]files ($) :: (a -> b) -> a -> b$ \x -> takeExtension :: FilePath -> StringtakeExtension x :: PackageDescriptionx (==) :: Eq a => a -> a -> Bool== ".tix"
return :: Monad m => forall a. a -> m areturn ($) :: (a -> b) -> a -> b$ map :: (a -> b) -> [a] -> [b]map (tixDir :: FilePath -> TestSuite -> FilePathtixDir distPref :: StringdistPref suite :: TestSuitesuite (</>) :: FilePath -> FilePath -> FilePath</>) tixFiles :: [FilePath]tixFiles
doHpcMarkup :: Verbosity
-> FilePath
-> String
-> TestSuite
-> IO ()
doHpcMarkup verbosity distPref libName suite = do
tixFiles <- findTixFiles :: FilePath -> TestSuite -> IO [FilePath]findTixFiles distPref :: StringdistPref suite :: TestSuitesuite
when :: Monad m => Bool -> m () -> m ()when (not :: Bool -> Boolnot ($) :: (a -> b) -> a -> b$ null :: [a] -> Boolnull tixFiles :: [FilePath]tixFiles) ($) :: (a -> b) -> a -> b$ do
let hpcOptions = map :: (a -> b) -> [a] -> [b]map (\x -> "--exclude=" (++) :: [a] -> [a] -> [a]++ display :: Text a => a -> Stringdisplay x :: PackageDescriptionx) excluded :: [ModuleName]excluded
unionOptions = [ "sum"
, "--union"
, "--output=" (++) :: [a] -> [a] -> [a]++ tixFilePath :: FilePath -> TestSuite -> FilePathtixFilePath distPref :: StringdistPref suite :: TestSuitesuite
]
(++) :: [a] -> [a] -> [a]++ hpcOptions :: [[Char]]hpcOptions (++) :: [a] -> [a] -> [a]++ tixFiles :: [FilePath]tixFiles
markupOptions = [ "markup"
, tixFilePath :: FilePath -> TestSuite -> FilePathtixFilePath distPref :: StringdistPref suite :: TestSuitesuite
, "--hpcdir=" (++) :: [a] -> [a] -> [a]++ hpcDir :: FilePath -> FilePath -> FilePathhpcDir distPref :: StringdistPref libName :: StringlibName
, "--destdir=" (++) :: [a] -> [a] -> [a]++ tixDir :: FilePath -> TestSuite -> FilePathtixDir distPref :: StringdistPref suite :: TestSuitesuite
]
(++) :: [a] -> [a] -> [a]++ hpcOptions :: [[Char]]hpcOptions
excluded = testModules :: TestSuite -> [ModuleName]testModules suite :: TestSuitesuite (++) :: [a] -> [a] -> [a]++ [ main :: ModuleNamemain ]
runHpc opts h = runProcess ::
FilePath
-> [String]
-> Maybe FilePath
-> Maybe [(String, String)]
-> Maybe Handle
-> Maybe Handle
-> Maybe Handle
-> IO ProcessHandlerunProcess "hpc" opts :: [String]opts Nothing :: Maybe aNothing Nothing :: Maybe aNothing Nothing :: Maybe aNothing
(Just :: a -> Maybe aJust h :: Handleh) (Just :: a -> Maybe aJust h :: Handleh)
bracket :: IO a -> (a -> IO b) -> (a -> IO c) -> IO cbracket (openHpcTemp :: FilePath -> IO FilePathopenHpcTemp ($) :: (a -> b) -> a -> b$ tixDir :: FilePath -> TestSuite -> FilePathtixDir distPref :: StringdistPref suite :: TestSuitesuite) deleteIfExists :: FilePath -> IO ()deleteIfExists
($) :: (a -> b) -> a -> b$ \hpcOut -> do
hUnion <- openFile :: FilePath -> IOMode -> IO HandleopenFile hpcOut :: FilePathhpcOut AppendMode :: IOModeAppendMode
procUnion <- runHpc :: [String] -> Handle -> IO ProcessHandlerunHpc unionOptions :: [[Char]]unionOptions hUnion :: HandlehUnion
exitUnion <- waitForProcess :: ProcessHandle -> IO ExitCodewaitForProcess procUnion :: ProcessHandleprocUnion
success <- case exitUnion :: ExitCodeexitUnion of
ExitSuccess -> do
hMarkup <- openFile :: FilePath -> IOMode -> IO HandleopenFile hpcOut :: FilePathhpcOut AppendMode :: IOModeAppendMode
procMarkup <- runHpc :: [String] -> Handle -> IO ProcessHandlerunHpc markupOptions :: [[Char]]markupOptions hMarkup :: HandlehMarkup
exitMarkup <- waitForProcess :: ProcessHandle -> IO ExitCodewaitForProcess procMarkup :: ProcessHandleprocMarkup
case exitMarkup :: ExitCodeexitMarkup of
ExitSuccess -> return :: Monad m => forall a. a -> m areturn True :: BoolTrue
_ -> return :: Monad m => forall a. a -> m areturn False :: BoolFalse
_ -> return :: Monad m => forall a. a -> m areturn False :: BoolFalse
unless :: Monad m => Bool -> m () -> m ()unless success :: Boolsuccess ($) :: (a -> b) -> a -> b$ do
errs <- readFile :: FilePath -> IO StringreadFile hpcOut :: FilePathhpcOut
die :: String -> IO adie ($) :: (a -> b) -> a -> b$ "HPC failed:\n" (++) :: [a] -> [a] -> [a]++ errs :: Stringerrs
when :: Monad m => Bool -> m () -> m ()when success :: Boolsuccess ($) :: (a -> b) -> a -> b$ notice :: Verbosity -> String -> IO ()notice verbosity :: Verbosityverbosity
($) :: (a -> b) -> a -> b$ "Test coverage report written to "
(++) :: [a] -> [a] -> [a]++ tixDir :: FilePath -> TestSuite -> FilePathtixDir distPref :: StringdistPref suite :: TestSuitesuite (</>) :: FilePath -> FilePath -> FilePath</> "hpc_index"
(<.>) :: FilePath -> String -> FilePath<.> "html"
return :: Monad m => forall a. a -> m areturn ()
where openHpcTemp dir = do
(f, h) <- openTempFile :: FilePath -> String -> IO (FilePath, Handle)openTempFile dir :: FilePathdir ($) :: (a -> b) -> a -> b$ "cabal-test-hpc-" (<.>) :: 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
deleteIfExists path = do
exists <- doesFileExist :: FilePath -> IO BooldoesFileExist path :: FilePathpath
when :: Monad m => Bool -> m () -> m ()when exists :: Boolexists ($) :: (a -> b) -> a -> b$ removeFile :: FilePath -> IO ()removeFile path :: FilePathpath