Skip to content

Commit d3a20b3

Browse files
ezyangkmicklas
authored andcommitted
Distinguish between internal and external libraries in build-depends
Fixes haskell#4155. We create a new `LibDependency` just used for parsing `build-depends` entries for now, but I hope it has a bright future in the brave new per-component world. Already in 'Cabal', this type will be used instead of 'Dependency' in most cases, implemented in the following commits of this PR. Used in: - Condition Trees - Querying the PackageIndex ----- Not sure about which type should have the (not)ThisPackageVersion function Also need to update some comments. Everything builds, however.
1 parent cfa13cf commit d3a20b3

File tree

49 files changed

+1032
-500
lines changed

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

49 files changed

+1032
-500
lines changed

Cabal/Cabal.cabal

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -294,8 +294,10 @@ library
294294
Distribution.Types.Dependency
295295
Distribution.Types.ExeDependency
296296
Distribution.Types.LegacyExeDependency
297+
Distribution.Types.LibDependency
297298
Distribution.Types.PkgconfigDependency
298299
Distribution.Types.DependencyMap
300+
Distribution.Types.LibDependencyMap
299301
Distribution.Types.ComponentId
300302
Distribution.Types.MungedPackageId
301303
Distribution.Types.PackageId

Cabal/Distribution/Backpack/ComponentsGraph.hs

Lines changed: 10 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -16,9 +16,10 @@ import Distribution.PackageDescription as PD hiding (Flag)
1616
import Distribution.Simple.BuildToolDepends
1717
import Distribution.Simple.LocalBuildInfo
1818
import Distribution.Types.ComponentRequestedSpec
19-
import Distribution.Types.UnqualComponentName
19+
import Distribution.Types.LibDependency
2020
import Distribution.Compat.Graph (Graph, Node(..))
2121
import qualified Distribution.Compat.Graph as Graph
22+
import Distribution.Types.Mixin
2223

2324
import Distribution.Text
2425
( Text(disp) )
@@ -64,18 +65,16 @@ mkComponentsGraph enabled pkg_descr =
6465
-- The dependencies for the given component
6566
componentDeps component =
6667
(CExeName <$> getAllInternalToolDependencies pkg_descr bi)
67-
68-
++ [ if pkgname == packageName pkg_descr
69-
then CLibName
70-
else CSubLibName toolname
71-
| Dependency pkgname _ <- targetBuildDepends bi
72-
, let toolname = packageNameToUnqualComponentName pkgname
73-
, toolname `elem` internalPkgDeps ]
68+
++ mixin_deps
69+
++ [ maybe CLibName CSubLibName (libDepLibraryName ld)
70+
| ld <- targetBuildDepends bi
71+
, libDepPackageName ld == packageName pkg_descr ]
7472
where
7573
bi = componentBuildInfo component
76-
internalPkgDeps = map (conv . libName) (allLibraries pkg_descr)
77-
conv Nothing = packageNameToUnqualComponentName $ packageName pkg_descr
78-
conv (Just s) = s
74+
mixin_deps =
75+
[ maybe CLibName CSubLibName (mixinLibraryName mix)
76+
| mix <- mixins bi
77+
, mixinPackageName mix == packageName pkg_descr ]
7978

8079
-- | Given the package description and a 'PackageDescription' (used
8180
-- to determine if a package name is internal or not), sort the

Cabal/Distribution/Backpack/ConfiguredComponent.hs

Lines changed: 52 additions & 66 deletions
Original file line numberDiff line numberDiff line change
@@ -22,15 +22,14 @@ import Distribution.Compat.Prelude hiding ((<>))
2222
import Distribution.Backpack.Id
2323

