[Git][ghc/ghc][wip/haskell-nix-patches/musl64/ghc-9.6-missing-symbols-deadbeef] 3 commits: wrk: remove typeclass in T25240

doyougnu (@doyougnu) gitlab at gitlab.haskell.org
Mon Sep 16 13:17:51 UTC 2024



doyougnu pushed to branch wip/haskell-nix-patches/musl64/ghc-9.6-missing-symbols-deadbeef at Glasgow Haskell Compiler / GHC


Commits:
5d683e0f by doyougnu at 2024-09-16T08:36:06-04:00
wrk: remove typeclass in T25240

- - - - -
5101d05e by doyougnu at 2024-09-16T08:43:08-04:00
wrk: link-unknown-symbols -> optimistic-linking

- - - - -
44eeff48 by doyougnu at 2024-09-16T09:17:28-04:00
wrk: add warnings

- - - - -


9 changed files:

- 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/FFI.hs
- testsuite/tests/ghci/linking/T25240/Makefile
- testsuite/tests/ghci/linking/T25240/T25240.hs
- testsuite/tests/interface-stability/base-exports.stdout


Changes:

=====================================
libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc
=====================================
@@ -162,7 +162,7 @@ data MiscFlags = MiscFlags
     , disableDelayedOsMemoryReturn :: Bool
     , internalCounters      :: Bool
     , linkerAlwaysPic       :: Bool
-    , linkUnknownSymbols    :: Bool
+    , linkerOptimistic      :: Bool
     , linkerMemBase         :: Word
       -- ^ address to ask the OS for memory for the linker, 0 ==> off
     , ioManager             :: IoManagerFlag
