[Git][ghc/ghc][wip/rts-configure-symbols] 4 commits: hadrian: `need` any `configure` script we will call

John Ericson (@Ericson2314) gitlab at gitlab.haskell.org
Wed Sep 20 15:03:31 UTC 2023



John Ericson pushed to branch wip/rts-configure-symbols at Glasgow Haskell Compiler / GHC


Commits:
9ab96d55 by John Ericson at 2023-09-20T11:02:16-04:00
hadrian: `need` any `configure` script we will call

When the script is changed, we should reconfigure.

- - - - -
47133bc7 by John Ericson at 2023-09-20T11:02:46-04:00
hadrian: Make it easier to debug Cabal configure

Right now, output is squashed. This make per-package configure scripts
extremely hard to maintain, because we get vague "library is missing"
errors when the actually probably is usually completely unrelated except
for also involving the C/C++ toolchain.

(I can always pass `-VVV` to Hadrian locally, but these errors are
subtle and I often cannot reproduce them locally!)

`--disable-option-checking` was added back in
75c6e0684dda585c37b4ac254cd7a13537a59a91 but seems to be a bit overkill;
if other flags are passed that are not recognized behind the two from
Cabal mentioned in the former comment, we *do* want to know about it.

- - - - -
9b4bd275 by John Ericson at 2023-09-20T11:03:08-04:00
hadrian: Increase verbosity of certain cabal commands

This is a hack to get around the cabal function we're calling
*decreasing* the verbosity it passes to another function, which is the
stuff we often actually care about. Sigh.

Keeping this a separate commit so if this makes things too verbose it is
easy to revert.

- - - - -
689094a5 by John Ericson at 2023-09-20T11:03:09-04:00
rts: Move most external symbols logic to the configure script

This is much more terse because we are programmatically handling the
leading underscore.

`findPtr` however is still handled in the Cabal file because we need a
newer Cabal to pass flags to the configure script automatically.

Co-Authored-By: Ben Gamari <ben at well-typed.com>

- - - - -


8 changed files:

- hadrian/src/Hadrian/Haskell/Cabal/Parse.hs
- hadrian/src/Hadrian/Oracles/Cabal/Rules.hs
- hadrian/src/Settings/Builders/Cabal.hs
- rts/.gitignore
- rts/configure.ac
- + rts/external-symbols.list.in
- + rts/rts.buildinfo.in
- rts/rts.cabal.in


Changes:

=====================================
hadrian/src/Hadrian/Haskell/Cabal/Parse.hs
=====================================
@@ -144,25 +144,29 @@ configurePackage context at Context {..} = do
     need deps
 
     -- Figure out what hooks we need.
+    let configureFile = replaceFileName (pkgCabalFile package) "configure"
+        -- induce dependency on the file
+        autoconfUserHooks = do
+          need [configureFile]
+          pure C.autoconfUserHooks
     hooks <- case C.buildType (C.flattenPackageDescription gpd) of
-        C.Configure -> pure C.autoconfUserHooks
+        C.Configure -> autoconfUserHooks
         C.Simple -> pure C.simpleUserHooks
         C.Make -> fail "build-type: Make is not supported"
         -- The 'time' package has a 'C.Custom' Setup.hs, but it's actually
         -- 'C.Configure' plus a @./Setup test@ hook. However, Cabal is also
         -- 'C.Custom', but doesn't have a configure script.
         C.Custom -> do
-            configureExists <- doesFileExist $
-                replaceFileName (pkgCabalFile package) "configure"
-            pure $ if configureExists then C.autoconfUserHooks else C.simpleUserHooks
+            configureExists <- doesFileExist configureFile
+            if configureExists then autoconfUserHooks else pure C.simpleUserHooks
 
     -- Compute the list of flags, and the Cabal configuration arguments
     flagList    <- interpret (target context (Cabal Flags stage) [] []) getArgs
     argList     <- interpret (target context (Cabal Setup stage) [] []) getArgs
     trackArgsHash (target context (Cabal Flags stage) [] [])
     trackArgsHash (target context (Cabal Setup stage) [] [])
