Skip to content

Commit fdd7fba

Browse files
ezyangEricson2314
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 000c693 commit fdd7fba

Some content is hidden

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

46 files changed

+730
-568
lines changed

Cabal/Cabal.cabal

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -217,8 +217,10 @@ library
217217
Distribution.Types.Dependency
218218
Distribution.Types.ExeDependency
219219
Distribution.Types.LegacyExeDependency
220+
Distribution.Types.LibDependency
220221
Distribution.Types.PkgconfigDependency
221222
Distribution.Types.DependencyMap
223+
Distribution.Types.LibDependencyMap
222224
Distribution.Types.ComponentId
223225
Distribution.Types.MungedPackageId
224226
Distribution.Types.PackageId

Cabal/Distribution/Backpack/ComponentsGraph.hs

Lines changed: 10 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -14,10 +14,10 @@ import Distribution.PackageDescription as PD hiding (Flag)
1414
import Distribution.Simple.BuildToolDepends
1515
import Distribution.Simple.LocalBuildInfo
1616
import Distribution.Types.ComponentRequestedSpec
17-
import Distribution.Types.Dependency
18-
import Distribution.Types.UnqualComponentName
17+
import Distribution.Types.LibDependency
1918
import Distribution.Compat.Graph (Node(..))
2019
import qualified Distribution.Compat.Graph as Graph
20+
import Distribution.Types.Mixin
2121

2222
import Distribution.Text
2323
( Text(disp) )
@@ -57,18 +57,16 @@ toComponentsGraph enabled pkg_descr =
5757
-- The dependencies for the given component
5858
componentDeps component =
5959
(CExeName <$> getAllInternalToolDependencies pkg_descr bi)
60-
61-
++ [ if pkgname == packageName pkg_descr
62-
then CLibName
63-
else CSubLibName toolname
64-
| Dependency pkgname _ <- targetBuildDepends bi
65-
, let toolname = packageNameToUnqualComponentName pkgname
66-
, toolname `elem` internalPkgDeps ]
60+
++ mixin_deps
61+
++ [ maybe CLibName CSubLibName (libDepLibraryName ld)
62+
| ld <- targetBuildDepends bi
63+
, libDepPackageName ld == packageName pkg_descr ]
6764
where
6865
bi = componentBuildInfo component
69-
internalPkgDeps = map (conv . libName) (allLibraries pkg_descr)
70-
conv Nothing = packageNameToUnqualComponentName $ packageName pkg_descr
71-
conv (Just s) = s
66+
mixin_deps =
67+
[ maybe CLibName CSubLibName (mixinLibraryName mix)
68+
| mix <- mixins bi
69+
, mixinPackageName mix == packageName pkg_descr ]
7270

7371
-- | Error message when there is a cycle; takes the SCC of components.
7472
componentCycleMsg :: [ComponentName] -> Doc

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)
@@ -42,7 +41,6 @@ import Distribution.Utils.LogProgress
4241
import Distribution.Utils.MapAccum
4342

4443
import Control.Monad
45-
import qualified Data.Set as Set
4644
import qualified Data.Map as Map
4745
import Distribution.Text
4846
import Text.PrettyPrint
@@ -95,59 +93,72 @@ dispConfiguredComponent cc =
9593
| incl <- cc_includes cc
9694
])
9795

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

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

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

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

Cabal/Distribution/PackageDescription/Check.hs

Lines changed: 35 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -47,6 +47,7 @@ import Distribution.Simple.CCompiler
4747
import Distribution.Types.ComponentRequestedSpec
4848
import Distribution.Types.CondTree
4949
import Distribution.Types.Dependency
50+
import Distribution.Types.LibDependency
5051
import Distribution.Types.ExeDependency
5152
import Distribution.Types.PackageName
5253
import Distribution.Types.UnqualComponentName
@@ -546,6 +547,11 @@ checkFields pkg =
546547
++ ". This version range does not include the current package, and must "
547548
++ "be removed as the current package's library will always be used."
548549

550+
, check (not (null depMissingInternalLibrary)) $
551+
PackageBuildImpossible $
552+
"The package depends on a missing internal library: "
553+
++ commaSep (map display depInternalExecutableWithImpossibleVersion)
554+
549555
, check (not (null depInternalExecutableWithExtraVersion)) $
550556
PackageBuildWarning $
551557
"The package has an extraneous version range for a dependency on an "
@@ -588,17 +594,14 @@ checkFields pkg =
588594
| (compiler, vr) <- testedWith pkg
589595
, isNoVersion vr ]
590596

591-
internalLibraries =
592-
map (maybe (packageName pkg) (unqualComponentNameToPackageName) . libName)
593-
(allLibraries pkg)
597+
internalLibraries = mapMaybe libName $ allLibraries pkg
594598

595599
internalExecutables = map exeName $ executables pkg
596600

597601
internalLibDeps =
598602
[ dep
599-
| bi <- allBuildInfo pkg
600-
, dep@(Dependency name _) <- targetBuildDepends bi
601-
, name `elem` internalLibraries
603+
| dep@(LibDependency name _ _) <- allBuildDepends pkg
604+
, name == packageName pkg
602605
]
603606

604607
internalExeDeps =
@@ -610,17 +613,23 @@ checkFields pkg =
610613

611614
depInternalLibraryWithExtraVersion =
612615
[ dep
613-
| dep@(Dependency _ versionRange) <- internalLibDeps
616+
| dep@(LibDependency _ _ versionRange) <- internalLibDeps
614617
, not $ isAnyVersion versionRange
615618
, packageVersion pkg `withinRange` versionRange
616619
]
617620

