Skip to content

Commit 073ccc8

Browse files
alt-romesandreabedini
authored andcommitted
Per-component multi-package builds with coverage enabled
This commits re-enables per-component builds when coverage checking is enabled. This restriction was previously added in #5004 to fix #4798. - #4798 was subsequently fixed "again" with the fix for #5213, in #7493 by fixing the paths of the testsuite `.mix` files to the same location as that of the main library component. Therefore the restriction to treat testsuites per-package (legacy-fallback) is no longer needed. We went further and fixed coverage for internal sublibraries, packages with backpack (but without generating coverage information for indefinite and instantiated units -- it is not clear what it would mean for HPC to support this), and coverage for multi-package projects. 1. We allow hpc in per-component builds 2. To generate hpc files in the appropriate component directories in the distribution tree, we remove the hack from #7493 and instead determine the `.mix` directories that are included in the call to `hpc markup` by passing the list of components in the project from the cabal-install invocation of test. We also drop an unnecessary directory in the hpc file hierarchy. 3. To account for internal (non-backpack) libraries, we include the mix dirs and modules of all (non-indefinite and non-instantiations) libraries in the project Indefinite libraries and instantiations are ignored as it is not obvious what it means for HPC to support backpack, e.g. covering a library function that two different instantiations 4. We now only reject coverage if there are no libraries at all in the project, rather than if there are no libraries in the package. This allows us to drop the coverage masking logic in cabal.project.coverage while still having coverage of cabal-install (i.e. cabal test --enable-coverage cabal-install now works without the workaround) Even though we allow multi-package project coverage, we still cover each package independently -- the tix files resulting from all packages are not combined for the time being. Multi-package project coverage is fixed in Cabal, however, the paths to the source files listed in the `.mix` files will be incorrect because package sources will no longer be in the root of the project tree, but rather under the subdir with the package. We add an error for multi-package projects when coverage is enabled, and track lifting this error in #9493. Includes tests for #6440, #6397, #8609, and #4798 (the test for #5213 already exists) Fixes #6440 (internal libs coverage), #6397 (backpack breaks coverage) , doesn't yet fix #8609 (multi-package coverage report) and fixes in a new way the previously fixed #4798, #5213.
1 parent f3eafa7 commit 073ccc8

File tree

40 files changed

+326
-192
lines changed

40 files changed

+326
-192
lines changed

Cabal/src/Distribution/Simple/Flag.hs

+6
Original file line numberDiff line numberDiff line change
@@ -29,6 +29,7 @@ module Distribution.Simple.Flag
2929
, flagToMaybe
3030
, flagToList
3131
, maybeToFlag
32+
, mergeListFlag
3233
, BooleanFlag (..)
3334
) where
3435

@@ -143,6 +144,11 @@ maybeToFlag :: Maybe a -> Flag a
143144
maybeToFlag Nothing = NoFlag
144145
maybeToFlag (Just x) = Flag x
145146

147+
-- | Merge the elements of a list 'Flag' with another list 'Flag'.
148+
mergeListFlag :: Flag [a] -> Flag [a] -> Flag [a]
149+
mergeListFlag currentFlags v =
150+
Flag $ concat (flagToList currentFlags ++ flagToList v)
151+
146152
-- | Types that represent boolean flags.
147153
class BooleanFlag a where
148154
asBool :: a -> Bool

Cabal/src/Distribution/Simple/GHC/BuildGeneric.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -402,7 +402,7 @@ gbuild verbosity numJobs pkg_descr lbi bm clbi = do
402402
distPref = fromFlag $ configDistPref $ configFlags lbi
403403
hpcdir way
404404
| gbuildIsRepl bm = mempty -- HPC is not supported in ghci
405-
| isCoverageEnabled = toFlag $ Hpc.mixDir distPref way (gbuildName bm)
405+
| isCoverageEnabled = toFlag $ Hpc.mixDir distPref way
406406
| otherwise = mempty
407407

408408
rpaths <- getRPaths lbi clbi

Cabal/src/Distribution/Simple/GHC/BuildOrRepl.hs

