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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/b54dc1341d08d102b6eb25f0f037f7b876567282

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

commit b54dc1341d08d102b6eb25f0f037f7b876567282
Author: Duncan Coutts <[email protected]>
Date:   Mon Dec 15 22:43:24 2008 +0000

    A bit more renaming in the top down resolver

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

 .../Distribution/Client/Dependency/TopDown.hs      |   62 ++++++++++---------
 1 files changed, 33 insertions(+), 29 deletions(-)

diff --git a/cabal-install/Distribution/Client/Dependency/TopDown.hs 
b/cabal-install/Distribution/Client/Dependency/TopDown.hs
index c51eeba..90c6b79 100644
--- a/cabal-install/Distribution/Client/Dependency/TopDown.hs
+++ b/cabal-install/Distribution/Client/Dependency/TopDown.hs
@@ -238,16 +238,16 @@ topDownResolver' :: Platform -> CompilerId
                  -> [PackageName]
                  -> Progress Log Failure [PlanPackage]
 topDownResolver' platform comp installed available
-                 userPreferences userConstraints targets =
+                 preferences constraints targets =
       fmap (uncurry finalise)
-    . (\cs -> search configure userPreferences cs initialPkgNames)
-  =<< constrainTopLevelDeps userConstraints constraints
+    . (\cs -> search configure preferences cs initialPkgNames)
+  =<< addTopLevelConstraints constraints constraintSet
 
   where
     configure   = configurePackage platform comp
-    constraints = Constraints.empty
-      (annotateInstalledPackages                 topSortNumber installed')
-      (annotateAvailablePackages userConstraints topSortNumber available')
+    constraintSet = Constraints.empty
+      (annotateInstalledPackages             topSortNumber installed')
+      (annotateAvailablePackages constraints topSortNumber available')
     (installed', available') = selectNeededSubset installed available
                                                   initialPkgNames
     topSortNumber = topologicalSortNumbering installed' available'
@@ -257,20 +257,24 @@ topDownResolver' platform comp installed available
     finalise selected = PackageIndex.allPackages
                       . improvePlan installed'
                       . PackageIndex.fromList
-                      . finaliseSelectedPackages userPreferences selected
-
-constrainTopLevelDeps :: [PackageConstraint] -> Constraints
-                      -> Progress a Failure Constraints
-constrainTopLevelDeps []                                      cs = Done cs
-constrainTopLevelDeps (PackageFlagsConstraint   _   _  :deps) cs =
-  constrainTopLevelDeps deps cs
-constrainTopLevelDeps (PackageVersionConstraint pkg ver:deps) cs =
+                      . finaliseSelectedPackages preferences selected
+
+addTopLevelConstraints :: [PackageConstraint] -> Constraints
+                       -> Progress a Failure Constraints
+addTopLevelConstraints []                                      cs = Done cs
+addTopLevelConstraints (PackageFlagsConstraint   _   _  :deps) cs =
+  addTopLevelConstraints deps cs
+
+addTopLevelConstraints (PackageVersionConstraint pkg ver:deps) cs =
   case addTopLevelVersionConstraint pkg ver cs of
-    Satisfiable cs' _       -> constrainTopLevelDeps deps cs'
-    Unsatisfiable           -> Fail (TopLevelDependencyUnsatisfiable dep)
-    ConflictsWith conflicts -> Fail (TopLevelDependencyConflict dep conflicts)
-  where
-    dep = Dependency pkg ver
+    Satisfiable cs' _       ->
+      addTopLevelConstraints deps cs'
+
+    Unsatisfiable           ->
+      Fail (TopLevelVersionConstraintUnsatisfiable pkg ver)
+
+    ConflictsWith conflicts ->
+      Fail (TopLevelVersionConstraintConflict pkg ver conflicts)
 
 configurePackage :: Platform -> CompilerId -> ConfigurePackage
 configurePackage (Platform arch os) comp available spkg = case spkg of
@@ -497,8 +501,8 @@ addPackageSelectConstraint pkgid constraints =
     reason = SelectedOther pkgid
 
 addPackageExcludeConstraint :: PackageIdentifier -> Constraints
-                     -> Satisfiable Constraints
-                          [PackageIdentifier] ExclusionReason
+                            -> Satisfiable Constraints
+                                 [PackageIdentifier] ExclusionReason
 addPackageExcludeConstraint pkgid constraints =
   Constraints.constrain dep reason constraints
   where
@@ -581,11 +585,11 @@ data Failure
    | DependencyConflict
        SelectedPackage TaggedDependency
        [(PackageIdentifier, [ExclusionReason])]
-   | TopLevelDependencyConflict
-       Dependency
+   | TopLevelVersionConstraintConflict
+       PackageName VersionRange
        [(PackageIdentifier, [ExclusionReason])]
-   | TopLevelDependencyUnsatisfiable
-       Dependency
+   | TopLevelVersionConstraintUnsatisfiable
+       PackageName VersionRange
 
 showLog :: Log -> String
 showLog (Select selected discarded) = case (selectedMsg, discardedMsg) of
@@ -639,13 +643,13 @@ showFailure (DependencyConflict pkg (TaggedDependency _ 
dep) conflicts) =
   ++ unlines [ showExclusionReason (packageId pkg') reason
              | (pkg', reasons) <- conflicts, reason <- reasons ]
 
-showFailure (TopLevelDependencyConflict dep conflicts) =
-     "dependencies conflict: "
-  ++ "top level dependency " ++ display dep ++ " however\n"
+showFailure (TopLevelVersionConstraintConflict name ver conflicts) =
+     "constraints conflict: "
+  ++ "top level constraint " ++ display (Dependency name ver) ++ " however\n"
   ++ unlines [ showExclusionReason (packageId pkg') reason
              | (pkg', reasons) <- conflicts, reason <- reasons ]
 
-showFailure (TopLevelDependencyUnsatisfiable (Dependency name ver)) =
+showFailure (TopLevelVersionConstraintUnsatisfiable name ver) =
      "There is no available version of " ++ display name
       ++ " that satisfies " ++ display ver
 



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

Reply via email to