-    verbosity   <- getVerbosity
-    let v = if verbosity >= Diagnostic then "-v3" else "-v0"
+    verbosity <- getVerbosity
+    let v = shakeVerbosityToCabalFlag verbosity
         argList' = argList ++ ["--flags=" ++ unwords flagList, v]
     when (verbosity >= Verbose) $
         putProgressInfo $ "| Package " ++ quote (pkgName package) ++ " configuration flags: " ++ unwords argList'
@@ -185,12 +189,18 @@ copyPackage context at Context {..} = do
     ctxPath   <- Context.contextPath context
     pkgDbPath <- packageDbPath (PackageDbLoc stage iplace)
     verbosity <- getVerbosity
-    let v = if verbosity >= Diagnostic then "-v3" else "-v0"
+    let v = shakeVerbosityToCabalFlag verbosity
     traced "cabal-copy" $
         C.defaultMainWithHooksNoReadArgs C.autoconfUserHooks gpd
             [ "copy", "--builddir", ctxPath, "--target-package-db", pkgDbPath, v ]
 
-
+-- | Increase by 1 by because 'simpleUserHooks' calls 'lessVerbose'
+shakeVerbosityToCabalFlag :: Verbosity -> String
+shakeVerbosityToCabalFlag = \case
+    Diagnostic -> "-v3"
+    Verbose -> "-v3"
+    Silent -> "-v0"
+    _ -> "-v2"
 
 -- | What type of file is Main
 data MainSourceType = HsMain | CppMain | CMain


=====================================
hadrian/src/Hadrian/Oracles/Cabal/Rules.hs
=====================================
@@ -73,7 +73,7 @@ cabalOracle = do
                      $ addKnownProgram ghcPkgProgram
                      $ emptyProgramDb
         (compiler, maybePlatform, _pkgdb) <- liftIO $
-            configure silent Nothing Nothing progDb
+            configure normal Nothing Nothing progDb
         let platform = fromMaybe (error msg) maybePlatform
             msg      = "PackageConfiguration oracle: cannot detect platform"
         return $ PackageConfiguration (compiler, platform)


=====================================
hadrian/src/Settings/Builders/Cabal.hs
=====================================
@@ -83,7 +83,6 @@ cabalSetupArgs = builder (Cabal Setup) ? do
 
 commonCabalArgs :: Stage -> Args
 commonCabalArgs stage = do
-  verbosity <- expr getVerbosity
   pkg       <- getPackage
   package_id <- expr $ pkgUnitId stage pkg
   let prefix = "${pkgroot}" ++ (if windowsHost then "" else "/..")
@@ -127,9 +126,7 @@ commonCabalArgs stage = do
             , with Alex
             , with Happy
             -- Update Target.trackArgument if changing these:
-            , verbosity < Verbose ?
-              pure [ "-v0", "--configure-option=--quiet"
-                   , "--configure-option=--disable-option-checking" ] ]
+            ]
 
 -- TODO: Isn't vanilla always built? If yes, some conditions are redundant.
 -- TODO: Need compiler_stage1_CONFIGURE_OPTS += --disable-library-for-ghci?


=====================================
rts/.gitignore
=====================================
@@ -18,6 +18,7 @@
 /config.status
 /configure
 
+/external-symbols.list
 /ghcautoconf.h.autoconf.in
 /ghcautoconf.h.autoconf
 /include/ghcautoconf.h


=====================================
rts/configure.ac
=====================================
@@ -55,3 +55,44 @@ cat $srcdir/../mk/config.h ghcautoconf.h.autoconf | sed \
    >> include/ghcautoconf.h
 echo "#endif /* __GHCAUTOCONF_H__ */" >> include/ghcautoconf.h
 ]
