Cheng Shao pushed to branch wip/wasm-dyld-pie at Glasgow Haskell Compiler / GHC Commits: 91b6be10 by Julian Ospald at 2025-10-20T18:21:03-04:00 Improve error handling in 'getPackageArchives' When the library dirs in the package conf files are not set up correctly, the JS linker will happily ignore such packages and not link against them, although they're part of the link plan. Fixes #26383 - - - - - 6c5269da by Sven Tennie at 2025-10-20T18:21:44-04:00 Align coding style Improve readability by using the same style for all constructor calls in this function. - - - - - 3d305889 by Sven Tennie at 2025-10-20T18:21:44-04:00 Reduce complexity by removing joins with mempty ldArgs, cArgs and cppArgs are all `mempty`. Thus concatenating them adds nothing but some complexity while reading the code. - - - - - 647d3b9c by Cheng Shao at 2025-10-24T13:13:48+02:00 wasm: reformat dyld source code This commit reformats dyld source code with prettier, to avoid introducing unnecessary diffs in subsequent patches when they're formatted before committing. - - - - - a13ec8dd by Cheng Shao at 2025-10-24T13:13:48+02:00 wasm: simplify _initialize logic in dyld This commit simplifies how we _initialize a wasm shared library in dyld and removes special treatment for libc.so, see added comment for detailed explanation. - - - - - 8 changed files: - compiler/GHC/StgToJS/Linker/Linker.hs - hadrian/src/Rules/Gmp.hs - hadrian/src/Rules/Libffi.hs - hadrian/src/Settings/Builders/Cabal.hs - hadrian/src/Settings/Builders/Common.hs - hadrian/src/Settings/Builders/DeriveConstants.hs - hadrian/src/Settings/Builders/Hsc2Hs.hs - utils/jsffi/dyld.mjs Changes: ===================================== compiler/GHC/StgToJS/Linker/Linker.hs ===================================== @@ -2,6 +2,7 @@ {-# LANGUAGE TupleSections #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE BlockArguments #-} +{-# LANGUAGE MultiWayIf #-} ----------------------------------------------------------------------------- -- | @@ -666,12 +667,19 @@ renderLinkerStats s = getPackageArchives :: StgToJSConfig -> UnitEnv -> [UnitId] -> IO [FilePath] -getPackageArchives cfg unit_env units = - filterM doesFileExist [ ST.unpack p > "lib" ++ ST.unpack l ++ profSuff <.> "a" - | u <- units - , p <- getInstalledPackageLibDirs ue_state u - , l <- getInstalledPackageHsLibs ue_state u - ] +getPackageArchives cfg unit_env units = do + fmap concat $ forM units $ \u -> do + let archives = [ ST.unpack p > "lib" ++ ST.unpack l ++ profSuff <.> "a" + | p <- getInstalledPackageLibDirs ue_state u + , l <- getInstalledPackageHsLibs ue_state u + ] + foundArchives <- filterM doesFileExist archives + if | not (null archives) + , null foundArchives + -> do + throwGhcExceptionIO (InstallationError $ "Could not find any library archives for unit-id: " <> (renderWithContext (csContext cfg) $ ppr u)) + | otherwise + -> pure foundArchives where ue_state = ue_homeUnitState unit_env ===================================== hadrian/src/Rules/Gmp.hs ===================================== @@ -11,7 +11,7 @@ import Target import Utilities import Hadrian.BuildPath import Hadrian.Expression -import Settings.Builders.Common (cArgs, getStagedCCFlags) +import Settings.Builders.Common (getStagedCCFlags) -- | Build in-tree GMP library objects (if GmpInTree flag is set) and return -- their paths. @@ -125,8 +125,7 @@ gmpRules = do cFlags <- interpretInContext ctx $ mconcat - [ cArgs - , getStagedCCFlags + [ getStagedCCFlags -- gmp symbols are only used by bignum logic in -- ghc-internal and shouldn't be exported by the -- ghc-internal shared library. ===================================== hadrian/src/Rules/Libffi.hs ===================================== @@ -130,17 +130,14 @@ fixLibffiMakefile top = configureEnvironment :: Stage -> Action [CmdOption] configureEnvironment stage = do context <- libffiContext stage - cFlags <- interpretInContext context $ mconcat - [ cArgs - , getStagedCCFlags ] - ldFlags <- interpretInContext context ldArgs + cFlags <- interpretInContext context getStagedCCFlags sequence [ builderEnvironment "CC" $ Cc CompileC stage , builderEnvironment "CXX" $ Cc CompileC stage - , builderEnvironment "AR" (Ar Unpack stage) + , builderEnvironment "AR" $ Ar Unpack stage , builderEnvironment "NM" Nm , builderEnvironment "RANLIB" Ranlib , return . AddEnv "CFLAGS" $ unwords cFlags ++ " -w" - , return . AddEnv "LDFLAGS" $ unwords ldFlags ++ " -w" ] + , return . AddEnv "LDFLAGS" $ "-w" ] -- Need the libffi archive and `trackAllow` all files in the build directory. -- See [Libffi indicating inputs]. ===================================== hadrian/src/Settings/Builders/Cabal.hs ===================================== @@ -188,18 +188,16 @@ configureArgs cFlags' ldFlags' = do values <- unwords <$> expr not (null values) ? arg ("--configure-option=" ++ key ++ "=" ++ values) - cFlags = mconcat [ remove ["-Werror"] cArgs - , getStagedCCFlags + cFlags = mconcat [ getStagedCCFlags -- See https://github.com/snowleopard/hadrian/issues/523 , arg $ "-iquote" , arg $ top -/- pkgPath pkg , cFlags' ] - ldFlags = ldArgs <> ldFlags' mconcat [ conf "CFLAGS" cFlags - , conf "LDFLAGS" ldFlags + , conf "LDFLAGS" ldFlags' , conf "--with-iconv-includes" $ arg =<< getSetting IconvIncludeDir , conf "--with-iconv-libraries" $ arg =<< getSetting IconvLibDir , conf "--with-gmp-includes" $ arg =<< getSetting GmpIncludeDir ===================================== hadrian/src/Settings/Builders/Common.hs ===================================== @@ -5,7 +5,7 @@ module Settings.Builders.Common ( module Oracles.Setting, module Settings, module UserSettings, - cIncludeArgs, ldArgs, cArgs, cppArgs, cWarnings, + cIncludeArgs, cWarnings, packageDatabaseArgs, bootPackageDatabaseArgs, getStagedCCFlags, wayCcArgs ) where @@ -38,15 +38,6 @@ cIncludeArgs = do , pure [ "-I" ++ pkgPath pkg -/- dir | dir <- incDirs ] , pure [ "-I" ++ unifyPath dir | dir <- depDirs ] ] -ldArgs :: Args -ldArgs = mempty - -cArgs :: Args -cArgs = mempty - -cppArgs :: Args -cppArgs = mempty - -- TODO: should be in a different file cWarnings :: Args cWarnings = mconcat ===================================== hadrian/src/Settings/Builders/DeriveConstants.hs ===================================== @@ -40,8 +40,7 @@ includeCcArgs :: Args includeCcArgs = do stage <- getStage rtsPath <- expr $ rtsBuildPath stage - mconcat [ cArgs - , cWarnings + mconcat [ cWarnings , prgFlags . ccProgram . tgtCCompiler <$> expr (targetStage Stage1) , queryTargetTarget tgtUnregisterised ? arg "-DUSE_MINIINTERPRETER" , arg "-Irts" ===================================== hadrian/src/Settings/Builders/Hsc2Hs.hs ===================================== @@ -50,7 +50,7 @@ getCFlags = do autogen <- expr $ autogenPath context let cabalMacros = autogen -/- "cabal_macros.h" expr $ need [cabalMacros] - mconcat [ remove ["-O"] (cArgs <> getStagedCCFlags) + mconcat [ remove ["-O"] getStagedCCFlags -- Either "-E" is not part of the configured cpp args, or we can't add those args to invocations of things like this -- ROMES:TODO: , prgFlags . cppProgram . tgtCPreprocessor <$> getStagedTargetConfig , cIncludeArgs @@ -64,6 +64,5 @@ getCFlags = do getLFlags :: Expr [String] getLFlags = mconcat [ prgFlags . ccLinkProgram . tgtCCompilerLink <$> getStagedTarget - , ldArgs , getContextData ldOpts , getContextData depLdOpts ] ===================================== utils/jsffi/dyld.mjs ===================================== @@ -834,6 +834,27 @@ class DyLD { ); } + // Both wasi implementations we use provide + // wasi.initialize(instance) to initialize a wasip1 reactor + // module. However, instance does not really need to be a + // WebAssembly.Instance object; the wasi implementations only need + // to access instance.exports.memory for the wasi syscalls to + // work. + // + // Given we'll reuse the same wasi object across different + // WebAssembly.Instance objects anyway and + // wasi.initialize(instance) can't be called more than once, we + // use this simple trick and pass a fake instance object that + // contains just enough info for the wasi implementation to + // initialize its internal state. Later when we load each wasm + // shared library, we can just manually invoke their + // initialization functions. + this.#wasi.initialize({ + exports: { + memory: this.#memory, + }, + }); + // Keep this in sync with rts/wasm/Wasm.S! for (let i = 1; i <= 10; ++i) { this.#regs[`__R${i}`] = new WebAssembly.Global({ @@ -930,10 +951,15 @@ class DyLD { async loadDLLs(packed) { // Normalize input to an array of strings. When called from Haskell // we pass a single JSString containing NUL-separated paths. - const paths = (typeof packed === "string" - ? (packed.length === 0 ? [] : packed.split("\0")) - : [packed] // tolerate an accidental single path object - ).filter((s) => s.length > 0).reverse(); + const paths = ( + typeof packed === "string" + ? packed.length === 0 + ? [] + : packed.split("\0") + : [packed] + ) // tolerate an accidental single path object + .filter((s) => s.length > 0) + .reverse(); // Compute a single downsweep plan for the whole batch. // Note: #downsweep mutates #loadedSos to break cycles and dedup. @@ -1154,22 +1180,6 @@ class DyLD { throw new Error(`cannot handle export ${k} ${v}`); } - // We call wasi.initialize when loading libc.so, then reuse the - // wasi instance globally. When loading later .so files, just - // manually invoke _initialize(). - if (soname === "libc.so") { - instance.exports.__wasm_apply_data_relocs(); - // wasm-ld forbits --export-memory with --shared, I don't know - // why but this is sufficient to make things work - this.#wasi.initialize({ - exports: { - memory: this.#memory, - _initialize: instance.exports._initialize, - }, - }); - continue; - } - // See // https://gitlab.haskell.org/haskell-wasm/llvm-project/-/blob/release/21.x/lld..., // __wasm_apply_data_relocs is now optional so only call it if @@ -1180,7 +1190,7 @@ class DyLD { // been called upon instantiation, see // Writer::createStartFunction(). if (instance.exports.__wasm_apply_data_relocs) { - instance.exports.__wasm_apply_data_relocs(); + instance.exports.__wasm_apply_data_relocs(); } instance.exports._initialize(); View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b5d2ee34d0686c7f599218a1f0006e7... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b5d2ee34d0686c7f599218a1f0006e7... You're receiving this email because of your account on gitlab.haskell.org.