+1-7
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,6 @@ import Control.Monad (forM_)
77
import qualified Distribution.ModuleName as ModuleName
88
import Distribution.Package
99
import Distribution.PackageDescription as PD
10-
import Distribution.Pretty
1110
import Distribution.Simple.BuildPaths
1211
import Distribution.Simple.Compiler
1312
import Distribution.Simple.Flag (Flag (..), fromFlag, toFlag)
@@ -97,15 +96,10 @@ buildOrReplLib mReplFlags verbosity numJobs pkg_descr lbi lib clbi = do
9796
-- Determine if program coverage should be enabled and if so, what
9897
-- '-hpcdir' should be.
9998
let isCoverageEnabled = libCoverage lbi
100-
-- TODO: Historically HPC files have been put into a directory which
101-
-- has the package name. I'm going to avoid changing this for
102-
-- now, but it would probably be better for this to be the
103-
-- component ID instead...
104-
pkg_name = prettyShow (PD.package pkg_descr)
10599
distPref = fromFlag $ configDistPref $ configFlags lbi
106100
hpcdir way
107101
| forRepl = mempty -- HPC is not supported in ghci
108-
| isCoverageEnabled = toFlag $ Hpc.mixDir distPref way pkg_name
102+
| isCoverageEnabled = toFlag $ Hpc.mixDir distPref way
109103
| otherwise = mempty
110104

111105
createDirectoryIfMissingVerbose verbosity True libTargetDir

Cabal/src/Distribution/Simple/GHCJS.hs

+3-8
Original file line numberDiff line numberDiff line change
@@ -481,7 +481,7 @@ buildOrReplLib
481481
-> Library
482482
-> ComponentLocalBuildInfo
483483
-> IO ()
484-
buildOrReplLib mReplFlags verbosity numJobs pkg_descr lbi lib clbi = do
484+
buildOrReplLib mReplFlags verbosity numJobs _pkg_descr lbi lib clbi = do
485485
let uid = componentUnitId clbi
486486
libTargetDir = componentBuildDir lbi clbi
487487
whenVanillaLib forceVanilla =
@@ -515,15 +515,10 @@ buildOrReplLib mReplFlags verbosity numJobs pkg_descr lbi lib clbi = do
515515
-- Determine if program coverage should be enabled and if so, what
516516
-- '-hpcdir' should be.
517517
let isCoverageEnabled = libCoverage lbi
518-
-- TODO: Historically HPC files have been put into a directory which
519-
-- has the package name. I'm going to avoid changing this for
520-
-- now, but it would probably be better for this to be the
521-
-- component ID instead...
522-
pkg_name = prettyShow (PD.package pkg_descr)
523518
distPref = fromFlag $ configDistPref $ configFlags lbi
524519
hpcdir way
525520
| forRepl = mempty -- HPC is not supported in ghci
526-
| isCoverageEnabled = toFlag $ Hpc.mixDir distPref way pkg_name
521+
| isCoverageEnabled = toFlag $ Hpc.mixDir distPref way
527522
| otherwise = mempty
528523

529524
createDirectoryIfMissingVerbose verbosity True libTargetDir
@@ -1243,7 +1238,7 @@ gbuild verbosity numJobs pkg_descr lbi bm clbi = do
12431238
distPref = fromFlag $ configDistPref $ configFlags lbi
12441239
hpcdir way
12451240
| gbuildIsRepl bm = mempty -- HPC is not supported in ghci
1246-
| isCoverageEnabled = toFlag $ Hpc.mixDir distPref way (gbuildName bm)
1241+
| isCoverageEnabled = toFlag $ Hpc.mixDir distPref way
12471242
| otherwise = mempty
12481243

12491244
rpaths <- getRPaths lbi clbi

Cabal/src/Distribution/Simple/Hpc.hs

