77{-# LANGUAGE RecordWildCards #-}
88{-# LANGUAGE TypeFamilies #-}
99{-# LANGUAGE ViewPatterns #-}
10- {-# LANGUAGE NoMonoLocalBinds #-} -- MUST come after TypeFamilies because TypeFamilies imply MonoLocalBinds
10+ -- MUST come after TypeFamilies because TypeFamilies imply MonoLocalBinds
11+ {-# LANGUAGE NoMonoLocalBinds #-}
1112
1213-- | Planning how to build everything in a project.
1314module Distribution.Client.ProjectPlanning
@@ -148,10 +149,11 @@ import Distribution.Simple.Program.Db
148149import Distribution.Simple.Program.Find
149150import Distribution.Simple.Setup
150151 ( Flag (.. )
152+ , TestFlags (testCoverageDistPrefs )
151153 , flagToList
152154 , flagToMaybe
153155 , fromFlagOrDefault
154- , toFlag , TestFlags ( testCoverageDistPrefs )
156+ , toFlag
155157 )
156158import qualified Distribution.Simple.Setup as Cabal
157159import Distribution.System
@@ -1724,7 +1726,7 @@ elaborateInstallPlan
17241726 dieProgress $
17251727 text " Internal libraries only supported with per-component builds."
17261728 $$ text " Per-component builds were disabled because"
1727- <+> fsep (punctuate comma reasons)
1729+ <+> fsep (punctuate comma reasons)
17281730 -- TODO: Maybe exclude Backpack too
17291731
17301732 elab0 = elaborateSolverToCommon spkg
@@ -4306,7 +4308,7 @@ setupHsTestFlags plan (ElaboratedConfiguredPackage{..}) sharedConfig verbosity d
43064308 covLibsDistPref = map (distBuildDirectory distDirLayout . elabDistDirParams sharedConfig) librariesToCover
43074309 -- The list of modules from libraries to consider in hpc, that Cabal passes to the hpc markup call
43084310 -- This list includes all modules, not only the exposed ones.
4309- covIncludeModules = concatMap (\ ElaboratedConfiguredPackage {elabModuleShape= modShape} -> Map. keys $ modShapeProvides modShape) librariesToCover
4311+ covIncludeModules = concatMap (\ ElaboratedConfiguredPackage {elabModuleShape = modShape} -> Map. keys $ modShapeProvides modShape) librariesToCover
43104312
43114313 -- The list of non-pre-existing libraries without module holes, i.e. the
43124314 -- main library and sub-libraries components of all the local packages in
@@ -4316,18 +4318,21 @@ setupHsTestFlags plan (ElaboratedConfiguredPackage{..}) sharedConfig verbosity d
43164318 -- this seemingly includes the packages that are not local to the project?!
43174319 -- Weird, because we filter on localToProject!
43184320 -- Try it on cabal-install: cabal test --enable-coverage cabal-install
4319- librariesToCover
4320- = mapMaybe (\ case
4321- InstallPlan. Installed elab@ ElaboratedConfiguredPackage {elabModuleShape= modShape}
4321+ librariesToCover =
4322+ mapMaybe
4323+ ( \ case
4324+ InstallPlan. Installed elab@ ElaboratedConfiguredPackage {elabModuleShape = modShape}
43224325 | elabLocalToProject
4323- , not (isIndefiniteOrInstantiation modShape)
4324- -> Just elab
4325- InstallPlan. Configured elab@ ElaboratedConfiguredPackage {elabModuleShape= modShape}
4326+ , not (isIndefiniteOrInstantiation modShape) ->
4327+ Just elab
4328+ InstallPlan. Configured elab@ ElaboratedConfiguredPackage {elabModuleShape = modShape}
43264329 | elabLocalToProject
4327- , not (isIndefiniteOrInstantiation modShape)
4328- -> Just elab
4330+ , not (isIndefiniteOrInstantiation modShape) ->
4331+ Just elab
43294332 _ -> Nothing
4330- ) $ Graph. toList $ InstallPlan. toGraph plan
4333+ )
4334+ $ Graph. toList
4335+ $ InstallPlan. toGraph plan
43314336
43324337 isIndefiniteOrInstantiation :: ModuleShape -> Bool
43334338 isIndefiniteOrInstantiation = not . Set. null . modShapeRequires
@@ -4465,7 +4470,6 @@ setupHsHaddockArgs :: ElaboratedConfiguredPackage -> [String]
44654470setupHsHaddockArgs elab =
44664471 map (showComponentTarget (packageId elab)) (elabHaddockTargets elab)
44674472
4468-
44694473------------------------------------------------------------------------------
44704474
44714475-- * Sharing installed packages
0 commit comments