[Git][ghc/ghc][master] Don't depend on registerPackage function in Cabal

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Tue Apr 23 19:03:15 UTC 2024



Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
3fff0977 by Matthew Pickering at 2024-04-23T15:02:38-04:00
Don't depend on registerPackage function in Cabal

More recent versions of Cabal modify the behaviour of libAbiHash which
breaks our usage of registerPackage.

It is simpler to inline the part of registerPackage that we need and
avoid any additional dependency and complication using the higher-level
function introduces.

- - - - -


1 changed file:

- hadrian/src/Hadrian/Haskell/Cabal/Parse.hs


Changes:

=====================================
hadrian/src/Hadrian/Haskell/Cabal/Parse.hs
=====================================
@@ -31,6 +31,7 @@ import qualified Distribution.PackageDescription.Parsec        as C
 import qualified Distribution.Simple.Compiler                  as C
 import qualified Distribution.Simple.Program.Db                as C
 import qualified Distribution.Simple                           as C
+import qualified Distribution.Simple.GHC                       as GHC
 import qualified Distribution.Simple.Program.Builtin           as C
 import qualified Distribution.Simple.Utils                     as C
 import qualified Distribution.Simple.Program.Types             as C
@@ -363,12 +364,11 @@ registerPackage rs context = do
     need [setupConfig] -- This triggers 'configurePackage'
     pd <- packageDescription <$> readContextData context
     db_path <- packageDbPath (PackageDbLoc (stage context) (iplace context))
-    dist_dir <- Context.buildPath context
     pid <- pkgUnitId (stage context) (package context)
     -- Note: the @cPath@ is ignored. The path that's used is the 'buildDir' path
     -- from the local build info @lbi at .
     lbi <- liftIO $ C.getPersistBuildConfig cPath
-    liftIO $ register db_path pid dist_dir pd lbi
+    liftIO $ register db_path pid pd lbi
     -- Then after the register, which just writes the .conf file, do the recache step.
     buildWithResources rs $
       target context (GhcPkg Recache (stage context)) [] []
@@ -377,25 +377,23 @@ registerPackage rs context = do
 -- into a different package database to the one it was configured against.
 register :: FilePath
          -> String -- ^ Package Identifier
-         -> FilePath
          -> C.PackageDescription
          -> LocalBuildInfo
          -> IO ()
-register pkg_db pid build_dir pd lbi
+register pkg_db pid pd lbi
   = withLibLBI pd lbi $ \lib clbi -> do
 
-    absPackageDBs    <- C.absolutePackageDBPaths packageDbs
-    installedPkgInfo <- C.generateRegistrationInfo
-                           C.silent pd lib lbi clbi False reloc build_dir
-                           (C.registrationPackageDB absPackageDBs)
-
+    when reloc $ error "register does not support reloc"
+    installedPkgInfo <- generateRegistrationInfo pd lbi lib clbi
     writeRegistrationFile installedPkgInfo
 
   where
     regFile   = pkg_db </> pid <.> "conf"
     reloc     = relocatable lbi
-    -- Using a specific package db here is why we have to copy the function from Cabal.
-    packageDbs = [C.SpecificPackageDB pkg_db]
+
+    generateRegistrationInfo pkg lbi lib clbi = do
+      abi_hash <- C.mkAbiHash <$> GHC.libAbiHash C.silent pkg lbi lib clbi
+      return (C.absoluteInstalledPackageInfo pkg abi_hash lib lbi clbi)
 
     writeRegistrationFile installedPkgInfo = do
       writeUTF8File regFile (CP.showInstalledPackageInfo installedPkgInfo)



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3fff09779d5830549ae455a15907b7bb9fe7859a

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3fff09779d5830549ae455a15907b7bb9fe7859a
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20240423/ed5a6303/attachment-0001.html>


More information about the ghc-commits mailing list