618621
depInternalLibraryWithImpossibleVersion =
619622
[ dep
620-
| dep@(Dependency _ versionRange) <- internalLibDeps
623+
| dep@(LibDependency _ _ versionRange) <- internalLibDeps
621624
, not $ packageVersion pkg `withinRange` versionRange
622625
]
623626

627+
depMissingInternalLibrary =
628+
[ dep
629+
| dep@(LibDependency _ (Just lName) _) <- internalLibDeps
630+
, not $ lName `elem` internalLibraries
631+
]
632+
624633
depInternalExecutableWithExtraVersion =
625634
[ dep
626635
| dep@(ExeDependency _ _ versionRange) <- internalExeDeps
@@ -1139,7 +1148,7 @@ checkCabalVersion pkg =
11391148
PackageDistInexcusable $
11401149
"The package uses full version-range expressions "
11411150
++ "in a 'build-depends' field: "
1142-
++ commaSep (map displayRawDependency versionRangeExpressions)
1151+
++ commaSep (map displayRawLibDependency versionRangeExpressions)
11431152
++ ". To use this new syntax the package needs to specify at least "
11441153
++ "'cabal-version: >= 1.8'. Alternatively, if broader compatibility "
11451154
++ "is important, then convert to conjunctive normal form, and use "
@@ -1154,7 +1163,7 @@ checkCabalVersion pkg =
11541163
++ "'cabal-version: >= 1.6'. Alternatively, if broader compatibility "
11551164
++ "is important then use: " ++ commaSep
11561165
[ display (Dependency name (eliminateWildcardSyntax versionRange))
1157-
| Dependency name versionRange <- depsUsingWildcardSyntax ]
1166+
| LibDependency name Nothing versionRange <- depsUsingWildcardSyntax ]
11581167

11591168
-- check use of "build-depends: foo ^>= 1.2.3" syntax
11601169
, checkVersion [2,0] (not (null depsUsingMajorBoundSyntax)) $
@@ -1165,8 +1174,8 @@ checkCabalVersion pkg =
11651174
++ ". To use this new syntax the package need to specify at least "
11661175
++ "'cabal-version: >= 2.0'. Alternatively, if broader compatibility "
11671176
++ "is important then use: " ++ commaSep
1168-
[ display (Dependency name (eliminateMajorBoundSyntax versionRange))
1169-
| Dependency name versionRange <- depsUsingMajorBoundSyntax ]
1177+
[ display (LibDependency name lname (eliminateMajorBoundSyntax versionRange))
1178+
| LibDependency name lname versionRange <- depsUsingMajorBoundSyntax ]
11701179

11711180
-- check use of "tested-with: GHC (>= 1.0 && < 1.4) || >=1.8 " syntax
11721181
, checkVersion [1,8] (not (null testedWithVersionRangeExpressions)) $
@@ -1292,7 +1301,7 @@ checkCabalVersion pkg =
12921301
_ -> False
12931302

12941303
versionRangeExpressions =
1295-
[ dep | dep@(Dependency _ vr) <- allBuildDepends pkg
1304+
[ dep | dep@(LibDependency _ _ vr) <- allBuildDepends pkg
12961305
, usesNewVersionRangeSyntax vr ]
12971306

12981307
testedWithVersionRangeExpressions =
@@ -1331,11 +1340,13 @@ checkCabalVersion pkg =
13311340
(+) (+)
13321341
(const 3) -- uses new ()'s syntax
13331342

1334-
depsUsingWildcardSyntax = [ dep | dep@(Dependency _ vr) <- allBuildDepends pkg
1335-
, usesWildcardSyntax vr ]
1343+
depsUsingWildcardSyntax = [ dep
1344+
| dep@(LibDependency _ _ vr) <- allBuildDepends pkg
1345+
, usesWildcardSyntax vr ]
13361346

1337-
depsUsingMajorBoundSyntax = [ dep | dep@(Dependency _ vr) <- allBuildDepends pkg
1338-
, usesMajorBoundSyntax vr ]
1347+
depsUsingMajorBoundSyntax = [ dep
1348+
| dep@(LibDependency _ _ vr) <- allBuildDepends pkg
1349+
, usesMajorBoundSyntax vr ]
13391350

13401351
usesBackpackIncludes = any (not . null . mixins) (allBuildInfo pkg)
13411352

@@ -1475,6 +1486,12 @@ displayRawDependency :: Dependency -> String
14751486
displayRawDependency (Dependency pkg vr) =
14761487
display pkg ++ " " ++ displayRawVersionRange vr
14771488

1489+
displayRawLibDependency :: LibDependency -> String
1490+
displayRawLibDependency (LibDependency pkg ml vr) =
1491+
display pkg
1492+
++ ":lib:" ++ maybe (display pkg) display ml
1493+
++ " " ++ displayRawVersionRange vr
1494+
14781495

14791496
-- ------------------------------------------------------------
14801497
-- * Checks on the GenericPackageDescription
@@ -1524,7 +1541,7 @@ checkPackageVersions pkg =
15241541
foldr intersectVersionRanges anyVersion baseDeps
15251542
where
15261543
baseDeps =
1527-
[ vr | Dependency pname vr <- allBuildDepends pkg'
1544+
[ vr | LibDependency pname _ vr <- allBuildDepends pkg'
15281545
, pname == mkPackageName "base" ]
15291546

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

0 commit comments

Comments
 (0)