Skip to content

Commit 6154796

Browse files
committed
Fix #2066: buildDepends is just an accessor function, not a field
- Post flag-solving, replace buildDepends with solved dependencies. - In most cases, just collect the build-depends of *enabled* components. B4ut in a few, we have no enable spec on hand and must collect them all
1 parent 6750de6 commit 6154796

File tree

14 files changed

+74
-101
lines changed

14 files changed

+74
-101
lines changed

Cabal/Distribution/PackageDescription.hs

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -83,6 +83,8 @@ module Distribution.PackageDescription (
8383
hcStaticOptions,
8484

8585
-- ** Supplementary build information
86+
allBuildDepends,
87+
enabledBuildDepends,
8688
ComponentName(..),
8789
defaultLibName,
8890
HookedBuildInfo,

Cabal/Distribution/PackageDescription/Check.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1369,7 +1369,7 @@ checkCabalVersion pkg =
13691369
_ -> False
13701370

13711371
versionRangeExpressions =
1372-
[ dep | dep@(Dependency _ vr) <- buildDepends pkg
1372+
[ dep | dep@(Dependency _ vr) <- allBuildDepends pkg
13731373
, usesNewVersionRangeSyntax vr ]
13741374

13751375
testedWithVersionRangeExpressions =
@@ -1397,10 +1397,10 @@ checkCabalVersion pkg =
13971397
alg (VersionRangeParensF _) = 3
13981398
alg _ = 1 :: Int
13991399

1400-
depsUsingWildcardSyntax = [ dep | dep@(Dependency _ vr) <- buildDepends pkg
1400+
depsUsingWildcardSyntax = [ dep | dep@(Dependency _ vr) <- allBuildDepends pkg
14011401
, usesWildcardSyntax vr ]
14021402

1403-
depsUsingMajorBoundSyntax = [ dep | dep@(Dependency _ vr) <- buildDepends pkg
1403+
depsUsingMajorBoundSyntax = [ dep | dep@(Dependency _ vr) <- allBuildDepends pkg
14041404
, usesMajorBoundSyntax vr ]
14051405

14061406
usesBackpackIncludes = any (not . null . mixins) (allBuildInfo pkg)
@@ -1547,7 +1547,7 @@ checkPackageVersions pkg =
15471547
foldr intersectVersionRanges anyVersion baseDeps
15481548
where
15491549
baseDeps =
1550-
[ vr | Dependency pname vr <- buildDepends pkg'
1550+
[ vr | Dependency pname vr <- allBuildDepends pkg'
15511551
, pname == mkPackageName "base" ]
15521552

15531553
-- Just in case finalizePD fails for any reason,

Cabal/Distribution/PackageDescription/Configuration.hs

Lines changed: 32 additions & 46 deletions
Original file line numberDiff line numberDiff line change
@@ -44,8 +44,10 @@ import Distribution.Compiler
4444
import Distribution.System
4545
import Distribution.Simple.Utils
4646
import Distribution.Text
47+
import Distribution.Compat.Lens
4748
import Distribution.Compat.ReadP as ReadP hiding ( char )
4849
import qualified Distribution.Compat.ReadP as ReadP ( char )
50+
import qualified Distribution.Types.BuildInfo.Lens as L
4951
import Distribution.Types.ComponentRequestedSpec
5052
import Distribution.Types.ForeignLib
5153
import Distribution.Types.Component
@@ -351,18 +353,18 @@ overallDependencies enabled (TargetSet targets) = mconcat depss
351353
-- | Collect up the targets in a TargetSet of tagged targets, storing the
352354
-- dependencies as we go.
353355
flattenTaggedTargets :: TargetSet PDTagged -> (Maybe Library, [(UnqualComponentName, Component)])
354-
flattenTaggedTargets (TargetSet targets) = foldr untag (Nothing, []) targets
355-
where
356-
untag (_, Lib _) (Just _, _) = userBug "Only one library expected"
357-
untag (_, Lib l) (Nothing, comps) = (Just l, comps)
358-
untag (_, SubComp n c) (mb_lib, comps)
359-
| any ((== n) . fst) comps =
360-
userBug $ "There exist several components with the same name: '" ++ unUnqualComponentName n ++ "'"
361-
362-
| otherwise = (mb_lib, (n, c) : comps)
363-
364-
untag (_, PDNull) x = x -- actually this should not happen, but let's be liberal
365-
356+
flattenTaggedTargets (TargetSet targets) = foldr untag (Nothing, []) targets where
357+
untag (depMap, pdTagged) accum = case (pdTagged, accum) of
358+
(Lib _, (Just _, _)) -> userBug "Only one library expected"
359+
(Lib l, (Nothing, comps)) -> (Just $ redoBD l, comps)
360+
(SubComp n c, (mb_lib, comps))
361+
| any ((== n) . fst) comps ->
362+
userBug $ "There exist several components with the same name: '" ++ display n ++ "'"
363+
| otherwise -> (mb_lib, (n, redoBD c) : comps)
364+
(PDNull, x) -> x -- actually this should not happen, but let's be liberal
365+
where
366+
redoBD :: L.HasBuildInfo a => a -> a
367+
redoBD = set L.targetBuildDepends $ fromDepMap depMap
366368

367369
------------------------------------------------------------------------------
368370
-- Convert GenericPackageDescription to PackageDescription
@@ -447,7 +449,6 @@ finalizePD userflags enabled satisfyDep
447449
, executables = exes'
448450
, testSuites = tests'
449451
, benchmarks = bms'
450-
, buildDepends = fromDepMap (overallDependencies enabled targetSet)
451452
}
452453
, flagVals )
453454
where
@@ -517,38 +518,25 @@ flattenPackageDescription
517518
, executables = reverse exes
518519
, testSuites = reverse tests
519520
, benchmarks = reverse bms
520-
, buildDepends = ldeps
521-
++ reverse sub_ldeps
522-
++ reverse pldeps
523-
++ reverse edeps
524-
++ reverse tdeps
525-
++ reverse bdeps
526521
}
527522
where
528-
(mlib, ldeps) = case mlib0 of
529-
Just lib -> let (l,ds) = ignoreConditions lib in
530-
(Just ((libFillInDefaults l) { libName = Nothing }), ds)
531-
Nothing -> (Nothing, [])
532-
(sub_libs, sub_ldeps) = foldr flattenLib ([],[]) sub_libs0
533-
(flibs, pldeps) = foldr flattenFLib ([],[]) flibs0
534-
(exes, edeps) = foldr flattenExe ([],[]) exes0
535-
(tests, tdeps) = foldr flattenTst ([],[]) tests0
536-
(bms, bdeps) = foldr flattenBm ([],[]) bms0
537-
flattenLib (n, t) (es, ds) =
538-
let (e, ds') = ignoreConditions t in
539-
( (libFillInDefaults $ e { libName = Just n, libExposed = False }) : es, ds' ++ ds )
540-
flattenFLib (n, t) (es, ds) =
541-
let (e, ds') = ignoreConditions t in
542-
( (flibFillInDefaults $ e { foreignLibName = n }) : es, ds' ++ ds )
543-
flattenExe (n, t) (es, ds) =
544-
let (e, ds') = ignoreConditions t in
545-
( (exeFillInDefaults $ e { exeName = n }) : es, ds' ++ ds )
546-
flattenTst (n, t) (es, ds) =
547-
let (e, ds') = ignoreConditions t in
548-
( (testFillInDefaults $ e { testName = n }) : es, ds' ++ ds )
549-
flattenBm (n, t) (es, ds) =
550-
let (e, ds') = ignoreConditions t in
551-
( (benchFillInDefaults $ e { benchmarkName = n }) : es, ds' ++ ds )
523+
mlib = f <$> mlib0
524+
where f lib = (libFillInDefaults . fst . ignoreConditions $ lib) { libName = Nothing }
525+
sub_libs = flattenLib <$> sub_libs0
526+
flibs = flattenFLib <$> flibs0
527+
exes = flattenExe <$> exes0
528+
tests = flattenTst <$> tests0
529+
bms = flattenBm <$> bms0
530+
flattenLib (n, t) = libFillInDefaults $ (fst $ ignoreConditions t)
531+
{ libName = Just n, libExposed = False }
532+
flattenFLib (n, t) = flibFillInDefaults $ (fst $ ignoreConditions t)
533+
{ foreignLibName = n }
534+
flattenExe (n, t) = exeFillInDefaults $ (fst $ ignoreConditions t)
535+
{ exeName = n }
536+
flattenTst (n, t) = testFillInDefaults $ (fst $ ignoreConditions t)
537+
{ testName = n }
538+
flattenBm (n, t) = benchFillInDefaults $ (fst $ ignoreConditions t)
539+
{ benchmarkName = n }
552540

553541
-- This is in fact rather a hack. The original version just overrode the
554542
-- default values, however, when adding conditions we had to switch to a
@@ -620,12 +608,10 @@ transformAllBuildDepends f gpd = gpd'
620608
where
621609
onBI bi = bi { targetBuildDepends = map f $ targetBuildDepends bi }
622610
onSBI stp = stp { setupDepends = map f $ setupDepends stp }
623-
onPD pd = pd { buildDepends = map f $ buildDepends pd }
624611

625-
pd' = onPD $ packageDescription gpd
626612
gpd' = transformAllCondTrees id id id id (map f)
627613
. transformAllBuildInfos onBI onSBI
628-
$ gpd { packageDescription = pd' }
614+
$ gpd
629615

630616
-- | Walk all 'CondTree's inside a 'GenericPackageDescription' and apply
631617
-- appropriate transformations to all nodes. Helper function used by

Cabal/Distribution/PackageDescription/FieldGrammar.hs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -86,7 +86,6 @@ packageDescriptionFieldGrammar = PackageDescription
8686
<*> optionalFieldDefAla "description" FreeText L.description ""
8787
<*> optionalFieldDefAla "category" FreeText L.category ""
8888
<*> prefixedFields "x-" L.customFieldsPD
89-
<*> pure [] -- build-depends
9089
<*> optionalField "build-type" L.buildTypeRaw
9190
<*> pure Nothing -- custom-setup
9291
-- components

Cabal/Distribution/Simple/Build.hs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -481,7 +481,6 @@ testSuiteLibV09AsLibAndExe pkg_descr
481481
}
482482
pkg = pkg_descr {
483483
package = (package pkg_descr) { pkgName = mkPackageName $ unMungedPackageName compat_name }
484-
, buildDepends = targetBuildDepends $ testBuildInfo test
485484
, executables = []
486485
, testSuites = []
487486
, subLibraries = [lib]

Cabal/Distribution/Simple/Configure.hs

Lines changed: 4 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -470,15 +470,6 @@ configure (pkg_descr0, pbi) cfg = do
470470

471471
debug verbosity $ "Finalized package description:\n"
472472
++ showPackageDescription pkg_descr
473-
-- NB: showPackageDescription does not display the AWFUL HACK GLOBAL
474-
-- buildDepends, so we have to display it separately. See #2066
475-
-- Some day, we should eliminate this, so that
476-
-- configureFinalizedPackage returns the set of overall dependencies
477-
-- separately. Then 'configureDependencies' and
478-
-- 'Distribution.PackageDescription.Check' need to be adjusted
479-
-- accordingly.
480-
debug verbosity $ "Finalized build-depends: "
481-
++ intercalate ", " (map display (buildDepends pkg_descr))
482473

483474
checkCompilerProblems verbosity comp pkg_descr enabled
484475
checkPackageProblems verbosity pkg_descr0
@@ -513,6 +504,7 @@ configure (pkg_descr0, pbi) cfg = do
513504
installedPackageSet
514505
requiredDepsMap
515506
pkg_descr
507+
enabled
516508

517509
-- Compute installation directory templates, based on user
518510
-- configuration.
@@ -1017,14 +1009,15 @@ configureDependencies
10171009
-> InstalledPackageIndex -- ^ installed packages
10181010
-> Map PackageName InstalledPackageInfo -- ^ required deps
10191011
-> PackageDescription
1012+
-> ComponentRequestedSpec
10201013
-> IO [PreExistingComponent]
10211014
configureDependencies verbosity use_external_internal_deps
1022-
internalPackageSet installedPackageSet requiredDepsMap pkg_descr = do
1015+
internalPackageSet installedPackageSet requiredDepsMap pkg_descr enableSpec = do
10231016
let failedDeps :: [FailedDependency]
10241017
allPkgDeps :: [ResolvedDependency]
10251018
(failedDeps, allPkgDeps) = partitionEithers
10261019
[ (\s -> (dep, s)) <$> status
1027-
| dep <- buildDepends pkg_descr
1020+
| dep <- enabledBuildDepends pkg_descr enableSpec
10281021
, let status = selectDependency (package pkg_descr)
10291022
internalPackageSet installedPackageSet
10301023
requiredDepsMap use_external_internal_deps dep ]

Cabal/Distribution/Types/BuildInfo.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -150,7 +150,7 @@ instance Monoid BuildInfo where
150150
staticOptions = [],
151151
customFieldsBI = [],
152152
targetBuildDepends = [],
153-
mixins = []
153+
mixins = []
154154
}
155155
mappend = (<>)
156156

@@ -196,7 +196,7 @@ instance Semigroup BuildInfo where
196196
staticOptions = combine staticOptions,
197197
customFieldsBI = combine customFieldsBI,
198198
targetBuildDepends = combineNub targetBuildDepends,
199-
mixins = combine mixins
199+
mixins = combine mixins
200200
}
201201
where
202202
combine field = field a `mappend` field b

Cabal/Distribution/Types/PackageDescription.hs

Lines changed: 11 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -49,6 +49,8 @@ module Distribution.Types.PackageDescription (
4949
withForeignLib,
5050
allBuildInfo,
5151
enabledBuildInfos,
52+
allBuildDepends,
53+
enabledBuildDepends,
5254
updatePackageDescription,
5355
pkgComponents,
5456
pkgBuildableComponents,
@@ -60,6 +62,8 @@ module Distribution.Types.PackageDescription (
6062
import Prelude ()
6163
import Distribution.Compat.Prelude
6264

65+
import Control.Monad ((<=<))
66+
6367
import Distribution.Types.Library
6468
import Distribution.Types.TestSuite
6569
import Distribution.Types.Executable
@@ -124,18 +128,6 @@ data PackageDescription
124128
-- with x-, stored in a
125129
-- simple assoc-list.
126130

127-
-- | YOU PROBABLY DON'T WANT TO USE THIS FIELD. This field is
128-
-- special! Depending on how far along processing the
129-
-- PackageDescription we are, the contents of this field are
130-
-- either nonsense, or the collected dependencies of *all* the
131-
-- components in this package. buildDepends is initialized by
132-
-- 'finalizePD' and 'flattenPackageDescription';
133-
-- prior to that, dependency info is stored in the 'CondTree'
134-
-- built around a 'GenericPackageDescription'. When this
135-
-- resolution is done, dependency info is written to the inner
136-
-- 'BuildInfo' and this field. This is all horrible, and #2066
137-
-- tracks progress to get rid of this field.
138-
buildDepends :: [Dependency],
139131
-- | The original @build-type@ value as parsed from the
140132
-- @.cabal@ file without defaulting. See also 'buildType'.
141133
--
@@ -247,7 +239,6 @@ emptyPackageDescription
247239
author = "",
248240
stability = "",
249241
testedWith = [],
250-
buildDepends = [],
251242
homepage = "",
252243
pkgUrl = "",
253244
bugReports = "",
@@ -398,6 +389,13 @@ enabledBuildInfos pkg enabled =
398389
-- * Utils
399390
-- ------------------------------------------------------------
400391

392+
allBuildDepends :: PackageDescription -> [Dependency]
393+
allBuildDepends = targetBuildDepends <=< allBuildInfo
394+
395+
enabledBuildDepends :: PackageDescription -> ComponentRequestedSpec -> [Dependency]
396+
enabledBuildDepends spec pd = targetBuildDepends =<< enabledBuildInfos spec pd
397+
398+
401399
updatePackageDescription :: HookedBuildInfo -> PackageDescription -> PackageDescription
402400
updatePackageDescription (mb_lib_bi, exe_bi) p
403401
= p{ executables = updateExecutables exe_bi (executables p)

Cabal/Distribution/Types/PackageDescription/Lens.hs

Lines changed: 0 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -11,7 +11,6 @@ import Distribution.Compiler (CompilerFlavor)
1111
import Distribution.License (License)
1212
import Distribution.Types.Benchmark (Benchmark)
1313
import Distribution.Types.BuildType (BuildType)
14-
import Distribution.Types.Dependency (Dependency)
1514
import Distribution.Types.Executable (Executable)
1615
import Distribution.Types.ForeignLib (ForeignLib)
1716
import Distribution.Types.Library (Library)
@@ -89,10 +88,6 @@ customFieldsPD :: Lens' PackageDescription [(String,String)]
8988
customFieldsPD f s = fmap (\x -> s { T.customFieldsPD = x }) (f (T.customFieldsPD s))
9089
{-# INLINE customFieldsPD #-}
9190

92-
buildDepends :: Lens' PackageDescription [Dependency]
93-
buildDepends f s = fmap (\x -> s { T.buildDepends = x }) (f (T.buildDepends s))
94-
{-# INLINE buildDepends #-}
95-
9691
specVersionRaw :: Lens' PackageDescription (Either Version VersionRange)
9792
specVersionRaw f s = fmap (\x -> s { T.specVersionRaw = x }) (f (T.specVersionRaw s))
9893
{-# INLINE specVersionRaw #-}

cabal-install/Distribution/Client/Dependency.hs

Lines changed: 8 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -930,24 +930,24 @@ configuredPackageProblems platform cinfo
930930
(sortNubOn dependencyName required)
931931
(sortNubOn packageName specified)
932932

933+
compSpec = enableStanzas stanzas
933934
-- TODO: It would be nicer to use ComponentDeps here so we can be more
934-
-- precise in our checks. That's a bit tricky though, as this currently
935-
-- relies on the 'buildDepends' field of 'PackageDescription'. (OTOH, that
936-
-- field is deprecated and should be removed anyway.) As long as we _do_
937-
-- use a flat list here, we have to allow for duplicates when we fold
938-
-- specifiedDeps; once we have proper ComponentDeps here we should get rid
939-
-- of the `nubOn` in `mergeDeps`.
935+
-- precise in our checks. In fact, this no longer relies on buildDepends and
936+
-- thus should be easier to fix. As long as we _do_ use a flat list here, we
937+
-- have to allow for duplicates when we fold specifiedDeps; once we have
938+
-- proper ComponentDeps here we should get rid of the `nubOn` in
939+
-- `mergeDeps`.
940940
requiredDeps :: [Dependency]
941941
requiredDeps =
942942
--TODO: use something lower level than finalizePD
943943
case finalizePD specifiedFlags
944-
(enableStanzas stanzas)
944+
compSpec
945945
(const True)
946946
platform cinfo
947947
[]
948948
(packageDescription pkg) of
949949
Right (resolvedPkg, _) ->
950-
externalBuildDepends resolvedPkg
950+
externalBuildDepends resolvedPkg compSpec
951951
++ maybe [] PD.setupDepends (PD.setupBuildInfo resolvedPkg)
952952
Left _ ->
953953
error "configuredPackageInvalidDeps internal error"

cabal-install/Distribution/Client/GenBounds.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -29,7 +29,7 @@ import Distribution.Client.Setup
2929
import Distribution.Package
3030
( Package(..), unPackageName, packageName, packageVersion )
3131
import Distribution.PackageDescription
32-
( buildDepends )
32+
( enabledBuildDepends )
3333
import Distribution.PackageDescription.Configuration
3434
( finalizePD )
3535
import Distribution.PackageDescription.Parsec
@@ -122,7 +122,7 @@ genBounds verbosity packageDBs repoCtxt comp platform progdb mSandboxPkgInfo
122122
Left _ -> putStrLn "finalizePD failed"
123123
Right (pd,_) -> do
124124
let needBounds = filter (not . hasUpperBound . depVersion) $
125-
buildDepends pd
125+
enabledBuildDepends pd defaultComponentRequestedSpec
126126

127127
if (null needBounds)
128128
then putStrLn

cabal-install/Distribution/Client/List.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -470,7 +470,7 @@ mergePackageInfo versionPref installedPkgs sourcePkgs selectedPkg showVer =
470470
source,
471471
dependencies =
472472
combine (map (SourceDependency . simplifyDependency)
473-
. Source.buildDepends) source
473+
. Source.allBuildDepends) source
474474
(map InstalledDependency . Installed.depends) installed,
475475
haddockHtml = fromMaybe "" . join
476476
. fmap (listToMaybe . Installed.haddockHTMLs)

cabal-install/Distribution/Client/Outdated.hs

Lines changed: 3 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -27,9 +27,8 @@ import Distribution.Solver.Types.PackageConstraint
2727
import Distribution.Solver.Types.PackageIndex
2828
import Distribution.Client.Sandbox.PackageEnvironment
2929

30-
import Distribution.Package (PackageName
31-
,packageVersion)
32-
import Distribution.PackageDescription (buildDepends)
30+
import Distribution.Package (PackageName, packageVersion)
31+
import Distribution.PackageDescription (allBuildDepends)
3332
import Distribution.PackageDescription.Configuration (finalizePD)
3433
import Distribution.Simple.Compiler (Compiler, compilerInfo)
3534
import Distribution.Simple.Setup (fromFlagOrDefault)
@@ -152,7 +151,7 @@ depsFromPkgDesc verbosity comp platform = do
152151
case epd of
153152
Left _ -> die' verbosity "finalizePD failed"
154153
Right (pd, _) -> do
155-
let bd = buildDepends pd
154+
let bd = allBuildDepends pd
156155
debug verbosity
157156
"Reading the list of dependencies from the package description"
158157
return bd

0 commit comments

Comments
 (0)