1
1
{-# LANGUAGE DeriveDataTypeable #-}
2
2
{-# LANGUAGE FlexibleContexts #-}
3
+ {-# LANGUAGE LambdaCase #-}
4
+ {-# LANGUAGE NamedFieldPuns #-}
3
5
{-# LANGUAGE OverloadedStrings #-}
4
6
{-# LANGUAGE RankNTypes #-}
5
7
{-# LANGUAGE RecordWildCards #-}
@@ -44,6 +46,7 @@ module Distribution.Simple.Configure
44
46
, localBuildInfoFile
45
47
, getInstalledPackages
46
48
, getInstalledPackagesMonitorFiles
49
+ , getInstalledPackagesById
47
50
, getPackageDBContents
48
51
, configCompilerEx
49
52
, configCompilerAuxEx
@@ -56,6 +59,7 @@ module Distribution.Simple.Configure
56
59
, platformDefines
57
60
) where
58
61
62
+ import Control.Monad
59
63
import Distribution.Compat.Prelude
60
64
import Prelude ()
61
65
@@ -78,7 +82,7 @@ import Distribution.Simple.BuildTarget
78
82
import Distribution.Simple.BuildToolDepends
79
83
import Distribution.Simple.Compiler
80
84
import Distribution.Simple.LocalBuildInfo
81
- import Distribution.Simple.PackageIndex (InstalledPackageIndex )
85
+ import Distribution.Simple.PackageIndex (InstalledPackageIndex , lookupUnitId )
82
86
import qualified Distribution.Simple.PackageIndex as PackageIndex
83
87
import Distribution.Simple.PreProcess
84
88
import Distribution.Simple.Program
@@ -162,6 +166,7 @@ import qualified Data.Maybe as M
162
166
import qualified Data.Set as Set
163
167
import qualified Distribution.Compat.NonEmptySet as NES
164
168
import Distribution.Simple.Errors
169
+ import Distribution.Simple.Flag (mergeListFlag )
165
170
import Distribution.Types.AnnotatedId
166
171
167
172
type UseExternalInternalDeps = Bool
@@ -877,10 +882,21 @@ configure (pkg_descr0, pbi) cfg = do
877
882
Map. empty
878
883
buildComponents
879
884
885
+ -- For whole-package configure, we have to determine the additional
886
+ -- configCoverageFor of the main lib and sub libs here.
887
+ let extraCoverageFor :: [UnitId ] = case enabled of
888
+ -- Whole package configure, add package libs
889
+ ComponentRequestedSpec {} -> mapMaybe (\ case LibComponentLocalBuildInfo {componentUnitId} -> Just componentUnitId; _ -> Nothing ) buildComponents
890
+ -- Component configure, no need to do anything
891
+ OneComponentRequestedSpec {} -> []
892
+
893
+ -- TODO: Should we also enforce something here on that --coverage-for cannot
894
+ -- include indefinite components or instantiations?
895
+
880
896
let lbi =
881
897
(setCoverageLBI . setProfLBI)
882
898
LocalBuildInfo
883
- { configFlags = cfg
899
+ { configFlags = cfg{configCoverageFor = mergeListFlag (configCoverageFor cfg) (toFlag extraCoverageFor)}
884
900
, flagAssignment = flags
885
901
, componentEnabledSpec = enabled
886
902
, extraConfigArgs = [] -- Currently configure does not
@@ -1747,6 +1763,28 @@ getInstalledPackagesMonitorFiles verbosity comp packageDBs progdb platform =
1747
1763
++ prettyShow other
1748
1764
return []
1749
1765
1766
+ -- | Looks up the 'InstalledPackageInfo' of the given 'UnitId's from the
1767
+ -- 'PackageDBStack' in the 'LocalBuildInfo'.
1768
+ getInstalledPackagesById
1769
+ :: (Exception (VerboseException exception ), Show exception , Typeable exception )
1770
+ => Verbosity
1771
+ -> LocalBuildInfo
1772
+ -> (UnitId -> exception )
1773
+ -- ^ Construct an exception that is thrown if a
1774
+ -- unit-id is not found in the installed packages,
1775
+ -- from the unit-id that is missing.
1776
+ -> [UnitId ]
1777
+ -- ^ The unit ids to lookup in the installed packages
1778
+ -> IO [InstalledPackageInfo ]
1779
+ getInstalledPackagesById verbosity LocalBuildInfo {compiler, withPackageDB, withPrograms} mkException unitids = do
1780
+ ipindex <- getInstalledPackages verbosity compiler withPackageDB withPrograms
1781
+ mapM
1782
+ ( \ uid -> case lookupUnitId ipindex uid of
1783
+ Nothing -> dieWithException verbosity (mkException uid)
1784
+ Just ipkg -> return ipkg
1785
+ )
1786
+ unitids
1787
+
1750
1788
-- | The user interface specifies the package dbs to use with a combination of
1751
1789
-- @--global@, @--user@ and @--package-db=global|user|clear|$file@.
1752
1790
-- This function combines the global/user flag and interprets the package-db
0 commit comments