+
+dnl ######################################################################
+dnl Generate external symbol flags (-Wl,-u...)
+dnl ######################################################################
+
+dnl See Note [Undefined symbols in the RTS]
+
+[
+symbolExtraDefs=''
+if [[ "$CABAL_FLAG_find_ptr" = 1 ]]; then
+    symbolExtraDefs+=' -DFIND_PTR'
+fi
+
+cat $srcdir/external-symbols.list.in \
+    | "$CC" $symbolExtraDefs -E -P -traditional -Iinclude - -o - \
+    | sed -e '/^ *$/d' \
+    > external-symbols.list \
+    || exit 1
+
+if [[ "$CABAL_FLAG_leading_underscore" = 1 ]]; then
+    sedExpr='s/^(.*)$/  "-Wl,-u,_\1"/'
+else
+    sedExpr='s/^(.*)$/  "-Wl,-u,\1"/'
+fi
+sed -E -e "${sedExpr}" external-symbols.list > external-symbols.flags
+unset sedExpr
+rm -f external-symbols.list
+]
+
+dnl ######################################################################
+dnl Generate build-info
+dnl ######################################################################
+
+[
+cat $srcdir/rts.buildinfo.in \
+    | "$CC" -E -P -traditional - -o - \
+    | sed -e '/^ *$/d' \
+    > rts.buildinfo \
+    || exit 1
+rm -f external-symbols.flags
+]


=====================================
rts/external-symbols.list.in
=====================================
@@ -0,0 +1,97 @@
+#include "ghcautoconf.h"
+
+#if 0
+See Note [Undefined symbols in the RTS]
+#endif
+
+#if mingw32_HOST_OS
+base_GHCziEventziWindows_processRemoteCompletion_closure
+#endif
+
+#if FIND_PTR
+findPtr
+#endif
+
+base_GHCziTopHandler_runIO_closure
+base_GHCziTopHandler_runNonIO_closure
+ghczmprim_GHCziTupleziPrim_Z0T_closure
+ghczmprim_GHCziTypes_True_closure
+ghczmprim_GHCziTypes_False_closure
+base_GHCziPack_unpackCString_closure
+base_GHCziWeakziFinalizze_runFinalizzerBatch_closure
+base_GHCziIOziException_stackOverflow_closure
+base_GHCziIOziException_heapOverflow_closure
+base_GHCziIOziException_allocationLimitExceeded_closure
+base_GHCziIOziException_blockedIndefinitelyOnMVar_closure
+base_GHCziIOziException_blockedIndefinitelyOnSTM_closure
+base_GHCziIOziException_cannotCompactFunction_closure
+base_GHCziIOziException_cannotCompactPinned_closure
+base_GHCziIOziException_cannotCompactMutable_closure
+base_GHCziIOPort_doubleReadException_closure
+base_ControlziExceptionziBase_nonTermination_closure
+base_ControlziExceptionziBase_nestedAtomically_closure
+base_GHCziEventziThread_blockedOnBadFD_closure
+base_GHCziConcziSync_runSparks_closure
+base_GHCziConcziIO_ensureIOManagerIsRunning_closure
+base_GHCziConcziIO_interruptIOManager_closure
+base_GHCziConcziIO_ioManagerCapabilitiesChanged_closure
+base_GHCziConcziSignal_runHandlersPtr_closure
+base_GHCziTopHandler_flushStdHandles_closure
+base_GHCziTopHandler_runMainIO_closure
+ghczmprim_GHCziTypes_Czh_con_info
+ghczmprim_GHCziTypes_Izh_con_info
+ghczmprim_GHCziTypes_Fzh_con_info
+ghczmprim_GHCziTypes_Dzh_con_info
+ghczmprim_GHCziTypes_Wzh_con_info
+base_GHCziPtr_Ptr_con_info
+base_GHCziPtr_FunPtr_con_info
+base_GHCziInt_I8zh_con_info
+base_GHCziInt_I16zh_con_info
+base_GHCziInt_I32zh_con_info
+base_GHCziInt_I64zh_con_info
+base_GHCziWord_W8zh_con_info
+base_GHCziWord_W16zh_con_info
+base_GHCziWord_W32zh_con_info
+base_GHCziWord_W64zh_con_info
+base_GHCziStable_StablePtr_con_info
+hs_atomic_add8
+hs_atomic_add16
+hs_atomic_add32
+hs_atomic_add64
+hs_atomic_sub8
+hs_atomic_sub16
+hs_atomic_sub32
+hs_atomic_sub64
+hs_atomic_and8
+hs_atomic_and16
+hs_atomic_and32
+hs_atomic_and64
+hs_atomic_nand8
+hs_atomic_nand16
+hs_atomic_nand32
+hs_atomic_nand64
+hs_atomic_or8
+hs_atomic_or16
+hs_atomic_or32
+hs_atomic_or64
+hs_atomic_xor8
+hs_atomic_xor16
+hs_atomic_xor32
+hs_atomic_xor64
+hs_cmpxchg8
+hs_cmpxchg16
+hs_cmpxchg32
+hs_cmpxchg64
+hs_xchg8
+hs_xchg16
+hs_xchg32
+hs_xchg64
+hs_atomicread8
+hs_atomicread16
+hs_atomicread32
+hs_atomicread64
+hs_atomicwrite8
+hs_atomicwrite16
+hs_atomicwrite32
+hs_atomicwrite64
+base_GHCziStackziCloneStack_StackSnapshot_closure


