Repository : ssh://darcs.haskell.org//srv/darcs/packages/Cabal

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/1be2c49bc7fbdc69489ec749f9ebbd4ea0f22878

>---------------------------------------------------------------

commit 1be2c49bc7fbdc69489ec749f9ebbd4ea0f22878
Author: Andres Loeh <[email protected]>
Date:   Thu Oct 27 13:33:09 2011 +0000

    removing dead code for global flag enforcement
    
    This is all covered by the function that enforces package constraints,
    as global flag constraints are translated into package-specific flag
    constraints outside of the solver.

>---------------------------------------------------------------

 .../Client/Dependency/Modular/Preference.hs        |   20 --------------------
 1 files changed, 0 insertions(+), 20 deletions(-)

diff --git a/cabal-install/Distribution/Client/Dependency/Modular/Preference.hs 
b/cabal-install/Distribution/Client/Dependency/Modular/Preference.hs
index 79a8940..8404bf0 100644
--- a/cabal-install/Distribution/Client/Dependency/Modular/Preference.hs
+++ b/cabal-install/Distribution/Client/Dependency/Modular/Preference.hs
@@ -2,7 +2,6 @@ module Distribution.Client.Dependency.Modular.Preference where
 
 -- Reordering or pruning the tree in order to prefer or make certain choices.
 
-import Control.Applicative
 import qualified Data.List as L
 import qualified Data.Map as M
 import Data.Monoid
@@ -176,25 +175,6 @@ avoidReinstalls p = trav go
         notReinstall _  _            x = x
     go x          = x
 
-type GlobalFlags = M.Map Flag    Bool
-type LocalFlags  = M.Map (FN PN) Bool
-
--- | Enforce flag choices explicitly given by some outer context,
--- for example by the user on the command line. For maximum
--- flexibility we allow both global and local choices, where local
--- choices override the global ones.
-enforceFlagChoices :: GlobalFlags -> LocalFlags -> Tree a -> Tree a
-enforceFlagChoices gfs lfs = trav go
-  where
-    go (FChoiceF qfn@(FN _ f) r tr cs) =
-      case M.lookup (fmap unQualify qfn) lfs <|> M.lookup f gfs of -- find 
flag in either map
-         Nothing -> FChoiceF qfn r tr            cs  -- if nothing specified, 
use old node
-         Just b  -> FChoiceF qfn r tr (enforce b cs) -- keep only the chosen 
variant
-    go x = x
-
-    enforce :: Bool -> PSQ Bool (Tree a) -> PSQ Bool (Tree a)
-    enforce b = P.filterKeys (== b)
-
 -- | Always choose the first goal in the list next, abandoning all
 -- other choices.
 --



_______________________________________________
Cvs-libraries mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-libraries

Reply via email to