2424
import Distribution.Types.AnnotatedId
25-
import Distribution.Types.Dependency
25+
import Distribution.Types.LibDependency
2626
import Distribution.Types.ExeDependency
2727
import Distribution.Types.IncludeRenaming
2828
import Distribution.Types.ComponentId
2929
import Distribution.Types.PackageId
3030
import Distribution.Types.PackageName
3131
import Distribution.Types.Mixin
3232
import Distribution.Types.ComponentName
33-
import Distribution.Types.UnqualComponentName
3433
import Distribution.Types.ComponentInclude
3534
import Distribution.Package
3635
import Distribution.PackageDescription as PD hiding (Flag)
@@ -43,7 +42,6 @@ import Distribution.Utils.MapAccum
4342
import Distribution.Utils.Generic
4443

4544
import Control.Monad
46-
import qualified Data.Set as Set
4745
import qualified Data.Map as Map
4846
import Distribution.Text
4947
import Text.PrettyPrint
@@ -96,59 +94,72 @@ dispConfiguredComponent cc =
9694
| incl <- cc_includes cc
9795
])
9896

97+
-- | This is a mapping that keeps track of package-internal libraries
98+
-- and executables. Although a component of the key is a general
99+
-- 'ComponentName', actually only 'CLib', 'CSubLib' and 'CExe' will ever
100+
-- be here.
99101
type ConfiguredComponentMap =
100102
Map PackageName (Map ComponentName (AnnotatedId ComponentId))
101103

104+
-- Executable map must be different because an executable can
105+
-- have the same name as a library. Ew.
106+
107+
-- | Given some ambient environment of package names that
108+
-- are "in scope", looks at the 'BuildInfo' to decide
109+
-- what the packages actually resolve to, and then builds
110+
-- a 'ConfiguredComponent'.
102111
toConfiguredComponent
103112
:: PackageDescription
104113
-> ComponentId
105114
-> ConfiguredComponentMap
106115
-> Component
107116
-> LogProgress ConfiguredComponent
108117
toConfiguredComponent pkg_descr this_cid dep_map component = do
109-
lib_deps <-
110-
if newPackageDepsBehaviour pkg_descr
111-
then forM (targetBuildDepends bi) $ \(Dependency name _) -> do
112-
let (pn, cn) = fixFakePkgName pkg_descr name
113-
value <- case Map.lookup cn =<< Map.lookup pn dep_map of
114-
Nothing ->
115-
dieProgress $
116-
text "Dependency on unbuildable" <+>
117-
text (showComponentName cn) <+>
118-
text "from" <+> disp pn
119-
Just v -> return v
120-
return value
121-
else return old_style_lib_deps
118+
let reg_lib_deps =
119+
if newPackageDepsBehaviour pkg_descr
120+
then
121+
[ (pn, cn)
122+
| LibDependency pn mb_ln _ <- targetBuildDepends bi
123+
, let cn = libraryComponentName mb_ln ]
124+
else
125+
-- dep_map contains a mix of internal and external deps.
126+
-- We want all the public libraries (dep_cn == CLibName)
127+
-- of all external deps (dep /= pn). Note that this
128+
-- excludes the public library of the current package:
129+
-- this is not supported by old-style deps behavior
130+
-- because it would imply a cyclic dependency for the
131+
-- library itself.
132+
[ (pn, cn)
133+
| (pn, comp_map) <- Map.toList dep_map
134+
, pn /= packageName pkg_descr
135+
, (cn, _) <- Map.toList comp_map
136+
, cn == CLibName ]
137+
138+
reg_lib_map, mixin_map :: Map (PackageName, ComponentName) (IncludeRenaming, Bool)
139+
140+
reg_lib_map = Map.fromList $
141+
reg_lib_deps `zip` repeat (defaultIncludeRenaming, True)
142+
143+
mixin_map = Map.fromList
144+
[ ((pn, cn), (rns, False))
145+
| Mixin pn mb_ln rns <- mixins bi
146+
, let cn = libraryComponentName mb_ln ]
122147

