Skip to content

Commit a774cc3

Browse files
committed
Multiple libraries (allow depending on sublibs)
Create a new syntax for depending on any library of any package. The syntax is build-depends: pkgname:{pkgname, sublibname} -any where the second `pkgname` specifies a dependency on the main unnamed library. Closes haskell#4206.
1 parent d751bfe commit a774cc3

File tree

32 files changed

+261
-136
lines changed

32 files changed

+261
-136
lines changed

Cabal/Distribution/Backpack/ComponentsGraph.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -68,7 +68,7 @@ mkComponentsGraph enabled pkg_descr =
6868
++ [ if pkgname == packageName pkg_descr
6969
then CLibName LMainLibName
7070
else CLibName (LSubLibName toolname)
71-
| Dependency pkgname _ <- targetBuildDepends bi
71+
| Dependency pkgname _ _ <- targetBuildDepends bi
7272
, let toolname = packageNameToUnqualComponentName pkgname
7373
, toolname `elem` internalPkgDeps ]
7474
where

Cabal/Distribution/Backpack/ConfiguredComponent.hs

Lines changed: 28 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -30,6 +30,7 @@ import Distribution.Types.PackageId
3030
import Distribution.Types.PackageName
3131
import Distribution.Types.Mixin
3232
import Distribution.Types.ComponentName
33+
import Distribution.Types.LibraryName
3334
import Distribution.Types.UnqualComponentName
3435
import Distribution.Types.ComponentInclude
3536
import Distribution.Package
@@ -165,16 +166,40 @@ toConfiguredComponent
165166
toConfiguredComponent pkg_descr this_cid lib_dep_map exe_dep_map component = do
166167
lib_deps <-
167168
if newPackageDepsBehaviour pkg_descr
168-
then forM (targetBuildDepends bi) $ \(Dependency name _) -> do
169+
then fmap concat $ forM (targetBuildDepends bi) $ \(Dependency name _ sublibs) -> do
169170
let (pn, cn) = fixFakePkgName pkg_descr name
170-
value <- case Map.lookup cn =<< Map.lookup pn lib_dep_map of
171+
pkg <- case Map.lookup pn lib_dep_map of
172+
Nothing ->
173+
dieProgress $
174+
text "Dependency on unbuildable" <+>
175+
text "package" <+> disp pn
176+
Just p -> return p
177+
mainLibraryComponent <-
178+
if sublibs /= Set.singleton LMainLibName
179+
then pure Nothing
180+
-- No sublibraries were specified, so we may be in the
181+
-- legacy case where the package name is used as library
182+
-- name
183+
else Just <$>
184+
case Map.lookup cn pkg of
171185
Nothing ->
172186
dieProgress $
173187
text "Dependency on unbuildable (i.e. 'buildable: False')" <+>
174188
text (showComponentName cn) <+>
175189
text "from" <+> disp pn
176190
Just v -> return v
177-
return value
191+
subLibrariesComponents <- forM (Set.toList sublibs) $ \lib ->
192+
let comp = CLibName lib in
193+
case Map.lookup (CLibName $ LSubLibName $ packageNameToUnqualComponentName name) pkg
194+
<|> Map.lookup comp pkg
195+
of
196+
Nothing ->
197+
dieProgress $
198+
text "Dependency on unbuildable" <+>
199+
text (showLibraryName lib) <+>
200+
text "from" <+> disp pn
201+
Just v -> return v
202+
return (maybeToList mainLibraryComponent ++ subLibrariesComponents)
178203
else return old_style_lib_deps
179204
mkConfiguredComponent
180205
pkg_descr this_cid

Cabal/Distribution/PackageDescription/Check.hs

Lines changed: 17 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -585,7 +585,7 @@ checkFields pkg =
585585
, name `elem` map display knownLanguages ]
586586

