Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
06108198 by Luite Stegeman at 2025-09-30T14:09:24-04:00
rts: Fix lost wakeups in threadPaused for threads blocked on black holes
The lazy blackholing code in threadPaused could overwrite closures
that were already eagerly blackholed, and as such wouldn't have a
marked update frame. If the black hole was overwritten by its
original owner, this would lead to an undetected collision, and
the contents of any existing blocking queue being lost.
This adds a check for eagerly blackholed closures and avoids
overwriting their contents.
Fixes #26324
- - - - -
4bb1576e by Luite Stegeman at 2025-09-30T14:09:24-04:00
rts: push the correct update frame in stg_AP_STACK
The frame contains an eager black hole (__stg_EAGER_BLACKHOLE_info) so
we should push an stg_bh_upd_frame_info instead of an stg_upd_frame_info.
- - - - -
9f1423b8 by Cheng Shao at 2025-09-30T14:09:25-04:00
ghci: fix lookupSymbolInDLL behavior on wasm
This patch fixes lookupSymbolInDLL behavior on wasm to return Nothing
instead of throwing. On wasm, we only have lookupSymbol, and the
driver would attempt to call lookupSymbolInDLL first before falling
back to lookupSymbol, so lookupSymbolInDLL needs to return Nothing
gracefully for the fallback behavior to work.
- - - - -
583d3d53 by Cheng Shao at 2025-09-30T14:09:25-04:00
hadrian/compiler: enable internal-interpreter for ghc library in wasm stage1
This commit enables the internal-interpreter flag for ghc library in
wasm stage1, as well as other minor adjustments to make it actually
possible to launch a ghc api session that makes use of the internal
interpreter. Closes #26431 #25400.
- - - - -
bb886749 by Cheng Shao at 2025-09-30T14:09:25-04:00
testsuite: add T26431 test case
This commit adds T26431 to testsuite/tests/ghci-wasm which goes
through the complete bytecode compilation/linking/running pipeline in
wasm, so to witness that the ghc shared library in wasm have full
support for internal-interpreter.
- - - - -
74e01719 by Matthew Pickering at 2025-09-30T14:09:26-04:00
driver: Load bytecode static pointer entries during linking
Previously the entries were loaded too eagerly, during upsweep, but we
should delay loading them until we know that the relevant bytecode
object is demanded.
Towards #25230
- - - - -
51c7def9 by Cheng Shao at 2025-09-30T14:09:27-04:00
autoconf/ghc-toolchain: remove obsolete C99 check
This patch removes obsolete c99 check from autoconf/ghc-toolchain. For
all toolchain & platform combination we support, gnu11 or above is
already supported without any -std flag required, and our RTS already
required C11 quite a few years ago, so the C99 check is completely
pointless.
- - - - -
21 changed files:
- compiler/GHC.hs
- compiler/GHC/Cmm/Parser.y
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Iface/Tidy/StaticPtrTable.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Runtime/Interpreter/Types.hs
- configure.ac
- distrib/configure.ac.in
- hadrian/src/Settings/Packages.hs
- libraries/ghci/GHCi/ObjLink.hs
- m4/fp_cmm_cpp_cmd_with_args.m4
- − m4/fp_set_cflags_c99.m4
- rts/Apply.cmm
- rts/ThreadPaused.c
- + testsuite/tests/ghci-wasm/T26431.hs
- + testsuite/tests/ghci-wasm/T26431.stdout
- testsuite/tests/ghci-wasm/all.T
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cc.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cpp.hs
Changes:
=====================================
compiler/GHC.hs
=====================================
@@ -716,17 +716,14 @@ setTopSessionDynFlags dflags = do
-- see Note [Target code interpreter]
interp <- if
+#if !defined(wasm32_HOST_ARCH)
-- Wasm dynamic linker
| ArchWasm32 <- platformArch $ targetPlatform dflags
-> do
s <- liftIO $ newMVar InterpPending
loader <- liftIO Loader.uninitializedLoader
dyld <- liftIO $ makeAbsolute $ topDir dflags > "dyld.mjs"
-#if defined(wasm32_HOST_ARCH)
- let libdir = sorry "cannot spawn child process on wasm"
-#else
libdir <- liftIO $ last <$> Loader.getGccSearchDirectory logger dflags "libraries"
-#endif
let profiled = ways dflags `hasWay` WayProf
way_tag = if profiled then "_p" else ""
let cfg =
@@ -747,6 +744,7 @@ setTopSessionDynFlags dflags = do
wasmInterpUnitState = ue_homeUnitState $ hsc_unit_env hsc_env
}
pure $ Just $ Interp (ExternalInterp $ ExtWasm $ ExtInterpState cfg s) loader lookup_cache
+#endif
-- JavaScript interpreter
| ArchJavaScript <- platformArch (targetPlatform dflags)
=====================================
compiler/GHC/Cmm/Parser.y
=====================================
@@ -1321,6 +1321,7 @@ stmtMacros = listToUFM [
( fsLit "PROF_HEADER_CREATE", \[e] -> profHeaderCreate e ),
( fsLit "PUSH_UPD_FRAME", \[sp,e] -> emitPushUpdateFrame sp e ),
+ ( fsLit "PUSH_BH_UPD_FRAME", \[sp,e] -> emitPushBHUpdateFrame sp e ),
( fsLit "SET_HDR", \[ptr,info,ccs] ->
emitSetDynHdr ptr info ccs ),
( fsLit "TICK_ALLOC_PRIM", \[hdr,goods,slop] ->
@@ -1336,6 +1337,10 @@ emitPushUpdateFrame :: CmmExpr -> CmmExpr -> FCode ()
emitPushUpdateFrame sp e = do
emitUpdateFrame sp mkUpdInfoLabel e
+emitPushBHUpdateFrame :: CmmExpr -> CmmExpr -> FCode ()
+emitPushBHUpdateFrame sp e = do
+ emitUpdateFrame sp mkBHUpdInfoLabel e
+
pushStackFrame :: [CmmParse CmmExpr] -> CmmParse () -> CmmParse ()
pushStackFrame fields body = do
profile <- getProfile
=====================================
compiler/GHC/Driver/Main.hs
=====================================
@@ -102,7 +102,6 @@ module GHC.Driver.Main
, dumpIfaceStats
, ioMsgMaybe
, showModuleIndex
- , hscAddSptEntries
, writeInterfaceOnlyMode
, loadByteCode
, genModDetails
@@ -2515,9 +2514,6 @@ hscParsedDecls hsc_env decls = runInteractiveHsc hsc_env $ do
let src_span = srcLocSpan interactiveSrcLoc
_ <- liftIO $ loadDecls interp hsc_env src_span linkable
- {- Load static pointer table entries -}
- liftIO $ hscAddSptEntries hsc_env (cg_spt_entries tidy_cg)
-
let tcs = filterOut isImplicitTyCon (mg_tcs simpl_mg)
patsyns = mg_patsyns simpl_mg
@@ -2539,18 +2535,6 @@ hscParsedDecls hsc_env decls = runInteractiveHsc hsc_env $ do
fam_insts defaults fix_env
return (new_tythings, new_ictxt)
--- | Load the given static-pointer table entries into the interpreter.
--- See Note [Grand plan for static forms] in "GHC.Iface.Tidy.StaticPtrTable".
-hscAddSptEntries :: HscEnv -> [SptEntry] -> IO ()
-hscAddSptEntries hsc_env entries = do
- let interp = hscInterp hsc_env
- let add_spt_entry :: SptEntry -> IO ()
- add_spt_entry (SptEntry n fpr) = do
- -- These are only names from the current module
- (val, _, _) <- loadName interp hsc_env n
- addSptEntry interp fpr val
- mapM_ add_spt_entry entries
-
{-
Note [Fixity declarations in GHCi]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
=====================================
compiler/GHC/Driver/Make.hs
=====================================
@@ -56,8 +56,6 @@ import GHC.Tc.Utils.Monad ( initIfaceCheck, concatMapM )
import GHC.Runtime.Interpreter
import qualified GHC.Linker.Loader as Linker
-import GHC.Linker.Types
-
import GHC.Driver.Config.Diagnostic
import GHC.Driver.Pipeline
@@ -72,8 +70,6 @@ import GHC.Driver.MakeSem
import GHC.Driver.Downsweep
import GHC.Driver.MakeAction
-import GHC.ByteCode.Types
-
import GHC.Iface.Load ( cannotFindModule, readIface )
import GHC.IfaceToCore ( typecheckIface )
import GHC.Iface.Recomp ( RecompileRequired(..), CompileReason(..) )
@@ -1232,31 +1228,9 @@ upsweep_mod :: HscEnv
upsweep_mod hsc_env mHscMessage old_hmi summary mod_index nmods = do
hmi <- compileOne' mHscMessage hsc_env summary
mod_index nmods (hm_iface <$> old_hmi) (maybe emptyHomeModInfoLinkable hm_linkable old_hmi)
-
- -- MP: This is a bit janky, because before you add the entries you have to extend the HPT with the module
- -- you just compiled. Another option, would be delay adding anything until after upsweep has finished, but I
- -- am unsure if this is sound (wrt running TH splices for example).
- -- This function only does anything if the linkable produced is a BCO, which
- -- used to only happen with the bytecode backend, but with
- -- @-fprefer-byte-code@, @HomeModInfo@ has bytecode even when generating
- -- object code, see #25230.
hscInsertHPT hmi hsc_env
- addSptEntries (hsc_env)
- (homeModInfoByteCode hmi)
-
return hmi
--- | Add the entries from a BCO linkable to the SPT table, see
--- See Note [Grand plan for static forms] in GHC.Iface.Tidy.StaticPtrTable.
-addSptEntries :: HscEnv -> Maybe Linkable -> IO ()
-addSptEntries hsc_env mlinkable =
- hscAddSptEntries hsc_env
- [ spt
- | linkable <- maybeToList mlinkable
- , bco <- linkableBCOs linkable
- , spt <- bc_spt_entries bco
- ]
-
-- Note [When source is considered modified]
-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
=====================================
compiler/GHC/Driver/Session.hs
=====================================
@@ -3763,12 +3763,17 @@ makeDynFlagsConsistent dflags
-- only supports dynamic code
| LinkInMemory <- ghcLink dflags
, sTargetRTSLinkerOnlySupportsSharedLibs $ settings dflags
+#if defined(HAVE_INTERNAL_INTERPRETER)
+ , not (ways dflags `hasWay` WayDyn)
+#else
, not (ways dflags `hasWay` WayDyn && gopt Opt_ExternalInterpreter dflags)
+#endif
= flip loopNoWarn "Forcing dynamic way because target RTS linker only supports dynamic code" $
- -- See checkOptions, -fexternal-interpreter is
- -- required when using --interactive with a non-standard
- -- way (-prof, -static, or -dynamic).
+#if !defined(HAVE_INTERNAL_INTERPRETER)
+ -- Force -fexternal-interpreter if internal-interpreter is not
+ -- available at this stage
setGeneralFlag' Opt_ExternalInterpreter $
+#endif
addWay' WayDyn dflags
| LinkInMemory <- ghcLink dflags
=====================================
compiler/GHC/Iface/Tidy/StaticPtrTable.hs
=====================================
@@ -124,7 +124,7 @@ Here is a running example:
* If we are compiling for the byte-code interpreter, we instead explicitly add
the SPT entries (recorded in CgGuts' cg_spt_entries field) to the interpreter
process' SPT table using the addSptEntry interpreter message. This happens
- in upsweep after we have compiled the module (see GHC.Driver.Make.upsweep').
+ when the bytecode object is linked in `dynLinkBCOs`.
-}
import GHC.Prelude
=====================================
compiler/GHC/Linker/Loader.hs
=====================================
@@ -718,6 +718,7 @@ loadDecls interp hsc_env span linkable = do
let ce2 = extendClosureEnv (closure_env le2) nms_fhvs
!pls2 = pls { linker_env = le2 { closure_env = ce2 }
, linked_breaks = lb2 }
+ mapM_ (linkSptEntry interp ce2) (concatMap bc_spt_entries cbcs)
return (pls2, (nms_fhvs, links_needed, units_needed))
where
cbcs = linkableBCOs linkable
@@ -951,10 +952,28 @@ dynLinkBCOs interp pls bcos = do
-- Wrap finalizers on the ones we want to keep
new_binds <- makeForeignNamedHValueRefs interp to_add
+
let ce2 = extendClosureEnv (closure_env le2) new_binds
+
+ -- Add SPT entries
+ mapM_ (linkSptEntry interp ce2) (concatMap bc_spt_entries cbcs)
+
return $! pls1 { linker_env = le2 { closure_env = ce2 }
, linked_breaks = lb2 }
+-- | Register SPT entries for this module in the interpreter
+-- Assumes that the name from the SPT has already been loaded into the interpreter.
+linkSptEntry :: Interp -> ClosureEnv -> SptEntry -> IO ()
+linkSptEntry interp ce (SptEntry name fpr) = do
+ case lookupNameEnv ce name of
+ -- The SPT entries only point to locally defined names, which should have already been
+ -- loaded into the interpreter before this function is called.
+ Nothing -> pprPanic "linkSptEntry" (ppr name)
+ Just (_, hval) -> addSptEntry interp fpr hval
+
+
+
+
-- Link a bunch of BCOs and return references to their values
linkSomeBCOs :: Interp
-> PkgsLoaded
@@ -1614,6 +1633,9 @@ gccSearchDirCache = unsafePerformIO $ newIORef []
-- which dominate a large percentage of startup time on Windows.
getGccSearchDirectory :: Logger -> DynFlags -> String -> IO [FilePath]
getGccSearchDirectory logger dflags key = do
+#if defined(wasm32_HOST_ARCH)
+ pure []
+#else
cache <- readIORef gccSearchDirCache
case lookup key cache of
Just x -> return x
@@ -1640,6 +1662,7 @@ getGccSearchDirectory logger dflags key = do
x:_ -> case break (=='=') x of
(_ , []) -> []
(_, (_:xs)) -> xs
+#endif
-- | Get a list of system search directories, this to alleviate pressure on
-- the findSysDll function.
=====================================
compiler/GHC/Runtime/Interpreter/Types.hs
=====================================
@@ -214,7 +214,7 @@ data JSInterpConfig = JSInterpConfig
data WasmInterpConfig = WasmInterpConfig
{ wasmInterpDyLD :: !FilePath -- ^ Location of dyld.mjs script
- , wasmInterpLibDir :: FilePath -- ^ wasi-sdk sysroot libdir containing libc.so, etc
+ , wasmInterpLibDir :: !FilePath -- ^ wasi-sdk sysroot libdir containing libc.so, etc
, wasmInterpOpts :: ![String] -- ^ Additional command line arguments for iserv
-- wasm ghci browser mode
=====================================
configure.ac
=====================================
@@ -448,11 +448,6 @@ AC_SUBST([CmmCPPCmd])
AC_SUBST([CmmCPPArgs])
AC_SUBST([CmmCPPSupportsG0])
-FP_SET_CFLAGS_C99([CC],[CFLAGS],[CPPFLAGS])
-FP_SET_CFLAGS_C99([CC_STAGE0],[CONF_CC_OPTS_STAGE0],[CONF_CPP_OPTS_STAGE0])
-FP_SET_CFLAGS_C99([CC],[CONF_CC_OPTS_STAGE1],[CONF_CPP_OPTS_STAGE1])
-FP_SET_CFLAGS_C99([CC],[CONF_CC_OPTS_STAGE2],[CONF_CPP_OPTS_STAGE2])
-
dnl ** Do we have a compatible emsdk version?
dnl --------------------------------------------------------------
EMSDK_VERSION("3.1.20", "", "")
=====================================
distrib/configure.ac.in
=====================================
@@ -163,11 +163,6 @@ AC_SUBST([CmmCPPCmd])
AC_SUBST([CmmCPPArgs])
AC_SUBST([CmmCPPSupportsG0])
-FP_SET_CFLAGS_C99([CC],[CFLAGS],[CPPFLAGS])
-dnl FP_SET_CFLAGS_C99([CC_STAGE0],[CONF_CC_OPTS_STAGE0],[CONF_CPP_OPTS_STAGE0])
-FP_SET_CFLAGS_C99([CC],[CONF_CC_OPTS_STAGE1],[CONF_CPP_OPTS_STAGE1])
-FP_SET_CFLAGS_C99([CC],[CONF_CC_OPTS_STAGE2],[CONF_CPP_OPTS_STAGE2])
-
dnl ** Which ld to use?
dnl --------------------------------------------------------------
FIND_LD([$target],[GccUseLdOpt])
=====================================
hadrian/src/Settings/Packages.hs
=====================================
@@ -82,15 +82,18 @@ packageArgs = do
]
, builder (Cabal Flags) ? mconcat
- -- For the ghc library, internal-interpreter only makes
- -- sense when we're not cross compiling. For cross GHC,
- -- external interpreter is used for loading target code
- -- and internal interpreter is supposed to load native
- -- code for plugins (!7377), however it's unfinished work
- -- (#14335) and completely untested in CI for cross
- -- backends at the moment, so we might as well disable it
- -- for cross GHC.
- [ andM [expr (ghcWithInterpreter stage), notCross] `cabalFlag` "internal-interpreter"
+ -- In order to enable internal-interpreter for the ghc
+ -- library:
+ --
+ -- 1. ghcWithInterpreter must be True ("Use interpreter" =
+ -- "YES")
+ -- 2. For non-cross case it can be enabled
+ -- 3. For cross case, disable for stage0 since that runs
+ -- on the host and must rely on external interpreter to
+ -- load target code, otherwise enable for stage1 since
+ -- that runs on the target and can use target's own
+ -- ghci object linker
+ [ andM [expr (ghcWithInterpreter stage), orM [notCross, stage1]] `cabalFlag` "internal-interpreter"
, orM [ notM cross, haveCurses ] `cabalFlag` "terminfo"
, arg "-build-tool-depends"
, flag UseLibzstd `cabalFlag` "with-libzstd"
=====================================
libraries/ghci/GHCi/ObjLink.hs
=====================================
@@ -113,8 +113,7 @@ foreign import javascript unsafe "__ghc_wasm_jsffi_dyld.lookupSymbol($1)"
js_lookupSymbol :: JSString -> IO (Ptr a)
lookupSymbolInDLL :: Ptr LoadedDLL -> String -> IO (Maybe (Ptr a))
-lookupSymbolInDLL _ sym =
- throwIO $ ErrorCall $ "lookupSymbolInDLL: unsupported on wasm for " <> sym
+lookupSymbolInDLL _ _ = pure Nothing
resolveObjs :: IO Bool
resolveObjs = pure True
=====================================
m4/fp_cmm_cpp_cmd_with_args.m4
=====================================
@@ -56,27 +56,6 @@ else
AC_MSG_RESULT([no])
fi
-AC_MSG_CHECKING([the C-- preprocessor for C99 support])
-cat > conftest.c <