[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 8 commits: driver: force merge objects when building dynamic objects

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Wed Apr 24 15:13:07 UTC 2024



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
d2b17f32 by Cheng Shao at 2024-04-23T15:01:22-04:00
driver: force merge objects when building dynamic objects

This patch forces the driver to always merge objects when building
dynamic objects even when ar -L is supported. It is an oversight of
!8887: original rationale of that patch is favoring the relatively
cheap ar -L operation over object merging when ar -L is supported,
which makes sense but only if we are building static objects! Omitting
check for whether we are building dynamic objects will result in
broken .so files with undefined reference errors at executable link
time when building GHC with llvm-ar. Fixes #22210.

- - - - -
209d09f5 by Julian Ospald at 2024-04-23T15:02:03-04:00
Allow non-absolute values for bootstrap GHC variable

Fixes #24682

- - - - -
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.

- - - - -
70967189 by Cheng Shao at 2024-04-24T11:11:33-04:00
ghc-bignum: remove obsolete ln script

This commit removes an obsolete ln script in ghc-bignum/gmp. See
060251c24ad160264ae8553efecbb8bed2f06360 for its original intention,
but it's been obsolete for a long time, especially since the removal
of the make build system. Hence the house cleaning.

- - - - -
42959129 by Cheng Shao at 2024-04-24T11:11:33-04:00
ghc-bignum: update gmp to 6.3.0

This patch bumps the gmp-tarballs submodule and updates gmp to 6.3.0.
The tarball format is now xz, and gmpsrc.patch has been patched into
the tarball so hadrian no longer needs to deal with patching logic
when building in-tree GMP.

- - - - -
07de0186 by Cheng Shao at 2024-04-24T11:11:33-04:00
hadrian: remove obsolete Patch logic

This commit removes obsolete Patch logic from hadrian, given we no
longer need to patch the gmp tarball when building in-tree GMP.

- - - - -
40f4d343 by Cheng Shao at 2024-04-24T11:11:33-04:00
autoconf: remove obsolete patch detection

This commit removes obsolete deletection logic of the patch command
from autoconf scripts, given we no longer need to patch anything in
the GHC build process.

- - - - -
03c13f34 by Sylvain Henry at 2024-04-24T11:11:45-04:00
JS: correctly handle RUBBISH literals (#24664)

- - - - -


10 changed files:

- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/StgToJS/Literal.hs
- configure.ac
- hadrian/cfg/system.config.in
- hadrian/src/Builder.hs
- hadrian/src/Hadrian/Haskell/Cabal/Parse.hs
- hadrian/src/Rules/Gmp.hs
- libraries/ghc-bignum/gmp/gmp-tarballs
- − libraries/ghc-bignum/gmp/gmpsrc.patch
- − libraries/ghc-bignum/gmp/ln


Changes:

=====================================
compiler/GHC/Driver/Pipeline/Execute.hs
=====================================
@@ -1040,13 +1040,22 @@ this is accomplished with the `ld -r` command. We rely on this for two ends:
 The command used for object linking is set using the -pgmlm and -optlm
 command-line options.
 
-Sadly, the LLD linker that we use on Windows does not support the `-r` flag
-needed to support object merging (see #21068). For this reason on Windows we do
-not support GHCi objects.  To deal with foreign stubs we build a static archive
-of all of a module's object files instead merging them. Consequently, we can
-end up producing `.o` files which are in fact static archives. However,
-toolchains generally don't have a problem with this as they use file headers,
-not the filename, to determine the nature of inputs.
+However, `ld -r` is broken in some cases:
+
+ * The LLD linker that we use on Windows does not support the `-r`
+   flag needed to support object merging (see #21068). For this reason
+   on Windows we do not support GHCi objects.
+ * `wasm-ld -r` is prohibitively slow, especially when handling large
+   input objects (e.g. profiled objects).
+
+In these cases, we bundle a module's own object file with its foreign
+stub's object file, instead of merging them. Consequently, we can end
+up producing `.o` files which are in fact static archives. This can
+only work if `ar -L` is supported, so the archive `.o` files can be
+properly added to the final static library. We must also take care not
+to produce archive `.dyn_o` when building dynamic objects, otherwise
+we end up with broken `.so` files when GHC is built with `llvm-ar`
+(#22210).
 
 Note that this has somewhat non-obvious consequences when producing
 initializers and finalizers. See Note [Initializers and finalizers in Cmm]
@@ -1072,7 +1081,7 @@ via gcc.
 -- | See Note [Object merging].
 joinObjectFiles :: HscEnv -> [FilePath] -> FilePath -> IO ()
 joinObjectFiles hsc_env o_files output_fn
-  | can_merge_objs && not dashLSupported = do
+  | can_merge_objs && (not dashLSupported || is_dyn) = do
   let toolSettings' = toolSettings dflags
       ldIsGnuLd = toolSettings_ldIsGnuLd toolSettings'
       ld_r args = GHC.SysTools.runMergeObjects (hsc_logger hsc_env) (hsc_tmpfs hsc_env) (hsc_dflags hsc_env) (
@@ -1100,6 +1109,7 @@ joinObjectFiles hsc_env o_files output_fn
   withAtomicRename output_fn $ \tmp_ar ->
       liftIO $ runAr logger dflags Nothing $ map Option $ ["qc" ++ dashL, tmp_ar] ++ o_files
   where
+    is_dyn = ways dflags `hasWay` WayDyn
     dashLSupported = sArSupportsDashL (settings dflags)
     dashL = if dashLSupported then "L" else ""
     can_merge_objs = isJust (pgm_lm (hsc_dflags hsc_env))


=====================================
compiler/GHC/StgToJS/Literal.hs
=====================================
@@ -22,6 +22,7 @@ import GHC.StgToJS.Symbols
 import GHC.Data.FastString
 import GHC.Types.Literal
 import GHC.Types.Basic
+import GHC.Types.RepType
 import GHC.Utils.Misc
 import GHC.Utils.Panic
 import GHC.Utils.Outputable
@@ -68,7 +69,27 @@ genLit = \case
     | otherwise              -> return [ toJExpr (global (mkRawSymbol True name))
                                        , ValExpr (JInt 0)
                                        ]
-  LitRubbish {} -> return [ null_ ]
+  LitRubbish _ rr_ty ->
+    -- Generate appropriate rubbish literals, otherwise it might trip up the
+    -- code generator when a primop is applied to a rubbish literal (see #24664)
+    let reps = runtimeRepPrimRep (text "GHC.StgToJS.Literal.genLit") rr_ty
+        rub  = \case
+                  BoxedRep _ -> [ null_ ]
+                  AddrRep    -> [ null_, ValExpr (JInt 0) ]
+                  WordRep    -> [ ValExpr (JInt 0) ]
+                  Word8Rep   -> [ ValExpr (JInt 0) ]
+                  Word16Rep  -> [ ValExpr (JInt 0) ]
+                  Word32Rep  -> [ ValExpr (JInt 0) ]
+                  Word64Rep  -> [ ValExpr (JInt 0), ValExpr (JInt 0) ]
+                  IntRep     -> [ ValExpr (JInt 0) ]
+                  Int8Rep    -> [ ValExpr (JInt 0) ]
+                  Int16Rep   -> [ ValExpr (JInt 0) ]
+                  Int32Rep   -> [ ValExpr (JInt 0) ]
+                  Int64Rep   -> [ ValExpr (JInt 0), ValExpr (JInt 0) ]
+                  DoubleRep  -> [ ValExpr (JInt 0) ]
+                  FloatRep   -> [ ValExpr (JInt 0) ]
+                  VecRep _ _ -> panic "GHC.StgToJS.Literal.genLit: VecRep unsupported"
+    in return (concatMap rub reps)
 
 -- | generate a literal for the static init tables
 genStaticLit :: Literal -> G [StaticLit]


=====================================
configure.ac
=====================================
@@ -97,11 +97,11 @@ dnl use either is considered a Feature.
 dnl ** What command to use to compile compiler sources ?
 dnl --------------------------------------------------------------
 
-AC_ARG_VAR(GHC,[Use as the full path to GHC. [default=autodetect]])
-AC_PATH_PROG([GHC], [ghc])
+AC_ARG_VAR(GHC,[Use as the bootstrap GHC. [default=autodetect]])
+AC_CHECK_PROG([GHC], [ghc], [ghc])
 AC_ARG_WITH([ghc],
-        AS_HELP_STRING([--with-ghc=PATH], [Use PATH as the full path to ghc (obsolete, use GHC=PATH instead) [default=autodetect]]),
-        AC_MSG_ERROR([--with-ghc=$withval is obsolete (use './configure GHC=$withval' or 'GHC=$withval ./configure' instead)]))
+        AS_HELP_STRING([--with-ghc=PATH], [Use PATH as the bootstrap ghc (obsolete, use GHC=PATH instead) [default=autodetect]]),
+        AC_MSG_ERROR([--with-ghc=$withval is obsolete (use './configure GHC=$withval' instead)]))
 AC_SUBST(WithGhc,$GHC)
 
 AC_ARG_ENABLE(bootstrap-with-devel-snapshot,
@@ -740,10 +740,6 @@ dnl ** check for tar
 dnl   if GNU tar is named gtar, look for it first.
 AC_PATH_PROGS(TarCmd,gnutar gtar tar,tar)
 
-dnl ** check for patch
-dnl if GNU patch is named gpatch, look for it first
-AC_PATH_PROGS(PatchCmd,gpatch patch, patch)
-
 dnl ** check for autoreconf
 AC_PATH_PROG(AutoreconfCmd, autoreconf, autoreconf)
 


=====================================
hadrian/cfg/system.config.in
=====================================
@@ -17,7 +17,6 @@ sphinx-build   = @SPHINXBUILD@
 system-ghc     = @WithGhc@
 system-ghc-pkg = @GhcPkgCmd@
 tar            = @TarCmd@
-patch          = @PatchCmd@
 xelatex        = @XELATEX@
 makeindex      = @MAKEINDEX@
 makeinfo       = @MAKEINFO@


=====================================
hadrian/src/Builder.hs
=====================================
@@ -8,10 +8,7 @@ module Builder (
     -- * Builder properties
     builderProvenance, systemBuilderPath, builderPath, isSpecified, needBuilders,
     runBuilder, runBuilderWith, runBuilderWithCmdOptions, getBuilderPath,
-    builderEnvironment,
-
-    -- * Ad hoc builder invocation
-    applyPatch
+    builderEnvironment
     ) where
 
 import Control.Exception.Extra (Partial)
@@ -184,7 +181,6 @@ data Builder = Alex
              | MergeObjects Stage -- ^ linker to be used to merge object files.
              | Nm
              | Objdump
-             | Patch
              | Python
              | Ranlib
              | Testsuite TestMode
@@ -443,7 +439,6 @@ systemBuilderPath builder = case builder of
     Makeinfo        -> fromKey "makeinfo"
     Nm              -> fromTargetTC "nm" (Toolchain.nmProgram . tgtNm)
     Objdump         -> fromKey "objdump"
-    Patch           -> fromKey "patch"
     Python          -> fromKey "python"
     Ranlib          -> fromTargetTC "ranlib" (maybeProg Toolchain.ranlibProgram . tgtRanlib)
     Testsuite _     -> fromKey "python"
@@ -511,15 +506,6 @@ systemBuilderPath builder = case builder of
 isSpecified :: Builder -> Action Bool
 isSpecified = fmap (not . null) . systemBuilderPath
 
--- | Apply a patch by executing the 'Patch' builder in a given directory.
-applyPatch :: FilePath -> FilePath -> Action ()
-applyPatch dir patch = do
-    let file = dir -/- patch
-    needBuilders [Patch]
-    path <- builderPath Patch
-    putBuild $ "| Apply patch " ++ file
-    quietly $ cmd' [Cwd dir, FileStdin file] [path, "-p0"]
-
 -- Note [cmd wrapper]
 -- ~~~~~~~~~~~~~~~~~~
 -- `cmd'` is a wrapper for Shake's `cmd` that allows us to customize what is


=====================================
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)


=====================================
hadrian/src/Rules/Gmp.hs
=====================================
@@ -143,23 +143,18 @@ gmpRules = do
                 gmpP      = takeDirectory gmpBuildP
             ctx <- makeGmpPathContext gmpP
             removeDirectory gmpBuildP
-            -- Note: We use a tarball like gmp-4.2.4-nodoc.tar.bz2, which is
-            -- gmp-4.2.4.tar.bz2 repacked without the doc/ directory contents.
+            -- Note: We use a tarball like gmp-4.2.4-nodoc.tar.xz, which is
+            -- gmp-4.2.4.tar.xz repacked without the doc/ directory contents.
             -- That's because the doc/ directory contents are under the GFDL,
             -- which causes problems for Debian.
             tarball <- unifyPath . fromSingleton "Exactly one GMP tarball is expected"
-                   <$> getDirectoryFiles top [gmpBase -/- "gmp-tarballs/gmp*.tar.bz2"]
+                   <$> getDirectoryFiles top [gmpBase -/- "gmp-tarballs/gmp*.tar.xz"]
 
             withTempDir $ \dir -> do
                 let tmp = unifyPath dir
                 need [top -/- tarball]
                 build $ target ctx (Tar Extract) [top -/- tarball] [tmp]
 
-                let patch     = gmpBase -/- "gmpsrc.patch"
-                    patchName = takeFileName patch
-                copyFile patch $ tmp -/- patchName
-                applyPatch tmp patchName
-
                 let name    = dropExtension . dropExtension $ takeFileName tarball
                     unpack  = fromMaybe . error $ "gmpRules: expected suffix "
                         ++ "-nodoc (found: " ++ name ++ ")."


=====================================
libraries/ghc-bignum/gmp/gmp-tarballs
=====================================
@@ -1 +1 @@
-Subproject commit 4f26049af40afb380eaf033ab91404cd2e214919
+Subproject commit 01149ce3471128e9fe0feca607579981f4b64395


=====================================
libraries/ghc-bignum/gmp/gmpsrc.patch deleted
=====================================
@@ -1,44 +0,0 @@
-diff -Naur gmp-6.2.1/Makefile.am gmpbuild/Makefile.am
---- gmp-6.2.1/Makefile.am	2020-11-15 02:45:09.000000000 +0800
-+++ gmpbuild/Makefile.am	2021-01-09 22:56:14.571708858 +0800
-@@ -112,7 +112,7 @@
- LIBGMPXX_LT_AGE      = 6
- 
- 
--SUBDIRS = tests mpn mpz mpq mpf printf scanf rand cxx demos tune doc
-+SUBDIRS = tests mpn mpz mpq mpf printf scanf rand cxx demos tune
- 
- EXTRA_DIST = configfsf.guess configfsf.sub .gdbinit INSTALL.autoconf \
- 	     COPYING.LESSERv3 COPYINGv2 COPYINGv3
-diff -Naur gmp-6.2.1/Makefile.in gmpbuild/Makefile.in
---- gmp-6.2.1/Makefile.in	2020-11-15 02:45:16.000000000 +0800
-+++ gmpbuild/Makefile.in	2021-01-10 16:15:37.387670402 +0800
-@@ -572,7 +572,7 @@
- LIBGMPXX_LT_CURRENT = 10
- LIBGMPXX_LT_REVISION = 1
- LIBGMPXX_LT_AGE = 6
--SUBDIRS = tests mpn mpz mpq mpf printf scanf rand cxx demos tune doc
-+SUBDIRS = tests mpn mpz mpq mpf printf scanf rand cxx demos tune
- 
- # Put asl.h here for now.
- 
-diff -Naur gmp-6.2.1/configure gmpbuild/configure
---- gmp-6.2.1/configure	2020-11-15 02:45:15.000000000 +0800
-+++ gmpbuild/configure	2021-01-10 16:13:59.196004951 +0800
-@@ -27985,7 +27985,7 @@
- # FIXME: Upcoming version of autoconf/automake may not like broken lines.
- #        Right now automake isn't accepting the new AC_CONFIG_FILES scheme.
- 
--ac_config_files="$ac_config_files Makefile mpf/Makefile mpn/Makefile mpq/Makefile mpz/Makefile printf/Makefile scanf/Makefile rand/Makefile cxx/Makefile tests/Makefile tests/devel/Makefile tests/mpf/Makefile tests/mpn/Makefile tests/mpq/Makefile tests/mpz/Makefile tests/rand/Makefile tests/misc/Makefile tests/cxx/Makefile doc/Makefile tune/Makefile demos/Makefile demos/calc/Makefile demos/expr/Makefile gmp.h:gmp-h.in gmp.pc:gmp.pc.in gmpxx.pc:gmpxx.pc.in"
-+ac_config_files="$ac_config_files Makefile mpf/Makefile mpn/Makefile mpq/Makefile mpz/Makefile printf/Makefile scanf/Makefile rand/Makefile cxx/Makefile tests/Makefile tests/devel/Makefile tests/mpf/Makefile tests/mpn/Makefile tests/mpq/Makefile tests/mpz/Makefile tests/rand/Makefile tests/misc/Makefile tests/cxx/Makefile tune/Makefile demos/Makefile demos/calc/Makefile demos/expr/Makefile gmp.h:gmp-h.in gmp.pc:gmp.pc.in gmpxx.pc:gmpxx.pc.in"
- 
- cat >confcache <<\_ACEOF
- # This file is a shell script that caches the results of configure
-@@ -29129,7 +29129,6 @@
-     "tests/rand/Makefile") CONFIG_FILES="$CONFIG_FILES tests/rand/Makefile" ;;
-     "tests/misc/Makefile") CONFIG_FILES="$CONFIG_FILES tests/misc/Makefile" ;;
-     "tests/cxx/Makefile") CONFIG_FILES="$CONFIG_FILES tests/cxx/Makefile" ;;
--    "doc/Makefile") CONFIG_FILES="$CONFIG_FILES doc/Makefile" ;;
-     "tune/Makefile") CONFIG_FILES="$CONFIG_FILES tune/Makefile" ;;
-     "demos/Makefile") CONFIG_FILES="$CONFIG_FILES demos/Makefile" ;;
-     "demos/calc/Makefile") CONFIG_FILES="$CONFIG_FILES demos/calc/Makefile" ;;


=====================================
libraries/ghc-bignum/gmp/ln deleted
=====================================
@@ -1,3 +0,0 @@
-#!/bin/sh
-exit 1
-



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d1b92a396fd4201d34d0d7dbe74c3d5dd86ff1fa...03c13f343554e7c51d80cb8e6ee7519a4bcc7ef8

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d1b92a396fd4201d34d0d7dbe74c3d5dd86ff1fa...03c13f343554e7c51d80cb8e6ee7519a4bcc7ef8
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/20240424/ffdb48ce/attachment-0001.html>


More information about the ghc-commits mailing list