@@ -538,7 +538,7 @@ getMiscFlags = do
             <*> (toBool <$>
                   (#{peek MISC_FLAGS, linkerAlwaysPic} ptr :: IO CBool))
             <*> (toBool <$>
-                  (#{peek MISC_FLAGS, linkUnknownSymbols} ptr :: IO CBool))
+                  (#{peek MISC_FLAGS, linkerOptimistic} ptr :: IO CBool))
             <*> #{peek MISC_FLAGS, linkerMemBase} ptr
             <*> (toEnum . fromIntegral
                  <$> (#{peek MISC_FLAGS, ioManager} ptr :: IO Word32))


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


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


=====================================
rts/include/rts/Flags.h
=====================================
@@ -267,7 +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 linkUnknownSymbols;     /* Should the runtime linker optimistically continue */
+    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,13 +97,16 @@ 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);
 
-                                // if --link-unknown-symbols is passed into the
+                                // if --optimistic-linking is passed into the
                                 // RTS we allow the linker to optimistically
                                 // continue
-                                if (RtsFlags.MiscFlags.linkUnknownSymbols) {
+                                if (RtsFlags.MiscFlags.linkerOptimistic) {
+                                    errorBelch("Warning: optimistically continuing by assigning %s to OxDEADBEEF.\n",
+                                            symbol->name);
                                     symbol->addr = (void*) 0xDEADBEEF;
                                 } else {
                                     return EXIT_FAILURE;


=====================================
testsuite/tests/ghci/linking/T25240/FFI.hs
=====================================
@@ -6,10 +6,10 @@
 {-# OPTIONS_GHC -fno-warn-missing-methods #-}
 
 module FFI
-  ( D(..), D2(..), tabulate
+  ( D(..), D2(..), tabulate, func
   ) where
 
-import GHC.Exts ( Double#, Double(D#) )
+import GHC.Exts ( Double#, Double )
 import Language.Haskell.TH ( CodeQ )
 
 data D = D Double
@@ -17,12 +17,9 @@ data D = D Double
 data D2 = D2 { x, y :: D }
   deriving Show
 
-tabulate :: ( Word -> CodeQ D ) -> CodeQ ( D2 )
+tabulate :: ( Word -> CodeQ D ) -> CodeQ D2
 tabulate f = [|| D2 $$( f 1 ) $$( f 2 ) ||]
 
 
--- Now an unrelated "Num D" instance.
-instance Num D where
-  ( D ( D# x ) ) * ( D ( D# y ) ) = D ( D# ( func x y ) )
 foreign import prim "prim_func"
   func :: Double# -> Double# -> Double#


=====================================
testsuite/tests/ghci/linking/T25240/Makefile
=====================================
@@ -4,7 +4,7 @@ include $(TOP)/mk/test.mk
 
 .PHONY: T25240
 T25240:
-	"$(TEST_HC)" $(TEST_HC_OPTS_INTERACTIVE) FFI.hs TH.hs T25240.hs +RTS --link-unknown-symbols -RTS
+	"$(TEST_HC)" $(TEST_HC_OPTS_INTERACTIVE) FFI.hs TH.hs T25240.hs +RTS --optimistic-linking -RTS
 
 .PHONY: T25240f
 T25240f:


=====================================
testsuite/tests/ghci/linking/T25240/T25240.hs
=====================================
@@ -3,24 +3,21 @@
 Here we have two modules, FFI and TH.
 
 In the FFI module, we define a data type D and a function to be used in Template
-Haskell, tabulate. Completely unrelatedly, we also include a Num D instance
-which makes use of a foreign import prim declaration, foreign import prim
-"prim_func". In the TH module, we use tabulate and get a linking error:
+Haskell, tabulate. Completely unrelatedly, we also include foreign import prim
+declaration, foreign import prim "prim_func". In the TH module, we use tabulate
+and get a linking error:
 
 FFI.o: unknown symbol `prim_func'
 
 
-This suggests we are trying to run some code at splice time involving the Num D
-instance, even though Num D is not involved in any way. In particular, if we
-change the use of prim_func to something like error "blah", then the error never
-gets thrown, which shows we don't run that code at splice time. Note that it is
-important to use a typeclass to trigger this bug. If we instead use the FFI
-import in a top-level binding, there are no problems. It doesn't matter that the
-class is Num or some other (possibly user-defined) class.
+This suggests we are trying to run some code at splice time involving prim_func,
+even prim_func is not involved in any way. In particular, if we change the use
+of prim_func to something like error "blah", then the error never gets thrown,
+which shows we don't run that code at splice time.
 
 The essential bug is that we have a symbol at link time which comes from dead
 code and yet we try to resolve it anyway. The fix is to pass the flag
---link-unknown-symbols to the RTS which will assign the symbol a magic number
+--optimistic-linking to the RTS which will assign the symbol a magic number
 0xDEADBEEF and allow the linker to continue. See MR!13012 for the implementation
 of that flag
 -}


=====================================
testsuite/tests/interface-stability/base-exports.stdout
=====================================
@@ -9106,7 +9106,7 @@ module GHC.RTS.Flags where
   type IoSubSystem :: *
   data IoSubSystem = IoPOSIX | IoNative
   type MiscFlags :: *
-  data MiscFlags = MiscFlags {tickInterval :: RtsTime, installSignalHandlers :: GHC.Types.Bool, installSEHHandlers :: GHC.Types.Bool, generateCrashDumpFile :: GHC.Types.Bool, generateStackTrace :: GHC.Types.Bool, machineReadable :: GHC.Types.Bool, disableDelayedOsMemoryReturn :: GHC.Types.Bool, internalCounters :: GHC.Types.Bool, linkerAlwaysPic :: GHC.Types.Bool, linkUnknownSymbols :: GHC.Types.Bool, linkerMemBase :: GHC.Types.Word, ioManager :: IoManagerFlag, numIoWorkerThreads :: GHC.Internal.Word.Word32}
+  data MiscFlags = MiscFlags {tickInterval :: RtsTime, installSignalHandlers :: GHC.Types.Bool, installSEHHandlers :: GHC.Types.Bool, generateCrashDumpFile :: GHC.Types.Bool, generateStackTrace :: GHC.Types.Bool, machineReadable :: GHC.Types.Bool, disableDelayedOsMemoryReturn :: GHC.Types.Bool, internalCounters :: GHC.Types.Bool, linkerAlwaysPic :: GHC.Types.Bool, linkerOptimistic :: GHC.Types.Bool, linkerMemBase :: GHC.Types.Word, ioManager :: IoManagerFlag, numIoWorkerThreads :: GHC.Internal.Word.Word32}
   type ParFlags :: *
   data ParFlags = ParFlags {nCapabilities :: GHC.Internal.Word.Word32, migrate :: GHC.Types.Bool, maxLocalSparks :: GHC.Internal.Word.Word32, parGcEnabled :: GHC.Types.Bool, parGcGen :: GHC.Internal.Word.Word32, parGcLoadBalancingEnabled :: GHC.Types.Bool, parGcLoadBalancingGen :: GHC.Internal.Word.Word32, parGcNoSyncWithIdle :: GHC.Internal.Word.Word32, parGcThreads :: GHC.Internal.Word.Word32, setAffinity :: GHC.Types.Bool}
   type ProfFlags :: *



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6b17092ff82644a47d7f41ccf649f77c4f8ed8ff...44eeff48eaaf43ebaa6e42fe2677a90ec38c8d0a

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6b17092ff82644a47d7f41ccf649f77c4f8ed8ff...44eeff48eaaf43ebaa6e42fe2677a90ec38c8d0a
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/20240916/6c26f9a3/attachment-0001.html>


More information about the ghc-commits mailing list