Skip to content

Commit ffaf323

Browse files
committed
Solver: Support dependencies on sub-libraries (issue haskell#6039).
This commit tracks dependencies on sub-libraries by extending the functionality for tracking executables that was added in e86f838. It also starts adding support for library visibility, though it currently only works for source packages. There is a TODO for handling installed packages. Fixes haskell#6038.
1 parent e98f6c2 commit ffaf323

File tree

7 files changed

+123
-53
lines changed

7 files changed

+123
-53
lines changed

cabal-install/Distribution/Solver/Modular/Dependency.hs

Lines changed: 6 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -52,6 +52,7 @@ import qualified Distribution.Solver.Modular.ConflictSet as CS
5252

5353
import Distribution.Solver.Types.ComponentDeps (Component(..))
5454
import Distribution.Solver.Types.PackagePath
55+
import Distribution.Types.LibraryName
5556
import Distribution.Types.PkgconfigVersionRange
5657
import Distribution.Types.UnqualComponentName
5758

@@ -128,7 +129,9 @@ data PkgComponent qpn = PkgComponent qpn ExposedComponent
128129

129130
-- | A component that can be depended upon by another package, i.e., a library
130131
-- or an executable.
131-
data ExposedComponent = ExposedLib | ExposedExe UnqualComponentName
132+
data ExposedComponent =
133+
ExposedLib LibraryName
134+
| ExposedExe UnqualComponentName
132135
deriving (Eq, Ord, Show)
133136

134137
-- | The reason that a dependency is active. It identifies the package and any
@@ -182,7 +185,7 @@ qualifyDeps QO{..} (Q pp@(PackagePath ns q) pn) = go
182185
-- Suppose package B has a setup dependency on package A.
183186
-- This will be recorded as something like
184187
--
185-
-- > LDep (DependencyReason "B") (Dep (PkgComponent "A" ExposedLib) (Constrained AnyVersion))
188+
-- > LDep (DependencyReason "B") (Dep (PkgComponent "A" (ExposedLib LMainLibName)) (Constrained AnyVersion))
186189
--
187190
-- Observe that when we qualify this dependency, we need to turn that
188191
-- @"A"@ into @"B-setup.A"@, but we should not apply that same qualifier
@@ -196,7 +199,7 @@ qualifyDeps QO{..} (Q pp@(PackagePath ns q) pn) = go
196199
goD (Pkg pkn vr) _ = Pkg pkn vr
197200
goD (Dep dep@(PkgComponent qpn (ExposedExe _)) ci) _ =
198201
Dep (Q (PackagePath ns (QualExe pn qpn)) <$> dep) ci
199-
goD (Dep dep@(PkgComponent qpn ExposedLib) ci) comp
202+
goD (Dep dep@(PkgComponent qpn (ExposedLib _)) ci) comp
200203
| qBase qpn = Dep (Q (PackagePath ns (QualBase pn)) <$> dep) ci
201204
| qSetup comp = Dep (Q (PackagePath ns (QualSetup pn)) <$> dep) ci
202205
| otherwise = Dep (Q (PackagePath ns inheritedQ ) <$> dep) ci

cabal-install/Distribution/Solver/Modular/Index.hs

Lines changed: 13 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
module Distribution.Solver.Modular.Index
22
( Index
33
, PInfo(..)
4+
, ComponentInfo(..)
45
, IsBuildable(..)
56
, defaultQualifyOptions
67
, mkIndex
@@ -14,6 +15,7 @@ import Distribution.Solver.Modular.Dependency
1415
import Distribution.Solver.Modular.Flag
1516
import Distribution.Solver.Modular.Package
1617
import Distribution.Solver.Modular.Tree
18+
import Distribution.Types.LibraryVisibility
1719

1820
-- | An index contains information about package instances. This is a nested
1921
-- dictionary. Package names are mapped to instances, which in turn is mapped
@@ -28,10 +30,20 @@ type Index = Map PN (Map I PInfo)
2830
-- globally, for reasons external to the solver. We currently use this
2931
-- for shadowing which essentially is a GHC limitation, and for
3032
-- installed packages that are broken.
31-
data PInfo = PInfo (FlaggedDeps PN) (Map ExposedComponent IsBuildable) FlagInfo (Maybe FailReason)
33+
data PInfo = PInfo (FlaggedDeps PN)
34+
(Map ExposedComponent ComponentInfo)
35+
FlagInfo
36+
(Maybe FailReason)
37+
38+
-- | Info associated with each library and executable in a package instance.
39+
data ComponentInfo = ComponentInfo {
40+
compVisibility :: LibraryVisibility
41+
, compIsBuildable :: IsBuildable
42+
}
3243

3344
-- | Whether a component is made unbuildable by a "buildable: False" field.
3445
newtype IsBuildable = IsBuildable Bool
46+
deriving Eq
3547

3648
mkIndex :: [(PN, I, PInfo)] -> Index
3749
mkIndex xs = M.map M.fromList (groupMap (L.map (\ (pn, i, pi) -> (pn, (i, pi))) xs))

cabal-install/Distribution/Solver/Modular/IndexConversion.hs

Lines changed: 50 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -26,6 +26,7 @@ import Distribution.PackageDescription.Configuration as PDC
2626
import qualified Distribution.Simple.PackageIndex as SI
2727
import Distribution.System
2828
import Distribution.Types.ForeignLib
29+
import Distribution.Types.LibraryVisibility
2930

3031
import Distribution.Solver.Types.ComponentDeps
3132
( Component(..), componentNameToComponent )
@@ -93,11 +94,18 @@ convIP :: SI.InstalledPackageIndex -> InstalledPackageInfo -> (PN, I, PInfo)
9394
convIP idx ipi =
9495
case mapM (convIPId (DependencyReason pn M.empty S.empty) comp idx) (IPI.depends ipi) of
9596
Nothing -> (pn, i, PInfo [] M.empty M.empty (Just Broken))
96-
Just fds -> ( pn
97-
, i
98-
, PInfo fds (M.singleton ExposedLib (IsBuildable True)) M.empty Nothing)
97+
Just fds -> ( pn, i, PInfo fds components M.empty Nothing)
9998
where
99+
-- TODO: Handle sub-libraries and visibility.
100+
components =
101+
M.singleton (ExposedLib LMainLibName)
102+
ComponentInfo {
103+
compVisibility = LibraryVisibilityPublic
104+
, compIsBuildable = IsBuildable True
105+
}
106+
100107
(pn, i) = convId ipi
108+
101109
-- 'sourceLibName' is unreliable, but for now we only really use this for
102110
-- primary libs anyways
103111
comp = componentNameToComponent $ CLibName $ sourceLibName ipi
@@ -141,7 +149,8 @@ convIPId dr comp idx ipid =
141149
case SI.lookupUnitId idx ipid of
142150
Nothing -> Nothing
143151
Just ipi -> let (pn, i) = convId ipi
144-
in Just (D.Simple (LDep dr (Dep (PkgComponent pn ExposedLib) (Fixed i))) comp)
152+
name = ExposedLib LMainLibName -- TODO: Handle sub-libraries.
153+
in Just (D.Simple (LDep dr (Dep (PkgComponent pn name) (Fixed i))) comp)
145154
-- NB: something we pick up from the
146155
-- InstalledPackageIndex is NEVER an executable
147156

@@ -236,12 +245,29 @@ convGPD os arch cinfo constraints strfl solveExes pn
236245
fr | reqSpecVer > maxSpecVer = Just (UnsupportedSpecVer reqSpecVer)
237246
| otherwise = Nothing
238247

239-
components :: Map ExposedComponent IsBuildable
240-
components = M.fromList $ libComps ++ exeComps
248+
components :: Map ExposedComponent ComponentInfo
249+
components = M.fromList $ libComps ++ subLibComps ++ exeComps
241250
where
242-
libComps = [ (ExposedLib, IsBuildable $ isBuildable libBuildInfo lib)
251+
libComps = [ ( ExposedLib LMainLibName
252+
, ComponentInfo {
253+
compVisibility = PD.libVisibility (condTreeData lib)
254+
, compIsBuildable = isBuildable libBuildInfo lib
255+
}
256+
)
243257
| lib <- maybeToList mlib ]
244-
exeComps = [ (ExposedExe name, IsBuildable $ isBuildable buildInfo exe)
258+
subLibComps = [ ( ExposedLib (LSubLibName name)
259+
, ComponentInfo {
260+
compVisibility = PD.libVisibility (condTreeData lib)
261+
, compIsBuildable = isBuildable libBuildInfo lib
262+
}
263+
)
264+
| (name, lib) <- sub_libs ]
265+
exeComps = [ ( ExposedExe name
266+
, ComponentInfo {
267+
compVisibility = LibraryVisibilityPublic
268+
, compIsBuildable = isBuildable buildInfo exe
269+
}
270+
)
245271
| (name, exe) <- exes ]
246272
isBuildable = isBuildableComponent os arch cinfo constraints
247273

@@ -259,11 +285,11 @@ isBuildableComponent :: OS
259285
-> [LabeledPackageConstraint]
260286
-> (a -> BuildInfo)
261287
-> CondTree ConfVar [Dependency] a
262-
-> Bool
288+
-> IsBuildable
263289
isBuildableComponent os arch cinfo constraints getInfo tree =
264290
case simplifyCondition $ extractCondition (buildable . getInfo) tree of
265-
Lit False -> False
266-
_ -> True
291+
Lit False -> IsBuildable False
292+
_ -> IsBuildable True
267293
where
268294
flagAssignment :: [(FlagName, Bool)]
269295
flagAssignment =
@@ -355,8 +381,10 @@ convCondTree flags dr pkg os arch cinfo pn fds comp getInfo ipns solveExes@(Solv
355381
-- duplicates could grow exponentially from the leaves to the root
356382
-- of the tree.
357383
mergeSimpleDeps $
358-
L.map (\d -> D.Simple (convLibDep dr d) comp)
359-
(mapMaybe (filterIPNs ipns) ds) -- unconditional package dependencies
384+
[ D.Simple singleDep comp
385+
| dep <- mapMaybe (filterIPNs ipns) ds
386+
, singleDep <- convLibDeps dr dep ] -- unconditional package dependencies
387+
360388
++ L.map (\e -> D.Simple (LDep dr (Ext e)) comp) (PD.allExtensions bi) -- unconditional extension dependencies
361389
++ L.map (\l -> D.Simple (LDep dr (Lang l)) comp) (PD.allLanguages bi) -- unconditional language dependencies
362390
++ L.map (\(PkgconfigDependency pkn vr) -> D.Simple (LDep dr (Pkg pkn vr)) comp) (PD.pkgconfigDepends bi) -- unconditional pkg-config dependencies
@@ -560,9 +588,12 @@ unionDRs :: DependencyReason pn -> DependencyReason pn -> DependencyReason pn
560588
unionDRs (DependencyReason pn' fs1 ss1) (DependencyReason _ fs2 ss2) =
561589
DependencyReason pn' (M.union fs1 fs2) (S.union ss1 ss2)
562590

563-
-- | Convert a Cabal dependency on a library to a solver-specific dependency.
564-
convLibDep :: DependencyReason PN -> Dependency -> LDep PN
565-
convLibDep dr (Dependency pn vr _) = LDep dr $ Dep (PkgComponent pn ExposedLib) (Constrained vr)
591+
-- | Convert a Cabal dependency on a set of library components (from a single
592+
-- package) to solver-specific dependencies.
593+
convLibDeps :: DependencyReason PN -> Dependency -> [LDep PN]
594+
convLibDeps dr (Dependency pn vr libs) =
595+
[ LDep dr $ Dep (PkgComponent pn (ExposedLib lib)) (Constrained vr)
596+
| lib <- S.toList libs ]
566597

567598
-- | Convert a Cabal dependency on an executable (build-tools) to a solver-specific dependency.
568599
convExeDep :: DependencyReason PN -> ExeDependency -> LDep PN
@@ -571,5 +602,6 @@ convExeDep dr (ExeDependency pn exe vr) = LDep dr $ Dep (PkgComponent pn (Expose
571602
-- | Convert setup dependencies
572603
convSetupBuildInfo :: PN -> SetupBuildInfo -> FlaggedDeps PN
573604
convSetupBuildInfo pn nfo =
574-
L.map (\d -> D.Simple (convLibDep (DependencyReason pn M.empty S.empty) d) ComponentSetup)
575-
(PD.setupDepends nfo)
605+
[ D.Simple singleDep ComponentSetup
606+
| dep <- PD.setupDepends nfo
607+
, singleDep <- convLibDeps (DependencyReason pn M.empty S.empty) dep ]

cabal-install/Distribution/Solver/Modular/Message.hs

Lines changed: 9 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -19,6 +19,7 @@ import Distribution.Solver.Modular.Version
1919
import Distribution.Solver.Types.ConstraintSource
2020
import Distribution.Solver.Types.PackagePath
2121
import Distribution.Solver.Types.Progress
22+
import Distribution.Types.LibraryName
2223
import Distribution.Types.UnqualComponentName
2324

2425
data Message =
@@ -108,8 +109,10 @@ showFR _ (MissingPkgconfigPackage pn vr) = " (conflict: pkg-config package " ++
108109
showFR _ (NewPackageDoesNotMatchExistingConstraint d) = " (conflict: " ++ showConflictingDep d ++ ")"
109110
showFR _ (ConflictingConstraints d1 d2) = " (conflict: " ++ L.intercalate ", " (L.map showConflictingDep [d1, d2]) ++ ")"
110111
showFR _ (NewPackageIsMissingRequiredComponent comp dr) = " (does not contain " ++ showExposedComponent comp ++ ", which is required by " ++ showDependencyReason dr ++ ")"
112+
showFR _ (NewPackageHasPrivateRequiredComponent comp dr) = " (" ++ showExposedComponent comp ++ " is private, but it is required by " ++ showDependencyReason dr ++ ")"
111113
showFR _ (NewPackageHasUnbuildableRequiredComponent comp dr) = " (" ++ showExposedComponent comp ++ " is not buildable in the current environment, but it is required by " ++ showDependencyReason dr ++ ")"
112114
showFR _ (PackageRequiresMissingComponent qpn comp) = " (requires " ++ showExposedComponent comp ++ " from " ++ showQPN qpn ++ ", but the component does not exist)"
115+
showFR _ (PackageRequiresPrivateComponent qpn comp) = " (requires " ++ showExposedComponent comp ++ " from " ++ showQPN qpn ++ ", but the component is private)"
113116
showFR _ (PackageRequiresUnbuildableComponent qpn comp) = " (requires " ++ showExposedComponent comp ++ " from " ++ showQPN qpn ++ ", but the component is not buildable in the current environment)"
114117
showFR _ CannotInstall = " (only already installed instances can be used)"
115118
showFR _ CannotReinstall = " (avoiding to reinstall a package with same version but new dependencies)"
@@ -135,8 +138,9 @@ showFR _ (MalformedStanzaChoice qsn) = " (INTERNAL ERROR: MALFORMED STANZA
135138
showFR _ EmptyGoalChoice = " (INTERNAL ERROR: EMPTY GOAL CHOICE)"
136139

137140
showExposedComponent :: ExposedComponent -> String
138-
showExposedComponent ExposedLib = "library"
139-
showExposedComponent (ExposedExe name) = "executable '" ++ unUnqualComponentName name ++ "'"
141+
showExposedComponent (ExposedLib LMainLibName) = "library"
142+
showExposedComponent (ExposedLib (LSubLibName name)) = "library '" ++ unUnqualComponentName name ++ "'"
143+
showExposedComponent (ExposedExe name) = "executable '" ++ unUnqualComponentName name ++ "'"
140144

141145
constraintSource :: ConstraintSource -> String
142146
constraintSource src = "constraint from " ++ showConstraintSource src
@@ -145,8 +149,9 @@ showConflictingDep :: ConflictingDep -> String
145149
showConflictingDep (ConflictingDep dr (PkgComponent qpn comp) ci) =
146150
let DependencyReason qpn' _ _ = dr
147151
componentStr = case comp of
148-
ExposedExe exe -> " (exe " ++ unUnqualComponentName exe ++ ")"
149-
ExposedLib -> ""
152+
ExposedExe exe -> " (exe " ++ unUnqualComponentName exe ++ ")"
153+
ExposedLib LMainLibName -> ""
154+
ExposedLib (LSubLibName lib) -> " (lib " ++ unUnqualComponentName lib ++ ")"
150155
in case ci of
151156
Fixed i -> (if qpn /= qpn' then showDependencyReason dr ++ " => " else "") ++
152157
showQPN qpn ++ componentStr ++ "==" ++ showI i

cabal-install/Distribution/Solver/Modular/Tree.hs

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -102,8 +102,10 @@ data FailReason = UnsupportedExtension Extension
102102
| NewPackageDoesNotMatchExistingConstraint ConflictingDep
103103
| ConflictingConstraints ConflictingDep ConflictingDep
104104
| NewPackageIsMissingRequiredComponent ExposedComponent (DependencyReason QPN)
105+
| NewPackageHasPrivateRequiredComponent ExposedComponent (DependencyReason QPN)
105106
| NewPackageHasUnbuildableRequiredComponent ExposedComponent (DependencyReason QPN)
106107
| PackageRequiresMissingComponent QPN ExposedComponent
108+
| PackageRequiresPrivateComponent QPN ExposedComponent
107109
| PackageRequiresUnbuildableComponent QPN ExposedComponent
108110
| CannotInstall
109111
| CannotReinstall

0 commit comments

Comments
 (0)