Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data POption = POption I (Maybe PackagePath)
- data Tree d c
- = PChoice QPN RevDepMap c (WeightedPSQ [Weight] POption (Tree d c))
- | FChoice QFN RevDepMap c WeakOrTrivial FlagType Bool (WeightedPSQ [Weight] Bool (Tree d c))
- | SChoice QSN RevDepMap c WeakOrTrivial (WeightedPSQ [Weight] Bool (Tree d c))
- | GoalChoice RevDepMap (PSQ (Goal QPN) (Tree d c))
- | Done RevDepMap d
- | Fail ConflictSet FailReason
- data TreeF d c a
- = PChoiceF QPN RevDepMap c (WeightedPSQ [Weight] POption a)
- | FChoiceF QFN RevDepMap c WeakOrTrivial FlagType Bool (WeightedPSQ [Weight] Bool a)
- | SChoiceF QSN RevDepMap c WeakOrTrivial (WeightedPSQ [Weight] Bool a)
- | GoalChoiceF RevDepMap (PSQ (Goal QPN) a)
- | DoneF RevDepMap d
- | FailF ConflictSet FailReason
- type Weight = Double
- data FailReason
- = UnsupportedExtension Extension
- | UnsupportedLanguage Language
- | MissingPkgconfigPackage PkgconfigName PkgconfigVersionRange
- | NewPackageDoesNotMatchExistingConstraint ConflictingDep
- | ConflictingConstraints ConflictingDep ConflictingDep
- | NewPackageIsMissingRequiredComponent ExposedComponent (DependencyReason QPN)
- | NewPackageHasPrivateRequiredComponent ExposedComponent (DependencyReason QPN)
- | NewPackageHasUnbuildableRequiredComponent ExposedComponent (DependencyReason QPN)
- | PackageRequiresMissingComponent QPN ExposedComponent
- | PackageRequiresPrivateComponent QPN ExposedComponent
- | PackageRequiresUnbuildableComponent QPN ExposedComponent
- | CannotInstall
- | CannotReinstall
- | NotExplicit
- | Shadowed
- | Broken UnitId
- | UnknownPackage
- | GlobalConstraintVersion VR ConstraintSource
- | GlobalConstraintInstalled ConstraintSource
- | GlobalConstraintSource ConstraintSource
- | GlobalConstraintFlag ConstraintSource
- | ManualFlag
- | MalformedFlagChoice QFN
- | MalformedStanzaChoice QSN
- | EmptyGoalChoice
- | Backjump
- | MultipleInstances
- | DependenciesNotLinked String
- | CyclicDependencies
- | UnsupportedSpecVer Ver
- data ConflictingDep = ConflictingDep (DependencyReason QPN) (PkgComponent QPN) CI
- ana :: (a -> TreeF d c a) -> a -> Tree d c
- cata :: (TreeF d c a -> a) -> Tree d c -> a
- inn :: TreeF d c (Tree d c) -> Tree d c
- innM :: Monad m => TreeF d c (m (Tree d c)) -> m (Tree d c)
- para :: (TreeF d c (a, Tree d c) -> a) -> Tree d c -> a
- trav :: TreeTrav d c a -> Tree d c -> Tree d a
- zeroOrOneChoices :: Tree d c -> Bool
- active :: Tree d c -> Bool
- type TreeTrav d c a = TreeF d c (Tree d a) -> TreeF d a (Tree d a)
- type EndoTreeTrav d c = TreeTrav d c c
Documentation
A package option is a package instance with an optional linking annotation
The modular solver has a number of package goals to solve for, and can only
pick a single package version for a single goal. In order to allow to
install multiple versions of the same package as part of a single solution
the solver uses qualified goals. For example, 0.P
and 1.P
might both
be qualified goals for P
, allowing to pick a difference version of package
P
for 0.P
and 1.P
.
Linking is an essential part of this story. In addition to picking a specific
version for 1.P
, the solver can also decide to link 1.P
to 0.P
(or
vice versa). It means that 1.P
and 0.P
really must be the very same package
(and hence must have the same build time configuration, and their
dependencies must also be the exact same).
See http://www.well-typed.com/blog/2015/03/qualified-goals/ for details.
Type of the search tree. Inlining the choice nodes for now. Weights on package, flag, and stanza choices control the traversal order.
The tree can hold additional data on Done
nodes (type d
) and choice nodes
(type c
). For example, during the final traversal, choice nodes contain the
variables that introduced the choices, and Done
nodes contain the
assignments for all variables.
TODO: The weight type should be changed from [Double] to Double to avoid giving too much weight to preferences that are applied later.
PChoice QPN RevDepMap c (WeightedPSQ [Weight] POption (Tree d c)) | Choose a version for a package (or choose to link) |
FChoice QFN RevDepMap c WeakOrTrivial FlagType Bool (WeightedPSQ [Weight] Bool (Tree d c)) | Choose a value for a flag The Bool is the default value. |
SChoice QSN RevDepMap c WeakOrTrivial (WeightedPSQ [Weight] Bool (Tree d c)) | Choose whether or not to enable a stanza |
GoalChoice RevDepMap (PSQ (Goal QPN) (Tree d c)) | Choose which choice to make next Invariants:
|
Done RevDepMap d | We're done -- we found a solution! |
Fail ConflictSet FailReason | We failed to find a solution in this path through the tree |
Functor for the tree type. a
is the type of nodes' children. d
and c
have the same meaning as in Tree
.
PChoiceF QPN RevDepMap c (WeightedPSQ [Weight] POption a) | |
FChoiceF QFN RevDepMap c WeakOrTrivial FlagType Bool (WeightedPSQ [Weight] Bool a) | |
SChoiceF QSN RevDepMap c WeakOrTrivial (WeightedPSQ [Weight] Bool a) | |
GoalChoiceF RevDepMap (PSQ (Goal QPN) a) | |
DoneF RevDepMap d | |
FailF ConflictSet FailReason |
Instances
Functor (TreeF d c) Source # | |
Foldable (TreeF d c) Source # | |
Defined in Distribution.Solver.Modular.Tree fold :: Monoid m => TreeF d c m -> m # foldMap :: Monoid m => (a -> m) -> TreeF d c a -> m # foldMap' :: Monoid m => (a -> m) -> TreeF d c a -> m # foldr :: (a -> b -> b) -> b -> TreeF d c a -> b # foldr' :: (a -> b -> b) -> b -> TreeF d c a -> b # foldl :: (b -> a -> b) -> b -> TreeF d c a -> b # foldl' :: (b -> a -> b) -> b -> TreeF d c a -> b # foldr1 :: (a -> a -> a) -> TreeF d c a -> a # foldl1 :: (a -> a -> a) -> TreeF d c a -> a # toList :: TreeF d c a -> [a] # length :: TreeF d c a -> Int # elem :: Eq a => a -> TreeF d c a -> Bool # maximum :: Ord a => TreeF d c a -> a # minimum :: Ord a => TreeF d c a -> a # | |
Traversable (TreeF d c) Source # | |
Defined in Distribution.Solver.Modular.Tree |
data FailReason Source #
Instances
Eq FailReason Source # | |
Defined in Distribution.Solver.Modular.Tree (==) :: FailReason -> FailReason -> Bool # (/=) :: FailReason -> FailReason -> Bool # | |
Show FailReason Source # | |
Defined in Distribution.Solver.Modular.Tree showsPrec :: Int -> FailReason -> ShowS # show :: FailReason -> String # showList :: [FailReason] -> ShowS # |
data ConflictingDep Source #
Information about a dependency involved in a conflict, for error messages.
Instances
Eq ConflictingDep Source # | |
Defined in Distribution.Solver.Modular.Tree (==) :: ConflictingDep -> ConflictingDep -> Bool # (/=) :: ConflictingDep -> ConflictingDep -> Bool # | |
Show ConflictingDep Source # | |
Defined in Distribution.Solver.Modular.Tree showsPrec :: Int -> ConflictingDep -> ShowS # show :: ConflictingDep -> String # showList :: [ConflictingDep] -> ShowS # |
zeroOrOneChoices :: Tree d c -> Bool Source #
Approximates the number of active choices that are available in a node. Note that we count goal choices as having one choice, always.
type EndoTreeTrav d c = TreeTrav d c c Source #