Add NoImplicitPrelude to buildTypeScript
[cabal.git] / cabal-install / src / Distribution / Client / Dependency.hs
blob66a0a103c232a761534d5448d9eb486377e36d87
1 -----------------------------------------------------------------------------
3 -----------------------------------------------------------------------------
5 -- |
6 -- Module : Distribution.Client.Dependency
7 -- Copyright : (c) David Himmelstrup 2005,
8 -- Bjorn Bringert 2007
9 -- Duncan Coutts 2008
10 -- License : BSD-like
12 -- Maintainer : cabal-devel@gmail.com
13 -- Stability : provisional
14 -- Portability : portable
16 -- Top level interface to dependency resolution.
17 module Distribution.Client.Dependency
18 ( -- * The main package dependency resolver
19 DepResolverParams
20 , resolveDependencies
21 , Progress (..)
22 , foldProgress
24 -- * Alternate, simple resolver that does not do dependencies recursively
25 , resolveWithoutDependencies
27 -- * Constructing resolver policies
28 , PackageProperty (..)
29 , PackageConstraint (..)
30 , scopeToplevel
31 , PackagesPreferenceDefault (..)
32 , PackagePreference (..)
34 -- ** Standard policy
35 , basicInstallPolicy
36 , standardInstallPolicy
37 , PackageSpecifier (..)
39 -- ** Extra policy options
40 , upgradeDependencies
41 , reinstallTargets
43 -- ** Policy utils
44 , addConstraints
45 , addPreferences
46 , setPreferenceDefault
47 , setReorderGoals
48 , setCountConflicts
49 , setFineGrainedConflicts
50 , setMinimizeConflictSet
51 , setIndependentGoals
52 , setAvoidReinstalls
53 , setShadowPkgs
54 , setStrongFlags
55 , setAllowBootLibInstalls
56 , setOnlyConstrained
57 , setMaxBackjumps
58 , setEnableBackjumping
59 , setSolveExecutables
60 , setGoalOrder
61 , setSolverVerbosity
62 , removeLowerBounds
63 , removeUpperBounds
64 , addDefaultSetupDependencies
65 , addSetupCabalMinVersionConstraint
66 , addSetupCabalMaxVersionConstraint
67 ) where
69 import Distribution.Client.Compat.Prelude
71 import Distribution.Client.Dependency.Types
72 ( PackagesPreferenceDefault (..)
74 import Distribution.Client.SolverInstallPlan (SolverInstallPlan)
75 import qualified Distribution.Client.SolverInstallPlan as SolverInstallPlan
76 import Distribution.Client.Types
77 ( AllowNewer (..)
78 , AllowOlder (..)
79 , PackageSpecifier (..)
80 , RelaxDepMod (..)
81 , RelaxDepScope (..)
82 , RelaxDepSubject (..)
83 , RelaxDeps (..)
84 , RelaxedDep (..)
85 , SourcePackageDb (SourcePackageDb)
86 , UnresolvedPkgLoc
87 , UnresolvedSourcePackage
88 , isRelaxDeps
89 , pkgSpecifierConstraints
90 , pkgSpecifierTarget
92 import Distribution.Client.Utils
93 ( MergeResult (..)
94 , duplicatesBy
95 , mergeBy
97 import qualified Distribution.Compat.Graph as Graph
98 import Distribution.Compiler
99 ( CompilerInfo (..)
101 import Distribution.Package
102 ( Package (..)
103 , PackageId
104 , PackageIdentifier (PackageIdentifier)
105 , PackageName
106 , mkPackageName
107 , packageName
108 , packageVersion
110 import qualified Distribution.PackageDescription as PD
111 import Distribution.PackageDescription.Configuration
112 ( finalizePD
114 import qualified Distribution.PackageDescription.Configuration as PD
115 import Distribution.Simple.PackageIndex (InstalledPackageIndex)
116 import qualified Distribution.Simple.PackageIndex as InstalledPackageIndex
117 import Distribution.Simple.Setup
118 ( asBool
120 import Distribution.Solver.Modular
121 ( PruneAfterFirstSuccess (..)
122 , SolverConfig (..)
123 , modularResolver
125 import Distribution.System
126 ( Platform
128 import Distribution.Types.Dependency
129 import Distribution.Verbosity
130 ( normal
132 import Distribution.Version
134 import Distribution.Solver.Types.ComponentDeps (ComponentDeps)
135 import qualified Distribution.Solver.Types.ComponentDeps as CD
136 import Distribution.Solver.Types.ConstraintSource
137 import Distribution.Solver.Types.DependencyResolver
138 import Distribution.Solver.Types.InstalledPreference as Preference
139 import Distribution.Solver.Types.LabeledPackageConstraint
140 import Distribution.Solver.Types.OptionalStanza
141 import Distribution.Solver.Types.PackageConstraint
142 import qualified Distribution.Solver.Types.PackageIndex as PackageIndex
143 import Distribution.Solver.Types.PackagePath
144 import Distribution.Solver.Types.PackagePreferences
145 import Distribution.Solver.Types.PkgConfigDb (PkgConfigDb)
146 import Distribution.Solver.Types.Progress
147 import Distribution.Solver.Types.ResolverPackage
148 import Distribution.Solver.Types.Settings
149 import Distribution.Solver.Types.SolverId
150 import Distribution.Solver.Types.SolverPackage
151 import Distribution.Solver.Types.SourcePackage
152 import Distribution.Solver.Types.Variable
154 import Control.Exception
155 ( assert
157 import Data.List
158 ( maximumBy
160 import qualified Data.Map as Map
161 import qualified Data.Set as Set
163 -- ------------------------------------------------------------
165 -- * High level planner policy
167 -- ------------------------------------------------------------
169 -- | The set of parameters to the dependency resolver. These parameters are
170 -- relatively low level but many kinds of high level policies can be
171 -- implemented in terms of adjustments to the parameters.
172 data DepResolverParams = DepResolverParams
173 { depResolverTargets :: Set PackageName
174 , depResolverConstraints :: [LabeledPackageConstraint]
175 , depResolverPreferences :: [PackagePreference]
176 , depResolverPreferenceDefault :: PackagesPreferenceDefault
177 , depResolverInstalledPkgIndex :: InstalledPackageIndex
178 , depResolverSourcePkgIndex :: PackageIndex.PackageIndex UnresolvedSourcePackage
179 , depResolverReorderGoals :: ReorderGoals
180 , depResolverCountConflicts :: CountConflicts
181 , depResolverFineGrainedConflicts :: FineGrainedConflicts
182 , depResolverMinimizeConflictSet :: MinimizeConflictSet
183 , depResolverIndependentGoals :: IndependentGoals
184 , depResolverAvoidReinstalls :: AvoidReinstalls
185 , depResolverShadowPkgs :: ShadowPkgs
186 , depResolverStrongFlags :: StrongFlags
187 , depResolverAllowBootLibInstalls :: AllowBootLibInstalls
188 -- ^ Whether to allow base and its dependencies to be installed.
189 , depResolverOnlyConstrained :: OnlyConstrained
190 -- ^ Whether to only allow explicitly constrained packages plus
191 -- goals or to allow any package.
192 , depResolverMaxBackjumps :: Maybe Int
193 , depResolverEnableBackjumping :: EnableBackjumping
194 , depResolverSolveExecutables :: SolveExecutables
195 -- ^ Whether or not to solve for dependencies on executables.
196 -- This should be true, except in the legacy code path where
197 -- we can't tell if an executable has been installed or not,
198 -- so we shouldn't solve for them. See #3875.
199 , depResolverGoalOrder :: Maybe (Variable QPN -> Variable QPN -> Ordering)
200 -- ^ Function to override the solver's goal-ordering heuristics.
201 , depResolverVerbosity :: Verbosity
204 showDepResolverParams :: DepResolverParams -> String
205 showDepResolverParams p =
206 "targets: "
207 ++ intercalate ", " (map prettyShow $ Set.toList (depResolverTargets p))
208 ++ "\nconstraints: "
209 ++ concatMap
210 (("\n " ++) . showLabeledConstraint)
211 (depResolverConstraints p)
212 ++ "\npreferences: "
213 ++ concatMap
214 (("\n " ++) . showPackagePreference)
215 (depResolverPreferences p)
216 ++ "\nstrategy: "
217 ++ show (depResolverPreferenceDefault p)
218 ++ "\nreorder goals: "
219 ++ show (asBool (depResolverReorderGoals p))
220 ++ "\ncount conflicts: "
221 ++ show (asBool (depResolverCountConflicts p))
222 ++ "\nfine grained conflicts: "
223 ++ show (asBool (depResolverFineGrainedConflicts p))
224 ++ "\nminimize conflict set: "
225 ++ show (asBool (depResolverMinimizeConflictSet p))
226 ++ "\nindependent goals: "
227 ++ show (asBool (depResolverIndependentGoals p))
228 ++ "\navoid reinstalls: "
229 ++ show (asBool (depResolverAvoidReinstalls p))
230 ++ "\nshadow packages: "
231 ++ show (asBool (depResolverShadowPkgs p))
232 ++ "\nstrong flags: "
233 ++ show (asBool (depResolverStrongFlags p))
234 ++ "\nallow boot library installs: "
235 ++ show (asBool (depResolverAllowBootLibInstalls p))
236 ++ "\nonly constrained packages: "
237 ++ show (depResolverOnlyConstrained p)
238 ++ "\nmax backjumps: "
239 ++ maybe
240 "infinite"
241 show
242 (depResolverMaxBackjumps p)
243 where
244 showLabeledConstraint :: LabeledPackageConstraint -> String
245 showLabeledConstraint (LabeledPackageConstraint pc src) =
246 showPackageConstraint pc ++ " (" ++ showConstraintSource src ++ ")"
248 -- | A package selection preference for a particular package.
250 -- Preferences are soft constraints that the dependency resolver should try to
251 -- respect where possible. It is not specified if preferences on some packages
252 -- are more important than others.
253 data PackagePreference
254 = -- | A suggested constraint on the version number.
255 PackageVersionPreference PackageName VersionRange
256 | -- | If we prefer versions of packages that are already installed.
257 PackageInstalledPreference PackageName InstalledPreference
258 | -- | If we would prefer to enable these optional stanzas
259 -- (i.e. test suites and/or benchmarks)
260 PackageStanzasPreference PackageName [OptionalStanza]
262 -- | Provide a textual representation of a package preference
263 -- for debugging purposes.
264 showPackagePreference :: PackagePreference -> String
265 showPackagePreference (PackageVersionPreference pn vr) =
266 prettyShow pn ++ " " ++ prettyShow (simplifyVersionRange vr)
267 showPackagePreference (PackageInstalledPreference pn ip) =
268 prettyShow pn ++ " " ++ show ip
269 showPackagePreference (PackageStanzasPreference pn st) =
270 prettyShow pn ++ " " ++ show st
272 basicDepResolverParams
273 :: InstalledPackageIndex
274 -> PackageIndex.PackageIndex UnresolvedSourcePackage
275 -> DepResolverParams
276 basicDepResolverParams installedPkgIndex sourcePkgIndex =
277 DepResolverParams
278 { depResolverTargets = Set.empty
279 , depResolverConstraints = []
280 , depResolverPreferences = []
281 , depResolverPreferenceDefault = PreferLatestForSelected
282 , depResolverInstalledPkgIndex = installedPkgIndex
283 , depResolverSourcePkgIndex = sourcePkgIndex
284 , depResolverReorderGoals = ReorderGoals False
285 , depResolverCountConflicts = CountConflicts True
286 , depResolverFineGrainedConflicts = FineGrainedConflicts True
287 , depResolverMinimizeConflictSet = MinimizeConflictSet False
288 , depResolverIndependentGoals = IndependentGoals False
289 , depResolverAvoidReinstalls = AvoidReinstalls False
290 , depResolverShadowPkgs = ShadowPkgs False
291 , depResolverStrongFlags = StrongFlags False
292 , depResolverAllowBootLibInstalls = AllowBootLibInstalls False
293 , depResolverOnlyConstrained = OnlyConstrainedNone
294 , depResolverMaxBackjumps = Nothing
295 , depResolverEnableBackjumping = EnableBackjumping True
296 , depResolverSolveExecutables = SolveExecutables True
297 , depResolverGoalOrder = Nothing
298 , depResolverVerbosity = normal
301 addTargets
302 :: [PackageName]
303 -> DepResolverParams
304 -> DepResolverParams
305 addTargets extraTargets params =
306 params
307 { depResolverTargets = Set.fromList extraTargets `Set.union` depResolverTargets params
310 addConstraints
311 :: [LabeledPackageConstraint]
312 -> DepResolverParams
313 -> DepResolverParams
314 addConstraints extraConstraints params =
315 params
316 { depResolverConstraints =
317 extraConstraints
318 ++ depResolverConstraints params
321 addPreferences
322 :: [PackagePreference]
323 -> DepResolverParams
324 -> DepResolverParams
325 addPreferences extraPreferences params =
326 params
327 { depResolverPreferences =
328 extraPreferences
329 ++ depResolverPreferences params
332 setPreferenceDefault
333 :: PackagesPreferenceDefault
334 -> DepResolverParams
335 -> DepResolverParams
336 setPreferenceDefault preferenceDefault params =
337 params
338 { depResolverPreferenceDefault = preferenceDefault
341 setReorderGoals :: ReorderGoals -> DepResolverParams -> DepResolverParams
342 setReorderGoals reorder params =
343 params
344 { depResolverReorderGoals = reorder
347 setCountConflicts :: CountConflicts -> DepResolverParams -> DepResolverParams
348 setCountConflicts count params =
349 params
350 { depResolverCountConflicts = count
353 setFineGrainedConflicts :: FineGrainedConflicts -> DepResolverParams -> DepResolverParams
354 setFineGrainedConflicts fineGrained params =
355 params
356 { depResolverFineGrainedConflicts = fineGrained
359 setMinimizeConflictSet :: MinimizeConflictSet -> DepResolverParams -> DepResolverParams
360 setMinimizeConflictSet minimize params =
361 params
362 { depResolverMinimizeConflictSet = minimize
365 setIndependentGoals :: IndependentGoals -> DepResolverParams -> DepResolverParams
366 setIndependentGoals indep params =
367 params
368 { depResolverIndependentGoals = indep
371 setAvoidReinstalls :: AvoidReinstalls -> DepResolverParams -> DepResolverParams
372 setAvoidReinstalls avoid params =
373 params
374 { depResolverAvoidReinstalls = avoid
377 setShadowPkgs :: ShadowPkgs -> DepResolverParams -> DepResolverParams
378 setShadowPkgs shadow params =
379 params
380 { depResolverShadowPkgs = shadow
383 setStrongFlags :: StrongFlags -> DepResolverParams -> DepResolverParams
384 setStrongFlags sf params =
385 params
386 { depResolverStrongFlags = sf
389 setAllowBootLibInstalls :: AllowBootLibInstalls -> DepResolverParams -> DepResolverParams
390 setAllowBootLibInstalls i params =
391 params
392 { depResolverAllowBootLibInstalls = i
395 setOnlyConstrained :: OnlyConstrained -> DepResolverParams -> DepResolverParams
396 setOnlyConstrained i params =
397 params
398 { depResolverOnlyConstrained = i
401 setMaxBackjumps :: Maybe Int -> DepResolverParams -> DepResolverParams
402 setMaxBackjumps n params =
403 params
404 { depResolverMaxBackjumps = n
407 setEnableBackjumping :: EnableBackjumping -> DepResolverParams -> DepResolverParams
408 setEnableBackjumping b params =
409 params
410 { depResolverEnableBackjumping = b
413 setSolveExecutables :: SolveExecutables -> DepResolverParams -> DepResolverParams
414 setSolveExecutables b params =
415 params
416 { depResolverSolveExecutables = b
419 setGoalOrder
420 :: Maybe (Variable QPN -> Variable QPN -> Ordering)
421 -> DepResolverParams
422 -> DepResolverParams
423 setGoalOrder order params =
424 params
425 { depResolverGoalOrder = order
428 setSolverVerbosity :: Verbosity -> DepResolverParams -> DepResolverParams
429 setSolverVerbosity verbosity params =
430 params
431 { depResolverVerbosity = verbosity
434 -- | Some packages are specific to a given compiler version and should never be
435 -- reinstalled.
436 dontInstallNonReinstallablePackages :: DepResolverParams -> DepResolverParams
437 dontInstallNonReinstallablePackages params =
438 addConstraints extraConstraints params
439 where
440 extraConstraints =
441 [ LabeledPackageConstraint
442 (PackageConstraint (ScopeAnyQualifier pkgname) PackagePropertyInstalled)
443 ConstraintSourceNonReinstallablePackage
444 | pkgname <- nonReinstallablePackages
447 -- | The set of non-reinstallable packages includes those which cannot be
448 -- rebuilt using a GHC installation and Hackage-published source distribution.
449 -- There are a few reasons why this might be true:
451 -- * the package overrides its unit ID (e.g. with ghc's @-this-unit-id@ flag),
452 -- which can result in multiple indistinguishable packages (having potentially
453 -- different ABIs) with the same unit ID.
455 -- * the package contains definitions of wired-in declarations which tie
456 -- it to a particular compiler (e.g. we can't build link against
457 -- @base-4.18.0.0@ using GHC 9.6.1).
459 -- * the package does not have a complete (that is, buildable) source distribution.
460 -- For instance, some packages provided by GHC rely on files outside of the
461 -- source tree generated by GHC's build system.
462 nonReinstallablePackages :: [PackageName]
463 nonReinstallablePackages =
464 [ mkPackageName "base"
465 , mkPackageName "ghc-bignum"
466 , mkPackageName "ghc-prim"
467 , mkPackageName "ghc"
468 , mkPackageName "integer-gmp"
469 , mkPackageName "integer-simple"
470 , mkPackageName "template-haskell"
473 addSourcePackages
474 :: [UnresolvedSourcePackage]
475 -> DepResolverParams
476 -> DepResolverParams
477 addSourcePackages pkgs params =
478 params
479 { depResolverSourcePkgIndex =
480 foldl
481 (flip PackageIndex.insert)
482 (depResolverSourcePkgIndex params)
483 pkgs
486 hideInstalledPackagesSpecificBySourcePackageId
487 :: [PackageId]
488 -> DepResolverParams
489 -> DepResolverParams
490 hideInstalledPackagesSpecificBySourcePackageId pkgids params =
491 -- TODO: this should work using exclude constraints instead
492 params
493 { depResolverInstalledPkgIndex =
494 foldl'
495 (flip InstalledPackageIndex.deleteSourcePackageId)
496 (depResolverInstalledPkgIndex params)
497 pkgids
500 hideInstalledPackagesAllVersions
501 :: [PackageName]
502 -> DepResolverParams
503 -> DepResolverParams
504 hideInstalledPackagesAllVersions pkgnames params =
505 -- TODO: this should work using exclude constraints instead
506 params
507 { depResolverInstalledPkgIndex =
508 foldl'
509 (flip InstalledPackageIndex.deletePackageName)
510 (depResolverInstalledPkgIndex params)
511 pkgnames
514 -- | Remove upper bounds in dependencies using the policy specified by the
515 -- 'AllowNewer' argument (all/some/none).
517 -- Note: It's important to apply 'removeUpperBounds' after
518 -- 'addSourcePackages'. Otherwise, the packages inserted by
519 -- 'addSourcePackages' won't have upper bounds in dependencies relaxed.
520 removeUpperBounds :: AllowNewer -> DepResolverParams -> DepResolverParams
521 removeUpperBounds (AllowNewer relDeps) = removeBounds RelaxUpper relDeps
523 -- | Dual of 'removeUpperBounds'
524 removeLowerBounds :: AllowOlder -> DepResolverParams -> DepResolverParams
525 removeLowerBounds (AllowOlder relDeps) = removeBounds RelaxLower relDeps
527 data RelaxKind = RelaxLower | RelaxUpper
529 -- | Common internal implementation of 'removeLowerBounds'/'removeUpperBounds'
530 removeBounds :: RelaxKind -> RelaxDeps -> DepResolverParams -> DepResolverParams
531 removeBounds _ rd params | not (isRelaxDeps rd) = params -- no-op optimisation
532 removeBounds relKind relDeps params =
533 params
534 { depResolverSourcePkgIndex = sourcePkgIndex'
536 where
537 sourcePkgIndex' :: PackageIndex.PackageIndex UnresolvedSourcePackage
538 sourcePkgIndex' = relaxDeps <$> depResolverSourcePkgIndex params
540 relaxDeps :: UnresolvedSourcePackage -> UnresolvedSourcePackage
541 relaxDeps srcPkg =
542 srcPkg
543 { srcpkgDescription = relaxPackageDeps relKind relDeps (srcpkgDescription srcPkg)
546 -- | Relax the dependencies of this package if needed.
548 -- Helper function used by 'removeBounds'
549 relaxPackageDeps
550 :: RelaxKind
551 -> RelaxDeps
552 -> PD.GenericPackageDescription
553 -> PD.GenericPackageDescription
554 relaxPackageDeps _ rd gpd | not (isRelaxDeps rd) = gpd -- subsumed by no-op case in 'removeBounds'
555 relaxPackageDeps relKind RelaxDepsAll gpd = PD.transformAllBuildDepends relaxAll gpd
556 where
557 relaxAll :: Dependency -> Dependency
558 relaxAll (Dependency pkgName verRange cs) =
559 Dependency pkgName (removeBound relKind RelaxDepModNone verRange) cs
560 relaxPackageDeps relKind (RelaxDepsSome depsToRelax0) gpd =
561 PD.transformAllBuildDepends relaxSome gpd
562 where
563 thisPkgName = packageName gpd
564 thisPkgId = packageId gpd
565 depsToRelax = Map.fromList $ mapMaybe f depsToRelax0
567 f :: RelaxedDep -> Maybe (RelaxDepSubject, RelaxDepMod)
568 f (RelaxedDep scope rdm p) = case scope of
569 RelaxDepScopeAll -> Just (p, rdm)
570 RelaxDepScopePackage p0
571 | p0 == thisPkgName -> Just (p, rdm)
572 | otherwise -> Nothing
573 RelaxDepScopePackageId p0
574 | p0 == thisPkgId -> Just (p, rdm)
575 | otherwise -> Nothing
577 relaxSome :: Dependency -> Dependency
578 relaxSome d@(Dependency depName verRange cs)
579 | Just relMod <- Map.lookup RelaxDepSubjectAll depsToRelax =
580 -- a '*'-subject acts absorbing, for consistency with
581 -- the 'Semigroup RelaxDeps' instance
582 Dependency depName (removeBound relKind relMod verRange) cs
583 | Just relMod <- Map.lookup (RelaxDepSubjectPkg depName) depsToRelax =
584 Dependency depName (removeBound relKind relMod verRange) cs
585 | otherwise = d -- no-op
587 -- | Internal helper for 'relaxPackageDeps'
588 removeBound :: RelaxKind -> RelaxDepMod -> VersionRange -> VersionRange
589 removeBound RelaxLower RelaxDepModNone = removeLowerBound
590 removeBound RelaxUpper RelaxDepModNone = removeUpperBound
591 removeBound RelaxLower RelaxDepModCaret = transformCaretLower
592 removeBound RelaxUpper RelaxDepModCaret = transformCaretUpper
594 -- | Supply defaults for packages without explicit Setup dependencies
596 -- Note: It's important to apply 'addDefaultSetupDepends' after
597 -- 'addSourcePackages'. Otherwise, the packages inserted by
598 -- 'addSourcePackages' won't have upper bounds in dependencies relaxed.
599 addDefaultSetupDependencies
600 :: (UnresolvedSourcePackage -> Maybe [Dependency])
601 -> DepResolverParams
602 -> DepResolverParams
603 addDefaultSetupDependencies defaultSetupDeps params =
604 params
605 { depResolverSourcePkgIndex =
606 fmap applyDefaultSetupDeps (depResolverSourcePkgIndex params)
608 where
609 applyDefaultSetupDeps :: UnresolvedSourcePackage -> UnresolvedSourcePackage
610 applyDefaultSetupDeps srcpkg =
611 srcpkg
612 { srcpkgDescription =
613 gpkgdesc
614 { PD.packageDescription =
615 pkgdesc
616 { PD.setupBuildInfo =
617 case PD.setupBuildInfo pkgdesc of
618 Just sbi -> Just sbi
619 Nothing -> case defaultSetupDeps srcpkg of
620 Nothing -> Nothing
621 Just deps
622 | isCustom ->
623 Just
624 PD.SetupBuildInfo
625 { PD.defaultSetupDepends = True
626 , PD.setupDepends = deps
628 | otherwise -> Nothing
632 where
633 isCustom = PD.buildType pkgdesc == PD.Custom || PD.buildType pkgdesc == PD.Hooks
634 gpkgdesc = srcpkgDescription srcpkg
635 pkgdesc = PD.packageDescription gpkgdesc
637 -- | If a package has a custom setup then we need to add a setup-depends
638 -- on Cabal.
639 addSetupCabalMinVersionConstraint
640 :: Version
641 -> DepResolverParams
642 -> DepResolverParams
643 addSetupCabalMinVersionConstraint minVersion =
644 addConstraints
645 [ LabeledPackageConstraint
646 ( PackageConstraint
647 (ScopeAnySetupQualifier cabalPkgname)
648 (PackagePropertyVersion $ orLaterVersion minVersion)
650 ConstraintSetupCabalMinVersion
652 where
653 cabalPkgname = mkPackageName "Cabal"
655 -- | Variant of 'addSetupCabalMinVersionConstraint' which sets an
656 -- upper bound on @setup.Cabal@ labeled with 'ConstraintSetupCabalMaxVersion'.
657 addSetupCabalMaxVersionConstraint
658 :: Version
659 -> DepResolverParams
660 -> DepResolverParams
661 addSetupCabalMaxVersionConstraint maxVersion =
662 addConstraints
663 [ LabeledPackageConstraint
664 ( PackageConstraint
665 (ScopeAnySetupQualifier cabalPkgname)
666 (PackagePropertyVersion $ earlierVersion maxVersion)
668 ConstraintSetupCabalMaxVersion
670 where
671 cabalPkgname = mkPackageName "Cabal"
673 upgradeDependencies :: DepResolverParams -> DepResolverParams
674 upgradeDependencies = setPreferenceDefault PreferAllLatest
676 reinstallTargets :: DepResolverParams -> DepResolverParams
677 reinstallTargets params =
678 hideInstalledPackagesAllVersions (Set.toList $ depResolverTargets params) params
680 -- | A basic solver policy on which all others are built.
681 basicInstallPolicy
682 :: InstalledPackageIndex
683 -> SourcePackageDb
684 -> [PackageSpecifier UnresolvedSourcePackage]
685 -> DepResolverParams
686 basicInstallPolicy
687 installedPkgIndex
688 (SourcePackageDb sourcePkgIndex sourcePkgPrefs)
689 pkgSpecifiers =
690 addPreferences
691 [ PackageVersionPreference name ver
692 | (name, ver) <- Map.toList sourcePkgPrefs
694 . addConstraints
695 (concatMap pkgSpecifierConstraints pkgSpecifiers)
696 . addTargets
697 (map pkgSpecifierTarget pkgSpecifiers)
698 . hideInstalledPackagesSpecificBySourcePackageId
699 [packageId pkg | SpecificSourcePackage pkg <- pkgSpecifiers]
700 . addSourcePackages
701 [pkg | SpecificSourcePackage pkg <- pkgSpecifiers]
702 $ basicDepResolverParams
703 installedPkgIndex
704 sourcePkgIndex
706 -- | The policy used by all the standard commands, install, fetch, freeze etc
707 -- (but not the v2-build and related commands).
709 -- It extends the 'basicInstallPolicy' with a policy on setup deps.
710 standardInstallPolicy
711 :: InstalledPackageIndex
712 -> SourcePackageDb
713 -> [PackageSpecifier UnresolvedSourcePackage]
714 -> DepResolverParams
715 standardInstallPolicy installedPkgIndex sourcePkgDb pkgSpecifiers =
716 addDefaultSetupDependencies mkDefaultSetupDeps $
717 basicInstallPolicy
718 installedPkgIndex
719 sourcePkgDb
720 pkgSpecifiers
721 where
722 -- Force Cabal >= 1.24 dep when the package is affected by #3199.
723 mkDefaultSetupDeps :: UnresolvedSourcePackage -> Maybe [Dependency]
724 mkDefaultSetupDeps srcpkg
725 | affected =
726 Just [Dependency (mkPackageName "Cabal") (orLaterVersion $ mkVersion [1, 24]) mainLibSet]
727 | otherwise = Nothing
728 where
729 gpkgdesc = srcpkgDescription srcpkg
730 pkgdesc = PD.packageDescription gpkgdesc
731 bt = PD.buildType pkgdesc
732 affected = (bt == PD.Custom || bt == PD.Hooks) && hasBuildableFalse gpkgdesc
734 -- Does this package contain any components with non-empty 'build-depends'
735 -- and a 'buildable' field that could potentially be set to 'False'? False
736 -- positives are possible.
737 hasBuildableFalse :: PD.GenericPackageDescription -> Bool
738 hasBuildableFalse gpkg =
739 not (all alwaysTrue (zipWith PD.cOr buildableConditions noDepConditions))
740 where
741 buildableConditions = PD.extractConditions PD.buildable gpkg
742 noDepConditions =
743 PD.extractConditions
744 (null . PD.targetBuildDepends)
745 gpkg
746 alwaysTrue (PD.Lit True) = True
747 alwaysTrue _ = False
749 -- ------------------------------------------------------------
751 -- * Interface to the standard resolver
753 -- ------------------------------------------------------------
755 runSolver :: SolverConfig -> DependencyResolver UnresolvedPkgLoc
756 runSolver = modularResolver
758 -- | Run the dependency solver.
760 -- Since this is potentially an expensive operation, the result is wrapped in a
761 -- a 'Progress' structure that can be unfolded to provide progress information,
762 -- logging messages and the final result or an error.
763 resolveDependencies
764 :: Platform
765 -> CompilerInfo
766 -> PkgConfigDb
767 -> DepResolverParams
768 -> Progress String String SolverInstallPlan
769 resolveDependencies platform comp pkgConfigDB params =
770 Step (showDepResolverParams finalparams) $
771 fmap (validateSolverResult platform comp indGoals) $
772 runSolver
773 ( SolverConfig
774 reordGoals
775 cntConflicts
776 fineGrained
777 minimize
778 indGoals
779 noReinstalls
780 shadowing
781 strFlags
782 onlyConstrained_
783 maxBkjumps
784 enableBj
785 solveExes
786 order
787 verbosity
788 (PruneAfterFirstSuccess False)
790 platform
791 comp
792 installedPkgIndex
793 sourcePkgIndex
794 pkgConfigDB
795 preferences
796 constraints
797 targets
798 where
799 finalparams@( DepResolverParams
800 targets
801 constraints
802 prefs
803 defpref
804 installedPkgIndex
805 sourcePkgIndex
806 reordGoals
807 cntConflicts
808 fineGrained
809 minimize
810 indGoals
811 noReinstalls
812 shadowing
813 strFlags
814 _allowBootLibs
815 onlyConstrained_
816 maxBkjumps
817 enableBj
818 solveExes
819 order
820 verbosity
822 if asBool (depResolverAllowBootLibInstalls params)
823 then params
824 else dontInstallNonReinstallablePackages params
826 preferences :: PackageName -> PackagePreferences
827 preferences = interpretPackagesPreference targets defpref prefs
829 -- | Give an interpretation to the global 'PackagesPreference' as
830 -- specific per-package 'PackageVersionPreference'.
831 interpretPackagesPreference
832 :: Set PackageName
833 -> PackagesPreferenceDefault
834 -> [PackagePreference]
835 -> (PackageName -> PackagePreferences)
836 interpretPackagesPreference selected defaultPref prefs =
837 \pkgname ->
838 PackagePreferences
839 (versionPref pkgname)
840 (installPref pkgname)
841 (stanzasPref pkgname)
842 where
843 versionPref :: PackageName -> [VersionRange]
844 versionPref pkgname =
845 fromMaybe [anyVersion] (Map.lookup pkgname versionPrefs)
846 versionPrefs =
847 Map.fromListWith
848 (++)
849 [ (pkgname, [pref])
850 | PackageVersionPreference pkgname pref <- prefs
853 installPref :: PackageName -> InstalledPreference
854 installPref pkgname =
855 fromMaybe (installPrefDefault pkgname) (Map.lookup pkgname installPrefs)
856 installPrefs =
857 Map.fromList
858 [ (pkgname, pref)
859 | PackageInstalledPreference pkgname pref <- prefs
861 installPrefDefault = case defaultPref of
862 PreferAllLatest -> const Preference.PreferLatest
863 PreferAllOldest -> const Preference.PreferOldest
864 PreferAllInstalled -> const Preference.PreferInstalled
865 PreferLatestForSelected -> \pkgname ->
866 -- When you say cabal install foo, what you really mean is, prefer the
867 -- latest version of foo, but the installed version of everything else
868 if pkgname `Set.member` selected
869 then Preference.PreferLatest
870 else Preference.PreferInstalled
872 stanzasPref :: PackageName -> [OptionalStanza]
873 stanzasPref pkgname =
874 fromMaybe [] (Map.lookup pkgname stanzasPrefs)
875 stanzasPrefs =
876 Map.fromListWith
877 (\a b -> nub (a ++ b))
878 [ (pkgname, pref)
879 | PackageStanzasPreference pkgname pref <- prefs
882 -- ------------------------------------------------------------
884 -- * Checking the result of the solver
886 -- ------------------------------------------------------------
888 -- | Make an install plan from the output of the dep resolver.
889 -- It checks that the plan is valid, or it's an error in the dep resolver.
890 validateSolverResult
891 :: Platform
892 -> CompilerInfo
893 -> IndependentGoals
894 -> [ResolverPackage UnresolvedPkgLoc]
895 -> SolverInstallPlan
896 validateSolverResult platform comp indepGoals pkgs =
897 case planPackagesProblems platform comp pkgs of
898 [] -> case SolverInstallPlan.new indepGoals graph of
899 Right plan -> plan
900 Left problems -> error (formatPlanProblems problems)
901 problems -> error (formatPkgProblems problems)
902 where
903 graph :: Graph.Graph (ResolverPackage UnresolvedPkgLoc)
904 graph = Graph.fromDistinctList pkgs
906 formatPkgProblems :: [PlanPackageProblem] -> String
907 formatPkgProblems = formatProblemMessage . map showPlanPackageProblem
908 formatPlanProblems :: [SolverInstallPlan.SolverPlanProblem] -> String
909 formatPlanProblems = formatProblemMessage . map SolverInstallPlan.showPlanProblem
911 formatProblemMessage problems =
912 unlines $
913 "internal error: could not construct a valid install plan."
914 : "The proposed (invalid) plan contained the following problems:"
915 : problems
916 ++ "Proposed plan:"
917 : [SolverInstallPlan.showPlanIndex pkgs]
919 data PlanPackageProblem
920 = InvalidConfiguredPackage
921 (SolverPackage UnresolvedPkgLoc)
922 [PackageProblem]
923 | DuplicatePackageSolverId SolverId [ResolverPackage UnresolvedPkgLoc]
925 showPlanPackageProblem :: PlanPackageProblem -> String
926 showPlanPackageProblem (InvalidConfiguredPackage pkg packageProblems) =
927 "Package "
928 ++ prettyShow (packageId pkg)
929 ++ " has an invalid configuration, in particular:\n"
930 ++ unlines
931 [ " " ++ showPackageProblem problem
932 | problem <- packageProblems
934 showPlanPackageProblem (DuplicatePackageSolverId pid dups) =
935 "Package "
936 ++ prettyShow (packageId pid)
937 ++ " has "
938 ++ show (length dups)
939 ++ " duplicate instances."
941 planPackagesProblems
942 :: Platform
943 -> CompilerInfo
944 -> [ResolverPackage UnresolvedPkgLoc]
945 -> [PlanPackageProblem]
946 planPackagesProblems platform cinfo pkgs =
947 [ InvalidConfiguredPackage pkg packageProblems
948 | Configured pkg <- pkgs
949 , let packageProblems = configuredPackageProblems platform cinfo pkg
950 , not (null packageProblems)
952 ++ [ DuplicatePackageSolverId (Graph.nodeKey aDup) dups
953 | dups <- duplicatesBy (comparing Graph.nodeKey) pkgs
954 , aDup <- case dups of
955 [] -> []
956 (ad : _) -> [ad]
959 data PackageProblem
960 = DuplicateFlag PD.FlagName
961 | MissingFlag PD.FlagName
962 | ExtraFlag PD.FlagName
963 | DuplicateDeps [PackageId]
964 | MissingDep Dependency
965 | ExtraDep PackageId
966 | InvalidDep Dependency PackageId
968 showPackageProblem :: PackageProblem -> String
969 showPackageProblem (DuplicateFlag flag) =
970 "duplicate flag in the flag assignment: " ++ PD.unFlagName flag
971 showPackageProblem (MissingFlag flag) =
972 "missing an assignment for the flag: " ++ PD.unFlagName flag
973 showPackageProblem (ExtraFlag flag) =
974 "extra flag given that is not used by the package: " ++ PD.unFlagName flag
975 showPackageProblem (DuplicateDeps pkgids) =
976 "duplicate packages specified as selected dependencies: "
977 ++ intercalate ", " (map prettyShow pkgids)
978 showPackageProblem (MissingDep dep) =
979 "the package has a dependency "
980 ++ prettyShow dep
981 ++ " but no package has been selected to satisfy it."
982 showPackageProblem (ExtraDep pkgid) =
983 "the package configuration specifies "
984 ++ prettyShow pkgid
985 ++ " but (with the given flag assignment) the package does not actually"
986 ++ " depend on any version of that package."
987 showPackageProblem (InvalidDep dep pkgid) =
988 "the package depends on "
989 ++ prettyShow dep
990 ++ " but the configuration specifies "
991 ++ prettyShow pkgid
992 ++ " which does not satisfy the dependency."
994 -- | A 'ConfiguredPackage' is valid if the flag assignment is total and if
995 -- in the configuration given by the flag assignment, all the package
996 -- dependencies are satisfied by the specified packages.
997 configuredPackageProblems
998 :: Platform
999 -> CompilerInfo
1000 -> SolverPackage UnresolvedPkgLoc
1001 -> [PackageProblem]
1002 configuredPackageProblems
1003 platform
1004 cinfo
1005 (SolverPackage pkg specifiedFlags stanzas specifiedDeps0 _specifiedExeDeps') =
1006 [ DuplicateFlag flag
1007 | flag <- PD.findDuplicateFlagAssignments specifiedFlags
1009 ++ [MissingFlag flag | OnlyInLeft flag <- mergedFlags]
1010 ++ [ExtraFlag flag | OnlyInRight flag <- mergedFlags]
1011 ++ [ DuplicateDeps pkgs
1012 | pkgs <-
1013 CD.nonSetupDeps
1014 ( fmap
1015 (duplicatesBy (comparing packageName))
1016 specifiedDeps1
1019 ++ [MissingDep dep | OnlyInLeft dep <- mergedDeps]
1020 ++ [ExtraDep pkgid | OnlyInRight pkgid <- mergedDeps]
1021 ++ [ InvalidDep dep pkgid | InBoth dep pkgid <- mergedDeps, not (packageSatisfiesDependency pkgid dep)
1023 where
1024 -- TODO: sanity tests on executable deps
1026 thisPkgName :: PackageName
1027 thisPkgName = packageName (srcpkgDescription pkg)
1029 specifiedDeps1 :: ComponentDeps [PackageId]
1030 specifiedDeps1 = fmap (map solverSrcId) specifiedDeps0
1032 specifiedDeps :: [PackageId]
1033 specifiedDeps = CD.flatDeps specifiedDeps1
1035 mergedFlags :: [MergeResult PD.FlagName PD.FlagName]
1036 mergedFlags =
1037 mergeBy
1038 compare
1039 (sort $ map PD.flagName (PD.genPackageFlags (srcpkgDescription pkg)))
1040 (sort $ map fst (PD.unFlagAssignment specifiedFlags)) -- TODO
1041 packageSatisfiesDependency :: PackageIdentifier -> Dependency -> Bool
1042 packageSatisfiesDependency
1043 (PackageIdentifier name version)
1044 (Dependency name' versionRange _) =
1045 assert (name == name') $
1046 version `withinRange` versionRange
1048 dependencyName (Dependency name _ _) = name
1050 mergedDeps :: [MergeResult Dependency PackageId]
1051 mergedDeps = mergeDeps requiredDeps specifiedDeps
1053 mergeDeps
1054 :: [Dependency]
1055 -> [PackageId]
1056 -> [MergeResult Dependency PackageId]
1057 mergeDeps required specified =
1058 let sortNubOn f = nubBy ((==) `on` f) . sortBy (compare `on` f)
1059 in mergeBy
1060 (\dep pkgid -> dependencyName dep `compare` packageName pkgid)
1061 (sortNubOn dependencyName required)
1062 (sortNubOn packageName specified)
1064 compSpec = enableStanzas stanzas
1065 -- TODO: It would be nicer to use ComponentDeps here so we can be more
1066 -- precise in our checks. In fact, this no longer relies on buildDepends and
1067 -- thus should be easier to fix. As long as we _do_ use a flat list here, we
1068 -- have to allow for duplicates when we fold specifiedDeps; once we have
1069 -- proper ComponentDeps here we should get rid of the `nubOn` in
1070 -- `mergeDeps`.
1071 requiredDeps :: [Dependency]
1072 requiredDeps =
1073 -- TODO: use something lower level than finalizePD
1074 case finalizePD
1075 specifiedFlags
1076 compSpec
1077 (const True)
1078 platform
1079 cinfo
1081 (srcpkgDescription pkg) of
1082 Right (resolvedPkg, _) ->
1083 -- we filter self/internal dependencies. They are still there.
1084 -- This is INCORRECT.
1086 -- If we had per-component solver, it would make this unnecessary,
1087 -- but no finalizePDs picks components we are not building, eg. exes.
1088 -- See #3775
1090 filter
1091 ((/= thisPkgName) . dependencyName)
1092 (PD.enabledBuildDepends resolvedPkg compSpec)
1093 ++ maybe [] PD.setupDepends (PD.setupBuildInfo resolvedPkg)
1094 Left _ ->
1095 error "configuredPackageInvalidDeps internal error"
1097 -- ------------------------------------------------------------
1099 -- * Simple resolver that ignores dependencies
1101 -- ------------------------------------------------------------
1103 -- | A simplistic method of resolving a list of target package names to
1104 -- available packages.
1106 -- Specifically, it does not consider package dependencies at all. Unlike
1107 -- 'resolveDependencies', no attempt is made to ensure that the selected
1108 -- packages have dependencies that are satisfiable or consistent with
1109 -- each other.
1111 -- It is suitable for tasks such as selecting packages to download for user
1112 -- inspection. It is not suitable for selecting packages to install.
1114 -- Note: if no installed package index is available, it is OK to pass 'mempty'.
1115 -- It simply means preferences for installed packages will be ignored.
1116 resolveWithoutDependencies
1117 :: DepResolverParams
1118 -> Either [ResolveNoDepsError] [UnresolvedSourcePackage]
1119 resolveWithoutDependencies
1120 ( DepResolverParams
1121 targets
1122 constraints
1123 prefs
1124 defpref
1125 installedPkgIndex
1126 sourcePkgIndex
1127 _reorderGoals
1128 _countConflicts
1129 _fineGrained
1130 _minimizeConflictSet
1131 _indGoals
1132 _avoidReinstalls
1133 _shadowing
1134 _strFlags
1135 _maxBjumps
1136 _enableBj
1137 _solveExes
1138 _allowBootLibInstalls
1139 _onlyConstrained
1140 _order
1141 _verbosity
1143 collectEithers $ map selectPackage (Set.toList targets)
1144 where
1145 selectPackage :: PackageName -> Either ResolveNoDepsError UnresolvedSourcePackage
1146 selectPackage pkgname
1147 | null choices = Left $! ResolveUnsatisfiable pkgname requiredVersions
1148 | otherwise = Right $! maximumBy bestByPrefs choices
1149 where
1150 -- Constraints
1151 requiredVersions :: VersionRange
1152 requiredVersions = packageConstraints pkgname
1153 choices :: [UnresolvedSourcePackage]
1154 choices =
1155 PackageIndex.lookupDependency
1156 sourcePkgIndex
1157 pkgname
1158 requiredVersions
1160 -- Preferences
1161 PackagePreferences preferredVersions preferInstalled _ =
1162 packagePreferences pkgname
1164 bestByPrefs :: UnresolvedSourcePackage -> UnresolvedSourcePackage -> Ordering
1165 bestByPrefs = comparing $ \pkg ->
1166 (installPref pkg, versionPref pkg, packageVersion pkg)
1167 installPref :: UnresolvedSourcePackage -> Bool
1168 installPref = case preferInstalled of
1169 Preference.PreferLatest -> const False
1170 Preference.PreferOldest -> const False
1171 Preference.PreferInstalled ->
1173 . null
1174 . InstalledPackageIndex.lookupSourcePackageId
1175 installedPkgIndex
1176 . packageId
1177 versionPref :: Package a => a -> Int
1178 versionPref pkg =
1179 length . filter (packageVersion pkg `withinRange`) $
1180 preferredVersions
1182 packageConstraints :: PackageName -> VersionRange
1183 packageConstraints pkgname =
1184 Map.findWithDefault anyVersion pkgname packageVersionConstraintMap
1185 packageVersionConstraintMap :: Map PackageName VersionRange
1186 packageVersionConstraintMap =
1187 let pcs = map unlabelPackageConstraint constraints
1188 in Map.fromList
1189 [ (scopeToPackageName scope, range)
1190 | PackageConstraint
1191 scope
1192 (PackagePropertyVersion range) <-
1196 packagePreferences :: PackageName -> PackagePreferences
1197 packagePreferences = interpretPackagesPreference targets defpref prefs
1199 collectEithers :: [Either a b] -> Either [a] [b]
1200 collectEithers = collect . partitionEithers
1201 where
1202 collect ([], xs) = Right xs
1203 collect (errs, _) = Left errs
1205 -- | Errors for 'resolveWithoutDependencies'.
1206 data ResolveNoDepsError
1207 = -- | A package name which cannot be resolved to a specific package.
1208 -- Also gives the constraint on the version and whether there was
1209 -- a constraint on the package being installed.
1210 ResolveUnsatisfiable PackageName VersionRange
1212 instance Show ResolveNoDepsError where
1213 show (ResolveUnsatisfiable name ver) =
1214 "There is no available version of "
1215 ++ prettyShow name
1216 ++ " that satisfies "
1217 ++ prettyShow (simplifyVersionRange ver)