Skip to content
Snippets Groups Projects
Commit 64a014ec authored by Andres Löh's avatar Andres Löh
Browse files

Rename cycle detection phase and typos.

A number of small changes:

- Some comment typos fixed.
- The main function for cycle detection is now called
  `cycleDetectionPhase`, in analogy with all the other
  phases.

I've run a superficial performance test trying to install
all of Hackage on a clean db with ghc-7.10.3. This is not
likely to trigger any situations where cycle detection
actually kicks in, but it confirms in general that there is
no negative performance (or correctness) impact for the
common case.

I've also considered moving the cycle detection phase to
"earlier" in the solver, but after performance testing, decided
against it, and documented the decision and the reasons in
the code.
parent 2c59a451
No related branches found
No related tags found
No related merge requests found
{-# LANGUAGE CPP #-}
module Distribution.Client.Dependency.Modular.Cycles (
detectCycles
detectCyclesPhase
) where
import Prelude hiding (cycle)
......@@ -24,9 +24,9 @@ import Distribution.Client.Dependency.Modular.Tree
type DetectCycles = Reader (ConflictSet QPN)
-- | Find any reject any solutions that are cyclic
detectCycles :: Tree QGoalReasonChain -> Tree QGoalReasonChain
detectCycles = (`runReader` Set.empty) . cata go
-- | Find and reject any solutions that are cyclic
detectCyclesPhase :: Tree QGoalReasonChain -> Tree QGoalReasonChain
detectCyclesPhase = (`runReader` Set.empty) . cata go
where
-- Most cases are simple; we just need to remember which choices we made
go :: TreeF QGoalReasonChain (DetectCycles (Tree QGoalReasonChain)) -> DetectCycles (Tree QGoalReasonChain)
......@@ -46,7 +46,7 @@ detectCycles = (`runReader` Set.empty) . cata go
-- | Given the reverse dependency map from a 'Done' node in the tree, as well
-- as the full conflict set containing all decisions that led to that 'Done'
-- node, check of the solution is cyclic. If it is, return the conflic set
-- node, check if the solution is cyclic. If it is, return the conflic set
-- containing all decisions that could potentially break the cycle.
findCycles :: ConflictSet QPN -> RevDepMap -> Maybe (ConflictSet QPN)
findCycles fullSet revDeps = do
......
......@@ -32,16 +32,41 @@ data SolverConfig = SolverConfig {
maxBackjumps :: Maybe Int
}
solve :: SolverConfig -> -- solver parameters
-- | Run all solver phases.
--
-- In principle, we have a valid tree after 'validationPhase', which
-- means that every 'Done' node should correspond to valid solution.
--
-- There is one exception, though, and that is cycle detection, which
-- has been added relatively recently. Cycles are only removed directly
-- before exploration.
--
-- Semantically, there is no difference. Cycle detection, as implemented
-- now, only occurs for 'Done' nodes we encounter during exploration,
-- and cycle detection itself does not change the shape of the tree,
-- it only marks some 'Done' nodes as 'Fail', if they contain cyclic
-- solutions.
--
-- There is a tiny performance impact, however, in doing cycle detection
-- directly after validation. Probably because cycle detection maintains
-- some information, and the various reorderings implemented by
-- 'preferencesPhase' and 'heuristicsPhase' are ever so slightly more
-- costly if that information is already around during the reorderings.
--
-- With the current positioning directly before the 'explorePhase', there
-- seems to be no statistically significant performance impact of cycle
-- detection in the common case where there are no cycles.
--
solve :: SolverConfig -> -- ^ solver parameters
CompilerInfo ->
Index -> -- all available packages as an index
(PN -> PackagePreferences) -> -- preferences
Map PN [LabeledPackageConstraint] -> -- global constraints
[PN] -> -- global goals
Index -> -- ^ all available packages as an index
(PN -> PackagePreferences) -> -- ^ preferences
Map PN [LabeledPackageConstraint] -> -- ^ global constraints
[PN] -> -- ^ global goals
Log Message (Assignment, RevDepMap)
solve sc cinfo idx userPrefs userConstraints userGoals =
explorePhase $
detectCycles $
detectCyclesPhase$
heuristicsPhase $
preferencesPhase $
validationPhase $
......
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