Skip to content

Commit 4aeeb7b

Browse files
committed
Fix haskell#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 790b3d6 commit 4aeeb7b

File tree

15 files changed

+89
-98
lines changed

15 files changed

+89
-98
lines changed

Cabal/Distribution/PackageDescription.hs

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

8484
-- ** Supplementary build information
85+
allBuildDepends,
86+
enabledBuildDepends,
8587
ComponentName(..),
8688
defaultLibName,
8789
HookedBuildInfo,

Cabal/Distribution/PackageDescription/Check.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1292,7 +1292,7 @@ checkCabalVersion pkg =
12921292
_ -> False
12931293

12941294
versionRangeExpressions =
1295-
[ dep | dep@(Dependency _ vr) <- buildDepends pkg
1295+
[ dep | dep@(Dependency _ vr) <- allBuildDepends pkg
12961296
, usesNewVersionRangeSyntax vr ]
12971297

12981298
testedWithVersionRangeExpressions =
@@ -1331,10 +1331,10 @@ checkCabalVersion pkg =
13311331
(+) (+)
13321332
(const 3) -- uses new ()'s syntax
13331333

1334-
depsUsingWildcardSyntax = [ dep | dep@(Dependency _ vr) <- buildDepends pkg
1334+
depsUsingWildcardSyntax = [ dep | dep@(Dependency _ vr) <- allBuildDepends pkg
13351335
, usesWildcardSyntax vr ]
13361336

1337-
depsUsingMajorBoundSyntax = [ dep | dep@(Dependency _ vr) <- buildDepends pkg
1337+
depsUsingMajorBoundSyntax = [ dep | dep@(Dependency _ vr) <- allBuildDepends pkg
13381338
, usesMajorBoundSyntax vr ]
13391339

13401340
usesBackpackIncludes = any (not . null . mixins) (allBuildInfo pkg)
@@ -1524,7 +1524,7 @@ checkPackageVersions pkg =
15241524
foldr intersectVersionRanges anyVersion baseDeps
15251525
where
15261526
baseDeps =
1527-
[ vr | Dependency pname vr <- buildDepends pkg'
1527+
[ vr | Dependency pname vr <- allBuildDepends pkg'
15281528
, pname == mkPackageName "base" ]
15291529

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

Cabal/Distribution/PackageDescription/Configuration.hs

Lines changed: 33 additions & 46 deletions
Original file line numberDiff line numberDiff line change
@@ -351,18 +351,21 @@ overallDependencies enabled (TargetSet targets) = mconcat depss
351351
-- | Collect up the targets in a TargetSet of tagged targets, storing the
352352
-- dependencies as we go.
353353
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-
354+
flattenTaggedTargets (TargetSet targets) = foldr untag (Nothing, []) targets where
355+
untag (depMap, pdTagged) accum = case (pdTagged, accum) of
356+
(Lib _, (Just _, _)) -> userBug "Only one library expected"
357+
(Lib l, (Nothing, comps)) -> (Just $ redoBD lensLibBD l, comps)
358+
(SubComp n c, (mb_lib, comps))
359+
| any ((== n) . fst) comps ->
360+
userBug $ "There exist several components with the same name: '" ++ display n ++ "'"
361+
| otherwise -> (mb_lib, (n, redoBD lensBuildInfo c) : comps)
362+
(PDNull, x) -> x -- actually this should not happen, but let's be liberal
363+
where
364+
redoBD :: ((BuildInfo -> BuildInfo) -> (a -> a)) -> (a -> a)
365+
redoBD bd_lens = bd_lens $ \bi -> bi { targetBuildDepends = fromDepMap depMap }
366+
367+
lensLibBD :: (BuildInfo -> BuildInfo) -> (Library -> Library)
368+
lensLibBD f = \l -> l { libBuildInfo = f $ libBuildInfo l }
366369

367370
------------------------------------------------------------------------------
368371
-- Convert GenericPackageDescription to PackageDescription
@@ -447,7 +450,6 @@ finalizePD userflags enabled satisfyDep
447450
, executables = exes'
448451
, testSuites = tests'
449452
, benchmarks = bms'
450-
, buildDepends = fromDepMap (overallDependencies enabled targetSet)
451453
}
452454
, flagVals )
453455
where
@@ -517,38 +519,25 @@ flattenPackageDescription
517519
, executables = reverse exes
518520
, testSuites = reverse tests
519521
, benchmarks = reverse bms
520-
, buildDepends = ldeps
521-
++ reverse sub_ldeps
522-
++ reverse pldeps
523-
++ reverse edeps
524-
++ reverse tdeps
525-
++ reverse bdeps
526522
}
527523
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 )
524+
mlib = f <$> mlib0
525+
where f lib = (libFillInDefaults . fst . ignoreConditions $ lib) { libName = Nothing }
526+
sub_libs = flattenLib <$> sub_libs0
527+
flibs = flattenFLib <$> flibs0
528+
exes = flattenExe <$> exes0
529+
tests = flattenTst <$> tests0
530+
bms = flattenBm <$> bms0
531+
flattenLib (n, t) = libFillInDefaults $ (fst $ ignoreConditions t)
532+
{ libName = Just n, libExposed = False }
533+
flattenFLib (n, t) = flibFillInDefaults $ (fst $ ignoreConditions t)
534+
{ foreignLibName = n }
535+
flattenExe (n, t) = exeFillInDefaults $ (fst $ ignoreConditions t)
536+
{ exeName = n }
537+
flattenTst (n, t) = testFillInDefaults $ (fst $ ignoreConditions t)
538+
{ testName = n }
539+
flattenBm (n, t) = benchFillInDefaults $ (fst $ ignoreConditions t)
540+
{ benchmarkName = n }
552541

553542
-- This is in fact rather a hack. The original version just overrode the
554543
-- default values, however, when adding conditions we had to switch to a
@@ -620,12 +609,10 @@ transformAllBuildDepends f gpd = gpd'
620609
where
621610
onBI bi = bi { targetBuildDepends = map f $ targetBuildDepends bi }
622611
onSBI stp = stp { setupDepends = map f $ setupDepends stp }
623-
onPD pd = pd { buildDepends = map f $ buildDepends pd }
624612

625-
pd' = onPD $ packageDescription gpd
626613
gpd' = transformAllCondTrees id id id id (map f)
627614
. transformAllBuildInfos onBI onSBI
628-
$ gpd { packageDescription = pd' }
615+
$ gpd
629616

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

Cabal/Distribution/PackageDescription/Parse.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -53,6 +53,7 @@ module Distribution.PackageDescription.Parse (
5353
import Prelude ()
5454
import Distribution.Compat.Prelude
5555

56+
import Distribution.Types.BuildInfo
5657
import Distribution.Types.Dependency
5758
import Distribution.Types.ForeignLib
5859
import Distribution.Types.ForeignLibType
@@ -427,7 +428,7 @@ binfoFieldDescrs =
427428
disp parse
428429
buildToolDepends (\xs binfo -> binfo{buildToolDepends=xs})
429430
, commaListFieldWithSep vcat "build-depends"
430-
disp parse
431+
disp parse
431432
targetBuildDepends (\xs binfo -> binfo{targetBuildDepends=xs})
432433
, commaListFieldWithSep vcat "mixins"
433434
disp parse

Cabal/Distribution/PackageDescription/Parsec/FieldDescr.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -427,11 +427,11 @@ binfoFieldDescrs =
427427
disp parsec
428428
buildToolDepends (\xs binfo -> binfo{buildToolDepends=xs})
429429
, commaListFieldWithSep vcat "build-depends"
430-
disp parsec
431-
targetBuildDepends (\xs binfo -> binfo{targetBuildDepends=xs})
430+
disp parsec
431+
targetBuildDepends (\xs binfo -> binfo{targetBuildDepends=xs})
432432
, commaListFieldWithSep vcat "mixins"
433-
disp parsec
434-
mixins (\xs binfo -> binfo{mixins=xs})
433+
disp parsec
434+
mixins (\xs binfo -> binfo{mixins=xs})
435435
, spaceListField "cpp-options"
436436
showToken parsecToken'
437437
cppOptions (\val binfo -> binfo{cppOptions=val})

Cabal/Distribution/Simple/Build.hs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -467,7 +467,6 @@ testSuiteLibV09AsLibAndExe pkg_descr
467467
}
468468
pkg = pkg_descr {
469469
package = (package pkg_descr) { pkgName = mkPackageName $ unMungedPackageName compat_name }
470-
, buildDepends = targetBuildDepends $ testBuildInfo test
471470
, executables = []
472471
, testSuites = []
473472
, subLibraries = [lib]

Cabal/Distribution/Simple/Configure.hs

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

484484
debug verbosity $ "Finalized package description:\n"
485485
++ showPackageDescription pkg_descr
486-
-- NB: showPackageDescription does not display the AWFUL HACK GLOBAL
487-
-- buildDepends, so we have to display it separately. See #2066
488-
-- Some day, we should eliminate this, so that
489-
-- configureFinalizedPackage returns the set of overall dependencies
490-
-- separately. Then 'configureDependencies' and
491-
-- 'Distribution.PackageDescription.Check' need to be adjusted
492-
-- accordingly.
493-
debug verbosity $ "Finalized build-depends: "
494-
++ intercalate ", " (map display (buildDepends pkg_descr))
495486

496487
checkCompilerProblems verbosity comp pkg_descr enabled
497488
checkPackageProblems verbosity pkg_descr0
@@ -526,6 +517,7 @@ configure (pkg_descr0', pbi) cfg = do
526517
installedPackageSet
527518
requiredDepsMap
528519
pkg_descr
520+
enabled
529521

530522
-- Compute installation directory templates, based on user
531523
-- configuration.
@@ -1003,14 +995,15 @@ configureDependencies
1003995
-> InstalledPackageIndex -- ^ installed packages
1004996
-> Map PackageName InstalledPackageInfo -- ^ required deps
1005997
-> PackageDescription
998+
-> ComponentRequestedSpec
1006999
-> IO [PreExistingComponent]
10071000
configureDependencies verbosity use_external_internal_deps
1008-
internalPackageSet installedPackageSet requiredDepsMap pkg_descr = do
1001+
internalPackageSet installedPackageSet requiredDepsMap pkg_descr enableSpec = do
10091002
let failedDeps :: [FailedDependency]
10101003
allPkgDeps :: [ResolvedDependency]
10111004
(failedDeps, allPkgDeps) = partitionEithers
10121005
[ (\s -> (dep, s)) <$> status
1013-
| dep <- buildDepends pkg_descr
1006+
| dep <- enabledBuildDepends pkg_descr enableSpec
10141007
, let status = selectDependency (package pkg_descr)
10151008
internalPackageSet installedPackageSet
10161009
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
@@ -116,7 +116,7 @@ instance Monoid BuildInfo where
116116
sharedOptions = [],
117117
customFieldsBI = [],
118118
targetBuildDepends = [],
119-
mixins = []
119+
mixins = []
120120
}
121121
mappend = (<>)
122122

@@ -152,7 +152,7 @@ instance Semigroup BuildInfo where
152152
sharedOptions = combine sharedOptions,
153153
customFieldsBI = combine customFieldsBI,
154154
targetBuildDepends = combineNub targetBuildDepends,
155-
mixins = combine mixins
155+
mixins = combine mixins
156156
}
157157
where
158158
combine field = field a `mappend` field b

Cabal/Distribution/Types/Component.hs

Lines changed: 9 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -5,6 +5,7 @@ module Distribution.Types.Component (
55
foldComponent,
66
componentBuildInfo,
77
componentBuildable,
8+
lensBuildInfo,
89
componentName,
910
partitionComponents,
1011
) where
@@ -53,6 +54,14 @@ componentBuildInfo :: Component -> BuildInfo
5354
componentBuildInfo =
5455
foldComponent libBuildInfo foreignLibBuildInfo buildInfo testBuildInfo benchmarkBuildInfo
5556

57+
lensBuildInfo :: (BuildInfo -> BuildInfo) -> (Component -> Component)
58+
lensBuildInfo f = \c -> case c of
59+
(CLib lib) -> CLib $ lib { libBuildInfo = f $ libBuildInfo lib }
60+
(CFLib flib) -> CFLib $ flib { foreignLibBuildInfo = f $ foreignLibBuildInfo flib }
61+
(CExe exe) -> CExe $ exe { buildInfo = f $ buildInfo exe }
62+
(CTest tst) -> CTest $ tst { testBuildInfo = f $ testBuildInfo tst }
63+
(CBench bch) -> CBench $ bch { benchmarkBuildInfo = f $ benchmarkBuildInfo bch }
64+
5665
-- | Is a component buildable (i.e., not marked with @buildable: False@)?
5766
-- See also this note in
5867
-- "Distribution.Types.ComponentRequestedSpec#buildable_vs_enabled_components".

Cabal/Distribution/Types/PackageDescription.hs

Lines changed: 11 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -45,6 +45,8 @@ module Distribution.Types.PackageDescription (
4545
withForeignLib,
4646
allBuildInfo,
4747
enabledBuildInfos,
48+
allBuildDepends,
49+
enabledBuildDepends,
4850
updatePackageDescription,
4951
pkgComponents,
5052
pkgBuildableComponents,
@@ -56,6 +58,8 @@ module Distribution.Types.PackageDescription (
5658
import Prelude ()
5759
import Distribution.Compat.Prelude
5860

61+
import Control.Monad ((<=<))
62+
5963
import Distribution.Types.Library
6064
import Distribution.Types.TestSuite
6165
import Distribution.Types.Executable
@@ -111,18 +115,6 @@ data PackageDescription
111115
-- with x-, stored in a
112116
-- simple assoc-list.
113117

114-
-- | YOU PROBABLY DON'T WANT TO USE THIS FIELD. This field is
115-
-- special! Depending on how far along processing the
116-
-- PackageDescription we are, the contents of this field are
117-
-- either nonsense, or the collected dependencies of *all* the
118-
-- components in this package. buildDepends is initialized by
119-
-- 'finalizePD' and 'flattenPackageDescription';
120-
-- prior to that, dependency info is stored in the 'CondTree'
121-
-- built around a 'GenericPackageDescription'. When this
122-
-- resolution is done, dependency info is written to the inner
123-
-- 'BuildInfo' and this field. This is all horrible, and #2066
124-
-- tracks progress to get rid of this field.
125-
buildDepends :: [Dependency],
126118
-- | The version of the Cabal spec that this package description uses.
127119
-- For historical reasons this is specified with a version range but
128120
-- only ranges of the form @>= v@ make sense. We are in the process of
@@ -190,7 +182,6 @@ emptyPackageDescription
190182
author = "",
191183
stability = "",
192184
testedWith = [],
193-
buildDepends = [],
194185
homepage = "",
195186
pkgUrl = "",
196187
bugReports = "",
@@ -338,6 +329,13 @@ enabledBuildInfos pkg enabled =
338329
-- * Utils
339330
-- ------------------------------------------------------------
340331

332+
allBuildDepends :: PackageDescription -> [Dependency]
333+
allBuildDepends = targetBuildDepends <=< allBuildInfo
334+
335+
enabledBuildDepends :: PackageDescription -> ComponentRequestedSpec -> [Dependency]
336+
enabledBuildDepends spec pd = targetBuildDepends =<< enabledBuildInfos spec pd
337+
338+
341339
updatePackageDescription :: HookedBuildInfo -> PackageDescription -> PackageDescription
342340
updatePackageDescription (mb_lib_bi, exe_bi) p
343341
= p{ executables = updateExecutables exe_bi (executables p)

cabal-install/Distribution/Client/Dependency.hs

Lines changed: 8 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -880,24 +880,24 @@ configuredPackageProblems platform cinfo
880880
(sortNubOn dependencyName required)
881881
(sortNubOn packageName specified)
882882

883+
compSpec = enableStanzas stanzas
883884
-- TODO: It would be nicer to use ComponentDeps here so we can be more
884-
-- precise in our checks. That's a bit tricky though, as this currently
885-
-- relies on the 'buildDepends' field of 'PackageDescription'. (OTOH, that
886-
-- field is deprecated and should be removed anyway.) As long as we _do_
887-
-- use a flat list here, we have to allow for duplicates when we fold
888-
-- specifiedDeps; once we have proper ComponentDeps here we should get rid
889-
-- of the `nubOn` in `mergeDeps`.
885+
-- precise in our checks. In fact, this no longer relies on buildDepends and
886+
-- thus should be easier to fix. As long as we _do_ use a flat list here, we
887+
-- have to allow for duplicates when we fold specifiedDeps; once we have
888+
-- proper ComponentDeps here we should get rid of the `nubOn` in
889+
-- `mergeDeps`.
890890
requiredDeps :: [Dependency]
891891
requiredDeps =
892892
--TODO: use something lower level than finalizePD
893893
case finalizePD specifiedFlags
894-
(enableStanzas stanzas)
894+
compSpec
895895
(const True)
896896
platform cinfo
897897
[]
898898
(packageDescription pkg) of
899899
Right (resolvedPkg, _) ->
900-
externalBuildDepends resolvedPkg
900+
externalBuildDepends resolvedPkg compSpec
901901
++ maybe [] PD.setupDepends (PD.setupBuildInfo resolvedPkg)
902902
Left _ ->
903903
error "configuredPackageInvalidDeps internal error"

cabal-install/Distribution/Client/GenBounds.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -26,7 +26,7 @@ import Distribution.Client.Setup
2626
import Distribution.Package
2727
( Package(..), unPackageName, packageName, packageVersion )
2828
import Distribution.PackageDescription
29-
( buildDepends )
29+
( enabledBuildDepends )
3030
import Distribution.PackageDescription.Configuration
3131
( finalizePD )
3232
#ifdef CABAL_PARSEC
@@ -124,7 +124,7 @@ genBounds verbosity packageDBs repoCtxt comp platform progdb mSandboxPkgInfo
124124
Left _ -> putStrLn "finalizePD failed"
125125
Right (pd,_) -> do
126126
let needBounds = filter (not . hasUpperBound . depVersion) $
127-
buildDepends pd
127+
enabledBuildDepends pd defaultComponentRequestedSpec
128128

129129
if (null needBounds)
130130
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)

0 commit comments

Comments
 (0)