+42-90
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
11
{-# LANGUAGE FlexibleContexts #-}
2+
{-# LANGUAGE NamedFieldPuns #-}
23
{-# LANGUAGE RankNTypes #-}
34

45
-----------------------------------------------------------------------------
@@ -22,26 +23,26 @@ module Distribution.Simple.Hpc
2223
, tixDir
2324
, tixFilePath
2425
, markupPackage
25-
, markupTest
2626
) where
2727

2828
import Distribution.Compat.Prelude
2929
import Prelude ()
3030

3131
import Distribution.ModuleName (main)
3232
import Distribution.PackageDescription
33-
( Library (..)
34-
, TestSuite (..)
33+
( TestSuite (..)
3534
, testModules
3635
)
3736
import qualified Distribution.PackageDescription as PD
3837
import Distribution.Pretty
38+
import Distribution.Simple.Flag (fromFlagOrDefault)
3939
import Distribution.Simple.LocalBuildInfo (LocalBuildInfo (..))
4040
import Distribution.Simple.Program
4141
( hpcProgram
4242
, requireProgramVersion
4343
)
4444
import Distribution.Simple.Program.Hpc (markup, union)
45+
import Distribution.Simple.Setup (TestFlags (..))
4546
import Distribution.Simple.Utils (notice)
4647
import Distribution.Types.UnqualComponentName
4748
import Distribution.Verbosity (Verbosity ())
@@ -73,44 +74,16 @@ mixDir
7374
-- ^ \"dist/\" prefix
7475
-> Way
7576
-> FilePath
76-
-- ^ Component name
77-
-> FilePath
7877
-- ^ Directory containing test suite's .mix files
79-
mixDir distPref way name = hpcDir distPrefBuild way </> "mix" </> name
80-
where
81-
-- This is a hack for HPC over test suites, needed to match the directory
82-
-- where HPC saves and reads .mix files when the main library of the same
83-
-- package is being processed, perhaps in a previous cabal run (#5213).
84-
-- E.g., @distPref@ may be
85-
-- @./dist-newstyle/build/x86_64-linux/ghc-9.0.1/cabal-gh5213-0.1/t/tests@
86-
-- but the path where library mix files reside has two less components
87-
-- at the end (@t/tests@) and this reduced path needs to be passed to
88-
-- both @hpc@ and @ghc@. For non-default optimization levels, the path
89-
-- suffix is one element longer and the extra path element needs
90-
-- to be preserved.
91-
distPrefElements = splitDirectories distPref
92-
distPrefBuild = case drop (length distPrefElements - 3) distPrefElements of
93-
["t", _, "noopt"] ->
94-
joinPath $
95-
take (length distPrefElements - 3) distPrefElements
96-
++ ["noopt"]
97-
["t", _, "opt"] ->
98-
joinPath $
99-
take (length distPrefElements - 3) distPrefElements
100-
++ ["opt"]
101-
[_, "t", _] ->
102-
joinPath $ take (length distPrefElements - 2) distPrefElements
103-
_ -> distPref
78+
mixDir distPref way = hpcDir distPref way </> "mix"
10479

10580
tixDir
10681
:: FilePath
10782
-- ^ \"dist/\" prefix
10883
-> Way
10984
-> FilePath
110-
-- ^ Component name
111-
-> FilePath
11285
-- ^ Directory containing test suite's .tix files
113-
tixDir distPref way name = hpcDir distPref way </> "tix" </> name
86+
tixDir distPref way = hpcDir distPref way </> "tix"
11487

11588
-- | Path to the .tix file containing a test suite's sum statistics.
11689
tixFilePath
@@ -121,17 +94,15 @@ tixFilePath
12194
-- ^ Component name
12295
-> FilePath
12396
-- ^ Path to test suite's .tix file
124-
tixFilePath distPref way name = tixDir distPref way name </> name <.> "tix"
97+
tixFilePath distPref way name = tixDir distPref way </> name <.> "tix"
12598

12699
htmlDir
127100
:: FilePath
128101
-- ^ \"dist/\" prefix
129102
-> Way
130103
-> FilePath
131-
-- ^ Component name
132-
-> FilePath
133104
-- ^ Path to test suite's HTML markup directory
134-
htmlDir distPref way name = hpcDir distPref way </> "html" </> name
105+
htmlDir distPref way = hpcDir distPref way </> "html"
135106

136107
-- | Attempt to guess the way the test suites in this package were compiled
137108
-- and linked with the library so the correct module interfaces are found.
@@ -141,57 +112,18 @@ guessWay lbi
141112
| withDynExe lbi = Dyn
142113
| otherwise = Vanilla
143114

144-
-- | Generate the HTML markup for a test suite.
145-
markupTest
146-
:: Verbosity
147-
-> LocalBuildInfo
148-
-> FilePath
149-
-- ^ \"dist/\" prefix
150-
-> String
151-
-- ^ Library name
152-
-> TestSuite
153-
-> Library
154-
-> IO ()
155-
markupTest verbosity lbi distPref libraryName suite library = do
156-
tixFileExists <- doesFileExist $ tixFilePath distPref way $ testName'
157-
when tixFileExists $ do
158-
-- behaviour of 'markup' depends on version, so we need *a* version
159-
-- but no particular one
160-
(hpc, hpcVer, _) <-
161-
requireProgramVersion
162-
verbosity
163-
hpcProgram
164-
anyVersion
165-
(withPrograms lbi)
166-
let htmlDir_ = htmlDir distPref way testName'
167-
markup
168-
hpc
169-
hpcVer
170-
verbosity
171-
(tixFilePath distPref way testName')
172-
mixDirs
173-
htmlDir_
174-
(exposedModules library)
175-
notice verbosity $
176-
"Test coverage report written to "
177-
++ htmlDir_
178-
</> "hpc_index" <.> "html"
179-
where
180-
way = guessWay lbi
181-
testName' = unUnqualComponentName $ testName suite
182-
mixDirs = map (mixDir distPref way) [testName', libraryName]
183-
184-
-- | Generate the HTML markup for all of a package's test suites.
115+
-- | Generate the HTML markup for a package's test suites.
185116
markupPackage
186117
:: Verbosity
118+
-> TestFlags
187119
-> LocalBuildInfo
188120
-> FilePath
189-
-- ^ \"dist/\" prefix
121+
-- ^ Testsuite \"dist/\" prefix
190122
-> PD.PackageDescription
191123
-> [TestSuite]
192124
-> IO ()
193-
markupPackage verbosity lbi distPref pkg_descr suites = do
194-
let tixFiles = map (tixFilePath distPref way) testNames
125+
markupPackage verbosity TestFlags{testCoverageDistPrefs, testCoverageLibsModules} lbi testDistPref pkg_descr suites = do
126+
let tixFiles = map (tixFilePath testDistPref way) testNames
195127
tixFilesExist <- traverse doesFileExist tixFiles
196128
when (and tixFilesExist) $ do
197129
-- behaviour of 'markup' depends on version, so we need *a* version
@@ -202,19 +134,39 @@ markupPackage verbosity lbi distPref pkg_descr suites = do
202134
hpcProgram
203135
anyVersion
204136
(withPrograms lbi)
205-
let outFile = tixFilePath distPref way libraryName
206-
htmlDir' = htmlDir distPref way libraryName
207-
excluded = concatMap testModules suites ++ [main]
208-
createDirectoryIfMissing True $ takeDirectory outFile
209-
union hpc verbosity tixFiles outFile excluded
210-
markup hpc hpcVer verbosity outFile mixDirs htmlDir' included
137+
let htmlDir' = htmlDir testDistPref way
138+
-- The tix file used to generate the report is either the testsuite's
139+
-- tix file, when there is only one testsuite, or the sum of the tix
140+
-- files of all testsuites in the package, which gets put under pkgName
141+
-- for this component (a bit weird)
142+
-- TODO: cabal-install should pass to Cabal where to put the summed tix
143+
-- and report, and perhaps even the testsuites from other packages in
144+
-- the project which are currently not accounted for in the summed
145+
-- report.
146+
tixFile <- case suites of
147+
-- We call 'markupPackage' once for each testsuite to run individually,
148+
-- to get the coverage report of just the one testsuite
149+
[oneTest] -> do
150+
let testName' = unUnqualComponentName $ testName oneTest
151+
return $
152+
tixFilePath testDistPref way testName'
153+
-- And call 'markupPackage' once per `test` invocation with all the
154+
-- testsuites to run, which results in multiple tix files being considered
155+
_ -> do
156+
let excluded = concatMap testModules suites ++ [main]
157+
pkgName = prettyShow $ PD.package pkg_descr
158+
summedTixFile = tixFilePath testDistPref way pkgName
159+
createDirectoryIfMissing True $ takeDirectory summedTixFile
160+
union hpc verbosity tixFiles summedTixFile excluded
161+
return summedTixFile
162+
163+
markup hpc hpcVer verbosity tixFile mixDirs htmlDir' included
211164
notice verbosity $
212165
"Package coverage report written to "
213166
++ htmlDir'
214167
</> "hpc_index.html"
215168
where
216169
way = guessWay lbi
217170
testNames = fmap (unUnqualComponentName . testName) suites
218-
mixDirs = map (mixDir distPref way) $ libraryName : testNames
219-
included = concatMap (exposedModules) $ PD.allLibraries pkg_descr
220-
libraryName = prettyShow $ PD.package pkg_descr
171+
mixDirs = map (`mixDir` way) (fromFlagOrDefault [] testCoverageDistPrefs)
172+
included = fromFlagOrDefault [] testCoverageLibsModules

Cabal/src/Distribution/Simple/Setup/Test.hs

+44
Original file line numberDiff line numberDiff line change
@@ -40,6 +40,7 @@ import Distribution.Simple.Utils
4040
import Distribution.Verbosity
4141
import qualified Text.PrettyPrint as Disp
4242

43+
import Distribution.ModuleName (ModuleName)
4344
import Distribution.Simple.Setup.Common
4445

4546
-- ------------------------------------------------------------
@@ -88,6 +89,15 @@ data TestFlags = TestFlags
8889
, testKeepTix :: Flag Bool
8990
, testWrapper :: Flag FilePath
9091
, testFailWhenNoTestSuites :: Flag Bool
92+
, testCoverageLibsModules :: Flag [ModuleName]
93+
-- ^ The list of all modules from libraries in the local project that should
94+
-- be included in the hpc coverage report.
95+
, testCoverageDistPrefs :: Flag [FilePath]
96+
-- ^ The path to each library local to this project and to the test
97+
-- components being built, to include in coverage reporting (notably, this
98+
-- excludes indefinite libraries and instantiations because HPC does not
99+
-- support backpack - Nov. 2023). Cabal uses these paths as dist prefixes to
100+
-- determine the path to the `mix` dirs of each component to cover.
91101
, -- TODO: think about if/how options are passed to test exes
92102
testOptions :: [PathTemplate]
93103
}
@@ -107,6 +117,8 @@ defaultTestFlags =
107117
, testKeepTix = toFlag False
108118
, testWrapper = NoFlag
109119
, testFailWhenNoTestSuites = toFlag False
120+
, testCoverageLibsModules = NoFlag
121+
, testCoverageDistPrefs = NoFlag
110122
, testOptions = []
111123
}
112124

@@ -212,6 +224,38 @@ testOptions' showOrParseArgs =
212224
testFailWhenNoTestSuites
213225
(\v flags -> flags{testFailWhenNoTestSuites = v})
214226
trueArg
227+
, option
228+
[]
229+
["coverage-module"]
230+
"Module of a project-local library to include in the HPC report"
231+
testCoverageLibsModules
232+
( \v flags ->
233+
flags
234+
{ testCoverageLibsModules =
235+
mergeListFlag (testCoverageLibsModules flags) v
236+
}
237+
)
238+
( reqArg'
239+
"MODULE"
240+
(Flag . (: []) . fromString)
241+
(fmap prettyShow . fromFlagOrDefault [])
242+
)
243+
, option
244+
[]
245+
["coverage-dist-dir"]
246+
"The directory where Cabal puts generated build files of an HPC enabled component"
247+
testCoverageDistPrefs
248+
( \v flags ->
249+
flags
250+
{ testCoverageDistPrefs =
251+
mergeListFlag (testCoverageDistPrefs flags) v
252+
}
253+
)
254+
( reqArg'
255+
"DIR"
256+
(Flag . (: []))
257+
(fromFlagOrDefault [])
258+
)
215259
, option
216260
[]
217261
["test-options"]

Cabal/src/Distribution/Simple/Test.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -133,7 +133,7 @@ test args pkg_descr lbi flags = do
133133
writeFile packageLogFile $ show packageLog
134134

135135
when (LBI.testCoverage lbi) $
136-
markupPackage verbosity lbi distPref pkg_descr $
136+
markupPackage verbosity flags lbi distPref pkg_descr $
137137
map (fst . fst) testsToRun
138138

139139
unless allOk exitFailure

0 commit comments

Comments
 (0)