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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/22929525fad8a7baf2dc46ecb58c691d428b7ede

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

commit 22929525fad8a7baf2dc46ecb58c691d428b7ede
Author: Duncan Coutts <[email protected]>
Date:   Wed May 7 00:06:26 2008 +0000

    Add a dependency graph to the InstallPlan
    Uses Data.Graph and annoyingly we also need to keep functions
    around for mapping between Graph.Vertex <-> PackageIdentifier

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

 cabal-install/Hackage/InstallPlan.hs |   28 ++++++++++++++++++++++++----
 1 files changed, 24 insertions(+), 4 deletions(-)

diff --git a/cabal-install/Hackage/InstallPlan.hs 
b/cabal-install/Hackage/InstallPlan.hs
index 0ccc0d3..e715fed 100644
--- a/cabal-install/Hackage/InstallPlan.hs
+++ b/cabal-install/Hackage/InstallPlan.hs
@@ -71,6 +71,10 @@ import Distribution.Simple.Utils
 
 import Data.List
          ( sort, sortBy )
+import Data.Maybe
+         ( fromMaybe )
+import qualified Data.Graph as Graph
+import Data.Graph (Graph)
 import Control.Exception
          ( assert )
 
@@ -148,11 +152,14 @@ instance PackageFixedDeps (PlanPackage buildResult) where
 
 data InstallPlan buildResult = InstallPlan {
     planIndex    :: PackageIndex (PlanPackage buildResult),
+    planGraph    :: Graph,
+    planGraphRev :: Graph,
+    planPkgIdOf  :: Graph.Vertex -> PackageIdentifier,
+    planVertexOf :: PackageIdentifier -> Graph.Vertex,
     planOS       :: OS,
     planArch     :: Arch,
     planCompiler :: CompilerId
   }
-  deriving Show
 
 invariant :: InstallPlan a -> Bool
 invariant plan =
@@ -165,9 +172,22 @@ internalError msg = error $ "InstallPlan: internal error: 
" ++ msg
 --
 new :: OS -> Arch -> CompilerId -> PackageIndex (PlanPackage a)
     -> Either (InstallPlan a) [PlanProblem a]
-new os arch compiler index = case problems os arch compiler index of
-  []  -> Left (InstallPlan index os arch compiler)
-  ps  -> Right ps
+new os arch compiler index =
+  case problems os arch compiler index of
+    [] -> Left InstallPlan {
+            planIndex    = index,
+            planGraph    = graph,
+            planGraphRev = Graph.transposeG graph,
+            planPkgIdOf  = vertexToPkgId,
+            planVertexOf = fromMaybe noSuchPkgId . pkgIdToVertex,
+            planOS       = os,
+            planArch     = arch,
+            planCompiler = compiler
+          }
+      where (graph, vertexToPkgId, pkgIdToVertex) =
+              PackageIndex.dependencyGraph index
+            noSuchPkgId = internalError "package is not in the graph"
+    probs -> Right probs
 
 toList :: InstallPlan buildResult -> [PlanPackage buildResult]
 toList = PackageIndex.allPackages . planIndex



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

Reply via email to