Skip to content
Snippets Groups Projects
Commit a246b17e authored by Andres Löh's avatar Andres Löh Committed by Edward Z. Yang
Browse files

When lifting dependencies, compute the union of the ranges.

For a while now, we lift out dependencies from conditionals.  If a
package is dependended on regardless of the outcome of a test, the
dependency is lifted out. This has the advantage that we can choose an
instance for the package prior to choosing the value of the flag. Often,
this is the desired behaviour for flags, i.e., to have the flag choice
implied by the possible package choices, rather than the other way
around.

Prior to this change, lifting was simply adding an unconstrained
dependency to such a package at a higher level, which would then of
course still be refined after making the flag choice. We are now making
this more precise by actually computing the union of the ranges in both
branches of the conditional. So we will not choose an instance on the
top level that will later be rejected by both branches.
parent b6a15965
No related branches found
No related tags found
No related merge requests found
......@@ -164,7 +164,7 @@ convBranch :: OS -> Arch -> CompilerInfo ->
(Condition ConfVar,
CondTree ConfVar [Dependency] a,
Maybe (CondTree ConfVar [Dependency] a)) -> FlaggedDeps Component PN
convBranch os arch cinfo pi fds p comp (c', t', mf') =
convBranch os arch cinfo pi@(PI pn _) fds p comp (c', t', mf') =
go c' ( convCondTree os arch cinfo pi fds p comp t')
(maybe [] (convCondTree os arch cinfo pi fds p comp) mf')
where
......@@ -198,11 +198,16 @@ convBranch os arch cinfo pi fds p comp (c', t', mf') =
-- with deferring flag choices will then usually first resolve this package,
-- and try an already installed version before imposing a default flag choice
-- that might not be what we want.
--
-- Note that we make assumptions here on the form of the dependencies that
-- can occur at this point. In particular, no occurrences of Fixed, and no
-- occurrences of multiple version ranges, as all dependencies below this
-- point have been generated using 'convDep'.
extractCommon :: FlaggedDeps Component PN -> FlaggedDeps Component PN -> FlaggedDeps Component PN
extractCommon ps ps' = [ D.Simple (Dep pn (Constrained [])) comp
| D.Simple (Dep pn _) _ <- ps
, D.Simple (Dep pn' _) _ <- ps'
, pn == pn'
extractCommon ps ps' = [ D.Simple (Dep pn1 (Constrained [(vr1 .||. vr2, Goal (P pn) [])])) comp
| D.Simple (Dep pn1 (Constrained [(vr1, _)])) _ <- ps
, D.Simple (Dep pn2 (Constrained [(vr2, _)])) _ <- ps'
, pn1 == pn2
]
-- | Convert a Cabal dependency to a solver-specific dependency.
......
......@@ -29,6 +29,10 @@ eqVR = CV.thisVersion
(.&&.) :: VR -> VR -> VR
(.&&.) = CV.intersectVersionRanges
-- | Union of two version ranges.
(.||.) :: VR -> VR -> VR
(.||.) = CV.unionVersionRanges
-- | Simplify a version range.
simplifyVR :: VR -> VR
simplifyVR = CV.simplifyVersionRange
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment