[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 3 commits: linker: add --optimistic-linking flag

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Tue Oct 22 08:28:20 UTC 2024



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


Commits:
867e6115 by doyougnu at 2024-10-22T04:28:09-04:00
linker: add --optimistic-linking flag

This patch adds:

- the --optimistic-linking flag which binds unknown symbols in the
runtime linker to 0xDEADBEEF instead of exiting with failure

- The test T25240 which tests these flags using dead code in the FFI system.

- closes #25240

This patch is part of the upstreaming haskell.nix patches project.

- - - - -
0c6fb1f8 by doyougnu at 2024-10-22T04:28:09-04:00
ghc-internal: hide linkerOptimistic in MiscFlags

- - - - -
73e71758 by Cheng Shao at 2024-10-22T04:28:10-04:00
hadrian: fix bindist executable wrapper logic for cross targets

This commit fixes an oversight of hadrian wrapper generation logic:
when doing cross compilation, `wrapper` is called on executable names
with cross prefix, therefore we must use `isSuffixOf` when matching to
take the cross prefix into account. Also add missing cross prefix to
ghci wrapper content and fix hsc2hs wrapper logic.

- - - - -


21 changed files:

- docs/users_guide/9.14.1-notes.rst
- docs/users_guide/runtime_control.rst
- hadrian/bindist/Makefile
- hadrian/src/Rules/BinaryDist.hs
- libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc
- rts/Linker.c
- rts/RtsFlags.c
- rts/include/rts/Flags.h
- rts/linker/elf_got.c
- + testsuite/tests/ghci/linking/T25240/Makefile
- + testsuite/tests/ghci/linking/T25240/T25240.hs
- + testsuite/tests/ghci/linking/T25240/T25240.stderr
- + testsuite/tests/ghci/linking/T25240/T25240a.hs
- + testsuite/tests/ghci/linking/T25240/all.T
- testsuite/tests/ghci/should_run/T18064.stderr
- testsuite/tests/rts/linker/T11223/T11223_link_order_a_b_2_fail.stderr
- testsuite/tests/rts/linker/T11223/T11223_link_order_a_b_2_fail.stderr-ws-32-mingw32
- testsuite/tests/rts/linker/T11223/T11223_link_order_a_b_2_fail.stderr-ws-64-mingw32
- testsuite/tests/rts/linker/T11223/T11223_simple_duplicate_lib.stderr
- testsuite/tests/rts/linker/T11223/T11223_simple_duplicate_lib.stderr-ws-32-mingw32
- testsuite/tests/rts/linker/T11223/T11223_simple_duplicate_lib.stderr-ws-64-mingw32


Changes:

=====================================
docs/users_guide/9.14.1-notes.rst
=====================================
@@ -29,6 +29,10 @@ GHCi
 Runtime system
 ~~~~~~~~~~~~~~
 
+- Add new runtime flag :rts-flag:`--optimistic-linking` which instructs the
+  runtime linker to continue in the presence of unknown symbols. By default this
+  flag is not passed, preserving previous behavior.
+
 Cmm
 ~~~
 


=====================================
docs/users_guide/runtime_control.rst
=====================================
@@ -397,6 +397,11 @@ Miscellaneous RTS options
     heap larger than 1T. ``-xr`` is a no-op if GHC is configured with
     ``--disable-large-address-space`` or if the platform is 32-bit.
 
+.. rts-flag:: --optimistic-linking
+
+    If given, instruct the runtime linker to try to continue linking in the
+    presence of an unresolved symbol.
+
 .. _rts-options-gc:
 
 RTS options to control the garbage collector


=====================================
hadrian/bindist/Makefile
=====================================
@@ -243,7 +243,7 @@ install_wrappers: install_bin_libdir install_hsc2hs_wrapper
 .PHONY: install_hsc2hs_wrapper
 install_hsc2hs_wrapper:
 	@echo Copying hsc2hs wrapper
-	cp mk/hsc2hs wrappers/hsc2hs-ghc-$(ProjectVersion)
+	cp mk/hsc2hs wrappers/$(CrossCompilePrefix)hsc2hs-ghc-$(ProjectVersion)
 
 PKG_CONFS = $(shell find "$(DESTDIR)$(ActualLibsDir)/package.conf.d" -name '*.conf' | sed "s:   :\0xxx\0:g")
 .PHONY: update_package_db


=====================================
hadrian/src/Rules/BinaryDist.hs
=====================================
@@ -437,13 +437,14 @@ pkgToWrappers pkg = do
       | otherwise     -> pure []
 
 wrapper :: FilePath -> Action String
-wrapper "ghc"         = ghcWrapper
-wrapper "ghc-pkg"     = ghcPkgWrapper
-wrapper "ghci" = ghciScriptWrapper
-wrapper "haddock"     = haddockWrapper
-wrapper "hsc2hs"      = hsc2hsWrapper
-wrapper "runghc"      = runGhcWrapper
-wrapper "runhaskell"  = runGhcWrapper
+wrapper wrapper_name
+  | "runghc"     `isSuffixOf` wrapper_name = runGhcWrapper
+  | "ghc"        `isSuffixOf` wrapper_name = ghcWrapper
+  | "ghc-pkg"    `isSuffixOf` wrapper_name = ghcPkgWrapper
+  | "ghci"       `isSuffixOf` wrapper_name = ghciScriptWrapper
+  | "haddock"    `isSuffixOf` wrapper_name = haddockWrapper
+  | "hsc2hs"     `isSuffixOf` wrapper_name = hsc2hsWrapper
+  | "runhaskell" `isSuffixOf` wrapper_name = runGhcWrapper
 wrapper _             = commonWrapper
 
 -- | Wrapper scripts for different programs. Common is default wrapper.
@@ -473,9 +474,10 @@ runGhcWrapper = pure $ "exec \"$executablename\" -f \"$exedir/ghc\" ${1+\"$@\"}\
 -- | --interactive flag.
 ghciScriptWrapper :: Action String
 ghciScriptWrapper = do
+  prefix <- crossPrefix
   version <- setting ProjectVersion
   pure $ unlines
-    [ "executable=\"$bindir/ghc-" ++ version ++ "\""
+    [ "executable=\"$bindir/" ++ prefix ++ "ghc-" ++ version ++ "\""
     , "exec $executable --interactive \"$@\"" ]
 
 -- | When not on Windows, we want to ship the 3 flavours of the iserv program
@@ -548,4 +550,3 @@ createGhcii outDir = do
       [ "#!/bin/sh"
       , "exec \"$(dirname \"$0\")\"/ghc --interactive \"$@\""
       ]
-


=====================================
libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc
=====================================
@@ -162,6 +162,8 @@ data MiscFlags = MiscFlags
     , disableDelayedOsMemoryReturn :: Bool
     , internalCounters      :: Bool
     , linkerAlwaysPic       :: Bool
+    -- TODO: #25354 uncomment to expose this flag to base.
+    -- , linkerOptimistic      :: Bool
     , linkerMemBase         :: Word
       -- ^ address to ask the OS for memory for the linker, 0 ==> off
     , ioManager             :: IoManagerFlag


=====================================
rts/Linker.c
=====================================
@@ -967,10 +967,20 @@ SymbolAddr* lookupSymbol( SymbolName* lbl )
     // lookupDependentSymbol directly.
     SymbolAddr* r = lookupDependentSymbol(lbl, NULL, NULL);
     if (!r) {
-        errorBelch("^^ Could not load '%s', dependency unresolved. "
-                   "See top entry above.\n", lbl);
-        IF_DEBUG(linker, printLoadedObjects());
-        fflush(stderr);
+        if (!RtsFlags.MiscFlags.linkerOptimistic) {
+          errorBelch("^^ Could not load '%s', dependency unresolved. "
+                     "See top entry above. You might consider using --optimistic-linking\n",
+                     lbl);
+          IF_DEBUG(linker, printLoadedObjects());
+          fflush(stderr);
+        } else {
+          // if --optimistic-linking is passed into the RTS we allow the linker
+          // to optimistically continue
+          errorBelch("^^ Could not load '%s', dependency unresolved, "
+                     "optimistically continuing\n",
+                     lbl);
+          r = (void*) 0xDEADBEEF;
+        }
     }
 
     if (!runPendingInitializers()) {


=====================================
rts/RtsFlags.c
=====================================
@@ -269,6 +269,7 @@ void initRtsFlagsDefaults(void)
     RtsFlags.MiscFlags.disableDelayedOsMemoryReturn = false;
     RtsFlags.MiscFlags.internalCounters        = false;
     RtsFlags.MiscFlags.linkerAlwaysPic         = DEFAULT_LINKER_ALWAYS_PIC;
+    RtsFlags.MiscFlags.linkerOptimistic        = false;
     RtsFlags.MiscFlags.linkerMemBase           = 0;
     RtsFlags.MiscFlags.ioManager               = IO_MNGR_FLAG_AUTO;
 #if defined(THREADED_RTS) && defined(mingw32_HOST_OS)
@@ -998,6 +999,11 @@ error = true;
                       OPTION_UNSAFE;
                       RtsFlags.MiscFlags.generate_dump_file = true;
                   }
+                  else if (strequal("optimistic-linking",
+                              &rts_argv[arg][2])) {
+                       OPTION_UNSAFE;
+                       RtsFlags.MiscFlags.linkerOptimistic = true;
+                  }
                   else if (strequal("null-eventlog-writer",
                                &rts_argv[arg][2])) {
                       OPTION_UNSAFE;


=====================================
rts/include/rts/Flags.h
=====================================
@@ -267,6 +267,7 @@ typedef struct _MISC_FLAGS {
                                           there as well. */
     bool internalCounters;       /* See Note [Internal Counters Stats] */
     bool linkerAlwaysPic;        /* Assume the object code is always PIC */
+    bool linkerOptimistic;       /* Should the runtime linker optimistically continue */
     StgWord linkerMemBase;       /* address to ask the OS for memory
                                   * for the linker, NULL ==> off */
     IO_MANAGER_FLAG ioManager;   /* The I/O manager to use.  */


=====================================
rts/linker/elf_got.c
=====================================
@@ -97,9 +97,22 @@ fillGot(ObjectCode * oc) {
                             if(0 == strncmp(symbol->name,"_GLOBAL_OFFSET_TABLE_",21)) {
                                 symbol->addr = oc->info->got_start;
                             } else {
-                                errorBelch("Failed to lookup symbol: %s\n",
+                                errorBelch("Failed to lookup symbol: %s,"
+                                           " you might consider using --optimistic-linking\n",
                                            symbol->name);
-                                return EXIT_FAILURE;
+
+                                // if --optimistic-linking is passed into the
+                                // RTS we allow the linker to optimistically
+                                // continue
+                                if (RtsFlags.MiscFlags.linkerOptimistic) {
+                                    errorBelch("Failed to lookup symbol: %s,"
+                                               " optimistically continuing.\n",
+                                               symbol->name);
+                                    symbol->addr = (void*) 0xDEADBEEF;
+                                } else {
+                                    return EXIT_FAILURE;
+                                }
+
                             }
                         }
                     } else {


=====================================
testsuite/tests/ghci/linking/T25240/Makefile
=====================================
@@ -0,0 +1,7 @@
+TOP=../../../..
+include $(TOP)/mk/boilerplate.mk
+include $(TOP)/mk/test.mk
+
+.PHONY: T25240
+T25240:
+	"$(TEST_HC)" $(TEST_HC_OPTS_INTERACTIVE) T25240a.hs T25240.hs +RTS --optimistic-linking -RTS


=====================================
testsuite/tests/ghci/linking/T25240/T25240.hs
=====================================
@@ -0,0 +1,17 @@
+{-# LANGUAGE TemplateHaskell #-}
+
+{-
+
+When the RTS linker loads the T25240a module to run the pure foo splice, it
+tries to resolve the func symbol even if this function isn't required to run the
+splice code, i.e., its dead code. This test checks that by passing the
+--optimistic-linking flag the RTS linker continues to link even in the presence
+of unknown symbols.
+
+-}
+
+module T25240 where
+
+import T25240a
+
+$(pure foo)


=====================================
testsuite/tests/ghci/linking/T25240/T25240.stderr
=====================================
@@ -0,0 +1,2 @@
+ghc: ^^ Could not load 'func', dependency unresolved, optimistically continuing
+


=====================================
testsuite/tests/ghci/linking/T25240/T25240a.hs
=====================================
@@ -0,0 +1,13 @@
+{-# LANGUAGE TemplateHaskell #-}
+
+
+module T25240a
+  ( foo, func
+  ) where
+
+
+foo :: [a]
+foo = []
+
+foreign import ccall "func"
+  func :: Int -> Int


=====================================
testsuite/tests/ghci/linking/T25240/all.T
=====================================
@@ -0,0 +1,3 @@
+# skip on darwin because the leading underscores will make the test fail
+test('T25240', [when(leading_underscore(),skip), req_rts_linker, extra_files(['T25240a.hs'])],
+    makefile_test, ['T25240'])


=====================================
testsuite/tests/ghci/should_run/T18064.stderr
=====================================
@@ -1,2 +1,2 @@
-<interactive>: ^^ Could not load 'blah', dependency unresolved. See top entry above.
+<interactive>: ^^ Could not load 'blah', dependency unresolved. See top entry above. You might consider using --optimistic-linking
 


=====================================
testsuite/tests/rts/linker/T11223/T11223_link_order_a_b_2_fail.stderr
=====================================
@@ -9,7 +9,7 @@ This could be caused by:
    * Specifying the same object file twice on the GHCi command line
    * An incorrect `package.conf' entry, causing some object to be
      loaded twice.
-ghc-stage2: ^^ Could not load 'c', dependency unresolved. See top entry above.
+ghc-stage2: ^^ Could not load 'c', dependency unresolved. See top entry above. You might consider using --optimistic-linking
 
 
 GHC.ByteCode.Linker: can't find label


=====================================
testsuite/tests/rts/linker/T11223/T11223_link_order_a_b_2_fail.stderr-ws-32-mingw32
=====================================
@@ -9,7 +9,7 @@ This could be caused by:
    * Specifying the same object file twice on the GHCi command line
    * An incorrect `package.conf' entry, causing some object to be
      loaded twice.
-ghc-stage2.exe: ^^ Could not load '_c', dependency unresolved. See top entry above.
+ghc-stage2.exe: ^^ Could not load '_c', dependency unresolved. See top entry above. You might consider using --optimistic-linking
 
 
 GHC.ByteCode.Linker: can't find label


=====================================
testsuite/tests/rts/linker/T11223/T11223_link_order_a_b_2_fail.stderr-ws-64-mingw32
=====================================
@@ -9,7 +9,7 @@ This could be caused by:
    * Specifying the same object file twice on the GHCi command line
    * An incorrect `package.conf' entry, causing some object to be
      loaded twice.
-ghc-stage2.exe: ^^ Could not load 'c', dependency unresolved. See top entry above.
+ghc-stage2.exe: ^^ Could not load 'c', dependency unresolved. See top entry above. You might consider using --optimistic-linking
 
 
 GHC.ByteCode.Linker: can't find label


=====================================
testsuite/tests/rts/linker/T11223/T11223_simple_duplicate_lib.stderr
=====================================
@@ -9,7 +9,7 @@ This could be caused by:
    * Specifying the same object file twice on the GHCi command line
    * An incorrect `package.conf' entry, causing some object to be
      loaded twice.
-ghc-stage2: ^^ Could not load 'c', dependency unresolved. See top entry above.
+ghc-stage2: ^^ Could not load 'c', dependency unresolved. See top entry above. You might consider using --optimistic-linking
 
 
 GHC.ByteCode.Linker: can't find label


=====================================
testsuite/tests/rts/linker/T11223/T11223_simple_duplicate_lib.stderr-ws-32-mingw32
=====================================
@@ -9,7 +9,7 @@ This could be caused by:
    * Specifying the same object file twice on the GHCi command line
    * An incorrect `package.conf' entry, causing some object to be
      loaded twice.
-ghc-stage2.exe: ^^ Could not load '_c', dependency unresolved. See top entry above.
+ghc-stage2.exe: ^^ Could not load '_c', dependency unresolved. See top entry above. You might consider using --optimistic-linking
 
 
 GHC.ByteCode.Linker: can't find label


=====================================
testsuite/tests/rts/linker/T11223/T11223_simple_duplicate_lib.stderr-ws-64-mingw32
=====================================
@@ -9,7 +9,7 @@ This could be caused by:
    * Specifying the same object file twice on the GHCi command line
    * An incorrect `package.conf' entry, causing some object to be
      loaded twice.
-ghc-stage2.exe: ^^ Could not load 'c', dependency unresolved. See top entry above.
+ghc-stage2.exe: ^^ Could not load 'c', dependency unresolved. See top entry above. You might consider using --optimistic-linking
 
 
 GHC.ByteCode.Linker: can't find label



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4813cb1d29961f0d0a000f73864345bdb665d5af...73e7175865378652bc12b3af80cb8d6861904e1b

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4813cb1d29961f0d0a000f73864345bdb665d5af...73e7175865378652bc12b3af80cb8d6861904e1b
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/20241022/68c33134/attachment-0001.html>


More information about the ghc-commits mailing list