[Git][ghc/ghc][wip/T17962b] Refactor handling of object merging

Ben Gamari gitlab at gitlab.haskell.org
Sun Aug 2 15:46:46 UTC 2020



Ben Gamari pushed to branch wip/T17962b at Glasgow Haskell Compiler / GHC


Commits:
1696a5b7 by Ben Gamari at 2020-08-02T11:46:37-04:00
Refactor handling of object merging

Previously to merge a set of object files we would invoke the linker as
usual, adding -r to the command-line. However, this can result in
non-sensical command-lines which causes lld to balk (#17962).

To avoid this we introduce a new tool setting into GHC, -pgmlm, which is
the linker which we use to merge object files.

- - - - -


21 changed files:

- aclocal.m4
- compiler/GHC/Driver/Pipeline.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Settings.hs
- compiler/GHC/Settings/IO.hs
- compiler/GHC/SysTools/Tasks.hs
- configure.ac
- distrib/configure.ac.in
- docs/users_guide/phases.rst
- hadrian/cfg/system.config.in
- hadrian/hadrian.cabal
- hadrian/src/Builder.hs
- hadrian/src/Oracles/Setting.hs
- hadrian/src/Rules/Generate.hs
- hadrian/src/Rules/Library.hs
- hadrian/src/Settings/Builders/Ld.hs
- + hadrian/src/Settings/Builders/MergeObjects.hs
- hadrian/src/Settings/Default.hs
- includes/ghc.mk
- mk/config.mk.in
- rules/build-package-way.mk


Changes:

=====================================
aclocal.m4
=====================================
@@ -3,6 +3,15 @@
 # To be a good autoconf citizen, names of local macros have prefixed with FP_ to
 # ensure we don't clash with any pre-supplied autoconf ones.
 
+# FPTOOLS_WRITE_FILE
+# ------------------
+# Write $2 to the file named $1.
+AC_DEFUN([FPTOOLS_WRITE_FILE],
+[
+cat >$1 <<ACEOF
+$2
+ACEOF
+])
 
 AC_DEFUN([GHC_SELECT_FILE_EXTENSIONS],
 [
@@ -2471,7 +2480,6 @@ AC_DEFUN([FIND_LD],[
         # Make sure the user didn't specify LD manually.
         if test "z$LD" != "z"; then
             AC_CHECK_TARGET_TOOL([LD], [ld])
-            LD_NO_GOLD=$LD
             return
         fi
 
@@ -2484,7 +2492,6 @@ AC_DEFUN([FIND_LD],[
             if test "x$TmpLd" = "x"; then continue; fi
 
             out=`$TmpLd --version`
-            LD_NO_GOLD=$TmpLd
             case $out in
               "GNU ld"*)
                    FP_CC_LINKER_FLAG_TRY(bfd, $2) ;;
@@ -2492,8 +2499,6 @@ AC_DEFUN([FIND_LD],[
                    FP_CC_LINKER_FLAG_TRY(gold, $2)
                    if test "$cross_compiling" = "yes"; then
                        AC_MSG_NOTICE([Using ld.gold and assuming that it is not affected by binutils issue 22266]);
-                   else
-                       LD_NO_GOLD=ld;
                    fi
                    ;;
               "LLD"*)
@@ -2514,21 +2519,137 @@ AC_DEFUN([FIND_LD],[
 
         # Fallback
         AC_CHECK_TARGET_TOOL([LD], [ld])
-        # This isn't entirely safe since $LD may have been discovered to be
-        # ld.gold, but what else can we do?
-        if test "x$LD_NO_GOLD" = "x"; then LD_NO_GOLD=$LD; fi
     }
 
     if test "x$enable_ld_override" = "xyes"; then
         find_ld
     else
         AC_CHECK_TARGET_TOOL([LD], [ld])
-        if test "x$LD_NO_GOLD" = "x"; then LD_NO_GOLD=$LD; fi
     fi
 
     CHECK_LD_COPY_BUG([$1])
 ])
 
+
+# FIND_MERGE_OBJECTS
+# ------------------
+# Find which linker to use to merge object files.
+#
+AC_DEFUN([FIND_MERGE_OBJECTS],[
+    AC_REQUIRE([FIND_LD])
+
+    # check_for_T22266
+    # ------------------
+    #
+    # Test for binutils #22266. This bug manifested as GHC bug #14328 (see also: #14675, #14291).
+    # Uses test from
+    # https://sourceware.org/git/gitweb.cgi?p=binutils-gdb.git;h=033bfb739b525703bfe23f151d09e9beee3a2afe
+    #
+    # $1 = linker to test
+    # Returns 0 if not affected, 1 otherwise
+    check_for_T22266() {
+        AC_MSG_CHECKING([for ld.gold object merging bug (binutils 22266)])
+        if test "$cross_compiling" = "yes"; then
+            AC_MSG_RESULT([cross-compiling, assuming LD can merge objects correctly.])
+            return 0
+        else
+            FPTOOLS_WRITE_FILE([conftest.a.c], [
+              __attribute__((section(".data.a")))
+              static int int_from_a_1 = 0x11223344;
+
+              __attribute__((section(".data.rel.ro.a")))
+              int *p_int_from_a_2 = &int_from_a_1;
+
+              const char *hello (void);
+
+              const char *
+              hello (void)
+              {
+                return "XXXHello, world!" + 3;
+              }
+            ])
+
+            FPTOOLS_WRITE_FILE([conftest.main.c], [
+              #include <stdlib.h>
+              #include <string.h>
+
+              extern int *p_int_from_a_2;
+              extern const char *hello (void);
+
+              int main (void) {
+                if (*p_int_from_a_2 != 0x11223344)
+                  abort ();
+                if (strcmp(hello(), "Hello, world!") != 0)
+                  abort ();
+                return 0;
+              }
+            ])
+
+            FPTOOLS_WRITE_FILE([conftest.t], [
+              SECTIONS
+              {
+                  .text : {
+                      *(.text*)
+                  }
+                  .rodata :
+                  {
+                      *(.rodata .rodata.* .gnu.linkonce.r.*)
+                  }
+                  .data.rel.ro : {
+                      *(.data.rel.ro*)
+                  }
+                  .data : {
+                      *(.data*)
+                  }
+                  .bss : {
+                      *(.bss*)
+                  }
+              }
+            ])
+
+            $CC -c -o conftest.a.o conftest.a.c || AC_MSG_ERROR([Failed to compile test])
+            $SettingsMergeObjectsCommand $SettingsMergeObjectsFlags -T conftest.t conftest.a.o -o conftest.ar.o || AC_MSG_ERROR([Failed to merge test object])
+
+            $CC -c -o conftest.main.o conftest.main.c || AC_MSG_ERROR([Failed to compile test driver])
+            $CC conftest.ar.o conftest.main.o -o conftest || AC_MSG_ERROR([Failed to link test driver])
+
+            if ./conftest; then
+                AC_MSG_RESULT([not affected])
+                res=0
+            else
+                AC_MSG_RESULT([affected])
+                res=1
+            fi
+            rm -f conftest.a.o conftest.a.c  conttest.ar.o conftest.main.c conftest.main.o conftest
+            return $res
+        fi
+    }
+
+    if test -z "$SettingsMergeObjectsCommand"; then
+        SettingsMergeObjectsCommand="$LD"
+    fi
+    if test -z "$SettingsMergeObjectsFlags"; then
+        SettingsMergeObjectsFlags="-r"
+    fi
+
+    if ! check_for_T22266 "$SettingsMergeObjectsCommand"; then
+        AC_MSG_NOTICE([$SettingsMergeObjectsCommand is broken due to binutils 22266, looking for another linker...])
+        SettingsMergeObjectsCommand=""
+        AC_CHECK_TARGET_TOOL([SettingsMergeObjectsCommand], [ld])
+        if ! check_for_T22266 "$SettingsMergeObjectsCommand"; then
+            AC_MSG_ERROR([Linker is affected by binutils 22266 but couldn't find another unaffected linker. Please set the SettingsMergeObjectsCommand variable to a functional linker.])
+        fi
+    fi
+
+
+    if test "$windows" = YES -a "$EnableDistroToolchain" = "NO" -a "$WORD_SIZE" = 64; then
+        SettingsMergeObjectsFlags="$SettingsMergeObjectsFlags --oformat=pe-bigobj-x86-64"
+    fi
+
+    AC_SUBST(SettingsMergeObjectsCommand)
+    AC_SUBST(SettingsMergeObjectsFlags)
+])
+
 # FIND_PYTHON
 # -----------
 # Find the version of `python` to use (for the testsuite driver)


=====================================
compiler/GHC/Driver/Pipeline.hs
=====================================
@@ -2140,31 +2140,9 @@ joinObjectFiles dflags o_files output_fn = do
   let toolSettings' = toolSettings dflags
       ldIsGnuLd = toolSettings_ldIsGnuLd toolSettings'
       osInfo = platformOS (targetPlatform dflags)
-      ld_r args cc = GHC.SysTools.runLink dflags ([
-                       GHC.SysTools.Option "-nostdlib",
-                       GHC.SysTools.Option "-Wl,-r"
-                     ]
-                        -- See Note [No PIE while linking] in GHC.Driver.Session
-                     ++ (if toolSettings_ccSupportsNoPie toolSettings'
-                          then [GHC.SysTools.Option "-no-pie"]
-                          else [])
-
-                     ++ (if any (cc ==) [Clang, AppleClang, AppleClang51]
-                          then []
-                          else [GHC.SysTools.Option "-nodefaultlibs"])
-                     ++ (if osInfo == OSFreeBSD
-                          then [GHC.SysTools.Option "-L/usr/lib"]
-                          else [])
-                        -- gcc on sparc sets -Wl,--relax implicitly, but
-                        -- -r and --relax are incompatible for ld, so
-                        -- disable --relax explicitly.
-                     ++ (if platformArch (targetPlatform dflags)
-                                `elem` [ArchSPARC, ArchSPARC64]
-                         && ldIsGnuLd
-                            then [GHC.SysTools.Option "-Wl,-no-relax"]
-                            else [])
+      ld_r args = GHC.SysTools.runMergeObjects dflags (
                         -- See Note [Produce big objects on Windows]
-                     ++ [ GHC.SysTools.Option "-Wl,--oformat,pe-bigobj-x86-64"
+                        [ GHC.SysTools.Option "-Wl,--oformat,pe-bigobj-x86-64"
                         | OSMinGW32 == osInfo
                         , not $ target32Bit (targetPlatform dflags)
                         ]
@@ -2176,25 +2154,24 @@ joinObjectFiles dflags o_files output_fn = do
       -- suppress the generation of the .note.gnu.build-id section,
       -- which we don't need and sometimes causes ld to emit a
       -- warning:
-      ld_build_id | toolSettings_ldSupportsBuildId toolSettings' = ["-Wl,--build-id=none"]
+      ld_build_id | toolSettings_ldSupportsBuildId toolSettings' = ["--build-id=none"]
                   | otherwise                     = []
 
-  ccInfo <- getCompilerInfo dflags
   if ldIsGnuLd
      then do
           script <- newTempName dflags TFL_CurrentModule "ldscript"
           cwd <- getCurrentDirectory
           let o_files_abs = map (\x -> "\"" ++ (cwd </> x) ++ "\"") o_files
           writeFile script $ "INPUT(" ++ unwords o_files_abs ++ ")"
-          ld_r [GHC.SysTools.FileOption "" script] ccInfo
+          ld_r [GHC.SysTools.FileOption "" script]
      else if toolSettings_ldSupportsFilelist toolSettings'
      then do
           filelist <- newTempName dflags TFL_CurrentModule "filelist"
           writeFile filelist $ unlines o_files
           ld_r [GHC.SysTools.Option "-Wl,-filelist",
-                GHC.SysTools.FileOption "-Wl," filelist] ccInfo
+                GHC.SysTools.FileOption "-Wl," filelist]
      else do
-          ld_r (map (GHC.SysTools.FileOption "") o_files) ccInfo
+          ld_r (map (GHC.SysTools.FileOption "") o_files)
 
 -- -----------------------------------------------------------------------------
 -- Misc.


=====================================
compiler/GHC/Driver/Session.hs
=====================================
@@ -102,6 +102,7 @@ module GHC.Driver.Session (
         sPgm_c,
         sPgm_a,
         sPgm_l,
+        sPgm_lm,
         sPgm_dll,
         sPgm_T,
         sPgm_windres,
@@ -120,6 +121,7 @@ module GHC.Driver.Session (
         sOpt_cxx,
         sOpt_a,
         sOpt_l,
+        sOpt_lm,
         sOpt_windres,
         sOpt_lo,
         sOpt_lc,
@@ -142,10 +144,10 @@ module GHC.Driver.Session (
         ghcUsagePath, ghciUsagePath, topDir, tmpDir,
         versionedAppDir, versionedFilePath,
         extraGccViaCFlags, globalPackageDatabasePath,
-        pgm_L, pgm_P, pgm_F, pgm_c, pgm_a, pgm_l, pgm_dll, pgm_T,
+        pgm_L, pgm_P, pgm_F, pgm_c, pgm_a, pgm_l, pgm_lm, pgm_dll, pgm_T,
         pgm_windres, pgm_libtool, pgm_ar, pgm_ranlib, pgm_lo, pgm_lc,
         pgm_lcc, pgm_i,
-        opt_L, opt_P, opt_F, opt_c, opt_cxx, opt_a, opt_l, opt_i,
+        opt_L, opt_P, opt_F, opt_c, opt_cxx, opt_a, opt_l, opt_lm, opt_i,
         opt_P_signature,
         opt_windres, opt_lo, opt_lc, opt_lcc,
 
@@ -940,6 +942,8 @@ pgm_a                 :: DynFlags -> (String,[Option])
 pgm_a dflags = toolSettings_pgm_a $ toolSettings dflags
 pgm_l                 :: DynFlags -> (String,[Option])
 pgm_l dflags = toolSettings_pgm_l $ toolSettings dflags
+pgm_lm                 :: DynFlags -> (String,[Option])
+pgm_lm dflags = toolSettings_pgm_lm $ toolSettings dflags
 pgm_dll               :: DynFlags -> (String,[Option])
 pgm_dll dflags = toolSettings_pgm_dll $ toolSettings dflags
 pgm_T                 :: DynFlags -> String
@@ -986,6 +990,8 @@ opt_a dflags= toolSettings_opt_a $ toolSettings dflags
 opt_l                 :: DynFlags -> [String]
 opt_l dflags = concatMap (wayOptl (targetPlatform dflags)) (ways dflags)
             ++ toolSettings_opt_l (toolSettings dflags)
+opt_lm                :: DynFlags -> [String]
+opt_lm dflags= toolSettings_opt_lm $ toolSettings dflags
 opt_windres           :: DynFlags -> [String]
 opt_windres dflags= toolSettings_opt_windres $ toolSettings dflags
 opt_lcc                :: DynFlags -> [String]


=====================================
compiler/GHC/Settings.hs
=====================================
@@ -28,6 +28,7 @@ module GHC.Settings
   , sPgm_c
   , sPgm_a
   , sPgm_l
+  , sPgm_lm
   , sPgm_dll
   , sPgm_T
   , sPgm_windres
@@ -46,6 +47,7 @@ module GHC.Settings
   , sOpt_cxx
   , sOpt_a
   , sOpt_l
+  , sOpt_lm
   , sOpt_windres
   , sOpt_lo
   , sOpt_lc
@@ -99,6 +101,7 @@ data ToolSettings = ToolSettings
   , toolSettings_pgm_c       :: String
   , toolSettings_pgm_a       :: (String, [Option])
   , toolSettings_pgm_l       :: (String, [Option])
+  , toolSettings_pgm_lm      :: (String, [Option])
   , toolSettings_pgm_dll     :: (String, [Option])
   , toolSettings_pgm_T       :: String
   , toolSettings_pgm_windres :: String
@@ -124,6 +127,7 @@ data ToolSettings = ToolSettings
   , toolSettings_opt_cxx           :: [String]
   , toolSettings_opt_a             :: [String]
   , toolSettings_opt_l             :: [String]
+  , toolSettings_opt_lm            :: [String]
   , toolSettings_opt_windres       :: [String]
   , -- | LLVM: llvm optimiser
     toolSettings_opt_lo            :: [String]
@@ -200,6 +204,8 @@ sPgm_a :: Settings -> (String, [Option])
 sPgm_a = toolSettings_pgm_a . sToolSettings
 sPgm_l :: Settings -> (String, [Option])
 sPgm_l = toolSettings_pgm_l . sToolSettings
+sPgm_lm :: Settings -> (String, [Option])
+sPgm_lm = toolSettings_pgm_lm . sToolSettings
 sPgm_dll :: Settings -> (String, [Option])
 sPgm_dll = toolSettings_pgm_dll . sToolSettings
 sPgm_T :: Settings -> String
@@ -236,6 +242,8 @@ sOpt_a :: Settings -> [String]
 sOpt_a = toolSettings_opt_a . sToolSettings
 sOpt_l :: Settings -> [String]
 sOpt_l = toolSettings_opt_l . sToolSettings
+sOpt_lm :: Settings -> [String]
+sOpt_lm = toolSettings_opt_lm . sToolSettings
 sOpt_windres :: Settings -> [String]
 sOpt_windres = toolSettings_opt_windres . sToolSettings
 sOpt_lo :: Settings -> [String]


=====================================
compiler/GHC/Settings/IO.hs
=====================================
@@ -137,6 +137,8 @@ initSettings top_dir = do
         as_args  = map Option cc_args
         ld_prog  = cc_prog
         ld_args  = map Option (cc_args ++ words cc_link_args_str)
+  ld_r_prog <- getSetting "Merge objects command"
+  ld_r_args <- getSetting "Merge objects flags"
 
   llvmTarget <- getSetting "LLVM target"
 
@@ -183,6 +185,7 @@ initSettings top_dir = do
       , toolSettings_pgm_c   = cc_prog
       , toolSettings_pgm_a   = (as_prog, as_args)
       , toolSettings_pgm_l   = (ld_prog, ld_args)
+      , toolSettings_pgm_lm  = (ld_r_prog, map Option $ words ld_r_args)
       , toolSettings_pgm_dll = (mkdll_prog,mkdll_args)
       , toolSettings_pgm_T   = touch_path
       , toolSettings_pgm_windres = windres_path
@@ -201,6 +204,7 @@ initSettings top_dir = do
       , toolSettings_opt_cxx     = cxx_args
       , toolSettings_opt_a       = []
       , toolSettings_opt_l       = []
+      , toolSettings_opt_lm      = []
       , toolSettings_opt_windres = []
       , toolSettings_opt_lcc     = []
       , toolSettings_opt_lo      = []


=====================================
compiler/GHC/SysTools/Tasks.hs
=====================================
@@ -299,6 +299,13 @@ ld: warning: symbol referencing errors
     ld_postfix = tail . snd . ld_warn_break
     ld_warning_found = not . null . snd . ld_warn_break
 
+runMergeObjects :: DynFlags -> [Option] -> IO ()
+runMergeObjects dflags args = traceToolCommand dflags "merge-objects" $ do
+  let (p,args0) = pgm_lm dflags
+      optl_args = map Option (getOpts dflags opt_lm)
+      args2     = args0 ++ args ++ optl_args
+  mb_env <- getGccEnv args2
+  runSomethingResponseFile dflags id "Merge objects" p args2 mb_env
 
 runLibtool :: DynFlags -> [Option] -> IO ()
 runLibtool dflags args = traceToolCommand dflags "libtool" $ do


=====================================
configure.ac
=====================================
@@ -602,13 +602,12 @@ dnl ** Which ld to use
 dnl --------------------------------------------------------------
 AC_ARG_VAR(LD,[Use as the path to ld. See also --disable-ld-override.])
 FIND_LD([$target],[GccUseLdOpt])
+FIND_MERGE_OBJECTS()
 CONF_GCC_LINKER_OPTS_STAGE1="$CONF_GCC_LINKER_OPTS_STAGE1 $GccUseLdOpt"
 CONF_GCC_LINKER_OPTS_STAGE2="$CONF_GCC_LINKER_OPTS_STAGE2 $GccUseLdOpt"
 LdCmd="$LD"
-LdNoGoldCmd="$LD_NO_GOLD"
 CFLAGS="$CFLAGS $GccUseLdOpt"
 AC_SUBST([LdCmd])
-AC_SUBST([LdNoGoldCmd])
 
 FP_PROG_LD_IS_GNU
 FP_PROG_LD_BUILD_ID


=====================================
distrib/configure.ac.in
=====================================
@@ -96,6 +96,7 @@ FP_SET_CFLAGS_C99([CC],[CONF_CC_OPTS_STAGE2],[CONF_CPP_OPTS_STAGE2])
 dnl ** Which ld to use?
 dnl --------------------------------------------------------------
 FIND_LD([$target],[GccUseLdOpt])
+FIND_MERGE_OBJECTS()
 CONF_GCC_LINKER_OPTS_STAGE1="$CONF_GCC_LINKER_OPTS_STAGE1 $GccUseLdOpt"
 CONF_GCC_LINKER_OPTS_STAGE2="$CONF_GCC_LINKER_OPTS_STAGE2 $GccUseLdOpt"
 LdCmd="$LD"


=====================================
docs/users_guide/phases.rst
=====================================
@@ -73,6 +73,14 @@ given compilation phase:
 
     Use ⟨cmd⟩ as the linker.
 
+.. ghc-flag:: -pgmlm ⟨cmd⟩
+    :shortdesc: Use ⟨cmd⟩ as the linker when merging object files
+    :type: dynamic
+    :category: phase-programs
+
+    Use ⟨cmd⟩ as the linker when merging object files (e.g. when generating
+    joined objects for loading into GHCi).
+
 .. ghc-flag:: -pgmdll ⟨cmd⟩
     :shortdesc: Use ⟨cmd⟩ as the DLL generator
     :type: dynamic
@@ -189,6 +197,14 @@ the following flags:
 
     Pass ⟨option⟩ to the linker.
 
+.. ghc-flag:: -optlm ⟨option⟩
+    :shortdesc: pass ⟨option⟩ to the linker when merging object files.
+    :type: dynamic
+    :category: phase-options
+
+    Pass ⟨option⟩ to the linker when merging object files. In the case of a
+    standard ``ld``-style linker this should generally include the ``-r`` flag.
+
 .. ghc-flag:: -optdll ⟨option⟩
     :shortdesc: pass ⟨option⟩ to the DLL generator
     :type: dynamic


=====================================
hadrian/cfg/system.config.in
=====================================
@@ -115,6 +115,12 @@ conf-ld-linker-args-stage1  = @CONF_LD_LINKER_OPTS_STAGE1@
 conf-ld-linker-args-stage2  = @CONF_LD_LINKER_OPTS_STAGE2@
 conf-ld-linker-args-stage3  = @CONF_LD_LINKER_OPTS_STAGE3@
 
+conf-merge-objects-args-stage0  = @SettingsMergeObjectsFlags@
+conf-merge-objects-args-stage1  = @SettingsMergeObjectsFlags@
+conf-merge-objects-args-stage2  = @SettingsMergeObjectsFlags@
+conf-merge-objects-args-stage3  = @SettingsMergeObjectsFlags@
+
+
 # Settings:
 #==========
 
@@ -138,6 +144,8 @@ settings-c-compiler-link-flags = @SettingsCCompilerLinkFlags@
 settings-c-compiler-supports-no-pie = @SettingsCCompilerSupportsNoPie@
 settings-ld-command = @SettingsLdCommand@
 settings-ld-flags = @SettingsLdFlags@
+settings-merge-objects-command = @SettingsMergeObjectsCommand@
+settings-merge-objects-flags = @SettingsMergeObjectsFlags@
 settings-ar-command = @SettingsArCommand@
 settings-ranlib-command = @SettingsRanlibCommand@
 settings-dll-wrap-command = @SettingsDllWrapCommand@


=====================================
hadrian/hadrian.cabal
=====================================
@@ -99,6 +99,7 @@ executable hadrian
                        , Settings.Builders.HsCpp
                        , Settings.Builders.Ld
                        , Settings.Builders.Make
+                       , Settings.Builders.MergeObjects
                        , Settings.Builders.RunTest
                        , Settings.Builders.Xelatex
                        , Settings.Default


=====================================
hadrian/src/Builder.hs
=====================================
@@ -127,9 +127,10 @@ data Builder = Alex
              | Hpc
              | HsCpp
              | Hsc2Hs Stage
-             | Ld Stage
+             | Ld Stage --- ^ linker
              | Make FilePath
              | Makeinfo
+             | MergeObjects Stage -- ^ linker to be used to merge object files.
              | Nm
              | Objdump
              | Patch
@@ -311,6 +312,7 @@ systemBuilderPath builder = case builder of
     Happy           -> fromKey "happy"
     HsCpp           -> fromKey "hs-cpp"
     Ld _            -> fromKey "ld"
+    MergeObjects _  -> fromKey "settings-merge-objects-command"
     Make _          -> fromKey "make"
     Makeinfo        -> fromKey "makeinfo"
     Nm              -> fromKey "nm"


=====================================
hadrian/src/Oracles/Setting.hs
=====================================
@@ -91,6 +91,7 @@ data SettingList = ConfCcArgs Stage
                  | ConfCppArgs Stage
                  | ConfGccLinkerArgs Stage
                  | ConfLdLinkerArgs Stage
+                 | ConfMergeObjectsArgs Stage
                  | HsCppArgs
 
 -- TODO compute solely in Hadrian, removing these variables' definitions
@@ -109,6 +110,8 @@ data SettingsFileSetting
     | SettingsFileSetting_CCompilerSupportsNoPie
     | SettingsFileSetting_LdCommand
     | SettingsFileSetting_LdFlags
+    | SettingsFileSetting_MergeObjectsCommand
+    | SettingsFileSetting_MergeObjectsFlags
     | SettingsFileSetting_ArCommand
     | SettingsFileSetting_RanlibCommand
     | SettingsFileSetting_DllWrapCommand
@@ -176,6 +179,7 @@ settingList key = fmap words $ lookupValueOrError configFile $ case key of
     ConfCppArgs       stage -> "conf-cpp-args-"        ++ stageString stage
     ConfGccLinkerArgs stage -> "conf-gcc-linker-args-" ++ stageString stage
     ConfLdLinkerArgs  stage -> "conf-ld-linker-args-"  ++ stageString stage
+    ConfMergeObjectsArgs stage -> "conf-merge-objects-args-"  ++ stageString stage
     HsCppArgs               -> "hs-cpp-args"
 
 -- | Look up the value of a 'SettingList' in @cfg/system.config@, tracking the
@@ -191,6 +195,8 @@ settingsFileSetting key = lookupValueOrError configFile $ case key of
     SettingsFileSetting_CCompilerSupportsNoPie -> "settings-c-compiler-supports-no-pie"
     SettingsFileSetting_LdCommand -> "settings-ld-command"
     SettingsFileSetting_LdFlags -> "settings-ld-flags"
+    SettingsFileSetting_MergeObjectsCommand -> "settings-merge-objects-command"
+    SettingsFileSetting_MergeObjectsFlags -> "settings-merge-objects-flags"
     SettingsFileSetting_ArCommand -> "settings-ar-command"
     SettingsFileSetting_RanlibCommand -> "settings-ranlib-command"
     SettingsFileSetting_DllWrapCommand -> "settings-dll-wrap-command"


=====================================
hadrian/src/Rules/Generate.hs
=====================================
@@ -294,6 +294,8 @@ generateSettings = do
         , ("ld supports build-id", expr $ lookupValueOrError configFile "ld-has-build-id")
         , ("ld supports filelist", expr $ lookupValueOrError configFile "ld-has-filelist")
         , ("ld is GNU ld", expr $ lookupValueOrError configFile "ld-is-gnu-ld")
+        , ("Merge objects command", expr $ settingsFileSetting SettingsFileSetting_MergeObjectsCommand)
+        , ("Merge objects flags", expr $ settingsFileSetting SettingsFileSetting_MergeObjectsFlags)
         , ("ar command", expr $ settingsFileSetting SettingsFileSetting_ArCommand)
         , ("ar flags", expr $ lookupValueOrError configFile "ar-args")
         , ("ar supports at file", expr $ yesNo <$> flag ArSupportsAtFile)


=====================================
hadrian/src/Rules/Library.hs
=====================================
@@ -101,7 +101,7 @@ buildGhciLibO root ghcilibPath = do
     let context = libGhciContext l
     objs <- allObjects context
     need objs
-    build $ target context (Ld stage) objs [ghcilibPath]
+    build $ target context (MergeObjects stage) objs [ghcilibPath]
 
 -- * Helpers
 


=====================================
hadrian/src/Settings/Builders/Ld.hs
=====================================
@@ -4,6 +4,5 @@ import Settings.Builders.Common
 
 ldBuilderArgs :: Args
 ldBuilderArgs = builder Ld ? mconcat [ getStagedSettingList ConfLdLinkerArgs
-                                     , arg "-r"
                                      , arg "-o", arg =<< getOutput
                                      , getInputs ]


=====================================
hadrian/src/Settings/Builders/MergeObjects.hs
=====================================
@@ -0,0 +1,9 @@
+module Settings.Builders.MergeObjects (mergeObjectsBuilderArgs) where
+
+import Settings.Builders.Common
+
+mergeObjectsBuilderArgs :: Args
+mergeObjectsBuilderArgs = builder MergeObjects ? mconcat
+    [ getStagedSettingList ConfMergeObjectsArgs
+    , arg "-o", arg =<< getOutput
+    , getInputs ]


=====================================
hadrian/src/Settings/Default.hs
=====================================
@@ -37,6 +37,7 @@ import Settings.Builders.Hsc2Hs
 import Settings.Builders.HsCpp
 import Settings.Builders.Ld
 import Settings.Builders.Make
+import Settings.Builders.MergeObjects
 import Settings.Builders.RunTest
 import Settings.Builders.Xelatex
 import Settings.Packages
@@ -244,6 +245,7 @@ defaultBuilderArgs = mconcat
     , hsCppBuilderArgs
     , ldBuilderArgs
     , makeBuilderArgs
+    , mergeObjectsBuilderArgs
     , runTestBuilderArgs
     , validateBuilderArgs
     , xelatexBuilderArgs


=====================================
includes/ghc.mk
=====================================
@@ -223,6 +223,8 @@ $(includes_SETTINGS) : includes/Makefile | $$(dir $$@)/.
 	@echo ',("ld supports build-id", "$(LdHasBuildId)")' >> $@
 	@echo ',("ld supports filelist", "$(LdHasFilelist)")' >> $@
 	@echo ',("ld is GNU ld", "$(LdIsGNULd)")' >> $@
+	@echo ',("Merge objects command", "$(SettingsMergeObjectsCommand)")' >> $@
+	@echo ',("Merge objects flags", "$(SettingsMergeObjectsFlags)")' >> $@
 	@echo ',("ar command", "$(SettingsArCommand)")' >> $@
 	@echo ',("ar flags", "$(ArArgs)")' >> $@
 	@echo ',("ar supports at file", "$(ArSupportsAtFile)")' >> $@


=====================================
mk/config.mk.in
=====================================
@@ -500,6 +500,8 @@ SettingsCCompilerLinkFlags = @SettingsCCompilerLinkFlags@
 SettingsCCompilerSupportsNoPie = @SettingsCCompilerSupportsNoPie@
 SettingsLdCommand = @SettingsLdCommand@
 SettingsLdFlags = @SettingsLdFlags@
+SettingsMergeObjectsCommand = @SettingsMergeObjectsCommand@
+SettingsMergeObjectsFlags = @SettingsMergeObjectsFlags@
 SettingsArCommand = @SettingsArCommand@
 SettingsRanlibCommand = @SettingsRanlibCommand@
 SettingsDllWrapCommand = @SettingsDllWrapCommand@
@@ -733,7 +735,6 @@ HaveDtrace		= @HaveDtrace@
 USE_DTRACE = $(HaveDtrace)
 DTRACE			= @DtraceCmd@
 
-LD_NO_GOLD = @LdNoGoldCmd@
 LD = @LdCmd@
 NM = @NmCmd@
 AR = @ArCmd@


=====================================
rules/build-package-way.mk
=====================================
@@ -116,11 +116,7 @@ BINDIST_LIBS += $$($1_$2_$3_GHCI_LIB)
 endif
 endif
 $$($1_$2_$3_GHCI_LIB) : $$($1_$2_$3_HS_OBJS) $$($1_$2_$3_CMM_OBJS) $$($1_$2_$3_C_OBJS) $$($1_$2_$3_S_OBJS) $$($1_$2_EXTRA_OBJS) $$($1_$2_LD_SCRIPT)
-	$$(call cmd,LD_NO_GOLD) $$(CONF_LD_LINKER_OPTS_STAGE$4) -r $$(if $$($1_$2_LD_SCRIPT),$$($1_$2_LD_SCRIPT_CMD) $$($1_$2_LD_SCRIPT)) -o $$@ $$(EXTRA_LD_LINKER_OPTS) $$($1_$2_$3_HS_OBJS) $$($1_$2_$3_CMM_OBJS) $$($1_$2_$3_C_OBJS) $$($1_$2_$3_S_OBJS) $$($1_$2_EXTRA_OBJS)
-# NB. LD_NO_GOLD above: see #14328 (symptoms: #14675,#14291). At least
-# some versions of ld.gold appear to have a bug that causes the
-# generated GHCi library to have some bogus relocations. Performance
-# isn't critical here, so we fall back to the ordinary ld.
+	$$(call cmd,SettingsMergeObjectsCommand) $(SettingsMergeObjectsFlags) $$(if $$($1_$2_LD_SCRIPT),$$($1_$2_LD_SCRIPT_CMD) $$($1_$2_LD_SCRIPT)) -o $$@ $$(EXTRA_LD_LINKER_OPTS) $$($1_$2_$3_HS_OBJS) $$($1_$2_$3_CMM_OBJS) $$($1_$2_$3_C_OBJS) $$($1_$2_$3_S_OBJS) $$($1_$2_EXTRA_OBJS)
 ifeq "$$($1_$2_BUILD_GHCI_LIB)" "YES"
 # Don't bother making ghci libs for bootstrapping packages
 ifneq "$4" "0"



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1696a5b7453e9d505ab7367ecf4d8c627be5000d

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1696a5b7453e9d505ab7367ecf4d8c627be5000d
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/20200802/3efc1cc6/attachment-0001.html>


More information about the ghc-commits mailing list