[Git][ghc/ghc][wip/wasm-internal-interpreter] 2 commits: hadrian/compiler: enable internal-interpreter for ghc library in wasm stage1
Cheng Shao pushed to branch wip/wasm-internal-interpreter at Glasgow Haskell Compiler / GHC Commits: f94817b6 by Cheng Shao at 2025-09-29T14:15:26+02: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. - - - - - f00f557d by Cheng Shao at 2025-09-29T14:15:35+02: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. - - - - - 8 changed files: - compiler/GHC.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Linker/Loader.hs - compiler/GHC/Runtime/Interpreter/Types.hs - hadrian/src/Settings/Packages.hs - + testsuite/tests/ghci-wasm/T26431.hs - + testsuite/tests/ghci-wasm/T26431.stdout - testsuite/tests/ghci-wasm/all.T 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/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/Linker/Loader.hs ===================================== @@ -1564,6 +1564,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 @@ -1590,6 +1593,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 ===================================== 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" ===================================== testsuite/tests/ghci-wasm/T26431.hs ===================================== @@ -0,0 +1,35 @@ +import Control.Exception +import Control.Monad.IO.Class +import Data.Maybe +import GHC +import GHC.Plugins +import GHC.Runtime.Interpreter +import System.Environment.Blank + +main :: IO () +main = do + [libdir] <- getArgs + defaultErrorHandler defaultFatalMessager defaultFlushOut $ + runGhc (Just libdir) $ + do + dflags0 <- getSessionDynFlags + let dflags1 = + dflags0 + { ghcMode = CompManager, + backend = interpreterBackend, + ghcLink = LinkInMemory + } + logger <- getLogger + (dflags2, _, _) <- + parseDynamicFlags logger dflags1 $ + map noLoc ["-package", "ghc"] + _ <- setSessionDynFlags dflags2 + addTarget =<< guessTarget "hello.hs" Nothing Nothing + _ <- load LoadAllTargets + setContext + [ IIDecl $ simpleImportDecl $ mkModuleName "Prelude", + IIDecl $ simpleImportDecl $ mkModuleName "Main" + ] + hsc_env <- getSession + fhv <- compileExprRemote "main" + liftIO $ evalIO (fromJust $ hsc_interp hsc_env) fhv ===================================== testsuite/tests/ghci-wasm/T26431.stdout ===================================== @@ -0,0 +1 @@ +main = putStrLn "hello world" ===================================== testsuite/tests/ghci-wasm/all.T ===================================== @@ -10,3 +10,11 @@ test('T26430', [ extra_hc_opts('-L. -lT26430B')] , compile_and_run, [''] ) + +test('T26431', [ + extra_files(['../../../.gitlab/hello.hs']), + extra_hc_opts('-package ghc'), + extra_run_opts(f'"{config.libdir}"'), + ignore_stderr] +, compile_and_run, [''] +) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/32ffe4e29fa236af908cd0949e2f980... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/32ffe4e29fa236af908cd0949e2f980... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Cheng Shao (@TerrorJack)