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

On branch  : master

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

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

commit 1cb5d96359c082b5e3c46095e2bd16b6e5b23061
Author: Duncan Coutts <[email protected]>
Date:   Mon Jul 18 23:57:28 2011 +0000

    Fix cabal haddock for packages with internal dependencies

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

 cabal/Distribution/Simple/Haddock.hs        |    5 +++--
 cabal/Distribution/Simple/LocalBuildInfo.hs |   14 +++++++++-----
 2 files changed, 12 insertions(+), 7 deletions(-)

diff --git a/cabal/Distribution/Simple/Haddock.hs 
b/cabal/Distribution/Simple/Haddock.hs
index ffcf2d0..47ed428 100644
--- a/cabal/Distribution/Simple/Haddock.hs
+++ b/cabal/Distribution/Simple/Haddock.hs
@@ -442,8 +442,9 @@ haddockPackageFlags lbi htmlTemplate = do
   let allPkgs = installedPkgs lbi
       directDeps = map fst (externalPackageDeps lbi)
   transitiveDeps <- case dependencyClosure allPkgs directDeps of
-                    Left x -> return x
-                    Right _ -> die "Can't find transitive deps for haddock"
+    Left x    -> return x
+    Right inf -> die $ "internal error when calculating transative "
+                    ++ "package dependencies.\nDebug info: " ++ show inf
   interfaces <- sequence
     [ case interfaceAndHtmlPath ipkg of
         Nothing -> return (Left (packageId ipkg))
diff --git a/cabal/Distribution/Simple/LocalBuildInfo.hs 
b/cabal/Distribution/Simple/LocalBuildInfo.hs
index 8fa4f27..1e16f3e 100644
--- a/cabal/Distribution/Simple/LocalBuildInfo.hs
+++ b/cabal/Distribution/Simple/LocalBuildInfo.hs
@@ -140,13 +140,17 @@ data LocalBuildInfo = LocalBuildInfo {
         progSuffix    :: PathTemplate -- ^Suffix to be appended to installed 
executables
   } deriving (Read, Show)
 
--- | External package dependencies for the package as a whole, the union of the
--- individual 'targetPackageDeps'.
+-- | External package dependencies for the package as a whole. This is the
+-- union of the individual 'componentPackageDeps', less any internal deps.
 externalPackageDeps :: LocalBuildInfo -> [(InstalledPackageId, PackageId)]
-externalPackageDeps lbi = nub $
+externalPackageDeps lbi = filter (not . internal . snd) $ nub $
   -- TODO:  what about non-buildable components?
-     maybe [] componentPackageDeps (libraryConfig lbi)
-  ++ concatMap (componentPackageDeps . snd) (executableConfigs lbi)
+       maybe [] componentPackageDeps (libraryConfig lbi)
+    ++ concatMap (componentPackageDeps . snd) (executableConfigs lbi)
+  where
+    -- True if this dependency is an internal one (depends on the library
+    -- defined in the same package).
+    internal pkgid = pkgid == packageId (localPkgDescr lbi)
 
 -- | The installed package Id we use for local packages registered in the local
 -- package db. This is what is used for intra-package deps between components.



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

Reply via email to