[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 3 commits: Optimise ELF linker (#23464)

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Tue Jun 27 23:57:21 UTC 2023



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


Commits:
315ccd6d by aadaa_fgtaa at 2023-06-27T19:57:05-04:00
Optimise ELF linker (#23464)

- cache last elements of `relTable`, `relaTable` and `symbolTables` in `ocInit_ELF`
- cache shndx table in ObjectCode
- run `checkProddableBlock` only with debug rts

- - - - -
a7e3278e by Rodrigo Mesquita at 2023-06-27T19:57:06-04:00
Configure MergeObjs supports response files rather than Ld

The previous configuration script to test whether Ld supported response
files was
* Incorrect (see #23542)
* Used, in practice, to check if the *merge objects tool* supported
  response files.

This commit modifies the macro to run the merge objects tool (rather
than Ld), using a response file, and checking the result with $NM

Fixes #23542

- - - - -
12f0fb5a by Ben Gamari at 2023-06-27T19:57:07-04:00
Rip out runtime linker/compiler checks

We used to choose flags to pass to the toolchain at runtime based on the
platform running GHC, and in this commit we drop all of those runtime
linker checks

Ultimately, this represents a change in policy: We no longer adapt at
runtime to the toolchain being used, but rather make final decisions
about the toolchain used at /configure time/
(we have deleted Note [Run-time linker info] altogether!).

This works towards the goal of having all toolchain configuration logic
living in the same place, which facilities the work towards a
runtime-retargetable GHC (see #19877).

As of this commit, the runtime linker/compiler logic was moved to
autoconf, but soon it, and the rest of the existing toolchain
configuration logic, will live in the standalone ghc-toolchain program
(see !9263)

In particular, what used to be done at runtime is now as follows:
* The flags -Wl,--no-as-needed for needed shared libs are configured
  into settings
* The flag -fstack-check is configured into settings
* The check for broken tables-next-to-code was outdated
* We use the configured c compiler by default as the assembler program
* We drop `asmOpts` because we already configure -Qunused-arguments flag
  into settings (see !10589)

Fixes #23562

Co-author: Rodrigo Mesquita (@alt-romes)

- - - - -


24 changed files:

- compiler/GHC/Driver/Backend.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Linker/ExtraObj.hs
- compiler/GHC/Settings.hs
- compiler/GHC/Settings/IO.hs
- compiler/GHC/SysTools.hs
- − compiler/GHC/SysTools/Info.hs
- compiler/GHC/SysTools/Tasks.hs
- compiler/ghc.cabal.in
- configure.ac
- distrib/configure.ac.in
- hadrian/bindist/Makefile
- hadrian/bindist/config.mk.in
- hadrian/cfg/system.config.in
- hadrian/src/Rules/Generate.hs
- − m4/fp_ld_supports_response_files.m4
- + m4/fp_link_supports_no_as_needed.m4
- + m4/fp_merge_objects_supports_response_files.m4
- m4/fptools_set_c_ld_flags.m4
- rts/Linker.c
- rts/LinkerInternals.h
- rts/linker/Elf.c


Changes:

=====================================
compiler/GHC/Driver/Backend.hs
=====================================
@@ -58,8 +58,6 @@ module GHC.Driver.Backend
    , DefunctionalizedCodeOutput(..)
      -- *** Back-end functions for assembly
    , DefunctionalizedPostHscPipeline(..)
-   , DefunctionalizedAssemblerProg(..)
-   , DefunctionalizedAssemblerInfoGetter(..)
      -- *** Other back-end functions
    , DefunctionalizedCDefs(..)
      -- ** Names of back ends (for API clients of version 9.4 or earlier)
@@ -94,8 +92,6 @@ module GHC.Driver.Backend
    , backendSupportsHpc
    , backendSupportsCImport
    , backendSupportsCExport
-   , backendAssemblerProg
-   , backendAssemblerInfoGetter
    , backendCDefs
    , backendCodeOutput
    , backendUseJSLinker
@@ -348,40 +344,6 @@ data PrimitiveImplementation
   deriving Show
 
 
--- | Names a function that runs the assembler, of this type:
---
--- > Logger -> DynFlags -> Platform -> [Option] -> IO ()
---
--- The functions so named are defined in "GHC.Driver.Pipeline.Execute".
-
-data DefunctionalizedAssemblerProg
-  = StandardAssemblerProg
-       -- ^ Use the standard system assembler
-  | JSAssemblerProg
-       -- ^ JS Backend compile to JS via Stg, and so does not use any assembler
-  | DarwinClangAssemblerProg
-       -- ^ If running on Darwin, use the assembler from the @clang@
-       -- toolchain.  Otherwise use the standard system assembler.
-
-
-
--- | Names a function that discover from what toolchain the assembler
--- is coming, of this type:
---
--- > Logger -> DynFlags -> Platform -> IO CompilerInfo
---
--- The functions so named are defined in "GHC.Driver.Pipeline.Execute".
-
-data DefunctionalizedAssemblerInfoGetter
-  = StandardAssemblerInfoGetter
-       -- ^ Interrogate the standard system assembler
-  | JSAssemblerInfoGetter
-       -- ^ If using the JS backend; return 'Emscripten'
-  | DarwinClangAssemblerInfoGetter
-       -- ^ If running on Darwin, return `Clang`; otherwise
-       -- interrogate the standard system assembler.
-
-
 -- | Names a function that generates code and writes the results to a
 --  file, of this type:
 --
@@ -767,45 +729,6 @@ backendSupportsCExport (Named JavaScript)  = True
 backendSupportsCExport (Named Interpreter) = False
 backendSupportsCExport (Named NoBackend)   = True
 
--- | This (defunctionalized) function runs the assembler
--- used on the code that is written by this back end.  A
--- program determined by a combination of back end,
--- `DynFlags`, and `Platform` is run with the given
--- `Option`s.
---
--- The function's type is
--- @
--- Logger -> DynFlags -> Platform -> [Option] -> IO ()
--- @
---
--- This field is usually defaulted.
-backendAssemblerProg :: Backend -> DefunctionalizedAssemblerProg
-backendAssemblerProg (Named NCG)  = StandardAssemblerProg
-backendAssemblerProg (Named LLVM) = DarwinClangAssemblerProg
-backendAssemblerProg (Named ViaC) = StandardAssemblerProg
-backendAssemblerProg (Named JavaScript)  = JSAssemblerProg
-backendAssemblerProg (Named Interpreter) = StandardAssemblerProg
-backendAssemblerProg (Named NoBackend)   = StandardAssemblerProg
-
--- | This (defunctionalized) function is used to retrieve
--- an enumeration value that characterizes the C/assembler
--- part of a toolchain.  The function caches the info in a
--- mutable variable that is part of the `DynFlags`.
---
--- The function's type is
--- @
--- Logger -> DynFlags -> Platform -> IO CompilerInfo
--- @
---
--- This field is usually defaulted.
-backendAssemblerInfoGetter :: Backend -> DefunctionalizedAssemblerInfoGetter
-backendAssemblerInfoGetter (Named NCG)         = StandardAssemblerInfoGetter
-backendAssemblerInfoGetter (Named LLVM)        = DarwinClangAssemblerInfoGetter
-backendAssemblerInfoGetter (Named ViaC)        = StandardAssemblerInfoGetter
-backendAssemblerInfoGetter (Named JavaScript)  = JSAssemblerInfoGetter
-backendAssemblerInfoGetter (Named Interpreter) = StandardAssemblerInfoGetter
-backendAssemblerInfoGetter (Named NoBackend)   = StandardAssemblerInfoGetter
-
 -- | When using this back end, it may be necessary or
 -- advisable to pass some `-D` options to a C compiler.
 -- This (defunctionalized) function produces those


=====================================
compiler/GHC/Driver/DynFlags.hs
=====================================
@@ -116,7 +116,6 @@ import Control.Monad.Trans.Class (lift)
 import Control.Monad.Trans.Except (ExceptT)
 import Control.Monad.Trans.Reader (ReaderT)
 import Control.Monad.Trans.Writer (WriterT)
-import Data.IORef
 import System.IO
 import System.IO.Error (catchIOError)
 import System.Environment (lookupEnv)
@@ -420,15 +419,6 @@ data DynFlags = DynFlags {
   avx512pf              :: Bool, -- Enable AVX-512 PreFetch Instructions.
   fma                   :: Bool, -- ^ Enable FMA instructions.
 
-  -- | Run-time linker information (what options we need, etc.)
-  rtldInfo              :: IORef (Maybe LinkerInfo),
-
-  -- | Run-time C compiler information
-  rtccInfo              :: IORef (Maybe CompilerInfo),
-
-  -- | Run-time assembler information
-  rtasmInfo              :: IORef (Maybe CompilerInfo),
-
   -- Constants used to control the amount of optimization done.
 
   -- | Max size, in bytes, of inline array allocations.
@@ -490,9 +480,6 @@ class ContainsDynFlags t where
 initDynFlags :: DynFlags -> IO DynFlags
 initDynFlags dflags = do
  let
- refRtldInfo <- newIORef Nothing
- refRtccInfo <- newIORef Nothing
- refRtasmInfo <- newIORef Nothing
  canUseUnicode <- do let enc = localeEncoding
                          str = "‘’"
                      (withCString enc str $ \cstr ->
@@ -514,9 +501,6 @@ initDynFlags dflags = do
         useColor      = useColor',
         canUseColor   = stderrSupportsAnsiColors,
         colScheme     = colScheme',
-        rtldInfo      = refRtldInfo,
-        rtccInfo      = refRtccInfo,
-        rtasmInfo     = refRtasmInfo,
         tmpDir        = TempDir tmp_dir
         }
 
@@ -695,9 +679,6 @@ defaultDynFlags mySettings =
         avx512f = False,
         avx512pf = False,
         fma = False,
-        rtldInfo = panic "defaultDynFlags: no rtldInfo",
-        rtccInfo = panic "defaultDynFlags: no rtccInfo",
-        rtasmInfo = panic "defaultDynFlags: no rtasmInfo",
 
         maxInlineAllocSize = 128,
         maxInlineMemcpyInsns = 32,


=====================================
compiler/GHC/Driver/Main.hs
=====================================
@@ -109,9 +109,6 @@ module GHC.Driver.Main
 
 import GHC.Prelude
 
-import GHC.Platform
-import GHC.Platform.Ways
-
 import GHC.Driver.Plugins
 import GHC.Driver.Session
 import GHC.Driver.Backend
@@ -345,41 +342,11 @@ initHscEnv mb_top_dir = do
   mySettings <- initSysTools top_dir
   dflags <- initDynFlags (defaultDynFlags mySettings)
   hsc_env <- newHscEnv top_dir dflags
-  checkBrokenTablesNextToCode (hsc_logger hsc_env) dflags
   setUnsafeGlobalDynFlags dflags
    -- c.f. DynFlags.parseDynamicFlagsFull, which
    -- creates DynFlags and sets the UnsafeGlobalDynFlags
   return hsc_env
 
--- | The binutils linker on ARM emits unnecessary R_ARM_COPY relocations which
--- breaks tables-next-to-code in dynamically linked modules. This
--- check should be more selective but there is currently no released
--- version where this bug is fixed.
--- See https://sourceware.org/bugzilla/show_bug.cgi?id=16177 and
--- https://gitlab.haskell.org/ghc/ghc/issues/4210#note_78333
-checkBrokenTablesNextToCode :: Logger -> DynFlags -> IO ()
-checkBrokenTablesNextToCode logger dflags = do
-  let invalidLdErr = "Tables-next-to-code not supported on ARM \
-                     \when using binutils ld (please see: \
-                     \https://sourceware.org/bugzilla/show_bug.cgi?id=16177)"
-  broken <- checkBrokenTablesNextToCode' logger dflags
-  when broken (panic invalidLdErr)
-
-checkBrokenTablesNextToCode' :: Logger -> DynFlags -> IO Bool
-checkBrokenTablesNextToCode' logger dflags
-  | not (isARM arch)               = return False
-  | ways dflags `hasNotWay` WayDyn = return False
-  | not tablesNextToCode           = return False
-  | otherwise                      = do
-    linkerInfo <- liftIO $ GHC.SysTools.getLinkerInfo logger dflags
-    case linkerInfo of
-      GnuLD _  -> return True
-      _        -> return False
-  where platform = targetPlatform dflags
-        arch = platformArch platform
-        tablesNextToCode = platformTablesNextToCode platform
-
-
 -- -----------------------------------------------------------------------------
 
 getDiagnostics :: Hsc (Messages GhcMessage)


=====================================
compiler/GHC/Driver/Pipeline/Execute.hs
=====================================
@@ -287,12 +287,6 @@ runAsPhase :: Bool -> PipeEnv -> HscEnv -> Maybe ModLocation -> FilePath -> IO F
 runAsPhase with_cpp pipe_env hsc_env location input_fn = do
         let dflags     = hsc_dflags   hsc_env
         let logger     = hsc_logger   hsc_env
-        let unit_env   = hsc_unit_env hsc_env
-        let platform   = ue_platform unit_env
-
-        -- LLVM from version 3.0 onwards doesn't support the OS X system
-        -- assembler, so we use clang as the assembler instead. (#5636)
-        let as_prog = applyAssemblerProg $ backendAssemblerProg (backend dflags)
 
         let cmdline_include_paths = includePaths dflags
         let pic_c_flags = picCCOpts dflags
@@ -310,9 +304,8 @@ runAsPhase with_cpp pipe_env hsc_env location input_fn = do
                                 includePathsQuoteImplicit cmdline_include_paths]
         let runAssembler inputFilename outputFilename
               = withAtomicRename outputFilename $ \temp_outputFilename ->
-                    as_prog
+                    runAs
                        logger dflags
-                       platform
                        (local_includes ++ global_includes
                        -- See Note [-fPIC for assembler]
                        ++ map GHC.SysTools.Option pic_c_flags
@@ -392,22 +385,6 @@ runForeignJsPhase pipe_env hsc_env _location input_fn = do
   embedJsFile logger dflags tmpfs unit_env input_fn output_fn
   return output_fn
 
-
-applyAssemblerProg
-    :: DefunctionalizedAssemblerProg
-    -> Logger -> DynFlags -> Platform -> [Option] -> IO ()
-applyAssemblerProg StandardAssemblerProg logger dflags _platform =
-    runAs logger dflags
-applyAssemblerProg JSAssemblerProg logger dflags _platform =
-    runEmscripten logger dflags
-applyAssemblerProg DarwinClangAssemblerProg logger dflags platform =
-    if platformOS platform == OSDarwin then
-        runClang logger dflags
-    else
-        runAs logger dflags
-
-
-
 runCcPhase :: Phase -> PipeEnv -> HscEnv -> Maybe ModLocation -> FilePath -> IO FilePath
 runCcPhase cc_phase pipe_env hsc_env location input_fn = do
   let dflags    = hsc_dflags hsc_env


=====================================
compiler/GHC/Linker/ExtraObj.hs
=====================================
@@ -12,7 +12,6 @@ module GHC.Linker.ExtraObj
    , mkNoteObjsToLinkIntoBinary
    , checkLinkInfo
    , getLinkInfo
-   , getCompilerInfo
    , ghcLinkInfoSectionName
    , ghcLinkInfoNoteName
    , platformSupportsSavingLinkOpts
@@ -40,10 +39,8 @@ import qualified GHC.Data.ShortText as ST
 
 import GHC.SysTools.Elf
 import GHC.SysTools.Tasks
-import GHC.SysTools.Info
 import GHC.Linker.Unit
 
-import Control.Monad.IO.Class
 import Control.Monad
 import Data.Maybe
 
@@ -52,7 +49,6 @@ mkExtraObj logger tmpfs dflags unit_state extn xs
  = do cFile <- newTempName logger tmpfs (tmpDir dflags) TFL_CurrentModule extn
       oFile <- newTempName logger tmpfs (tmpDir dflags) TFL_GhcSession "o"
       writeFile cFile xs
-      ccInfo <- liftIO $ getCompilerInfo logger dflags
       runCc Nothing logger tmpfs dflags
             ([Option        "-c",
               FileOption "" cFile,
@@ -60,7 +56,7 @@ mkExtraObj logger tmpfs dflags unit_state extn xs
               FileOption "" oFile]
               ++ if extn /= "s"
                     then cOpts
-                    else asmOpts ccInfo)
+                    else [])
       return oFile
     where
       -- Pass a different set of options to the C compiler depending one whether
@@ -70,14 +66,6 @@ mkExtraObj logger tmpfs dflags unit_state extn xs
                     ++ map (FileOption "-I" . ST.unpack)
                             (unitIncludeDirs $ unsafeLookupUnit unit_state rtsUnit)
 
-      -- When compiling assembler code, we drop the usual C options, and if the
-      -- compiler is Clang, we add an extra argument to tell Clang to ignore
-      -- unused command line options. See trac #11684.
-      asmOpts ccInfo =
-            if any (ccInfo ==) [Clang, AppleClang, AppleClang51]
-                then [Option "-Qunused-arguments"]
-                else []
-
 -- When linking a binary, we need to create a C main() function that
 -- starts everything off.  This used to be compiled statically as part
 -- of the RTS, but that made it hard to change the -rtsopts setting,


=====================================
compiler/GHC/Settings.hs
=====================================
@@ -19,7 +19,7 @@ module GHC.Settings
   , sGlobalPackageDatabasePath
   , sLdSupportsCompactUnwind
   , sLdSupportsFilelist
-  , sLdSupportsResponseFiles
+  , sMergeObjsSupportsResponseFiles
   , sLdIsGnuLd
   , sGccSupportsNoPie
   , sUseInplaceMinGW
@@ -88,7 +88,7 @@ data Settings = Settings
 data ToolSettings = ToolSettings
   { toolSettings_ldSupportsCompactUnwind :: Bool
   , toolSettings_ldSupportsFilelist      :: Bool
-  , toolSettings_ldSupportsResponseFiles :: Bool
+  , toolSettings_mergeObjsSupportsResponseFiles :: Bool
   , toolSettings_ldIsGnuLd               :: Bool
   , toolSettings_ccSupportsNoPie         :: Bool
   , toolSettings_useInplaceMinGW         :: Bool
@@ -191,8 +191,8 @@ sLdSupportsCompactUnwind :: Settings -> Bool
 sLdSupportsCompactUnwind = toolSettings_ldSupportsCompactUnwind . sToolSettings
 sLdSupportsFilelist :: Settings -> Bool
 sLdSupportsFilelist = toolSettings_ldSupportsFilelist . sToolSettings
-sLdSupportsResponseFiles :: Settings -> Bool
-sLdSupportsResponseFiles = toolSettings_ldSupportsResponseFiles . sToolSettings
+sMergeObjsSupportsResponseFiles :: Settings -> Bool
+sMergeObjsSupportsResponseFiles = toolSettings_mergeObjsSupportsResponseFiles . sToolSettings
 sLdIsGnuLd :: Settings -> Bool
 sLdIsGnuLd = toolSettings_ldIsGnuLd . sToolSettings
 sGccSupportsNoPie :: Settings -> Bool


=====================================
compiler/GHC/Settings/IO.hs
=====================================
@@ -104,7 +104,7 @@ initSettings top_dir = do
 
   ldSupportsCompactUnwind <- getBooleanSetting "ld supports compact unwind"
   ldSupportsFilelist      <- getBooleanSetting "ld supports filelist"
-  ldSupportsResponseFiles <- getBooleanSetting "ld supports response files"
+  mergeObjsSupportsResponseFiles <- getBooleanSetting "Merge objects supports response files"
   ldIsGnuLd               <- getBooleanSetting "ld is GNU ld"
   arSupportsDashL         <- getBooleanSetting "ar supports -L"
 
@@ -173,7 +173,7 @@ initSettings top_dir = do
     , sToolSettings = ToolSettings
       { toolSettings_ldSupportsCompactUnwind = ldSupportsCompactUnwind
       , toolSettings_ldSupportsFilelist      = ldSupportsFilelist
-      , toolSettings_ldSupportsResponseFiles = ldSupportsResponseFiles
+      , toolSettings_mergeObjsSupportsResponseFiles = mergeObjsSupportsResponseFiles
       , toolSettings_ldIsGnuLd               = ldIsGnuLd
       , toolSettings_ccSupportsNoPie         = gccSupportsNoPie
       , toolSettings_useInplaceMinGW         = useInplaceMinGW


=====================================
compiler/GHC/SysTools.hs
=====================================
@@ -17,7 +17,6 @@ module GHC.SysTools (
 
         -- * Interface to system tools
         module GHC.SysTools.Tasks,
-        module GHC.SysTools.Info,
 
         -- * Fast file copy
         copyFile,
@@ -35,8 +34,6 @@ import GHC.Prelude
 import GHC.Utils.Panic
 import GHC.Driver.Session
 
-import GHC.Linker.ExtraObj
-import GHC.SysTools.Info
 import GHC.SysTools.Tasks
 import GHC.SysTools.BaseDir
 import GHC.Settings.IO


=====================================
compiler/GHC/SysTools/Info.hs deleted
=====================================
@@ -1,243 +0,0 @@
-{-# LANGUAGE ScopedTypeVariables #-}
------------------------------------------------------------------------------
---
--- Compiler information functions
---
--- (c) The GHC Team 2017
---
------------------------------------------------------------------------------
-module GHC.SysTools.Info where
-
-import GHC.Utils.Exception
-import GHC.Utils.Error
-import GHC.Driver.Session
-import GHC.Utils.Outputable
-import GHC.Utils.Misc
-import GHC.Utils.Logger
-
-import Data.List ( isInfixOf, isPrefixOf )
-import Data.IORef
-
-import System.IO
-
-import GHC.Platform
-import GHC.Prelude
-
-import GHC.SysTools.Process
-
-{- Note [Run-time linker info]
-   ~~~~~~~~~~~~~~~~~~~~~~~~~~~
-See also: #5240, #6063, #10110
-
-Before 'runLink', we need to be sure to get the relevant information
-about the linker we're using at runtime to see if we need any extra
-options.
-
-Generally, the linker changing from what was detected at ./configure
-time has always been possible using -pgml, but on Linux it can happen
-'transparently' by installing packages like binutils-gold, which
-change what /usr/bin/ld actually points to.
-
-Clang vs GCC notes:
-
-For gcc, 'gcc -Wl,--version' gives a bunch of output about how to
-invoke the linker before the version information string. For 'clang',
-the version information for 'ld' is all that's output. For this
-reason, we typically need to slurp up all of the standard error output
-and look through it.
-
-Other notes:
-
-We cache the LinkerInfo inside DynFlags, since clients may link
-multiple times. The definition of LinkerInfo is there to avoid a
-circular dependency.
-
--}
-
-{- Note [ELF needed shared libs]
-   ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-Some distributions change the link editor's default handling of
-ELF DT_NEEDED tags to include only those shared objects that are
-needed to resolve undefined symbols. For Template Haskell we need
-the last temporary shared library also if it is not needed for the
-currently linked temporary shared library. We specify --no-as-needed
-to override the default. This flag exists in GNU ld and GNU gold.
-
-The flag is only needed on ELF systems. On Windows (PE) and Mac OS X
-(Mach-O) the flag is not needed.
-
--}
-
-neededLinkArgs :: LinkerInfo -> [Option]
-neededLinkArgs (GnuLD o)     = o
-neededLinkArgs (Mold o)      = o
-neededLinkArgs (GnuGold o)   = o
-neededLinkArgs (LlvmLLD o)   = o
-neededLinkArgs (DarwinLD o)  = o
-neededLinkArgs (SolarisLD o) = o
-neededLinkArgs (AixLD o)     = o
-neededLinkArgs UnknownLD     = []
-
--- Grab linker info and cache it in DynFlags.
-getLinkerInfo :: Logger -> DynFlags -> IO LinkerInfo
-getLinkerInfo logger dflags = do
-  info <- readIORef (rtldInfo dflags)
-  case info of
-    Just v  -> return v
-    Nothing -> do
-      v <- getLinkerInfo' logger dflags
-      writeIORef (rtldInfo dflags) (Just v)
-      return v
-
--- See Note [Run-time linker info].
-getLinkerInfo' :: Logger -> DynFlags -> IO LinkerInfo
-getLinkerInfo' logger dflags = do
-  let platform = targetPlatform dflags
-      os = platformOS platform
-      (pgm,args0) = pgm_l dflags
-      args1       = map Option (getOpts dflags opt_l)
-      args2       = args0 ++ args1
-      args3       = filter notNull (map showOpt args2)
-
-      -- Try to grab the info from the process output.
-      parseLinkerInfo stdo _stde _exitc
-        | any ("GNU ld" `isPrefixOf`) stdo =
-          -- Set DT_NEEDED for all shared libraries. #10110.
-          return (GnuLD $ map Option [-- ELF specific flag
-                                      -- see Note [ELF needed shared libs]
-                                      "-Wl,--no-as-needed"])
-
-        | any ("mold" `isPrefixOf`) stdo =
-          return (Mold $ map Option [ --see Note [ELF needed shared libs]
-                                      "-Wl,--no-as-needed"])
-
-        | any ("GNU gold" `isPrefixOf`) stdo =
-          -- GNU gold only needs --no-as-needed. #10110.
-          -- ELF specific flag, see Note [ELF needed shared libs]
-          return (GnuGold [Option "-Wl,--no-as-needed"])
-
-        | any (\line -> "LLD" `isPrefixOf` line || "LLD" `elem` words line) stdo =
-          return (LlvmLLD $ map Option [ --see Note [ELF needed shared libs]
-                                        "-Wl,--no-as-needed" | osElfTarget os || os == OSMinGW32 ])
-
-         -- Unknown linker.
-        | otherwise = fail "invalid --version output, or linker is unsupported"
-
-  -- Process the executable call
-  catchIO (
-    case os of
-      OSSolaris2 ->
-        -- Solaris uses its own Solaris linker. Even all
-        -- GNU C are recommended to configure with Solaris
-        -- linker instead of using GNU binutils linker. Also
-        -- all GCC distributed with Solaris follows this rule
-        -- precisely so we assume here, the Solaris linker is
-        -- used.
-        return $ SolarisLD []
-      OSAIX ->
-        -- IBM AIX uses its own non-binutils linker as well
-        return $ AixLD []
-      OSDarwin ->
-        -- Darwin has neither GNU Gold or GNU LD, but a strange linker
-        -- that doesn't support --version. We can just assume that's
-        -- what we're using.
-        return $ DarwinLD []
-      OSMinGW32 ->
-        -- GHC doesn't support anything but GNU ld on Windows anyway.
-        -- Process creation is also fairly expensive on win32, so
-        -- we short-circuit here.
-        return $ GnuLD $ map Option
-          [ -- Emit stack checks
-            -- See Note [Windows stack allocations]
-           "-fstack-check"
-          ]
-      _ -> do
-        -- In practice, we use the compiler as the linker here. Pass
-        -- -Wl,--version to get linker version info.
-        (exitc, stdo, stde) <- readProcessEnvWithExitCode pgm
-                               (["-Wl,--version"] ++ args3)
-                               c_locale_env
-        -- Split the output by lines to make certain kinds
-        -- of processing easier. In particular, 'clang' and 'gcc'
-        -- have slightly different outputs for '-Wl,--version', but
-        -- it's still easy to figure out.
-        parseLinkerInfo (lines stdo) (lines stde) exitc
-    )
-    (\err -> do
-        debugTraceMsg logger 2
-            (text "Error (figuring out linker information):" <+>
-             text (show err))
-        errorMsg logger $ hang (text "Warning:") 9 $
-          text "Couldn't figure out linker information!" $$
-          text "Make sure you're using GNU ld, GNU gold" <+>
-          text "or the built in OS X linker, etc."
-        return UnknownLD
-    )
-
--- | Grab compiler info and cache it in DynFlags.
-getCompilerInfo :: Logger -> DynFlags -> IO CompilerInfo
-getCompilerInfo logger dflags = do
-  info <- readIORef (rtccInfo dflags)
-  case info of
-    Just v  -> return v
-    Nothing -> do
-      let pgm = pgm_c dflags
-      v <- getCompilerInfo' logger pgm
-      writeIORef (rtccInfo dflags) (Just v)
-      return v
-
--- | Grab assembler info and cache it in DynFlags.
-getAssemblerInfo :: Logger -> DynFlags -> IO CompilerInfo
-getAssemblerInfo logger dflags = do
-  info <- readIORef (rtasmInfo dflags)
-  case info of
-    Just v  -> return v
-    Nothing -> do
-      let (pgm, _) = pgm_a dflags
-      v <- getCompilerInfo' logger pgm
-      writeIORef (rtasmInfo dflags) (Just v)
-      return v
-
--- See Note [Run-time linker info].
-getCompilerInfo' :: Logger -> String -> IO CompilerInfo
-getCompilerInfo' logger pgm = do
-  let -- Try to grab the info from the process output.
-      parseCompilerInfo _stdo stde _exitc
-        -- Regular GCC
-        | any ("gcc version" `isInfixOf`) stde =
-          return GCC
-        -- Regular clang
-        | any ("clang version" `isInfixOf`) stde =
-          return Clang
-        -- FreeBSD clang
-        | any ("FreeBSD clang version" `isInfixOf`) stde =
-          return Clang
-        -- Xcode 5.1 clang
-        | any ("Apple LLVM version 5.1" `isPrefixOf`) stde =
-          return AppleClang51
-        -- Xcode 5 clang
-        | any ("Apple LLVM version" `isPrefixOf`) stde =
-          return AppleClang
-        -- Xcode 4.1 clang
-        | any ("Apple clang version" `isPrefixOf`) stde =
-          return AppleClang
-         -- Unknown compiler.
-        | otherwise = fail $ "invalid -v output, or compiler is unsupported (" ++ pgm ++ "): " ++ unlines stde
-
-  -- Process the executable call
-  catchIO (do
-      (exitc, stdo, stde) <-
-          readProcessEnvWithExitCode pgm ["-v"] c_locale_env
-      -- Split the output by lines to make certain kinds
-      -- of processing easier.
-      parseCompilerInfo (lines stdo) (lines stde) exitc
-      )
-      (\err -> do
-          debugTraceMsg logger 2
-              (text "Error (figuring out C compiler information):" <+>
-               text (show err))
-          errorMsg logger $ hang (text "Warning:") 9 $
-            text "Couldn't figure out C compiler information!" $$
-            text "Make sure you're using GNU gcc, or clang"
-          return UnknownCC
-      )


=====================================
compiler/GHC/SysTools/Tasks.hs
=====================================
@@ -19,7 +19,6 @@ import GHC.CmmToLlvm.Config (LlvmVersion, llvmVersionStr, supportedLlvmVersionUp
 import GHC.Settings
 
 import GHC.SysTools.Process
-import GHC.SysTools.Info
 
 import GHC.Driver.Session
 
@@ -278,15 +277,12 @@ figureLlvmVersion logger dflags = traceSystoolCommand logger "llc" $ do
 
 runLink :: Logger -> TmpFs -> DynFlags -> [Option] -> IO ()
 runLink logger tmpfs dflags args = traceSystoolCommand logger "linker" $ do
-  -- See Note [Run-time linker info]
-  --
   -- `-optl` args come at the end, so that later `-l` options
   -- given there manually can fill in symbols needed by
   -- Haskell libraries coming in via `args`.
-  linkargs <- neededLinkArgs `fmap` getLinkerInfo logger dflags
   let (p,args0) = pgm_l dflags
       optl_args = map Option (getOpts dflags opt_l)
-      args2     = args0 ++ linkargs ++ args ++ optl_args
+      args2     = args0 ++ args ++ optl_args
   mb_env <- getGccEnv args2
   runSomethingResponseFile logger tmpfs dflags ld_filter "Linker" p args2 mb_env
   where
@@ -349,7 +345,7 @@ runMergeObjects logger tmpfs dflags args =
             , "does not support object merging." ]
         optl_args = map Option (getOpts dflags opt_lm)
         args2     = args0 ++ args ++ optl_args
-    if toolSettings_ldSupportsResponseFiles (toolSettings dflags)
+    if toolSettings_mergeObjsSupportsResponseFiles (toolSettings dflags)
       then do
         mb_env <- getGccEnv args2
         runSomethingResponseFile logger tmpfs dflags id "Merge objects" p args2 mb_env


=====================================
compiler/ghc.cabal.in
=====================================
@@ -715,7 +715,6 @@ Library
         GHC.SysTools.BaseDir
         GHC.SysTools.Cpp
         GHC.SysTools.Elf
-        GHC.SysTools.Info
         GHC.SysTools.Process
         GHC.SysTools.Tasks
         GHC.SysTools.Terminal


=====================================
configure.ac
=====================================
@@ -648,7 +648,7 @@ FP_LD_NO_FIXUP_CHAINS([build], [CONF_GCC_LINKER_OPTS_STAGE0])
 FP_LD_NO_FIXUP_CHAINS([target], [CONF_GCC_LINKER_OPTS_STAGE1])
 FP_LD_NO_FIXUP_CHAINS([target], [CONF_GCC_LINKER_OPTS_STAGE2])
 
-FP_LD_SUPPORTS_RESPONSE_FILES
+FP_MERGE_OBJECTS_SUPPORTS_RESPONSE_FILES
 
 GHC_LLVM_TARGET_SET_VAR
 # we intend to pass trough --targets to llvm as is.


=====================================
distrib/configure.ac.in
=====================================
@@ -176,7 +176,7 @@ FP_LD_NO_FIXUP_CHAINS([build], [CONF_GCC_LINKER_OPTS_STAGE0])
 FP_LD_NO_FIXUP_CHAINS([target], [CONF_GCC_LINKER_OPTS_STAGE1])
 FP_LD_NO_FIXUP_CHAINS([target], [CONF_GCC_LINKER_OPTS_STAGE2])
 
-FP_LD_SUPPORTS_RESPONSE_FILES
+FP_MERGE_OBJECTS_SUPPORTS_RESPONSE_FILES
 
 AC_SUBST(CONF_CC_OPTS_STAGE0)
 AC_SUBST(CONF_CC_OPTS_STAGE1)


=====================================
hadrian/bindist/Makefile
=====================================
@@ -91,10 +91,10 @@ lib/settings : config.mk
 	@echo ',("ld flags", "$(SettingsLdFlags)")' >> $@
 	@echo ',("ld supports compact unwind", "$(LdHasNoCompactUnwind)")' >> $@
 	@echo ',("ld supports filelist", "$(LdHasFilelist)")' >> $@
-	@echo ',("ld supports response files", "$(LdSupportsResponseFiles)")' >> $@
 	@echo ',("ld is GNU ld", "$(LdIsGNULd)")' >> $@
 	@echo ',("Merge objects command", "$(SettingsMergeObjectsCommand)")' >> $@
 	@echo ',("Merge objects flags", "$(SettingsMergeObjectsFlags)")' >> $@
+	@echo ',("Merge objects supports response files", "$(MergeObjsSupportsResponseFiles)")' >> $@
 	@echo ',("ar command", "$(SettingsArCommand)")' >> $@
 	@echo ',("ar flags", "$(ArArgs)")' >> $@
 	@echo ',("ar supports at file", "$(ArSupportsAtFile)")' >> $@


=====================================
hadrian/bindist/config.mk.in
=====================================
@@ -235,7 +235,7 @@ GhcRtsWithLibdw=$(strip $(if $(filter $(TargetArch_CPP),i386 x86_64 s390x), at UseL
 # See Note [tooldir: How GHC finds mingw on Windows]
 
 LdHasFilelist = @LdHasFilelist@
-LdSupportsResponseFiles = @LdSupportsResponseFiles@
+MergeObjsSupportsResponseFiles = @MergeObjsSupportsResponseFiles@
 LdHasBuildId = @LdHasBuildId@
 LdHasFilelist = @LdHasFilelist@
 LdIsGNULd = @LdIsGNULd@


=====================================
hadrian/cfg/system.config.in
=====================================
@@ -139,7 +139,7 @@ conf-merge-objects-args-stage3  = @MergeObjsArgs@
 
 ld-has-no-compact-unwind = @LdHasNoCompactUnwind@
 ld-has-filelist = @LdHasFilelist@
-ld-supports-response-files = @LdSupportsResponseFiles@
+merge-objs-supports-response-files = @MergeObjsSupportsResponseFiles@
 ld-is-gnu-ld = @LdIsGNULd@
 ar-args = @ArArgs@
 


=====================================
hadrian/src/Rules/Generate.hs
=====================================
@@ -450,10 +450,10 @@ generateSettings = do
         , ("ld flags", expr $ settingsFileSetting SettingsFileSetting_LdFlags)
         , ("ld supports compact unwind", expr $ lookupSystemConfig "ld-has-no-compact-unwind")
         , ("ld supports filelist", expr $ lookupSystemConfig "ld-has-filelist")
-        , ("ld supports response files", expr $ lookupSystemConfig "ld-supports-response-files")
         , ("ld is GNU ld", expr $ lookupSystemConfig "ld-is-gnu-ld")
         , ("Merge objects command", expr $ settingsFileSetting SettingsFileSetting_MergeObjectsCommand)
         , ("Merge objects flags", expr $ settingsFileSetting SettingsFileSetting_MergeObjectsFlags)
+        , ("Merge objects supports response files", expr $ lookupSystemConfig "merge-objs-supports-response-files")
         , ("ar command", expr $ settingsFileSetting SettingsFileSetting_ArCommand)
         , ("ar flags", expr $ lookupSystemConfig "ar-args")
         , ("ar supports at file", expr $ yesNo <$> flag ArSupportsAtFile)


=====================================
m4/fp_ld_supports_response_files.m4 deleted
=====================================
@@ -1,19 +0,0 @@
-# FP_LD_SUPPORTS_RESPONSE_FILES
-# --------------------
-# See if whether we are using a version of ld which supports response files.
-AC_DEFUN([FP_LD_SUPPORTS_RESPONSE_FILES], [
-    AC_MSG_CHECKING([whether $LD supports response files])
-    echo 'int main(void) {return 0;}' > conftest.c
-    "$CC" -c -o conftest.o conftest.c > /dev/null 2>&1
-    printf -- "-o\nconftest\nconftest.o\n" > args.txt
-    if "$LD" -shared @args.txt > /dev/null 2>&1 || "$LD" -dylib @args.txt > /dev/null 2>&1
-    then
-        LdSupportsResponseFiles=YES
-        AC_MSG_RESULT([yes])
-    else
-        LdSupportsResponseFiles=NO
-        AC_MSG_RESULT([no])
-    fi
-    rm -f conftest.c conftest args.txt
-    AC_SUBST(LdSupportsResponseFiles)
-])


=====================================
m4/fp_link_supports_no_as_needed.m4
=====================================
@@ -0,0 +1,33 @@
+# FP_LINK_SUPPORTS_NO_AS_NEEDED
+# ----------------------------------
+# Set the Cc linker flag -Wl,--no-as-needed if it is supported
+# $1 is the name of the linker flags variable when linking with gcc
+# See also Note [ELF needed shared libs]
+AC_DEFUN([FP_LINK_SUPPORTS_NO_AS_NEEDED],
+[
+    AC_MSG_CHECKING([whether Cc linker supports -Wl,--no-as-needed])
+    echo 'int f(int a) {return 2*a;}' > conftest.a.c
+    echo 'int f(int a); int main(int argc, char **argv) {return f(0);}' > conftest.b.c
+    $CC -c -o conftest.a.o conftest.a.c > /dev/null 2>&1
+    $CC -c -o conftest.b.o conftest.b.c > /dev/null 2>&1
+    if "$CC" "$$1" -Wl,--no-as-needed -o conftest conftest.a.o conftest.b.o > /dev/null 2>&1
+    then
+        $1="$$1 -Wl,--no-as-needed"
+        AC_MSG_RESULT([yes])
+    else
+        AC_MSG_RESULT([no])
+    fi
+    rm -f conftest*
+])
+
+# Note [ELF needed shared libs]
+# ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+# Some distributions change the link editor's default handling of
+# ELF DT_NEEDED tags to include only those shared objects that are
+# needed to resolve undefined symbols. For Template Haskell we need
+# the last temporary shared library also if it is not needed for the
+# currently linked temporary shared library. We specify --no-as-needed
+# to override the default. This flag exists in GNU ld and GNU gold.
+#
+# The flag is only needed on ELF systems. On Windows (PE) and Mac OS X
+# (Mach-O) the flag is not needed.


=====================================
m4/fp_merge_objects_supports_response_files.m4
=====================================
@@ -0,0 +1,22 @@
+# FP_MERGE_OBJECTS_SUPPORTS_RESPONSE_FILES
+# --------------------
+# See if whether we are using a version of the merge objects tool which supports response files.
+AC_DEFUN([FP_MERGE_OBJECTS_SUPPORTS_RESPONSE_FILES], [
+    AC_MSG_CHECKING([whether $LD supports response files])
+    echo 'int funA(int x) {return x;}' > conftesta.c
+    echo 'int funB(int x) {return x;}' > conftestb.c
+    "$CC" -c -o conftesta.o conftesta.c > /dev/null 2>&1
+    "$CC" -c -o conftestb.o conftestb.c > /dev/null 2>&1
+    printf -- "-o\nconftest.o\nconftesta.o\nconftestb.o\n" > args.txt
+    "$MergeObjsCmd" "$MergeObjsArgs" @args.txt > /dev/null 2>&1
+    if ("$NM" conftest.o | grep "funA" > /dev/null 2>&1) && ("$NM" conftest.o | grep "funB" > /dev/null 2>&1)
+    then
+        MergeObjsSupportsResponseFiles=YES
+        AC_MSG_RESULT([yes])
+    else
+        MergeObjsSupportsResponseFiles=NO
+        AC_MSG_RESULT([no])
+    fi
+    rm -f conftesta.c conftestb.c conftesta.o conftestb.o conftest.o args.txt
+    AC_SUBST(MergeObjsSupportsResponseFiles)
+])


=====================================
m4/fptools_set_c_ld_flags.m4
=====================================
@@ -17,6 +17,21 @@ AC_DEFUN([FPTOOLS_SET_C_LD_FLAGS],
         ;;
     esac
 
+    # See Note [ELF needed shared libs]
+    case $$1 in
+    *-linux|*-freebsd*)
+        FP_LINK_SUPPORTS_NO_AS_NEEDED([$3])
+        ;;
+    esac
+
+    # Emit stack checks
+    # See Note [Windows stack allocations]
+    case $$1 in
+    *-mingw32*)
+        $3="$$3 -fstack-check"
+        ;;
+    esac
+
     case $$1 in
     i386-unknown-mingw32)
         $2="$$2 -march=i686"


=====================================
rts/Linker.c
=====================================
@@ -1379,6 +1379,10 @@ mkOc( ObjectType type, pathchar *path, char *image, int imageSize,
    oc->rx_m32 = m32_allocator_new(true);
 #endif
 
+#if defined(OBJFORMAT_ELF) && defined(SHN_XINDEX)
+   oc->shndx_table = SHNDX_TABLE_UNINIT;
+#endif
+
    oc->nc_ranges = NULL;
    oc->dlopen_handle = NULL;
 


=====================================
rts/LinkerInternals.h
=====================================
@@ -360,6 +360,15 @@ struct _ObjectCode {
     m32_allocator *rw_m32, *rx_m32;
 #endif
 
+#if defined(OBJFORMAT_ELF) && defined(SHN_XINDEX)
+    /* Cached address of ELF's shndx table, or SHNDX_TABLE_UNINIT if not
+     * initialized yet. It would be better to put it info ELF-specific
+     * ObjectCodeFormatInfo, but unfortunately shndx table is needed in
+     * ocVerifyImage_ELF which runs before ObjectCodeFormatInfo is
+     * initialized by ocInit_ELF. */
+    Elf_Word *shndx_table;
+#endif
+
     /*
      * The following are only valid if .type == DYNAMIC_OBJECT
      */
@@ -371,6 +380,15 @@ struct _ObjectCode {
     NativeCodeRange *nc_ranges;
 };
 
+#if defined(OBJFORMAT_ELF) && defined(SHN_XINDEX)
+/* We cannot simply use NULL to signal uninitialised shndx_table because NULL
+ * is valid return value of get_shndx_table. Thus SHNDX_TABLE_UNINIT is defined
+ * as the address of global variable shndx_table_uninit_label, defined in
+ * rts/linker/Elf.c, which is definitely unequal to any heap-allocated address */
+extern Elf_Word shndx_table_uninit_label;
+#define SHNDX_TABLE_UNINIT (&shndx_table_uninit_label)
+#endif
+
 #define OC_INFORMATIVE_FILENAME(OC)             \
     ( (OC)->archiveMemberName ?                 \
       (OC)->archiveMemberName :                 \


=====================================
rts/linker/Elf.c
=====================================
@@ -132,6 +132,11 @@
 
 */
 
+#if defined(SHN_XINDEX)
+/* global variable which address is used to signal an uninitialised shndx_table */
+Elf_Word shndx_table_uninit_label = 0;
+#endif
+
 static Elf_Word elf_shnum(Elf_Ehdr* ehdr)
 {
    Elf_Shdr* shdr = (Elf_Shdr*) ((char*)ehdr + ehdr->e_shoff);
@@ -154,16 +159,22 @@ static Elf_Word elf_shstrndx(Elf_Ehdr* ehdr)
 
 #if defined(SHN_XINDEX)
 static Elf_Word*
-get_shndx_table(Elf_Ehdr* ehdr)
+get_shndx_table(ObjectCode* oc)
 {
+   if (RTS_LIKELY(oc->shndx_table != SHNDX_TABLE_UNINIT)) {
+      return oc->shndx_table;
+   }
+
    Elf_Word  i;
-   char*     ehdrC    = (char*)ehdr;
+   char*     ehdrC    = oc->image;
+   Elf_Ehdr* ehdr     = (Elf_Ehdr*)ehdrC;
    Elf_Shdr* shdr     = (Elf_Shdr*) (ehdrC + ehdr->e_shoff);
    const Elf_Word shnum = elf_shnum(ehdr);
 
    for (i = 0; i < shnum; i++) {
      if (shdr[i].sh_type == SHT_SYMTAB_SHNDX) {
-       return (Elf32_Word*)(ehdrC + shdr[i].sh_offset);
+       oc->shndx_table = (Elf32_Word*)(ehdrC + shdr[i].sh_offset);
+       return oc->shndx_table;
      }
    }
    return NULL;
@@ -193,6 +204,10 @@ ocInit_ELF(ObjectCode * oc)
 
     oc->n_sections = elf_shnum(oc->info->elfHeader);
 
+    ElfRelocationTable *relTableLast = NULL;
+    ElfRelocationATable *relaTableLast = NULL;
+    ElfSymbolTable *symbolTablesLast = NULL;
+
     /* get the symbol table(s) */
     for(int i=0; i < oc->n_sections; i++) {
         if(SHT_REL  == oc->info->sectionHeader[i].sh_type) {
@@ -210,12 +225,12 @@ ocInit_ELF(ObjectCode * oc)
 
             relTab->sectionHeader      = &oc->info->sectionHeader[i];
 
-            if(oc->info->relTable == NULL) {
+            if(relTableLast == NULL) {
                 oc->info->relTable = relTab;
+                relTableLast = relTab;
             } else {
-                ElfRelocationTable * tail = oc->info->relTable;
-                while(tail->next != NULL) tail = tail->next;
-                tail->next = relTab;
+                relTableLast->next = relTab;
+                relTableLast = relTab;
             }
 
         } else if(SHT_RELA == oc->info->sectionHeader[i].sh_type) {
@@ -233,12 +248,12 @@ ocInit_ELF(ObjectCode * oc)
 
             relTab->sectionHeader      = &oc->info->sectionHeader[i];
 
-            if(oc->info->relaTable == NULL) {
+            if(relaTableLast == NULL) {
                 oc->info->relaTable = relTab;
+                relaTableLast = relTab;
             } else {
-                ElfRelocationATable * tail = oc->info->relaTable;
-                while(tail->next != NULL) tail = tail->next;
-                tail->next = relTab;
+                relaTableLast->next = relTab;
+                relaTableLast = relTab;
             }
 
         } else if(SHT_SYMTAB == oc->info->sectionHeader[i].sh_type) {
@@ -279,12 +294,12 @@ ocInit_ELF(ObjectCode * oc)
             }
 
             /* append the ElfSymbolTable */
-            if(oc->info->symbolTables == NULL) {
+            if(symbolTablesLast == NULL) {
                 oc->info->symbolTables = symTab;
+                symbolTablesLast = symTab;
             } else {
-                ElfSymbolTable * tail = oc->info->symbolTables;
-                while(tail->next != NULL) tail = tail->next;
-                tail->next = symTab;
+                symbolTablesLast->next = symTab;
+                symbolTablesLast = symTab;
             }
         }
     }
@@ -329,6 +344,9 @@ ocDeinit_ELF(ObjectCode * oc)
 
         stgFree(oc->info);
         oc->info = NULL;
+#if defined(SHN_XINDEX)
+        oc->shndx_table = SHNDX_TABLE_UNINIT;
+#endif
     }
 }
 
@@ -532,7 +550,7 @@ ocVerifyImage_ELF ( ObjectCode* oc )
       IF_DEBUG(linker_verbose,debugBelch("   no normal string tables (potentially, but not necessarily a problem)\n"));
    }
 #if defined(SHN_XINDEX)
-   Elf_Word* shndxTable = get_shndx_table(ehdr);
+   Elf_Word* shndxTable = get_shndx_table(oc);
 #endif
    nsymtabs = 0;
    IF_DEBUG(linker_verbose,debugBelch( "Symbol tables\n" ));
@@ -683,7 +701,7 @@ ocGetNames_ELF ( ObjectCode* oc )
    Elf_Shdr* shdr     = (Elf_Shdr*) (ehdrC + ehdr->e_shoff);
    Section * sections;
 #if defined(SHN_XINDEX)
-   Elf_Word* shndxTable = get_shndx_table(ehdr);
+   Elf_Word* shndxTable = get_shndx_table(oc);
 #endif
    const Elf_Word shnum = elf_shnum(ehdr);
 
@@ -1251,7 +1269,11 @@ do_Elf_Rel_relocations ( ObjectCode* oc, char* ehdrC,
        IF_DEBUG(linker_verbose,
                 debugBelch("Reloc: P = %p   S = %p   A = %p   type=%d\n",
                            (void*)P, (void*)S, (void*)A, reloc_type ));
+#if defined(DEBUG)
        checkProddableBlock ( oc, pP, sizeof(Elf_Word) );
+#else
+       (void) pP; /* suppress unused varialbe warning in non-debug build */
+#endif
 
 #if defined(i386_HOST_ARCH)
        value = S + A;
@@ -1555,7 +1577,7 @@ do_Elf_Rela_relocations ( ObjectCode* oc, char* ehdrC,
    int strtab_shndx = shdr[symtab_shndx].sh_link;
    int target_shndx = shdr[shnum].sh_info;
 #if defined(SHN_XINDEX)
-   Elf_Word* shndx_table = get_shndx_table((Elf_Ehdr*)ehdrC);
+   Elf_Word* shndx_table = get_shndx_table(oc);
 #endif
 #if defined(DEBUG) || defined(powerpc_HOST_ARCH) || defined(x86_64_HOST_ARCH)
    /* This #if def only serves to avoid unused-var warnings. */
@@ -1657,7 +1679,7 @@ do_Elf_Rela_relocations ( ObjectCode* oc, char* ehdrC,
          IF_DEBUG(linker_verbose,debugBelch("`%s' resolves to %p\n", symbol, (void*)S));
       }
 
-#if defined(DEBUG) || defined(powerpc_HOST_ARCH) || defined(x86_64_HOST_ARCH)
+#if defined(DEBUG)
       IF_DEBUG(linker_verbose,debugBelch("Reloc: P = %p   S = %p   A = %p\n",
                                          (void*)P, (void*)S, (void*)A ));
       checkProddableBlock(oc, (void*)P, sizeof(Elf_Word));
@@ -1920,7 +1942,7 @@ ocResolve_ELF ( ObjectCode* oc )
    const Elf_Word shnum = elf_shnum(ehdr);
 
 #if defined(SHN_XINDEX)
-    Elf_Word* shndxTable = get_shndx_table(ehdr);
+    Elf_Word* shndxTable = get_shndx_table(oc);
 #endif
 
     /* resolve section symbols



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a4d21106da0864fb79fe8c99eaa7a6c2c8d7ca78...12f0fb5afa382e1da45d4e8dd3b3a10c353fde24

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a4d21106da0864fb79fe8c99eaa7a6c2c8d7ca78...12f0fb5afa382e1da45d4e8dd3b3a10c353fde24
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/20230627/f40a1864/attachment-0001.html>


More information about the ghc-commits mailing list