=====================================
rts/rts.buildinfo.in
=====================================
@@ -0,0 +1,3 @@
+-- External symbols referenced by the RTS
+ld-options:
+#include "external-symbols.flags"


=====================================
rts/rts.cabal.in
=====================================
@@ -14,9 +14,12 @@ build-type: Configure
 extra-source-files:
     configure
     configure.ac
+    external-symbols.list.in
+    rts.buildinfo.in
 
 extra-tmp-files:
     autom4te.cache
+    rts.buildinfo
     config.log
     config.status
 
@@ -301,197 +304,6 @@ library
                         stg/Ticky.h
                         stg/Types.h
 
-      -- See Note [Undefined symbols in the RTS]
-      if flag(leading-underscore)
-        ld-options:
-           "-Wl,-u,_base_GHCziTopHandler_runIO_closure"
-           "-Wl,-u,_base_GHCziTopHandler_runNonIO_closure"
-           "-Wl,-u,_ghczmprim_GHCziTupleziPrim_Z0T_closure"
-           "-Wl,-u,_ghczmprim_GHCziTypes_True_closure"
-           "-Wl,-u,_ghczmprim_GHCziTypes_False_closure"
-           "-Wl,-u,_base_GHCziPack_unpackCString_closure"
-           "-Wl,-u,_base_GHCziWeakziFinalizze_runFinalizzerBatch_closure"
-           "-Wl,-u,_base_GHCziIOziException_stackOverflow_closure"
-           "-Wl,-u,_base_GHCziIOziException_heapOverflow_closure"
-           "-Wl,-u,_base_GHCziIOziException_allocationLimitExceeded_closure"
-           "-Wl,-u,_base_GHCziIOziException_blockedIndefinitelyOnMVar_closure"
-           "-Wl,-u,_base_GHCziIOziException_blockedIndefinitelyOnSTM_closure"
-           "-Wl,-u,_base_GHCziIOziException_cannotCompactFunction_closure"
-           "-Wl,-u,_base_GHCziIOziException_cannotCompactPinned_closure"
-           "-Wl,-u,_base_GHCziIOziException_cannotCompactMutable_closure"
-           "-Wl,-u,_base_GHCziIOPort_doubleReadException_closure"
-           "-Wl,-u,_base_ControlziExceptionziBase_nonTermination_closure"
-           "-Wl,-u,_base_ControlziExceptionziBase_nestedAtomically_closure"
-           "-Wl,-u,_base_GHCziEventziThread_blockedOnBadFD_closure"
-           "-Wl,-u,_base_GHCziConcziSync_runSparks_closure"
-           "-Wl,-u,_base_GHCziConcziIO_ensureIOManagerIsRunning_closure"
-           "-Wl,-u,_base_GHCziConcziIO_interruptIOManager_closure"
-           "-Wl,-u,_base_GHCziConcziIO_ioManagerCapabilitiesChanged_closure"
-           "-Wl,-u,_base_GHCziConcziSignal_runHandlersPtr_closure"
-           "-Wl,-u,_base_GHCziTopHandler_flushStdHandles_closure"
-           "-Wl,-u,_base_GHCziTopHandler_runMainIO_closure"
-           "-Wl,-u,_ghczmprim_GHCziTypes_Czh_con_info"
-           "-Wl,-u,_ghczmprim_GHCziTypes_Izh_con_info"
-           "-Wl,-u,_ghczmprim_GHCziTypes_Fzh_con_info"
-           "-Wl,-u,_ghczmprim_GHCziTypes_Dzh_con_info"
-           "-Wl,-u,_ghczmprim_GHCziTypes_Wzh_con_info"
-           "-Wl,-u,_base_GHCziPtr_Ptr_con_info"
-           "-Wl,-u,_base_GHCziPtr_FunPtr_con_info"
-           "-Wl,-u,_base_GHCziInt_I8zh_con_info"
-           "-Wl,-u,_base_GHCziInt_I16zh_con_info"
-           "-Wl,-u,_base_GHCziInt_I32zh_con_info"
-           "-Wl,-u,_base_GHCziInt_I64zh_con_info"
-           "-Wl,-u,_base_GHCziWord_W8zh_con_info"
-           "-Wl,-u,_base_GHCziWord_W16zh_con_info"
-           "-Wl,-u,_base_GHCziWord_W32zh_con_info"
-           "-Wl,-u,_base_GHCziWord_W64zh_con_info"
-           "-Wl,-u,_base_GHCziStable_StablePtr_con_info"
-           "-Wl,-u,_hs_atomic_add8"
-           "-Wl,-u,_hs_atomic_add16"
-           "-Wl,-u,_hs_atomic_add32"
-           "-Wl,-u,_hs_atomic_add64"
-           "-Wl,-u,_hs_atomic_sub8"
-           "-Wl,-u,_hs_atomic_sub16"
-           "-Wl,-u,_hs_atomic_sub32"
-           "-Wl,-u,_hs_atomic_sub64"
-           "-Wl,-u,_hs_atomic_and8"
-           "-Wl,-u,_hs_atomic_and16"
-           "-Wl,-u,_hs_atomic_and32"
-           "-Wl,-u,_hs_atomic_and64"
-           "-Wl,-u,_hs_atomic_nand8"
-           "-Wl,-u,_hs_atomic_nand16"
-           "-Wl,-u,_hs_atomic_nand32"
-           "-Wl,-u,_hs_atomic_nand64"
-           "-Wl,-u,_hs_atomic_or8"
-           "-Wl,-u,_hs_atomic_or16"
-           "-Wl,-u,_hs_atomic_or32"
-           "-Wl,-u,_hs_atomic_or64"
-           "-Wl,-u,_hs_atomic_xor8"
-           "-Wl,-u,_hs_atomic_xor16"
-           "-Wl,-u,_hs_atomic_xor32"
-           "-Wl,-u,_hs_atomic_xor64"
-           "-Wl,-u,_hs_cmpxchg8"
-           "-Wl,-u,_hs_cmpxchg16"
-           "-Wl,-u,_hs_cmpxchg32"
-           "-Wl,-u,_hs_cmpxchg64"
-           "-Wl,-u,_hs_xchg8"
-           "-Wl,-u,_hs_xchg16"
-           "-Wl,-u,_hs_xchg32"
-           "-Wl,-u,_hs_xchg64"
-           "-Wl,-u,_hs_atomicread8"
-           "-Wl,-u,_hs_atomicread16"
-           "-Wl,-u,_hs_atomicread32"
-           "-Wl,-u,_hs_atomicread64"
-           "-Wl,-u,_hs_atomicwrite8"
-           "-Wl,-u,_hs_atomicwrite16"
-           "-Wl,-u,_hs_atomicwrite32"
-           "-Wl,-u,_hs_atomicwrite64"
-           "-Wl,-u,_base_GHCziStackziCloneStack_StackSnapshot_closure"
-
-        if flag(find-ptr)
-          -- This symbol is useful in gdb, but not referred to anywhere,
-          -- so we need to force it to be included in the binary.
-          ld-options: "-Wl,-u,_findPtr"
-
-      else
-        ld-options:
-           "-Wl,-u,base_GHCziTopHandler_runIO_closure"
-           "-Wl,-u,base_GHCziTopHandler_runNonIO_closure"
-           "-Wl,-u,ghczmprim_GHCziTupleziPrim_Z0T_closure"
-           "-Wl,-u,ghczmprim_GHCziTypes_True_closure"
-           "-Wl,-u,ghczmprim_GHCziTypes_False_closure"
-           "-Wl,-u,base_GHCziPack_unpackCString_closure"
-           "-Wl,-u,base_GHCziWeakziFinalizze_runFinalizzerBatch_closure"
-           "-Wl,-u,base_GHCziIOziException_stackOverflow_closure"
-           "-Wl,-u,base_GHCziIOziException_heapOverflow_closure"
-           "-Wl,-u,base_GHCziIOziException_allocationLimitExceeded_closure"
-           "-Wl,-u,base_GHCziIOziException_blockedIndefinitelyOnMVar_closure"
-           "-Wl,-u,base_GHCziIOziException_blockedIndefinitelyOnSTM_closure"
-           "-Wl,-u,base_GHCziIOziException_cannotCompactFunction_closure"
-           "-Wl,-u,base_GHCziIOziException_cannotCompactPinned_closure"
-           "-Wl,-u,base_GHCziIOziException_cannotCompactMutable_closure"
-           "-Wl,-u,base_GHCziIOPort_doubleReadException_closure"
-           "-Wl,-u,base_ControlziExceptionziBase_nonTermination_closure"
-           "-Wl,-u,base_ControlziExceptionziBase_nestedAtomically_closure"
-           "-Wl,-u,base_GHCziEventziThread_blockedOnBadFD_closure"
-           "-Wl,-u,base_GHCziConcziSync_runSparks_closure"
-           "-Wl,-u,base_GHCziConcziIO_ensureIOManagerIsRunning_closure"
-           "-Wl,-u,base_GHCziConcziIO_interruptIOManager_closure"
-           "-Wl,-u,base_GHCziConcziIO_ioManagerCapabilitiesChanged_closure"
-           "-Wl,-u,base_GHCziConcziSignal_runHandlersPtr_closure"
-           "-Wl,-u,base_GHCziTopHandler_flushStdHandles_closure"
-           "-Wl,-u,base_GHCziTopHandler_runMainIO_closure"
-           "-Wl,-u,ghczmprim_GHCziTypes_Czh_con_info"
-           "-Wl,-u,ghczmprim_GHCziTypes_Izh_con_info"
-           "-Wl,-u,ghczmprim_GHCziTypes_Fzh_con_info"
-           "-Wl,-u,ghczmprim_GHCziTypes_Dzh_con_info"
-           "-Wl,-u,ghczmprim_GHCziTypes_Wzh_con_info"
-           "-Wl,-u,base_GHCziPtr_Ptr_con_info"
-           "-Wl,-u,base_GHCziPtr_FunPtr_con_info"
-           "-Wl,-u,base_GHCziInt_I8zh_con_info"
-           "-Wl,-u,base_GHCziInt_I16zh_con_info"
-           "-Wl,-u,base_GHCziInt_I32zh_con_info"
-           "-Wl,-u,base_GHCziInt_I64zh_con_info"
-           "-Wl,-u,base_GHCziWord_W8zh_con_info"
-           "-Wl,-u,base_GHCziWord_W16zh_con_info"
-           "-Wl,-u,base_GHCziWord_W32zh_con_info"
-           "-Wl,-u,base_GHCziWord_W64zh_con_info"
-           "-Wl,-u,base_GHCziStable_StablePtr_con_info"
-           "-Wl,-u,hs_atomic_add8"
-           "-Wl,-u,hs_atomic_add16"
-           "-Wl,-u,hs_atomic_add32"
-           "-Wl,-u,hs_atomic_add64"
-           "-Wl,-u,hs_atomic_sub8"
-           "-Wl,-u,hs_atomic_sub16"
-           "-Wl,-u,hs_atomic_sub32"
-           "-Wl,-u,hs_atomic_sub64"
-           "-Wl,-u,hs_atomic_and8"
-           "-Wl,-u,hs_atomic_and16"
-           "-Wl,-u,hs_atomic_and32"
-           "-Wl,-u,hs_atomic_and64"
-           "-Wl,-u,hs_atomic_nand8"
-           "-Wl,-u,hs_atomic_nand16"
-           "-Wl,-u,hs_atomic_nand32"
-           "-Wl,-u,hs_atomic_nand64"
-           "-Wl,-u,hs_atomic_or8"
-           "-Wl,-u,hs_atomic_or16"
-           "-Wl,-u,hs_atomic_or32"
-           "-Wl,-u,hs_atomic_or64"
-           "-Wl,-u,hs_atomic_xor8"
-           "-Wl,-u,hs_atomic_xor16"
-           "-Wl,-u,hs_atomic_xor32"
-           "-Wl,-u,hs_atomic_xor64"
-           "-Wl,-u,hs_cmpxchg8"
-           "-Wl,-u,hs_cmpxchg16"
-           "-Wl,-u,hs_cmpxchg32"
-           "-Wl,-u,hs_cmpxchg64"
-           "-Wl,-u,hs_xchg8"
-           "-Wl,-u,hs_xchg16"
-           "-Wl,-u,hs_xchg32"
-           "-Wl,-u,hs_xchg64"
-           "-Wl,-u,hs_atomicread8"
-           "-Wl,-u,hs_atomicread16"
-           "-Wl,-u,hs_atomicread32"
-           "-Wl,-u,hs_atomicread64"
-           "-Wl,-u,hs_atomicwrite8"
-           "-Wl,-u,hs_atomicwrite16"
-           "-Wl,-u,hs_atomicwrite32"
-           "-Wl,-u,hs_atomicwrite64"
-           "-Wl,-u,base_GHCziStackziCloneStack_StackSnapshot_closure"
-
-        if flag(find-ptr)
-          -- This symbol is useful in gdb, but not referred to anywhere,
-          -- so we need to force it to be included in the binary.
-          ld-options: "-Wl,-u,findPtr"
-
-      if os(windows)
-        if flag(leading-underscore)
-          ld-options:
-             "-Wl,-u,_base_GHCziEventziWindows_processRemoteCompletion_closure"
-        else
-          ld-options:
-             "-Wl,-u,base_GHCziEventziWindows_processRemoteCompletion_closure"
-
       if os(osx)
         ld-options: "-Wl,-search_paths_first"
                     -- See Note [fd_set_overflow]



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b838e3ce028249ccd08b8848bf016524353dd13b...689094a5fdac8d7601babef3fcc7aaf68fadcec9

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b838e3ce028249ccd08b8848bf016524353dd13b...689094a5fdac8d7601babef3fcc7aaf68fadcec9
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/20230920/2114b561/attachment-0001.html>


More information about the ghc-commits mailing list