Skip to content

Commit e86f838

Browse files
committed
Solver: Enforce dependencies on executables (fixes #4781).
This commit adds two checks to the validation phase of the solver: 1. It checks that each newly chosen package instance contains all executables that are required from that package so far. 2. It checks that each new build tool dependency that refers to a previously chosen package can be satisfied by the executables in that package. This commit also fixes a TODO related to solver log messages. Previously, it was possible for the log to associate an incorrect executable name with a dependency.
1 parent 7712505 commit e86f838

File tree

4 files changed

+123
-50
lines changed

4 files changed

+123
-50
lines changed

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

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -131,6 +131,8 @@ showFR _ (UnsupportedLanguage lang) = " (conflict: requires " ++ display l
131131
showFR _ (MissingPkgconfigPackage pn vr) = " (conflict: pkg-config package " ++ display pn ++ display vr ++ ", not found in the pkg-config database)"
132132
showFR _ (NewPackageDoesNotMatchExistingConstraint d) = " (conflict: " ++ showConflictingDep d ++ ")"
133133
showFR _ (ConflictingConstraints d1 d2) = " (conflict: " ++ L.intercalate ", " (L.map showConflictingDep [d1, d2]) ++ ")"
134+
showFR _ (NewPackageIsMissingRequiredExe exe dr) = " (does not contain executable " ++ unUnqualComponentName exe ++ ", which is required by " ++ showDependencyReason dr ++ ")"
135+
showFR _ (PackageRequiresMissingExe qpn exe) = " (requires executable " ++ unUnqualComponentName exe ++ " from " ++ showQPN qpn ++ ", but the executable does not exist)"
134136
showFR _ CannotInstall = " (only already installed instances can be used)"
135137
showFR _ CannotReinstall = " (avoiding to reinstall a package with same version but new dependencies)"
136138
showFR _ Shadowed = " (shadowed by another installed package with same version)"

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

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -100,6 +100,8 @@ data FailReason = UnsupportedExtension Extension
100100
| MissingPkgconfigPackage PkgconfigName VR
101101
| NewPackageDoesNotMatchExistingConstraint ConflictingDep
102102
| ConflictingConstraints ConflictingDep ConflictingDep
103+
| NewPackageIsMissingRequiredExe UnqualComponentName (DependencyReason QPN)
104+
| PackageRequiresMissingExe QPN UnqualComponentName
103105
| CannotInstall
104106
| CannotReinstall
105107
| Shadowed

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

Lines changed: 113 additions & 44 deletions
Original file line numberDiff line numberDiff line change
@@ -107,6 +107,15 @@ data ValidateState = VS {
107107
saved :: Map QPN (FlaggedDeps QPN),
108108

109109
pa :: PreAssignment,
110+
111+
-- Map from package name to the executables that are provided by the chosen
112+
-- instance of that package.
113+
availableExes :: Map QPN [UnqualComponentName],
114+
115+
-- Map from package name to the executables that are required from that
116+
-- package.
117+
requiredExes :: Map QPN ExeDeps,
118+
110119
qualifyOptions :: QualifyOptions
111120
}
112121

@@ -127,17 +136,28 @@ type PPreAssignment = Map QPN MergedPkgDep
127136
-- | A dependency on a package, including its DependencyReason.
128137
data PkgDep = PkgDep (DependencyReason QPN) (Maybe UnqualComponentName) QPN CI
129138

139+
-- | Map from executable name to one of the reasons that the executable is
140+
-- required.
141+
type ExeDeps = Map UnqualComponentName (DependencyReason QPN)
142+
130143
-- | MergedPkgDep records constraints about the instances that can still be
131144
-- chosen, and in the extreme case fixes a concrete instance. Otherwise, it is a
132145
-- list of version ranges paired with the goals / variables that introduced
133-
-- them. It also records whether a package is a build-tool dependency, for use
134-
-- in log messages.
146+
-- them. It also records whether a package is a build-tool dependency, for each
147+
-- reason that it was introduced.
148+
--
149+
-- It is important to store the executable name with the version constraint, for
150+
-- error messages, because whether something is a build-tool dependency affects
151+
-- its qualifier, which affects which constraint is applied.
135152
data MergedPkgDep =
136153
MergedDepFixed (Maybe UnqualComponentName) (DependencyReason QPN) I
137-
| MergedDepConstrained (Maybe UnqualComponentName) [VROrigin]
154+
| MergedDepConstrained [VROrigin]
138155

139156
-- | Version ranges paired with origins.
140-
type VROrigin = (VR, DependencyReason QPN)
157+
type VROrigin = (VR, Maybe UnqualComponentName, DependencyReason QPN)
158+
159+
-- | The information needed to create a 'Fail' node.
160+
type Conflict = (ConflictSet, FailReason)
141161

142162
validate :: Tree d c -> Validate (Tree d c)
143163
validate = cata go
@@ -184,9 +204,11 @@ validate = cata go
184204
pkgPresent <- asks presentPkgs -- obtain the present pkg-config pkgs
185205
idx <- asks index -- obtain the index
186206
svd <- asks saved -- obtain saved dependencies
207+
aExes <- asks availableExes
208+
rExes <- asks requiredExes
187209
qo <- asks qualifyOptions
188210
-- obtain dependencies and index-dictated exclusions introduced by the choice
189-
let (PInfo deps _ _ mfr) = idx ! pn ! i
211+
let (PInfo deps exes _ mfr) = idx ! pn ! i
190212
-- qualify the deps in the current scope
191213
let qdeps = qualifyDeps qo qpn deps
192214
-- the new active constraints are given by the instance we have chosen,
@@ -200,11 +222,22 @@ validate = cata go
200222
case mfr of
201223
Just fr -> -- The index marks this as an invalid choice. We can stop.
202224
return (Fail (varToConflictSet (P qpn)) fr)
203-
_ -> case mnppa of
204-
Left (c, fr) -> -- We have an inconsistency. We can stop.
205-
return (Fail c fr)
206-
Right nppa -> -- We have an updated partial assignment for the recursive validation.
207-
local (\ s -> s { pa = PA nppa pfa psa, saved = nsvd }) r
225+
Nothing ->
226+
let newDeps :: Either Conflict (PPreAssignment, Map QPN ExeDeps)
227+
newDeps = do
228+
nppa <- mnppa
229+
rExes' <- extendRequiredExes aExes rExes newactives
230+
checkExesInNewPackage rExes qpn exes
231+
return (nppa, rExes')
232+
in case newDeps of
233+
Left (c, fr) -> -- We have an inconsistency. We can stop.
234+
return (Fail c fr)
235+
Right (nppa, rExes') -> -- We have an updated partial assignment for the recursive validation.
236+
local (\ s -> s { pa = PA nppa pfa psa
237+
, saved = nsvd
238+
, availableExes = M.insert qpn exes aExes
239+
, requiredExes = rExes'
240+
}) r
208241

209242
-- What to do for flag nodes ...
210243
goF :: QFN -> Bool -> Validate (Tree d c) -> Validate (Tree d c)
@@ -213,7 +246,9 @@ validate = cata go
213246
extSupported <- asks supportedExt -- obtain the supported extensions
214247
langSupported <- asks supportedLang -- obtain the supported languages
215248
pkgPresent <- asks presentPkgs -- obtain the present pkg-config pkgs
216-
svd <- asks saved -- obtain saved dependencies
249+
svd <- asks saved -- obtain saved dependencies
250+
aExes <- asks availableExes
251+
rExes <- asks requiredExes
217252
-- Note that there should be saved dependencies for the package in question,
218253
-- because while building, we do not choose flags before we see the packages
219254
-- that define them.
@@ -226,10 +261,13 @@ validate = cata go
226261
-- We now try to get the new active dependencies we might learn about because
227262
-- we have chosen a new flag.
228263
let newactives = extractNewDeps (F qfn) b npfa psa qdeps
264+
mNewRequiredExes = extendRequiredExes aExes rExes newactives
229265
-- As in the package case, we try to extend the partial assignment.
230-
case extend extSupported langSupported pkgPresent newactives ppa of
231-
Left (c, fr) -> return (Fail c fr) -- inconsistency found
232-
Right nppa -> local (\ s -> s { pa = PA nppa npfa psa }) r
266+
let mnppa = extend extSupported langSupported pkgPresent newactives ppa
267+
case liftM2 (,) mnppa mNewRequiredExes of
268+
Left (c, fr) -> return (Fail c fr) -- inconsistency found
269+
Right (nppa, rExes') ->
270+
local (\ s -> s { pa = PA nppa npfa psa, requiredExes = rExes' }) r
233271

234272
-- What to do for stanza nodes (similar to flag nodes) ...
235273
goS :: QSN -> Bool -> Validate (Tree d c) -> Validate (Tree d c)
@@ -238,7 +276,9 @@ validate = cata go
238276
extSupported <- asks supportedExt -- obtain the supported extensions
239277
langSupported <- asks supportedLang -- obtain the supported languages
240278
pkgPresent <- asks presentPkgs -- obtain the present pkg-config pkgs
241-
svd <- asks saved -- obtain saved dependencies
279+
svd <- asks saved -- obtain saved dependencies
280+
aExes <- asks availableExes
281+
rExes <- asks requiredExes
242282
-- Note that there should be saved dependencies for the package in question,
243283
-- because while building, we do not choose flags before we see the packages
244284
-- that define them.
@@ -251,10 +291,28 @@ validate = cata go
251291
-- We now try to get the new active dependencies we might learn about because
252292
-- we have chosen a new flag.
253293
let newactives = extractNewDeps (S qsn) b pfa npsa qdeps
294+
mNewRequiredExes = extendRequiredExes aExes rExes newactives
254295
-- As in the package case, we try to extend the partial assignment.
255-
case extend extSupported langSupported pkgPresent newactives ppa of
256-
Left (c, fr) -> return (Fail c fr) -- inconsistency found
257-
Right nppa -> local (\ s -> s { pa = PA nppa pfa npsa }) r
296+
let mnppa = extend extSupported langSupported pkgPresent newactives ppa
297+
case liftM2 (,) mnppa mNewRequiredExes of
298+
Left (c, fr) -> return (Fail c fr) -- inconsistency found
299+
Right (nppa, rExes') ->
300+
local (\ s -> s { pa = PA nppa pfa npsa, requiredExes = rExes' }) r
301+
302+
-- | Check that a newly chosen package instance contains all executables that
303+
-- are required from that package so far.
304+
checkExesInNewPackage :: Map QPN ExeDeps
305+
-> QPN
306+
-> [UnqualComponentName]
307+
-> Either Conflict ()
308+
checkExesInNewPackage required qpn providedExes =
309+
case M.toList $ deleteKeys providedExes (M.findWithDefault M.empty qpn required) of
310+
(missingExe, dr) : _ -> let cs = CS.insert (P qpn) $ dependencyReasonToCS dr
311+
in Left (cs, NewPackageIsMissingRequiredExe missingExe dr)
312+
[] -> Right ()
313+
where
314+
deleteKeys :: Ord k => [k] -> Map k v -> Map k v
315+
deleteKeys ks m = L.foldr M.delete m ks
258316

259317
-- | We try to extract as many concrete dependencies from the given flagged
260318
-- dependencies as possible. We make use of all the flag knowledge we have
@@ -314,12 +372,11 @@ extend :: (Extension -> Bool) -- ^ is a given extension supported
314372
-> (PkgconfigName -> VR -> Bool) -- ^ is a given pkg-config requirement satisfiable
315373
-> [LDep QPN]
316374
-> PPreAssignment
317-
-> Either (ConflictSet, FailReason) PPreAssignment
375+
-> Either Conflict PPreAssignment
318376
extend extSupported langSupported pkgPresent newactives ppa = foldM extendSingle ppa newactives
319377
where
320378

321-
extendSingle :: PPreAssignment -> LDep QPN
322-
-> Either (ConflictSet, FailReason) PPreAssignment
379+
extendSingle :: PPreAssignment -> LDep QPN -> Either Conflict PPreAssignment
323380
extendSingle a (LDep dr (Ext ext )) =
324381
if extSupported ext then Right a
325382
else Left (dependencyReasonToCS dr, UnsupportedExtension ext)
@@ -330,18 +387,16 @@ extend extSupported langSupported pkgPresent newactives ppa = foldM extendSingle
330387
if pkgPresent pn vr then Right a
331388
else Left (dependencyReasonToCS dr, MissingPkgconfigPackage pn vr)
332389
extendSingle a (LDep dr (Dep mExe qpn ci)) =
333-
let mergedDep = M.findWithDefault (MergedDepConstrained Nothing []) qpn a
390+
let mergedDep = M.findWithDefault (MergedDepConstrained []) qpn a
334391
in case (\ x -> M.insert qpn x a) <$> merge mergedDep (PkgDep dr mExe qpn ci) of
335392
Left (c, (d, d')) -> Left (c, ConflictingConstraints d d')
336393
Right x -> Right x
337394

338395
-- | Extend a package preassignment with a package choice. For example, when
339396
-- the solver chooses foo-2.0, it tries to add the constraint foo==2.0.
340-
extendWithPackageChoice :: PI QPN
341-
-> PPreAssignment
342-
-> Either (ConflictSet, FailReason) PPreAssignment
397+
extendWithPackageChoice :: PI QPN -> PPreAssignment -> Either Conflict PPreAssignment
343398
extendWithPackageChoice (PI qpn i) ppa =
344-
let mergedDep = M.findWithDefault (MergedDepConstrained Nothing []) qpn ppa
399+
let mergedDep = M.findWithDefault (MergedDepConstrained []) qpn ppa
345400
newChoice = PkgDep (DependencyReason qpn [] []) Nothing qpn (Fixed i)
346401
in case (\ x -> M.insert qpn x ppa) <$> merge mergedDep newChoice of
347402
Left (c, (d, _d')) -> -- Don't include the package choice in the
@@ -372,48 +427,60 @@ merge ::
372427
#endif
373428
MergedPkgDep -> PkgDep -> Either (ConflictSet, (ConflictingDep, ConflictingDep)) MergedPkgDep
374429
merge (MergedDepFixed mExe1 vs1 i1) (PkgDep vs2 mExe2 p ci@(Fixed i2))
375-
| i1 == i2 = Right $ MergedDepFixed (mergeExes mExe1 mExe2) vs1 i1
430+
| i1 == i2 = Right $ MergedDepFixed mExe1 vs1 i1
376431
| otherwise =
377432
Left ( (CS.union `on` dependencyReasonToCS) vs1 vs2
378433
, ( ConflictingDep vs1 mExe1 p (Fixed i1)
379434
, ConflictingDep vs2 mExe2 p ci ) )
380435

381436
merge (MergedDepFixed mExe1 vs1 i@(I v _)) (PkgDep vs2 mExe2 p ci@(Constrained vr))
382-
| checkVR vr v = Right $ MergedDepFixed (mergeExes mExe1 mExe2) vs1 i
437+
| checkVR vr v = Right $ MergedDepFixed mExe1 vs1 i
383438
| otherwise =
384439
Left ( (CS.union `on` dependencyReasonToCS) vs1 vs2
385440
, ( ConflictingDep vs1 mExe1 p (Fixed i)
386441
, ConflictingDep vs2 mExe2 p ci ) )
387442

388-
merge (MergedDepConstrained mExe1 vrOrigins) (PkgDep vs2 mExe2 p ci@(Fixed i@(I v _))) =
443+
merge (MergedDepConstrained vrOrigins) (PkgDep vs2 mExe2 p ci@(Fixed i@(I v _))) =
389444
go vrOrigins -- I tried "reverse vrOrigins" here, but it seems to slow things down ...
390445
where
391446
go :: [VROrigin] -> Either (ConflictSet, (ConflictingDep, ConflictingDep)) MergedPkgDep
392-
go [] = Right (MergedDepFixed (mergeExes mExe1 mExe2) vs2 i)
393-
go ((vr, vs1) : vros)
447+
go [] = Right (MergedDepFixed mExe2 vs2 i)
448+
go ((vr, mExe1, vs1) : vros)
394449
| checkVR vr v = go vros
395450
| otherwise =
396451
Left ( (CS.union `on` dependencyReasonToCS) vs1 vs2
397452
, ( ConflictingDep vs1 mExe1 p (Constrained vr)
398453
, ConflictingDep vs2 mExe2 p ci ) )
399454

400-
merge (MergedDepConstrained mExe1 vrOrigins) (PkgDep vs2 mExe2 _ (Constrained vr)) =
401-
Right (MergedDepConstrained (mergeExes mExe1 mExe2) $
455+
merge (MergedDepConstrained vrOrigins) (PkgDep vs2 mExe2 _ (Constrained vr)) =
456+
Right (MergedDepConstrained $
402457

403458
-- TODO: This line appends the new version range, to preserve the order used
404459
-- before a refactoring. Consider prepending the version range, if there is
405460
-- no negative performance impact.
406-
vrOrigins ++ [(vr, vs2)])
407-
408-
-- TODO: This function isn't correct, because cabal may need to build libs
409-
-- and/or multiple exes for a package. The merged value is only used to
410-
-- determine whether to print the name of an exe next to conflicts in log
411-
-- message, though. It should be removed when component-based solving is
412-
-- implemented.
413-
mergeExes :: Maybe UnqualComponentName
414-
-> Maybe UnqualComponentName
415-
-> Maybe UnqualComponentName
416-
mergeExes = (<|>)
461+
vrOrigins ++ [(vr, mExe2, vs2)])
462+
463+
-- | Takes a list of new dependencies and uses it to try to update the map of
464+
-- known executable dependencies. It returns a failure when a new dependency
465+
-- requires an executable that is missing from one of the previously chosen
466+
-- packages.
467+
extendRequiredExes :: Map QPN [UnqualComponentName]
468+
-> Map QPN ExeDeps
469+
-> [LDep QPN]
470+
-> Either Conflict (Map QPN ExeDeps)
471+
extendRequiredExes available = foldM extendSingle
472+
where
473+
extendSingle :: Map QPN ExeDeps -> LDep QPN -> Either Conflict (Map QPN ExeDeps)
474+
extendSingle required (LDep dr (Dep (Just exe) qpn _)) =
475+
let exeDeps = M.findWithDefault M.empty qpn required
476+
in -- Only check for the existence of the exe if its package has already
477+
-- been chosen.
478+
case M.lookup qpn available of
479+
Just exes
480+
| L.notElem exe exes -> let cs = CS.insert (P qpn) (dependencyReasonToCS dr)
481+
in Left (cs, PackageRequiresMissingExe qpn exe)
482+
_ -> Right $ M.insertWith' M.union qpn (M.insert exe dr exeDeps) required
483+
extendSingle required _ = Right required
417484

418485
-- | Interface.
419486
validateTree :: CompilerInfo -> Index -> PkgConfigDb -> Tree d c -> Tree d c
@@ -428,5 +495,7 @@ validateTree cinfo idx pkgConfigDb t = runValidate (validate t) VS {
428495
, index = idx
429496
, saved = M.empty
430497
, pa = PA M.empty M.empty M.empty
498+
, availableExes = M.empty
499+
, requiredExes = M.empty
431500
, qualifyOptions = defaultQualifyOptions idx
432501
}

cabal-install/tests/UnitTests/Distribution/Solver/Modular/Solver.hs

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -1239,7 +1239,7 @@ dbBJ8 = [
12391239
-------------------------------------------------------------------------------}
12401240
dbBuildTools1 :: ExampleDb
12411241
dbBuildTools1 = [
1242-
Right $ exAv "alex" 1 [],
1242+
Right $ exAv "alex" 1 [] `withExe` ExExe "alex" [],
12431243
Right $ exAv "A" 1 [ExBuildToolAny "alex"]
12441244
]
12451245

@@ -1253,8 +1253,8 @@ dbBuildTools2 = [
12531253
-- Test that we can solve for different versions of executables
12541254
dbBuildTools3 :: ExampleDb
12551255
dbBuildTools3 = [
1256-
Right $ exAv "alex" 1 [],
1257-
Right $ exAv "alex" 2 [],
1256+
Right $ exAv "alex" 1 [] `withExe` ExExe "alex" [],
1257+
Right $ exAv "alex" 2 [] `withExe` ExExe "alex" [],
12581258
Right $ exAv "A" 1 [ExBuildToolFix "alex" 1],
12591259
Right $ exAv "B" 1 [ExBuildToolFix "alex" 2],
12601260
Right $ exAv "C" 1 [ExAny "A", ExAny "B"]
@@ -1263,7 +1263,7 @@ dbBuildTools3 = [
12631263
-- Test that exe is not related to library choices
12641264
dbBuildTools4 :: ExampleDb
12651265
dbBuildTools4 = [
1266-
Right $ exAv "alex" 1 [ExFix "A" 1],
1266+
Right $ exAv "alex" 1 [ExFix "A" 1] `withExe` ExExe "alex" [],
12671267
Right $ exAv "A" 1 [],
12681268
Right $ exAv "A" 2 [],
12691269
Right $ exAv "B" 1 [ExBuildToolFix "alex" 1, ExFix "A" 2]
@@ -1272,8 +1272,8 @@ dbBuildTools4 = [
12721272
-- Test that build-tools on build-tools works
12731273
dbBuildTools5 :: ExampleDb
12741274
dbBuildTools5 = [
1275-
Right $ exAv "alex" 1 [],
1276-
Right $ exAv "happy" 1 [ExBuildToolAny "alex"],
1275+
Right $ exAv "alex" 1 [] `withExe` ExExe "alex" [],
1276+
Right $ exAv "happy" 1 [ExBuildToolAny "alex"] `withExe` ExExe "happy" [],
12771277
Right $ exAv "A" 1 [ExBuildToolAny "happy"]
12781278
]
12791279

0 commit comments

Comments
 (0)