11{-# LANGUAGE DeriveDataTypeable #-}
22{-# LANGUAGE FlexibleContexts #-}
3+ {-# LANGUAGE LambdaCase #-}
4+ {-# LANGUAGE NamedFieldPuns #-}
35{-# LANGUAGE OverloadedStrings #-}
46{-# LANGUAGE RankNTypes #-}
57{-# LANGUAGE RecordWildCards #-}
@@ -44,6 +46,7 @@ module Distribution.Simple.Configure
4446 , localBuildInfoFile
4547 , getInstalledPackages
4648 , getInstalledPackagesMonitorFiles
49+ , getInstalledPackagesById
4750 , getPackageDBContents
4851 , configCompilerEx
4952 , configCompilerAuxEx
@@ -56,6 +59,7 @@ module Distribution.Simple.Configure
5659 , platformDefines
5760 ) where
5861
62+ import Control.Monad
5963import Distribution.Compat.Prelude
6064import Prelude ()
6165
@@ -78,7 +82,7 @@ import Distribution.Simple.BuildTarget
7882import Distribution.Simple.BuildToolDepends
7983import Distribution.Simple.Compiler
8084import Distribution.Simple.LocalBuildInfo
81- import Distribution.Simple.PackageIndex (InstalledPackageIndex )
85+ import Distribution.Simple.PackageIndex (InstalledPackageIndex , lookupUnitId )
8286import qualified Distribution.Simple.PackageIndex as PackageIndex
8387import Distribution.Simple.PreProcess
8488import Distribution.Simple.Program
@@ -162,6 +166,7 @@ import qualified Data.Maybe as M
162166import qualified Data.Set as Set
163167import qualified Distribution.Compat.NonEmptySet as NES
164168import Distribution.Simple.Errors
169+ import Distribution.Simple.Flag (mergeListFlag )
165170import Distribution.Types.AnnotatedId
166171
167172type UseExternalInternalDeps = Bool
@@ -877,10 +882,21 @@ configure (pkg_descr0, pbi) cfg = do
877882 Map. empty
878883 buildComponents
879884
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+
880896 let lbi =
881897 (setCoverageLBI . setProfLBI)
882898 LocalBuildInfo
883- { configFlags = cfg
899+ { configFlags = cfg{configCoverageFor = mergeListFlag (configCoverageFor cfg) (toFlag extraCoverageFor)}
884900 , flagAssignment = flags
885901 , componentEnabledSpec = enabled
886902 , extraConfigArgs = [] -- Currently configure does not
@@ -1747,6 +1763,28 @@ getInstalledPackagesMonitorFiles verbosity comp packageDBs progdb platform =
17471763 ++ prettyShow other
17481764 return []
17491765
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+
17501788-- | The user interface specifies the package dbs to use with a combination of
17511789-- @--global@, @--user@ and @--package-db=global|user|clear|$file@.
17521790-- This function combines the global/user flag and interprets the package-db
0 commit comments