Blame SOURCES/D4159.patch

a43873
diff --git a/utils/ghc-pkg/Main.hs b/utils/ghc-pkg/Main.hs
a43873
--- a/utils/ghc-pkg/Main.hs
a43873
+++ b/utils/ghc-pkg/Main.hs
a43873
@@ -1208,7 +1208,18 @@
a43873
       pkgsCabalFormat = packages db
a43873
 
a43873
       pkgsGhcCacheFormat :: [PackageCacheFormat]
a43873
-      pkgsGhcCacheFormat = map convertPackageInfoToCacheFormat pkgsCabalFormat
a43873
+      pkgsGhcCacheFormat
a43873
+        = map (recomputeValidAbiDeps pkgsCabalFormat) -- Note [Recompute abi-depends]
a43873
+        $ map convertPackageInfoToCacheFormat
a43873
+          pkgsCabalFormat
a43873
+
a43873
+      hasAnyAbiDepends :: InstalledPackageInfo -> Bool
a43873
+      hasAnyAbiDepends x = length (abiDepends x) > 0
a43873
+
a43873
+--  -- warn when we find any (possibly-)bogus abi-depends fields;
a43873
+--  -- Note [Recompute abi-depends]
a43873
+--  when (any hasAnyAbiDepends pkgsCabalFormat) $
a43873
+--      infoLn "ignoring (possibly broken) abi-depends field for packages"
a43873
 
a43873
   when (verbosity > Normal) $
a43873
       infoLn ("writing cache " ++ filename)
a43873
@@ -1231,6 +1242,45 @@
a43873
                             ModuleName
a43873
                             OpenModule
a43873
 
a43873
+{- Note [Recompute abi-depends]
a43873
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
a43873
+
a43873
+Like most fields, `ghc-pkg` relies on who-ever is performing package
a43873
+registration to fill in fields; this includes the `abi-depends` field present
a43873
+for the package.
a43873
+
a43873
+However, this was likely a mistake, and is not very robust; in certain cases,
a43873
+versions of Cabal may use bogus abi-depends fields for a package when doing
a43873
+builds. Why? Because package database information is aggressively cached; it is
a43873
+possible to work Cabal into a situation where it uses a cached version of
a43873
+`abi-depends`, rather than the one in the actual database after it has been
a43873
+recomputed.
a43873
+
a43873
+However, there is an easy fix: ghc-pkg /already/ knows the `abi-depends` of a
a43873
+package, because they are the ABIs of the packages pointed at by the `depends`
a43873
+field. So it can simply look up the abi from the dependencies in the original
a43873
+database, and ignore whatever the system registering gave it.
a43873
+
a43873
+So, instead, we do two things here:
a43873
+
a43873
+  - We throw away the information for a registered package's `abi-depends` field.
a43873
+
a43873
+  - We recompute it: we simply look up the unit ID of the package in the original
a43873
+    database, and use *its* abi-depends.
a43873
+
a43873
+See Trac #14381, and Cabal issue #4728.
a43873
+
a43873
+-}
a43873
+
a43873
+recomputeValidAbiDeps :: [InstalledPackageInfo] -> PackageCacheFormat -> PackageCacheFormat
a43873
+recomputeValidAbiDeps db pkg = pkg { GhcPkg.abiDepends = catMaybes (newAbiDeps) }
a43873
+  where
a43873
+    newAbiDeps = flip map (GhcPkg.abiDepends pkg) $ \(k, _) ->
a43873
+      case filter (\d -> installedUnitId d == k) db of
a43873
+        []  -> Nothing
a43873
+        [x] -> Just (k, unAbiHash (abiHash x))
a43873
+        _   -> Nothing -- ???
a43873
+
a43873
 convertPackageInfoToCacheFormat :: InstalledPackageInfo -> PackageCacheFormat
a43873
 convertPackageInfoToCacheFormat pkg =
a43873
     GhcPkg.InstalledPackageInfo {
a43873