587587
testedWithImpossibleRanges =
588-
[ Dependency (mkPackageName (display compiler)) vr
588+
[ Dependency (mkPackageName (display compiler)) vr Set.empty
589589
| (compiler, vr) <- testedWith pkg
590590
, isNoVersion vr ]
591591

@@ -598,7 +598,7 @@ checkFields pkg =
598598
internalLibDeps =
599599
[ dep
600600
| bi <- allBuildInfo pkg
601-
, dep@(Dependency name _) <- targetBuildDepends bi
601+
, dep@(Dependency name _ _) <- targetBuildDepends bi
602602
, name `elem` internalLibraries
603603
]
604604

@@ -611,14 +611,14 @@ checkFields pkg =
611611

612612
depInternalLibraryWithExtraVersion =
613613
[ dep
614-
| dep@(Dependency _ versionRange) <- internalLibDeps
614+
| dep@(Dependency _ versionRange _) <- internalLibDeps
615615
, not $ isAnyVersion versionRange
616616
, packageVersion pkg `withinRange` versionRange
617617
]
618618

619619
depInternalLibraryWithImpossibleVersion =
620620
[ dep
621-
| dep@(Dependency _ versionRange) <- internalLibDeps
621+
| dep@(Dependency _ versionRange _) <- internalLibDeps
622622
, not $ packageVersion pkg `withinRange` versionRange
623623
]
624624

@@ -1243,8 +1243,8 @@ checkCabalVersion pkg =
12431243
++ ". To use this new syntax the package need to specify at least "
12441244
++ "'cabal-version: >= 1.6'. Alternatively, if broader compatibility "
12451245
++ "is important then use: " ++ commaSep
1246-
[ display (Dependency name (eliminateWildcardSyntax versionRange))
1247-
| Dependency name versionRange <- depsUsingWildcardSyntax ]
1246+
[ display (Dependency name (eliminateWildcardSyntax versionRange) Set.empty)
1247+
| Dependency name versionRange _ <- depsUsingWildcardSyntax ]
12481248

12491249
-- check use of "build-depends: foo ^>= 1.2.3" syntax
12501250
, checkVersion [2,0] (not (null depsUsingMajorBoundSyntax)) $
@@ -1255,8 +1255,8 @@ checkCabalVersion pkg =
12551255
++ ". To use this new syntax the package need to specify at least "
12561256
++ "'cabal-version: 2.0'. Alternatively, if broader compatibility "
12571257
++ "is important then use: " ++ commaSep
1258-
[ display (Dependency name (eliminateMajorBoundSyntax versionRange))
1259-
| Dependency name versionRange <- depsUsingMajorBoundSyntax ]
1258+
[ display (Dependency name (eliminateMajorBoundSyntax versionRange) Set.empty)
1259+
| Dependency name versionRange _ <- depsUsingMajorBoundSyntax ]
12601260

12611261
, checkVersion [2,1] (any (not . null)
12621262
(concatMap buildInfoField
@@ -1292,8 +1292,8 @@ checkCabalVersion pkg =
12921292
++ ". To use this new syntax the package need to specify at least "
12931293
++ "'cabal-version: >= 1.6'. Alternatively, if broader compatibility "
12941294
++ "is important then use: " ++ commaSep
1295-
[ display (Dependency name (eliminateWildcardSyntax versionRange))
1296-
| Dependency name versionRange <- testedWithUsingWildcardSyntax ]
1295+
[ display (Dependency name (eliminateWildcardSyntax versionRange) Set.empty)
1296+
| Dependency name versionRange _ <- testedWithUsingWildcardSyntax ]
12971297

12981298
-- check use of "source-repository" section
12991299
, checkVersion [1,6] (not (null (sourceRepos pkg))) $
@@ -1367,11 +1367,11 @@ checkCabalVersion pkg =
13671367
buildInfoField field = map field (allBuildInfo pkg)
13681368

13691369
versionRangeExpressions =
1370-
[ dep | dep@(Dependency _ vr) <- allBuildDepends pkg
1370+
[ dep | dep@(Dependency _ vr _) <- allBuildDepends pkg
13711371
, usesNewVersionRangeSyntax vr ]
13721372

13731373
testedWithVersionRangeExpressions =
1374-
[ Dependency (mkPackageName (display compiler)) vr
1374+
[ Dependency (mkPackageName (display compiler)) vr Set.empty
13751375
| (compiler, vr) <- testedWith pkg
13761376
, usesNewVersionRangeSyntax vr ]
13771377

@@ -1395,16 +1395,16 @@ checkCabalVersion pkg =
13951395
alg (VersionRangeParensF _) = 3
13961396
alg _ = 1 :: Int
13971397

1398-
depsUsingWildcardSyntax = [ dep | dep@(Dependency _ vr) <- allBuildDepends pkg
1398+
depsUsingWildcardSyntax = [ dep | dep@(Dependency _ vr _) <- allBuildDepends pkg
13991399
, usesWildcardSyntax vr ]
14001400

1401-
depsUsingMajorBoundSyntax = [ dep | dep@(Dependency _ vr) <- allBuildDepends pkg
1401+
depsUsingMajorBoundSyntax = [ dep | dep@(Dependency _ vr _) <- allBuildDepends pkg
14021402
, usesMajorBoundSyntax vr ]
14031403

14041404
usesBackpackIncludes = any (not . null . mixins) (allBuildInfo pkg)
14051405

14061406
testedWithUsingWildcardSyntax =
1407-
[ Dependency (mkPackageName (display compiler)) vr
1407+
[ Dependency (mkPackageName (display compiler)) vr Set.empty
14081408
| (compiler, vr) <- testedWith pkg
14091409
, usesWildcardSyntax vr ]
14101410

@@ -1493,7 +1493,7 @@ checkCabalVersion pkg =
14931493
allModuleNamesAutogen = concatMap autogenModules (allBuildInfo pkg)
14941494

14951495
displayRawDependency :: Dependency -> String
1496-
displayRawDependency (Dependency pkg vr) =
1496+
displayRawDependency (Dependency pkg vr _sublibs) =
14971497
display pkg ++ " " ++ display vr
14981498

14991499

@@ -1545,7 +1545,7 @@ checkPackageVersions pkg =
15451545
foldr intersectVersionRanges anyVersion baseDeps
15461546
where
15471547
baseDeps =
1548-
[ vr | Dependency pname vr <- allBuildDepends pkg'
1548+
[ vr | Dependency pname vr _ <- allBuildDepends pkg'
15491549
, pname == mkPackageName "base" ]
15501550

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

Cabal/Distribution/PackageDescription/Configuration.hs

Lines changed: 14 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -65,6 +65,8 @@ import Distribution.Types.DependencyMap
6565

6666
import qualified Data.Map.Strict as Map.Strict
6767
import qualified Data.Map.Lazy as Map
68+
import Data.Set ( Set )
69+
import qualified Data.Set as Set
6870
import Data.Tree ( Tree(Node) )
6971

7072
------------------------------------------------------------------------------
@@ -229,7 +231,7 @@ resolveWithFlags dom enabled os arch impl constrs trees checkDeps =
229231
mp (Left xs) (Left ys) =
230232
let union = Map.foldrWithKey (Map.Strict.insertWith combine)
231233
(unDepMapUnion xs) (unDepMapUnion ys)
232-
combine x y = simplifyVersionRange $ unionVersionRanges x y
234+
combine x y = (\(vr, cs) -> (simplifyVersionRange vr,cs)) $ unionVersionRanges' x y
233235
in union `seq` Left (DepMapUnion union)
234236

235237
-- `mzero'
@@ -307,14 +309,22 @@ extractConditions f gpkg =
307309

308310

309311
-- | A map of dependencies that combines version ranges using 'unionVersionRanges'.
310-
newtype DepMapUnion = DepMapUnion { unDepMapUnion :: Map PackageName VersionRange }
312+
newtype DepMapUnion = DepMapUnion { unDepMapUnion :: Map PackageName (VersionRange, Set LibraryName) }
313+
314+
-- An union of versions should correspond to an intersection of the components.
315+
-- The intersection may not be necessary.
316+
unionVersionRanges' :: (VersionRange, Set LibraryName)
317+
-> (VersionRange, Set LibraryName)
318+
-> (VersionRange, Set LibraryName)
319+
unionVersionRanges' (vra, csa) (vrb, csb) =
320+
(unionVersionRanges vra vrb, Set.intersection csa csb)
311321

312322
toDepMapUnion :: [Dependency] -> DepMapUnion
313323
toDepMapUnion ds =
314-
DepMapUnion $ Map.fromListWith unionVersionRanges [ (p,vr) | Dependency p vr <- ds ]
324+
DepMapUnion $ Map.fromListWith unionVersionRanges' [ (p,(vr,cs)) | Dependency p vr cs <- ds ]
315325

316326
fromDepMapUnion :: DepMapUnion -> [Dependency]
317-
fromDepMapUnion m = [ Dependency p vr | (p,vr) <- Map.toList (unDepMapUnion m) ]
327+
fromDepMapUnion m = [ Dependency p vr cs | (p,(vr,cs)) <- Map.toList (unDepMapUnion m) ]
318328

319329
freeVars :: CondTree ConfVar c a -> [FlagName]
320330
freeVars t = [ f | Flag f <- freeVars' t ]

Cabal/Distribution/Simple/Configure.hs

Lines changed: 31 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -143,6 +143,8 @@ import Text.PrettyPrint
143143
import Distribution.Compat.Environment ( lookupEnv )
144144
import Distribution.Compat.Exception ( catchExit, catchIO )
145145

146+
import qualified Data.Set as Set
147+
146148

147149
type UseExternalInternalDeps = Bool
148150

@@ -874,7 +876,7 @@ dependencySatisfiable
874876
dependencySatisfiable
875877
use_external_internal_deps
876878
exact_config pn installedPackageSet internalPackageSet requiredDepsMap
877-
d@(Dependency depName vr)
879+
(Dependency depName vr sublibs)
878880

879881
| exact_config
880882
-- When we're given '--exact-configuration', we assume that all
@@ -889,7 +891,19 @@ dependencySatisfiable
889891
-- Except for internal deps, when we're NOT per-component mode;
890892
-- those are just True.
891893
then True
892-
else (depName, CLibName LMainLibName) `Map.member` requiredDepsMap
894+
else
895+
-- Backward compatibility for the old sublibrary syntax
896+
(sublibs == Set.singleton LMainLibName
897+
&& Map.member
898+
(pn, CLibName $ LSubLibName $ packageNameToUnqualComponentName depName)
899+
requiredDepsMap)
900+
901+
|| all
902+
(\lib ->
903+
(depName, CLibName lib)
904+
`Map.member`
905+
requiredDepsMap)
906+
sublibs
893907

894908
| isInternalDep
895909
= if use_external_internal_deps
@@ -908,11 +922,11 @@ dependencySatisfiable
908922
isInternalDep = Map.member depName internalPackageSet
909923

910924
depSatisfiable =
911-
not . null $ PackageIndex.lookupDependency installedPackageSet d
925+
not . null $ PackageIndex.lookupDependency installedPackageSet depName vr
912926

913927
internalDepSatisfiable =
914928
not . null $ PackageIndex.lookupInternalDependency
915-
installedPackageSet (Dependency pn vr) cn
929+
installedPackageSet pn vr cn
916930
where
917931
cn | pn == depName
918932
= Nothing
@@ -1025,8 +1039,8 @@ configureDependencies verbosity use_external_internal_deps
10251039
internalPackageSet installedPackageSet requiredDepsMap pkg_descr enableSpec = do
10261040
let failedDeps :: [FailedDependency]
10271041
allPkgDeps :: [ResolvedDependency]
1028-
(failedDeps, allPkgDeps) = partitionEithers
1029-
[ (\s -> (dep, s)) <$> status
1042+
(failedDeps, allPkgDeps) = partitionEithers $ concat
1043+
[ fmap (\s -> (dep, s)) <$> status
10301044
| dep <- enabledBuildDepends pkg_descr enableSpec
10311045
, let status = selectDependency (package pkg_descr)
10321046
internalPackageSet installedPackageSet
@@ -1197,10 +1211,10 @@ selectDependency :: PackageId -- ^ Package id of current package
11971211
-> UseExternalInternalDeps -- ^ Are we configuring a
11981212
-- single component?
11991213
-> Dependency
1200-
-> Either FailedDependency DependencyResolution
1214+
-> [Either FailedDependency DependencyResolution]
12011215
selectDependency pkgid internalIndex installedIndex requiredDepsMap
12021216
use_external_internal_deps
1203-
dep@(Dependency dep_pkgname vr) =
1217+
(Dependency dep_pkgname vr libs) =
12041218
-- If the dependency specification matches anything in the internal package
12051219
-- index, then we prefer that match to anything in the second.
12061220
-- For example:
@@ -1216,18 +1230,19 @@ selectDependency pkgid internalIndex installedIndex requiredDepsMap
12161230
-- even if there is a newer installed library "MyLibrary-0.2".
12171231
case Map.lookup dep_pkgname internalIndex of
12181232
Just cname -> if use_external_internal_deps
1219-
then do_external (Just cname)
1233+
then do_external (Just cname) <$> Set.toList libs
12201234
else do_internal
1221-
_ -> do_external Nothing
1235+
_ -> do_external Nothing <$> Set.toList libs
12221236
where
12231237

12241238
-- It's an internal library, and we're not per-component build
1225-
do_internal = Right $ InternalDependency
1226-
$ PackageIdentifier dep_pkgname $ packageVersion pkgid
1239+
do_internal = [Right $ InternalDependency
1240+
$ PackageIdentifier dep_pkgname $ packageVersion pkgid]
12271241

12281242
-- We have to look it up externally
1229-
do_external is_internal = do
1230-
ipi <- case Map.lookup (dep_pkgname, CLibName LMainLibName) requiredDepsMap of
1243+
do_external :: Maybe (Maybe UnqualComponentName) -> LibraryName -> Either FailedDependency DependencyResolution
1244+
do_external is_internal lib = do
1245+
ipi <- case Map.lookup (dep_pkgname, CLibName lib) requiredDepsMap of
12311246
-- If we know the exact pkg to use, then use it.
12321247
Just pkginstance -> Right pkginstance
12331248
-- Otherwise we just pick an arbitrary instance of the latest version.
@@ -1239,14 +1254,14 @@ selectDependency pkgid internalIndex installedIndex requiredDepsMap
12391254

12401255
-- It's an external package, normal situation
12411256
do_external_external =
1242-
case PackageIndex.lookupDependency installedIndex dep of
1257+
case PackageIndex.lookupDependency installedIndex dep_pkgname vr of
12431258
[] -> Left (DependencyNotExists dep_pkgname)
12441259
pkgs -> Right $ head $ snd $ last pkgs
12451260

12461261
-- It's an internal library, being looked up externally
12471262
do_external_internal mb_uqn =
12481263
case PackageIndex.lookupInternalDependency installedIndex
1249-
(Dependency (packageName pkgid) vr) mb_uqn of
1264+
(packageName pkgid) vr mb_uqn of
12501265
[] -> Left (DependencyMissingInternal dep_pkgname (packageName pkgid))
12511266
pkgs -> Right $ head $ snd $ last pkgs
12521267

Cabal/Distribution/Simple/PackageIndex.hs

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -469,11 +469,11 @@ lookupPackageName index name =
469469
--
470470
-- INVARIANT: List of eligible 'IPI.InstalledPackageInfo' is non-empty.
471471
--
472-
lookupDependency :: InstalledPackageIndex -> Dependency
472+
lookupDependency :: InstalledPackageIndex -> PackageName -> VersionRange
473473
-> [(Version, [IPI.InstalledPackageInfo])]
474-
lookupDependency index dep =
474+
lookupDependency index pn vr =
475475
-- Yes, a little bit of a misnomer here!
476-
lookupInternalDependency index dep Nothing
476+
lookupInternalDependency index pn vr Nothing
477477

478478
-- | Does a lookup by source package name and a range of versions.
479479
--
@@ -482,10 +482,10 @@ lookupDependency index dep =
482482
--
483483
-- INVARIANT: List of eligible 'IPI.InstalledPackageInfo' is non-empty.
484484
--
485-
lookupInternalDependency :: InstalledPackageIndex -> Dependency
485+
lookupInternalDependency :: InstalledPackageIndex -> PackageName -> VersionRange
486486
-> Maybe UnqualComponentName
487487
-> [(Version, [IPI.InstalledPackageInfo])]
488-
lookupInternalDependency index (Dependency name versionRange) libn =
488+
lookupInternalDependency index name versionRange libn =
489489
case Map.lookup (name, libn) (packageIdIndex index) of
490490
Nothing -> []
491491
Just pvers -> [ (ver, pkgs')

0 commit comments

Comments
 (0)