@@ -107,6 +107,15 @@ data ValidateState = VS {
107
107
saved :: Map QPN (FlaggedDeps QPN ),
108
108
109
109
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
+
110
119
qualifyOptions :: QualifyOptions
111
120
}
112
121
@@ -127,17 +136,28 @@ type PPreAssignment = Map QPN MergedPkgDep
127
136
-- | A dependency on a package, including its DependencyReason.
128
137
data PkgDep = PkgDep (DependencyReason QPN ) (Maybe UnqualComponentName ) QPN CI
129
138
139
+ -- | Map from executable name to one of the reasons that the executable is
140
+ -- required.
141
+ type ExeDeps = Map UnqualComponentName (DependencyReason QPN )
142
+
130
143
-- | MergedPkgDep records constraints about the instances that can still be
131
144
-- chosen, and in the extreme case fixes a concrete instance. Otherwise, it is a
132
145
-- 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.
135
152
data MergedPkgDep =
136
153
MergedDepFixed (Maybe UnqualComponentName ) (DependencyReason QPN ) I
137
- | MergedDepConstrained ( Maybe UnqualComponentName ) [VROrigin ]
154
+ | MergedDepConstrained [VROrigin ]
138
155
139
156
-- | 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 )
141
161
142
162
validate :: Tree d c -> Validate (Tree d c )
143
163
validate = cata go
@@ -184,9 +204,11 @@ validate = cata go
184
204
pkgPresent <- asks presentPkgs -- obtain the present pkg-config pkgs
185
205
idx <- asks index -- obtain the index
186
206
svd <- asks saved -- obtain saved dependencies
207
+ aExes <- asks availableExes
208
+ rExes <- asks requiredExes
187
209
qo <- asks qualifyOptions
188
210
-- 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
190
212
-- qualify the deps in the current scope
191
213
let qdeps = qualifyDeps qo qpn deps
192
214
-- the new active constraints are given by the instance we have chosen,
@@ -200,11 +222,22 @@ validate = cata go
200
222
case mfr of
201
223
Just fr -> -- The index marks this as an invalid choice. We can stop.
202
224
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
208
241
209
242
-- What to do for flag nodes ...
210
243
goF :: QFN -> Bool -> Validate (Tree d c ) -> Validate (Tree d c )
@@ -213,7 +246,9 @@ validate = cata go
213
246
extSupported <- asks supportedExt -- obtain the supported extensions
214
247
langSupported <- asks supportedLang -- obtain the supported languages
215
248
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
217
252
-- Note that there should be saved dependencies for the package in question,
218
253
-- because while building, we do not choose flags before we see the packages
219
254
-- that define them.
@@ -226,10 +261,13 @@ validate = cata go
226
261
-- We now try to get the new active dependencies we might learn about because
227
262
-- we have chosen a new flag.
228
263
let newactives = extractNewDeps (F qfn) b npfa psa qdeps
264
+ mNewRequiredExes = extendRequiredExes aExes rExes newactives
229
265
-- 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
233
271
234
272
-- What to do for stanza nodes (similar to flag nodes) ...
235
273
goS :: QSN -> Bool -> Validate (Tree d c ) -> Validate (Tree d c )
@@ -238,7 +276,9 @@ validate = cata go
238
276
extSupported <- asks supportedExt -- obtain the supported extensions
239
277
langSupported <- asks supportedLang -- obtain the supported languages
240
278
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
242
282
-- Note that there should be saved dependencies for the package in question,
243
283
-- because while building, we do not choose flags before we see the packages
244
284
-- that define them.
@@ -251,10 +291,28 @@ validate = cata go
251
291
-- We now try to get the new active dependencies we might learn about because
252
292
-- we have chosen a new flag.
253
293
let newactives = extractNewDeps (S qsn) b pfa npsa qdeps
294
+ mNewRequiredExes = extendRequiredExes aExes rExes newactives
254
295
-- 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
258
316
259
317
-- | We try to extract as many concrete dependencies from the given flagged
260
318
-- 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
314
372
-> (PkgconfigName -> VR -> Bool ) -- ^ is a given pkg-config requirement satisfiable
315
373
-> [LDep QPN ]
316
374
-> PPreAssignment
317
- -> Either ( ConflictSet , FailReason ) PPreAssignment
375
+ -> Either Conflict PPreAssignment
318
376
extend extSupported langSupported pkgPresent newactives ppa = foldM extendSingle ppa newactives
319
377
where
320
378
321
- extendSingle :: PPreAssignment -> LDep QPN
322
- -> Either (ConflictSet , FailReason ) PPreAssignment
379
+ extendSingle :: PPreAssignment -> LDep QPN -> Either Conflict PPreAssignment
323
380
extendSingle a (LDep dr (Ext ext )) =
324
381
if extSupported ext then Right a
325
382
else Left (dependencyReasonToCS dr, UnsupportedExtension ext)
@@ -330,18 +387,16 @@ extend extSupported langSupported pkgPresent newactives ppa = foldM extendSingle
330
387
if pkgPresent pn vr then Right a
331
388
else Left (dependencyReasonToCS dr, MissingPkgconfigPackage pn vr)
332
389
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
334
391
in case (\ x -> M. insert qpn x a) <$> merge mergedDep (PkgDep dr mExe qpn ci) of
335
392
Left (c, (d, d')) -> Left (c, ConflictingConstraints d d')
336
393
Right x -> Right x
337
394
338
395
-- | Extend a package preassignment with a package choice. For example, when
339
396
-- 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
343
398
extendWithPackageChoice (PI qpn i) ppa =
344
- let mergedDep = M. findWithDefault (MergedDepConstrained Nothing [] ) qpn ppa
399
+ let mergedDep = M. findWithDefault (MergedDepConstrained [] ) qpn ppa
345
400
newChoice = PkgDep (DependencyReason qpn [] [] ) Nothing qpn (Fixed i)
346
401
in case (\ x -> M. insert qpn x ppa) <$> merge mergedDep newChoice of
347
402
Left (c, (d, _d')) -> -- Don't include the package choice in the
@@ -372,48 +427,60 @@ merge ::
372
427
#endif
373
428
MergedPkgDep -> PkgDep -> Either (ConflictSet , (ConflictingDep , ConflictingDep )) MergedPkgDep
374
429
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
376
431
| otherwise =
377
432
Left ( (CS. union `on` dependencyReasonToCS) vs1 vs2
378
433
, ( ConflictingDep vs1 mExe1 p (Fixed i1)
379
434
, ConflictingDep vs2 mExe2 p ci ) )
380
435
381
436
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
383
438
| otherwise =
384
439
Left ( (CS. union `on` dependencyReasonToCS) vs1 vs2
385
440
, ( ConflictingDep vs1 mExe1 p (Fixed i)
386
441
, ConflictingDep vs2 mExe2 p ci ) )
387
442
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 _))) =
389
444
go vrOrigins -- I tried "reverse vrOrigins" here, but it seems to slow things down ...
390
445
where
391
446
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)
394
449
| checkVR vr v = go vros
395
450
| otherwise =
396
451
Left ( (CS. union `on` dependencyReasonToCS) vs1 vs2
397
452
, ( ConflictingDep vs1 mExe1 p (Constrained vr)
398
453
, ConflictingDep vs2 mExe2 p ci ) )
399
454
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 $
402
457
403
458
-- TODO: This line appends the new version range, to preserve the order used
404
459
-- before a refactoring. Consider prepending the version range, if there is
405
460
-- 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
417
484
418
485
-- | Interface.
419
486
validateTree :: CompilerInfo -> Index -> PkgConfigDb -> Tree d c -> Tree d c
@@ -428,5 +495,7 @@ validateTree cinfo idx pkgConfigDb t = runValidate (validate t) VS {
428
495
, index = idx
429
496
, saved = M. empty
430
497
, pa = PA M. empty M. empty M. empty
498
+ , availableExes = M. empty
499
+ , requiredExes = M. empty
431
500
, qualifyOptions = defaultQualifyOptions idx
432
501
}
0 commit comments