123-
-- Resolve each @mixins@ into the actual dependency
124-
-- from @lib_deps@.
125-
explicit_includes <- forM (mixins bi) $ \(Mixin name rns) -> do
126-
let (pkg, cname) = fixFakePkgName pkg_descr name
127-
aid <-
128-
case Map.lookup cname =<< Map.lookup pkg dep_map of
129-
Nothing ->
130-
dieProgress $
131-
text "Mix-in refers to non-existent package" <+>
132-
quotes (disp name) $$
133-
text "(did you forget to add the package to build-depends?)"
134-
Just r -> return r
148+
lib_deps = Map.toList $ reg_lib_map `Map.union` mixin_map
149+
150+
mixin_includes <- forM lib_deps $ \((pname, cname), (rns, implicit)) -> do
151+
aid <- case Map.lookup cname =<< Map.lookup pname dep_map of
152+
Nothing -> dieProgress $
153+
text "Dependency on unbuildable" <+>
154+
text (showComponentName cname) <+>
155+
text "from" <+> disp pname
156+
Just r -> return r
135157
return ComponentInclude {
136158
ci_ann_id = aid,
137159
ci_renaming = rns,
138-
ci_implicit = False
160+
ci_implicit = implicit
139161
}
140162

141-
-- Any @build-depends@ which is not explicitly mentioned in
142-
-- @backpack-include@ is converted into an "implicit" include.
143-
let used_explicitly = Set.fromList (map ci_id explicit_includes)
144-
implicit_includes
145-
= map (\aid -> ComponentInclude {
146-
ci_ann_id = aid,
147-
ci_renaming = defaultIncludeRenaming,
148-
ci_implicit = True
149-
})
150-
$ filter (flip Set.notMember used_explicitly . ann_id) lib_deps
151-
152163
return ConfiguredComponent {
153164
cc_ann_id = AnnotatedId {
154165
ann_id = this_cid,
@@ -158,22 +169,10 @@ toConfiguredComponent pkg_descr this_cid dep_map component = do
158169
cc_component = component,
159170
cc_public = componentName component == CLibName,
160171
cc_exe_deps = exe_deps,
161-
cc_includes = explicit_includes ++ implicit_includes
172+
cc_includes = mixin_includes
162173
}
163174
where
164175
bi = componentBuildInfo component
165-
-- dep_map contains a mix of internal and external deps.
166-
-- We want all the public libraries (dep_cn == CLibName)
167-
-- of all external deps (dep /= pn). Note that this
168-
-- excludes the public library of the current package:
169-
-- this is not supported by old-style deps behavior
170-
-- because it would imply a cyclic dependency for the
171-
-- library itself.
172-
old_style_lib_deps = [ e
173-
| (pn, comp_map) <- Map.toList dep_map
174-
, pn /= packageName pkg_descr
175-
, (cn, e) <- Map.toList comp_map
176-
, cn == CLibName ]
177176
-- We have to nub here, because 'getAllToolDependencies' may return
178177
-- duplicates (see #4986). (NB: This is not needed for lib_deps,
179178
-- since those elaborate into includes, for which there explicitly
@@ -264,16 +263,3 @@ newPackageDepsBehaviourMinVersion = mkVersion [1,7,1]
264263
newPackageDepsBehaviour :: PackageDescription -> Bool
265264
newPackageDepsBehaviour pkg =
266265
specVersion pkg >= newPackageDepsBehaviourMinVersion
267-
268-
-- | 'build-depends:' stanzas are currently ambiguous as the external packages
269-
-- and internal libraries are specified the same. For now, we assume internal
270-
-- libraries shadow, and this function disambiguates accordingly, but soon the
271-
-- underlying ambiguity will be addressed.
272-
fixFakePkgName :: PackageDescription -> PackageName -> (PackageName, ComponentName)
273-
fixFakePkgName pkg_descr pn =
274-
if subLibName `elem` internalLibraries
275-
then (packageName pkg_descr, CSubLibName subLibName)
276-
else (pn, CLibName)
277-
where
278-
subLibName = packageNameToUnqualComponentName pn
279-
internalLibraries = mapMaybe libName (allLibraries pkg_descr)

Cabal/Distribution/PackageDescription/Check.hs

Lines changed: 33 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -54,6 +54,7 @@ import Distribution.Text
5454
import Distribution.Types.ComponentRequestedSpec
5555
import Distribution.Types.CondTree
5656
import Distribution.Types.ExecutableScope
57+
import Distribution.Types.LibDependency
5758
import Distribution.Types.ExeDependency
5859
import Distribution.Types.UnqualComponentName
5960
import Distribution.Utils.Generic (isAscii)
@@ -550,6 +551,11 @@ checkFields pkg =
550551
++ ". This version range does not include the current package, and must "
551552
++ "be removed as the current package's library will always be used."
552553

554+
, check (not (null depMissingInternalLibrary)) $
555+
PackageBuildImpossible $
556+
"The package depends on a missing internal library: "
557+
++ commaSep (map display depInternalExecutableWithImpossibleVersion)
558+
553559
, check (not (null depInternalExecutableWithExtraVersion)) $
554560
PackageBuildWarning $
555561
"The package has an extraneous version range for a dependency on an "
@@ -592,17 +598,14 @@ checkFields pkg =
592598
| (compiler, vr) <- testedWith pkg
593599
, isNoVersion vr ]
594600

595-
internalLibraries =
596-
map (maybe (packageName pkg) (unqualComponentNameToPackageName) . libName)
597-
(allLibraries pkg)
601+
internalLibraries = mapMaybe libName $ allLibraries pkg
598602

599603
internalExecutables = map exeName $ executables pkg
600604

601605
internalLibDeps =
602606
[ dep
603-
| bi <- allBuildInfo pkg
604-
, dep@(Dependency name _) <- targetBuildDepends bi
605-
, name `elem` internalLibraries
607+
| dep@(LibDependency name _ _) <- allBuildDepends pkg
608+
, name == packageName pkg
606609
]
607610

608611
internalExeDeps =
@@ -614,17 +617,23 @@ checkFields pkg =
614617

615618
depInternalLibraryWithExtraVersion =
616619
[ dep
617-
| dep@(Dependency _ versionRange) <- internalLibDeps
620+
| dep@(LibDependency _ _ versionRange) <- internalLibDeps
618621
, not $ isAnyVersion versionRange
619622
, packageVersion pkg `withinRange` versionRange
620623
]
621624

622625
depInternalLibraryWithImpossibleVersion =
623626
[ dep
624-
| dep@(Dependency _ versionRange) <- internalLibDeps
627+
| dep@(LibDependency _ _ versionRange) <- internalLibDeps
625628
, not $ packageVersion pkg `withinRange` versionRange
626629
]
627630

631+
depMissingInternalLibrary =
632+
[ dep
633+
| dep@(LibDependency _ (Just lName) _) <- internalLibDeps
634+
, not $ lName `elem` internalLibraries
635+
]
636+
628637
depInternalExecutableWithExtraVersion =
629638
[ dep
630639
| dep@(ExeDependency _ _ versionRange) <- internalExeDeps
@@ -1207,7 +1216,7 @@ checkCabalVersion pkg =
12071216
PackageDistInexcusable $
12081217
"The package uses full version-range expressions "
12091218
++ "in a 'build-depends' field: "
1210-
++ commaSep (map displayRawDependency versionRangeExpressions)
1219+
++ commaSep (map displayRawLibDependency versionRangeExpressions)
12111220
++ ". To use this new syntax the package needs to specify at least "
12121221
++ "'cabal-version: >= 1.8'. Alternatively, if broader compatibility "
12131222
++ "is important, then convert to conjunctive normal form, and use "
@@ -1222,7 +1231,7 @@ checkCabalVersion pkg =
12221231
++ "'cabal-version: >= 1.6'. Alternatively, if broader compatibility "
12231232
++ "is important then use: " ++ commaSep
12241233
[ display (Dependency name (eliminateWildcardSyntax versionRange))
1225-
| Dependency name versionRange <- depsUsingWildcardSyntax ]
1234+
| LibDependency name Nothing versionRange <- depsUsingWildcardSyntax ]
12261235

12271236
-- check use of "build-depends: foo ^>= 1.2.3" syntax
12281237
, checkVersion [2,0] (not (null depsUsingMajorBoundSyntax)) $
@@ -1233,8 +1242,8 @@ checkCabalVersion pkg =
12331242
++ ". To use this new syntax the package need to specify at least "
12341243
++ "'cabal-version: >= 2.0'. Alternatively, if broader compatibility "
12351244
++ "is important then use: " ++ commaSep
1236-
[ display (Dependency name (eliminateMajorBoundSyntax versionRange))
1237-
| Dependency name versionRange <- depsUsingMajorBoundSyntax ]
1245+
[ display (LibDependency name lname (eliminateMajorBoundSyntax versionRange))
1246+
| LibDependency name lname versionRange <- depsUsingMajorBoundSyntax ]
12381247

12391248
, checkVersion [2,1] (any (not . null)
12401249
(concatMap buildInfoField
@@ -1369,7 +1378,7 @@ checkCabalVersion pkg =
13691378
_ -> False
13701379

13711380
versionRangeExpressions =
1372-
[ dep | dep@(Dependency _ vr) <- allBuildDepends pkg
1381+
[ dep | dep@(LibDependency _ _ vr) <- allBuildDepends pkg
13731382
, usesNewVersionRangeSyntax vr ]
13741383

13751384
testedWithVersionRangeExpressions =
@@ -1397,10 +1406,11 @@ checkCabalVersion pkg =
13971406
alg (VersionRangeParensF _) = 3
13981407
alg _ = 1 :: Int
13991408

1400-
depsUsingWildcardSyntax = [ dep | dep@(Dependency _ vr) <- allBuildDepends pkg
1401-
, usesWildcardSyntax vr ]
1409+
depsUsingWildcardSyntax = [ dep
1410+
| dep@(LibDependency _ _ vr) <- allBuildDepends pkg
1411+
, usesWildcardSyntax vr ]
14021412

1403-
depsUsingMajorBoundSyntax = [ dep | dep@(Dependency _ vr) <- allBuildDepends pkg
1413+
depsUsingMajorBoundSyntax = [ dep | dep@(LibDependency _ _ vr) <- allBuildDepends pkg
14041414
, usesMajorBoundSyntax vr ]
14051415

14061416
usesBackpackIncludes = any (not . null . mixins) (allBuildInfo pkg)
@@ -1498,6 +1508,12 @@ displayRawDependency :: Dependency -> String
14981508
displayRawDependency (Dependency pkg vr) =
14991509
display pkg ++ " " ++ display vr
15001510

1511+
displayRawLibDependency :: LibDependency -> String
1512+
displayRawLibDependency (LibDependency pkg ml vr) =
1513+
display pkg
1514+
++ ":lib:" ++ maybe (display pkg) display ml
1515+
++ " " ++ display vr
1516+
15011517

15021518
-- ------------------------------------------------------------
15031519
-- * Checks on the GenericPackageDescription
@@ -1547,7 +1563,7 @@ checkPackageVersions pkg =
15471563
foldr intersectVersionRanges anyVersion baseDeps
15481564
where
15491565
baseDeps =
1550-
[ vr | Dependency pname vr <- allBuildDepends pkg'
1566+
[ vr | LibDependency pname _ vr <- allBuildDepends pkg'
15511567
, pname == mkPackageName "base" ]
15521568

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

0 commit comments

Comments
 (0)