[Git][ghc/ghc][wip/romes/T26166] 3 commits: Move atomic.c from ghc-internal to rts
by Rodrigo Mesquita (@alt-romes) 29 Sep '25
by Rodrigo Mesquita (@alt-romes) 29 Sep '25
29 Sep '25
Rodrigo Mesquita pushed to branch wip/romes/T26166 at Glasgow Haskell Compiler / GHC
Commits:
8914693f by Rodrigo Mesquita at 2025-09-29T19:30:55+01:00
Move atomic.c from ghc-internal to rts
- - - - -
6445ca93 by Rodrigo Mesquita at 2025-09-29T22:18:41+01:00
Fix link failure in Cabal check assertion due to -u[_]init_ghc_hs_iface bc lack of definition and because -u<sym> -U<sym> does not work to allow the symbol to be undefined. brilliant...
- - - - -
b1446914 by Rodrigo Mesquita at 2025-09-29T22:19:42+01:00
fixup! Drop all undefined dynamic_lookup hacks
- - - - -
5 changed files:
- hadrian/src/Hadrian/Haskell/Cabal/Parse.hs
- libraries/ghc-internal/ghc-internal.cabal.in
- + libraries/ghc-internal/include/RtsIfaceStub.h
- libraries/ghc-internal/cbits/atomic.c → rts/prim/atomic.c
- rts/rts.cabal
Changes:
=====================================
hadrian/src/Hadrian/Haskell/Cabal/Parse.hs
=====================================
@@ -184,7 +184,7 @@ configurePackage context@Context {..} = do
trackArgsHash (target context (Cabal Setup stage) [] [])
verbosity <- getVerbosity
let v = shakeVerbosityToCabalFlag verbosity
- argList' = argList ++ ["--flags=" ++ unwords flagList, "-v3"]
+ argList' = argList ++ ["--flags=" ++ unwords flagList, v]
when (verbosity >= Verbose) $
putProgressInfo $ "| Package " ++ quote (pkgName package) ++ " configuration flags: " ++ unwords argList'
=====================================
libraries/ghc-internal/ghc-internal.cabal.in
=====================================
@@ -433,7 +433,11 @@ Library
if !arch(javascript)
-- See Note [RTS/ghc-internal interface].
- ld-options: -uinit_ghc_hs_iface
+ if os(darwin)
+ -- Leading underscores on symbols on darwin
+ ld-options: -u_init_ghc_hs_iface
+ else
+ ld-options: -uinit_ghc_hs_iface
-- To maximize usability
cc-options: -fPIC
c-sources:
@@ -447,7 +451,7 @@ Library
cbits/sysconf.c
cbits/fs.c
cbits/strerror.c
- cbits/atomic.c
+ -- cbits/atomic.c
cbits/bswap.c
cbits/bitrev.c
cbits/clz.c
@@ -481,6 +485,7 @@ Library
include-dirs: include
includes:
HsBase.h
+ RtsIfaceStub.h
install-includes:
HsBase.h
consUtils.h
=====================================
libraries/ghc-internal/include/RtsIfaceStub.h
=====================================
@@ -0,0 +1,4 @@
+#include <stdio.h>
+void __attribute__((weak)) init_ghc_hs_iface(void) {
+ fprintf(stderr, "init_ghc_hs_iface: weak constructor stub for init_ghc_hs_iface was not overriden by the actual constructor. Obviously wrong! This stub should never make it into the final object except for in the Cabal checkForeignDeps configuration checks!");
+};
=====================================
libraries/ghc-internal/cbits/atomic.c → rts/prim/atomic.c
=====================================
=====================================
rts/rts.cabal
=====================================
@@ -526,6 +526,7 @@ library
sm/Storage.c
sm/Sweep.c
fs.c
+ prim/atomic.c
-- I wish we had wildcards..., this would be:
-- *.c hooks/**/*.c sm/**/*.c eventlog/**/*.c linker/**/*.c
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4d62599a1232ecc8ff54192df31b43…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4d62599a1232ecc8ff54192df31b43…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/jeltsch/querying-newline-modes] Add an operation `System.IO.hGetNewlineMode`
by Wolfgang Jeltsch (@jeltsch) 29 Sep '25
by Wolfgang Jeltsch (@jeltsch) 29 Sep '25
29 Sep '25
Wolfgang Jeltsch pushed to branch wip/jeltsch/querying-newline-modes at Glasgow Haskell Compiler / GHC
Commits:
29c804df by Wolfgang Jeltsch at 2025-09-29T23:28:11+03:00
Add an operation `System.IO.hGetNewlineMode`
This commit also contains some small code and documentation changes for
related operations, for the sake of consistency.
- - - - -
4 changed files:
- libraries/base/changelog.md
- libraries/base/src/System/IO.hs
- libraries/ghc-internal/src/GHC/Internal/IO/Handle.hs
- libraries/ghc-internal/src/GHC/Internal/System/IO.hs
Changes:
=====================================
libraries/base/changelog.md
=====================================
@@ -10,6 +10,7 @@
* Fix bug where `naturalAndNot` was incorrectly truncating results ([CLC proposal #350](github.com/haskell/core-libraries-committee/issues/350))
* Remove extra laziness from `Data.Bifunctor.Bifunctor` instances for all tuples to have the same laziness as their `Data.Functor.Functor` counterparts (i.e. they became more strict than before) ([CLC proposal #339](https://github.com/haskell/core-libraries-committee/issues/339))
* Adjust the strictness of `Data.List.iterate'` to be more reasonable: every element of the output list is forced to WHNF when the `(:)` containing it is forced. ([CLC proposal #335)](https://github.com/haskell/core-libraries-committee/issues/335)
+ * Add `System.IO.hGetNewlineMode` ([CLC proposal #370](https://github.com/haskell/core-libraries-committee/issues/370))
## 4.22.0.0 *TBA*
* Shipped with GHC 9.14.1
=====================================
libraries/base/src/System/IO.hs
=====================================
@@ -175,6 +175,7 @@ module System.IO
-- Binary-mode 'Handle's do no newline translation at all.
hSetNewlineMode,
+ hGetNewlineMode,
Newline(..),
nativeNewline,
NewlineMode(..),
=====================================
libraries/ghc-internal/src/GHC/Internal/IO/Handle.hs
=====================================
@@ -40,7 +40,7 @@ module GHC.Internal.IO.Handle (
hIsOpen, hIsClosed, hIsReadable, hIsWritable, hGetBuffering, hIsSeekable,
hSetEcho, hGetEcho, hIsTerminalDevice,
- hSetNewlineMode, Newline(..), NewlineMode(..), nativeNewline,
+ hSetNewlineMode, hGetNewlineMode, Newline(..), NewlineMode(..), nativeNewline,
noNewlineTranslation, universalNewlineMode, nativeNewlineMode,
hShow,
@@ -238,7 +238,7 @@ hSetBuffering handle mode =
return Handle__{ haBufferMode = mode,.. }
-- -----------------------------------------------------------------------------
--- hSetEncoding
+-- Setting and getting the text encoding
-- | The action 'hSetEncoding' @hdl@ @encoding@ changes the text encoding
-- for the handle @hdl@ to @encoding@. The default encoding when a 'Handle' is
@@ -624,16 +624,22 @@ hSetBinaryMode handle bin =
haOutputNL = outputNL nl, .. }
-- -----------------------------------------------------------------------------
--- hSetNewlineMode
+-- Setting and getting the newline mode
--- | Set the 'NewlineMode' on the specified 'Handle'. All buffered
+-- | Set the 'NewlineMode' for the specified 'Handle'. All buffered
-- data is flushed first.
hSetNewlineMode :: Handle -> NewlineMode -> IO ()
-hSetNewlineMode handle NewlineMode{ inputNL=i, outputNL=o } =
+hSetNewlineMode handle NewlineMode{..} =
withAllHandles__ "hSetNewlineMode" handle $ \h_@Handle__{} ->
do
flushBuffer h_
- return h_{ haInputNL=i, haOutputNL=o }
+ return h_{ haInputNL = inputNL, haOutputNL = outputNL }
+
+-- | Return the current 'NewlineMode' for the specified 'Handle'.
+hGetNewlineMode :: Handle -> IO NewlineMode
+hGetNewlineMode hdl =
+ withHandle_ "hGetNewlineMode" hdl $ \h_@Handle__{..} ->
+ return NewlineMode{ inputNL = haInputNL, outputNL = haOutputNL }
-- -----------------------------------------------------------------------------
-- Duplicating a Handle
=====================================
libraries/ghc-internal/src/GHC/Internal/System/IO.hs
=====================================
@@ -213,6 +213,7 @@ module GHC.Internal.System.IO (
-- Binary-mode 'Handle's do no newline translation at all.
--
hSetNewlineMode,
+ hGetNewlineMode,
Newline(..), nativeNewline,
NewlineMode(..),
noNewlineTranslation, universalNewlineMode, nativeNewlineMode,
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/29c804dfeaac158b68268889fe8588f…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/29c804dfeaac158b68268889fe8588f…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc] Pushed new branch wip/jeltsch/querying-newline-modes
by Wolfgang Jeltsch (@jeltsch) 29 Sep '25
by Wolfgang Jeltsch (@jeltsch) 29 Sep '25
29 Sep '25
Wolfgang Jeltsch pushed new branch wip/jeltsch/querying-newline-modes at Glasgow Haskell Compiler / GHC
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/jeltsch/querying-newline-modes
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 8 commits: Remove hptAllInstances usage during upsweep
by Marge Bot (@marge-bot) 29 Sep '25
by Marge Bot (@marge-bot) 29 Sep '25
29 Sep '25
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
0ddd0fdc by soulomoon at 2025-09-28T19:24:10-04:00
Remove hptAllInstances usage during upsweep
Previously, during the upsweep phase when
checking safe imports, we were loading the module
interface with runTcInteractive, which in turn calls
hptAllInstances. This accesses non-below modules
from the home package table.
Change the implementation of checkSafeImports
to use initTcWithGbl and loadSysInterface to load the
module interface, since we already have TcGblEnv at hand.
This eliminates the unnecessary use of runTcInteractive
and hptAllInstances during the upsweep phase.
- - - - -
e05c496c by Ben Gamari at 2025-09-28T19:24:59-04:00
base: Update changelog to reflect timing of IOPort# removal
This change will make 9.14 afterall.
- - - - -
bdc9d130 by Cheng Shao at 2025-09-28T19:25:45-04:00
rts: fix wasm JSFFI initialization constructor code
This commit fixes wasm JSFFI initialization constructor code so that
the constructor is self-contained and avoids invoking a fake
__main_argc_argv function. The previous approach of reusing
__main_void logic in wasi-libc saves a tiny bit of code, at the
expense of link-time trouble whenever GHC links a wasm module without
-no-hs-main, in which case the driver-generated main function would
clash with the definition here, resulting in a linker error. It's
simply better to avoid messing with the main function, and it would
additionally allow linking wasm32-wasi command modules that does make
use of synchronous JSFFI.
- - - - -
5d59fc8f by Cheng Shao at 2025-09-28T19:26:27-04:00
rts: provide stub implementations of ExecPage functions for wasm
This patch provides stub implementations of ExecPage functions for
wasm. They are never actually invoked at runtime for any non-TNTC
platform, yet they can cause link-time errors of missing symbols when
the GHCi.InfoTable module gets linked into the final wasm module (e.g.
a GHC API program).
- - - - -
a4d664c7 by Cheng Shao at 2025-09-29T17:29:22+02:00
compiler/ghci: replace the LoadDLL message with LoadDLLs
As a part of #25407, this commit changes the LoadDLL message to
LoadDLLs, which takes a list of DLL paths to load and returns the list
of remote pointer handles. The wasm dyld is refactored to take
advantage of LoadDLLs and harvest background parallelism. On other
platforms, LoadDLLs is based on a fallback codepath that does
sequential loading.
The driver is not actually emitting singular LoadDLLs message with
multiple DLLs yet, this is left in subsequent commits.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
c7fc4bae by Cheng Shao at 2025-09-29T17:29:22+02:00
driver: separate downsweep/upsweep phase in loadPackages'
This commit refactors GHC.Linker.Loader.loadPackages' to be separated
into downsweep/upsweep phases:
- The downsweep phase performs dependency analysis and generates a
list of topologically sorted packages to load
- The upsweep phase sequentially loads these packages by calling
loadPackage
This is a necessary refactoring to make it possible to make loading of
DLLs concurrent.
- - - - -
ab180104 by Cheng Shao at 2025-09-29T17:57:19+02:00
driver: emit single LoadDLLs message to load multiple DLLs
This commit refactors the driver so that it emits a single LoadDLLs
message to load multiple DLLs in GHC.Linker.Loader.loadPackages'.
Closes #25407.
-------------------------
Metric Increase:
MultiLayerModulesTH_OneShot
TcPlugin_RewritePerf
-------------------------
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
6bf800f3 by Sean D. Gillespie at 2025-09-29T15:35:41-04:00
Fix SIZED_BIN_OP_TY_INT casts in RTS interpreter
Correct `SIZED_BIN_OP_TY_INT` cast to integer. Previously, it cast
its second operand as its parameter `ty`. This does not currently
cause any issues, since we are only using it for bit shifts.
Fixes #26287
- - - - -
15 changed files:
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Plugins.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Linker/MacOS.hs
- compiler/GHC/Linker/Types.hs
- compiler/GHC/Runtime/Interpreter.hs
- libraries/base/changelog.md
- libraries/ghci/GHCi/Message.hs
- libraries/ghci/GHCi/ObjLink.hs
- libraries/ghci/GHCi/Run.hs
- rts/ExecPage.c
- rts/Interpreter.c
- rts/wasm/JSFFI.c
- testsuite/tests/rts/linker/T2615.hs
- utils/jsffi/dyld.mjs
Changes:
=====================================
compiler/GHC/Driver/Main.hs
=====================================
@@ -165,7 +165,7 @@ import GHC.JS.Syntax
import GHC.IfaceToCore ( typecheckIface, typecheckWholeCoreBindings )
-import GHC.Iface.Load ( ifaceStats, writeIface, flagsToIfCompression, getGhcPrimIface )
+import GHC.Iface.Load ( ifaceStats, writeIface, flagsToIfCompression, getGhcPrimIface, loadSysInterface )
import GHC.Iface.Make
import GHC.Iface.Recomp
import GHC.Iface.Tidy
@@ -1765,7 +1765,7 @@ hscCheckSafe' m l = do
-- so we need to call 'getModuleInterface' to load from disk
case iface of
Just _ -> return iface
- Nothing -> snd `fmap` (liftIO $ getModuleInterface hsc_env m)
+ Nothing -> liftIO $ initIfaceLoad hsc_env (Just <$> loadSysInterface (text "checkSafeImports") m)
-- | Check the list of packages are trusted.
=====================================
compiler/GHC/Driver/Plugins.hs
=====================================
@@ -421,7 +421,7 @@ loadExternalPlugins ps = do
loadExternalPluginLib :: FilePath -> IO ()
loadExternalPluginLib path = do
-- load library
- loadDLL path >>= \case
+ loadDLLs [path] >>= \case
Left errmsg -> pprPanic "loadExternalPluginLib"
(vcat [ text "Can't load plugin library"
, text " Library path: " <> text path
=====================================
compiler/GHC/Linker/Loader.hs
=====================================
@@ -1,6 +1,7 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE ViewPatterns #-}
--
-- (c) The University of Glasgow 2002-2006
@@ -535,7 +536,7 @@ preloadLib interp hsc_env lib_paths framework_paths pls lib_spec = do
return pls
DLL dll_unadorned -> do
- maybe_errstr <- loadDLL interp (platformSOName platform dll_unadorned)
+ maybe_errstr <- loadDLLs interp [platformSOName platform dll_unadorned]
case maybe_errstr of
Right _ -> maybePutStrLn logger "done"
Left mm | platformOS platform /= OSDarwin ->
@@ -545,14 +546,14 @@ preloadLib interp hsc_env lib_paths framework_paths pls lib_spec = do
-- since (apparently) some things install that way - see
-- ticket #8770.
let libfile = ("lib" ++ dll_unadorned) <.> "so"
- err2 <- loadDLL interp libfile
+ err2 <- loadDLLs interp [libfile]
case err2 of
Right _ -> maybePutStrLn logger "done"
Left _ -> preloadFailed mm lib_paths lib_spec
return pls
DLLPath dll_path -> do
- do maybe_errstr <- loadDLL interp dll_path
+ do maybe_errstr <- loadDLLs interp [dll_path]
case maybe_errstr of
Right _ -> maybePutStrLn logger "done"
Left mm -> preloadFailed mm lib_paths lib_spec
@@ -892,7 +893,7 @@ dynLoadObjs interp hsc_env pls@LoaderState{..} objs = do
-- if we got this far, extend the lifetime of the library file
changeTempFilesLifetime tmpfs TFL_GhcSession [soFile]
- m <- loadDLL interp soFile
+ m <- loadDLLs interp [soFile]
case m of
Right _ -> return $! pls { temp_sos = (libPath, libName) : temp_sos }
Left err -> linkFail msg (text err)
@@ -1129,51 +1130,91 @@ loadPackages interp hsc_env new_pkgs = do
loadPackages' :: Interp -> HscEnv -> [UnitId] -> LoaderState -> IO LoaderState
loadPackages' interp hsc_env new_pks pls = do
- pkgs' <- link (pkgs_loaded pls) new_pks
- return $! pls { pkgs_loaded = pkgs'
- }
+ (reverse -> pkgs_info_list, pkgs_almost_loaded) <-
+ downsweep
+ ([], pkgs_loaded pls)
+ new_pks
+ loaded_pkgs_info_list <- loadPackage interp hsc_env pkgs_info_list
+ evaluate $
+ pls
+ { pkgs_loaded =
+ foldl'
+ ( \pkgs (new_pkg_info, (hs_cls, extra_cls, loaded_dlls)) ->
+ adjustUDFM
+ ( \old_pkg_info ->
+ old_pkg_info
+ { loaded_pkg_hs_objs = hs_cls,
+ loaded_pkg_non_hs_objs = extra_cls,
+ loaded_pkg_hs_dlls = loaded_dlls
+ }
+ )
+ pkgs
+ (Packages.unitId new_pkg_info)
+ )
+ pkgs_almost_loaded
+ (zip pkgs_info_list loaded_pkgs_info_list)
+ }
where
- link :: PkgsLoaded -> [UnitId] -> IO PkgsLoaded
- link pkgs new_pkgs =
- foldM link_one pkgs new_pkgs
-
- link_one pkgs new_pkg
- | new_pkg `elemUDFM` pkgs -- Already linked
- = return pkgs
-
- | Just pkg_cfg <- lookupUnitId (hsc_units hsc_env) new_pkg
- = do { let deps = unitDepends pkg_cfg
- -- Link dependents first
- ; pkgs' <- link pkgs deps
- -- Now link the package itself
- ; (hs_cls, extra_cls, loaded_dlls) <- loadPackage interp hsc_env pkg_cfg
- ; let trans_deps = unionManyUniqDSets [ addOneToUniqDSet (loaded_pkg_trans_deps loaded_pkg_info) dep_pkg
- | dep_pkg <- deps
- , Just loaded_pkg_info <- pure (lookupUDFM pkgs' dep_pkg)
- ]
- ; return (addToUDFM pkgs' new_pkg (LoadedPkgInfo new_pkg hs_cls extra_cls loaded_dlls trans_deps)) }
-
- | otherwise
- = throwGhcExceptionIO (CmdLineError ("unknown package: " ++ unpackFS (unitIdFS new_pkg)))
-
-
-loadPackage :: Interp -> HscEnv -> UnitInfo -> IO ([LibrarySpec], [LibrarySpec], [RemotePtr LoadedDLL])
-loadPackage interp hsc_env pkg
+ -- The downsweep process takes an initial 'PkgsLoaded' and uses it
+ -- to memoize new packages to load when recursively downsweeping
+ -- the dependencies. The returned 'PkgsLoaded' is popularized with
+ -- placeholder 'LoadedPkgInfo' for new packages yet to be loaded,
+ -- which need to be modified later to fill in the missing fields.
+ --
+ -- The [UnitInfo] list is an accumulated *reverse* topologically
+ -- sorted list of new packages to load: 'downsweep_one' appends a
+ -- package to its head after that package's transitive
+ -- dependencies go into that list. There are no duplicate items in
+ -- this list due to memoization.
+ downsweep ::
+ ([UnitInfo], PkgsLoaded) -> [UnitId] -> IO ([UnitInfo], PkgsLoaded)
+ downsweep = foldlM downsweep_one
+
+ downsweep_one ::
+ ([UnitInfo], PkgsLoaded) -> UnitId -> IO ([UnitInfo], PkgsLoaded)
+ downsweep_one (pkgs_info_list, pkgs) new_pkg
+ | new_pkg `elemUDFM` pkgs = pure (pkgs_info_list, pkgs)
+ | Just new_pkg_info <- lookupUnitId (hsc_units hsc_env) new_pkg = do
+ let new_pkg_deps = unitDepends new_pkg_info
+ (pkgs_info_list', pkgs') <- downsweep (pkgs_info_list, pkgs) new_pkg_deps
+ let new_pkg_trans_deps =
+ unionManyUniqDSets
+ [ addOneToUniqDSet (loaded_pkg_trans_deps loaded_pkg_info) dep_pkg
+ | dep_pkg <- new_pkg_deps,
+ loaded_pkg_info <- maybeToList $ pkgs' `lookupUDFM` dep_pkg
+ ]
+ pure
+ ( new_pkg_info : pkgs_info_list',
+ addToUDFM pkgs' new_pkg $
+ LoadedPkgInfo
+ { loaded_pkg_uid = new_pkg,
+ loaded_pkg_hs_objs = [],
+ loaded_pkg_non_hs_objs = [],
+ loaded_pkg_hs_dlls = [],
+ loaded_pkg_trans_deps = new_pkg_trans_deps
+ }
+ )
+ | otherwise =
+ throwGhcExceptionIO
+ (CmdLineError ("unknown package: " ++ unpackFS (unitIdFS new_pkg)))
+
+loadPackage :: Interp -> HscEnv -> [UnitInfo] -> IO [([LibrarySpec], [LibrarySpec], [RemotePtr LoadedDLL])]
+loadPackage interp hsc_env pkgs
= do
let dflags = hsc_dflags hsc_env
let logger = hsc_logger hsc_env
platform = targetPlatform dflags
is_dyn = interpreterDynamic interp
- dirs | is_dyn = map ST.unpack $ Packages.unitLibraryDynDirs pkg
- | otherwise = map ST.unpack $ Packages.unitLibraryDirs pkg
+ dirs | is_dyn = [map ST.unpack $ Packages.unitLibraryDynDirs pkg | pkg <- pkgs]
+ | otherwise = [map ST.unpack $ Packages.unitLibraryDirs pkg | pkg <- pkgs]
- let hs_libs = map ST.unpack $ Packages.unitLibraries pkg
+ let hs_libs = [map ST.unpack $ Packages.unitLibraries pkg | pkg <- pkgs]
-- The FFI GHCi import lib isn't needed as
-- GHC.Linker.Loader + rts/Linker.c link the
-- interpreted references to FFI to the compiled FFI.
-- We therefore filter it out so that we don't get
-- duplicate symbol errors.
- hs_libs' = filter ("HSffi" /=) hs_libs
+ hs_libs' = filter ("HSffi" /=) <$> hs_libs
-- Because of slight differences between the GHC dynamic linker and
-- the native system linker some packages have to link with a
@@ -1182,53 +1223,62 @@ loadPackage interp hsc_env pkg
-- libs do not exactly match the .so/.dll equivalents. So if the
-- package file provides an "extra-ghci-libraries" field then we use
-- that instead of the "extra-libraries" field.
- extdeplibs = map ST.unpack (if null (Packages.unitExtDepLibsGhc pkg)
+ extdeplibs = [map ST.unpack (if null (Packages.unitExtDepLibsGhc pkg)
then Packages.unitExtDepLibsSys pkg
- else Packages.unitExtDepLibsGhc pkg)
- linkerlibs = [ lib | '-':'l':lib <- (map ST.unpack $ Packages.unitLinkerOptions pkg) ]
- extra_libs = extdeplibs ++ linkerlibs
+ else Packages.unitExtDepLibsGhc pkg) | pkg <- pkgs]
+ linkerlibs = [[ lib | '-':'l':lib <- (map ST.unpack $ Packages.unitLinkerOptions pkg) ] | pkg <- pkgs]
+ extra_libs = zipWith (++) extdeplibs linkerlibs
-- See Note [Fork/Exec Windows]
gcc_paths <- getGCCPaths logger dflags (platformOS platform)
- dirs_env <- addEnvPaths "LIBRARY_PATH" dirs
+ dirs_env <- traverse (addEnvPaths "LIBRARY_PATH") dirs
hs_classifieds
- <- mapM (locateLib interp hsc_env True dirs_env gcc_paths) hs_libs'
+ <- sequenceA [mapM (locateLib interp hsc_env True dirs_env_ gcc_paths) hs_libs'_ | (dirs_env_, hs_libs'_) <- zip dirs_env hs_libs' ]
extra_classifieds
- <- mapM (locateLib interp hsc_env False dirs_env gcc_paths) extra_libs
- let classifieds = hs_classifieds ++ extra_classifieds
+ <- sequenceA [mapM (locateLib interp hsc_env False dirs_env_ gcc_paths) extra_libs_ | (dirs_env_, extra_libs_) <- zip dirs_env extra_libs]
+ let classifieds = zipWith (++) hs_classifieds extra_classifieds
-- Complication: all the .so's must be loaded before any of the .o's.
- let known_hs_dlls = [ dll | DLLPath dll <- hs_classifieds ]
- known_extra_dlls = [ dll | DLLPath dll <- extra_classifieds ]
- known_dlls = known_hs_dlls ++ known_extra_dlls
+ let known_hs_dlls = [[ dll | DLLPath dll <- hs_classifieds_ ] | hs_classifieds_ <- hs_classifieds]
+ known_extra_dlls = [ dll | extra_classifieds_ <- extra_classifieds, DLLPath dll <- extra_classifieds_ ]
+ known_dlls = concat known_hs_dlls ++ known_extra_dlls
#if defined(CAN_LOAD_DLL)
- dlls = [ dll | DLL dll <- classifieds ]
+ dlls = [ dll | classifieds_ <- classifieds, DLL dll <- classifieds_ ]
#endif
- objs = [ obj | Objects objs <- classifieds
- , obj <- objs ]
- archs = [ arch | Archive arch <- classifieds ]
+ objs = [ obj | classifieds_ <- classifieds, Objects objs <- classifieds_
+ , obj <- objs]
+ archs = [ arch | classifieds_ <- classifieds, Archive arch <- classifieds_ ]
-- Add directories to library search paths
let dll_paths = map takeDirectory known_dlls
- all_paths = nub $ map normalise $ dll_paths ++ dirs
+ all_paths = nub $ map normalise $ dll_paths ++ concat dirs
all_paths_env <- addEnvPaths "LD_LIBRARY_PATH" all_paths
pathCache <- mapM (addLibrarySearchPath interp) all_paths_env
maybePutSDoc logger
- (text "Loading unit " <> pprUnitInfoForUser pkg <> text " ... ")
+ (text "Loading units " <> vcat (map pprUnitInfoForUser pkgs) <> text " ... ")
#if defined(CAN_LOAD_DLL)
- loadFrameworks interp platform pkg
+ forM_ pkgs $ loadFrameworks interp platform
-- See Note [Crash early load_dyn and locateLib]
-- Crash early if can't load any of `known_dlls`
- mapM_ (load_dyn interp hsc_env True) known_extra_dlls
- loaded_dlls <- mapMaybeM (load_dyn interp hsc_env True) known_hs_dlls
+ _ <- load_dyn interp hsc_env True known_extra_dlls
+
+ -- We pass [[FilePath]] of dlls to load and flattens the list
+ -- before doing a LoadDLLs. The returned list of RemotePtrs
+ -- would need to be regrouped to the same shape of the input
+ -- [[FilePath]], each group's [RemotePtr LoadedDLL]
+ -- corresponds to the DLL handles of a Haskell unit.
+ let regroup :: [[a]] -> [b] -> [[b]]
+ regroup [] _ = []
+ regroup (l:ls) xs = xs0: regroup ls xs1 where (xs0, xs1) = splitAt (length l) xs
+ loaded_dlls <- regroup known_hs_dlls <$> load_dyn interp hsc_env True (concat known_hs_dlls)
-- For remaining `dlls` crash early only when there is surely
-- no package's DLL around ... (not is_dyn)
- mapM_ (load_dyn interp hsc_env (not is_dyn) . platformSOName platform) dlls
+ _ <- load_dyn interp hsc_env (not is_dyn) $ map (platformSOName platform) dlls
#else
- let loaded_dlls = []
+ let loaded_dlls = replicate (length pkgs) []
#endif
-- After loading all the DLLs, we can load the static objects.
-- Ordering isn't important here, because we do one final link
@@ -1248,9 +1298,9 @@ loadPackage interp hsc_env pkg
if succeeded ok
then do
maybePutStrLn logger "done."
- return (hs_classifieds, extra_classifieds, loaded_dlls)
- else let errmsg = text "unable to load unit `"
- <> pprUnitInfoForUser pkg <> text "'"
+ pure $ zip3 hs_classifieds extra_classifieds loaded_dlls
+ else let errmsg = text "unable to load units `"
+ <> vcat (map pprUnitInfoForUser pkgs) <> text "'"
in throwGhcExceptionIO (InstallationError (showSDoc dflags errmsg))
{-
@@ -1300,12 +1350,12 @@ restriction very easily.
-- we have already searched the filesystem; the strings passed to load_dyn
-- can be passed directly to loadDLL. They are either fully-qualified
-- ("/usr/lib/libfoo.so"), or unqualified ("libfoo.so"). In the latter case,
--- loadDLL is going to search the system paths to find the library.
-load_dyn :: Interp -> HscEnv -> Bool -> FilePath -> IO (Maybe (RemotePtr LoadedDLL))
-load_dyn interp hsc_env crash_early dll = do
- r <- loadDLL interp dll
+-- loadDLLs is going to search the system paths to find the library.
+load_dyn :: Interp -> HscEnv -> Bool -> [FilePath] -> IO [RemotePtr LoadedDLL]
+load_dyn interp hsc_env crash_early dlls = do
+ r <- loadDLLs interp dlls
case r of
- Right loaded_dll -> pure (Just loaded_dll)
+ Right loaded_dlls -> pure loaded_dlls
Left err ->
if crash_early
then cmdLineErrorIO err
@@ -1314,7 +1364,7 @@ load_dyn interp hsc_env crash_early dll = do
$ reportDiagnostic logger
neverQualify diag_opts
noSrcSpan (WarningWithFlag Opt_WarnMissedExtraSharedLib) $ withPprStyle defaultUserStyle (note err)
- pure Nothing
+ pure []
where
diag_opts = initDiagOpts (hsc_dflags hsc_env)
logger = hsc_logger hsc_env
@@ -1370,7 +1420,7 @@ locateLib interp hsc_env is_hs lib_dirs gcc_dirs lib0
-- then look in library-dirs and inplace GCC for a static library (libfoo.a)
-- then try "gcc --print-file-name" to search gcc's search path
-- for a dynamic library (#5289)
- -- otherwise, assume loadDLL can find it
+ -- otherwise, assume loadDLLs can find it
--
-- The logic is a bit complicated, but the rationale behind it is that
-- loading a shared library for us is O(1) while loading an archive is
=====================================
compiler/GHC/Linker/MacOS.hs
=====================================
@@ -162,7 +162,7 @@ loadFramework interp extraPaths rootname
-- sorry for the hardcoded paths, I hope they won't change anytime soon:
defaultFrameworkPaths = ["/Library/Frameworks", "/System/Library/Frameworks"]
- -- Try to call loadDLL for each candidate path.
+ -- Try to call loadDLLs for each candidate path.
--
-- See Note [macOS Big Sur dynamic libraries]
findLoadDLL [] errs =
@@ -170,7 +170,7 @@ loadFramework interp extraPaths rootname
-- has no built-in paths for frameworks: give up
return $ Just errs
findLoadDLL (p:ps) errs =
- do { dll <- loadDLL interp (p </> fwk_file)
+ do { dll <- loadDLLs interp [p </> fwk_file]
; case dll of
Right _ -> return Nothing
Left err -> findLoadDLL ps ((p ++ ": " ++ err):errs)
=====================================
compiler/GHC/Linker/Types.hs
=====================================
@@ -494,7 +494,7 @@ data LibrarySpec
| DLL String -- "Unadorned" name of a .DLL/.so
-- e.g. On unix "qt" denotes "libqt.so"
-- On Windows "burble" denotes "burble.DLL" or "libburble.dll"
- -- loadDLL is platform-specific and adds the lib/.so/.DLL
+ -- loadDLLs is platform-specific and adds the lib/.so/.DLL
-- suffixes platform-dependently
| DLLPath FilePath -- Absolute or relative pathname to a dynamic library
=====================================
compiler/GHC/Runtime/Interpreter.hs
=====================================
@@ -38,7 +38,7 @@ module GHC.Runtime.Interpreter
, lookupSymbol
, lookupSymbolInDLL
, lookupClosure
- , loadDLL
+ , loadDLLs
, loadArchive
, loadObj
, unloadObj
@@ -559,13 +559,13 @@ withSymbolCache interp str determine_addr = do
purgeLookupSymbolCache :: Interp -> IO ()
purgeLookupSymbolCache interp = purgeInterpSymbolCache (interpSymbolCache interp)
--- | loadDLL loads a dynamic library using the OS's native linker
+-- | 'loadDLLs' loads dynamic libraries using the OS's native linker
-- (i.e. dlopen() on Unix, LoadLibrary() on Windows). It takes either
--- an absolute pathname to the file, or a relative filename
--- (e.g. "libfoo.so" or "foo.dll"). In the latter case, loadDLL
--- searches the standard locations for the appropriate library.
-loadDLL :: Interp -> String -> IO (Either String (RemotePtr LoadedDLL))
-loadDLL interp str = interpCmd interp (LoadDLL str)
+-- absolute pathnames to the files, or relative filenames
+-- (e.g. "libfoo.so" or "foo.dll"). In the latter case, 'loadDLLs'
+-- searches the standard locations for the appropriate libraries.
+loadDLLs :: Interp -> [String] -> IO (Either String [RemotePtr LoadedDLL])
+loadDLLs interp strs = interpCmd interp (LoadDLLs strs)
loadArchive :: Interp -> String -> IO ()
loadArchive interp path = do
@@ -761,4 +761,3 @@ readIModModBreaks hug mod = imodBreaks_modBreaks . expectJust <$> readIModBreaks
fromEvalResult :: EvalResult a -> IO a
fromEvalResult (EvalException e) = throwIO (fromSerializableException e)
fromEvalResult (EvalSuccess a) = return a
-
=====================================
libraries/base/changelog.md
=====================================
@@ -6,7 +6,6 @@
* Fix issues with toRational for types capable to represent infinite and not-a-number values ([CLC proposal #338](https://github.com/haskell/core-libraries-committee/issues/338))
* Ensure that `rationalToFloat` and `rationalToDouble` always inline in the end. ([CLC proposal #356](https://github.com/haskell/core-libraries-committee/issues/356))
* Modify the implementation of `Data.List.sortOn` to use `(>)` instead of `compare`. ([CLC proposal #332](https://github.com/haskell/core-libraries-committee/issues/332))
- * `GHC.Exts.IOPort#` and its related operations have been removed ([CLC #213](https://github.com/haskell/core-libraries-committee/issues/213))
* Add `thenA` and `thenM`. ([CLC proposal #351](https://github.com/haskell/core-libraries-committee/issues/351))
* Fix bug where `naturalAndNot` was incorrectly truncating results ([CLC proposal #350](github.com/haskell/core-libraries-committee/issues/350))
* Remove extra laziness from `Data.Bifunctor.Bifunctor` instances for all tuples to have the same laziness as their `Data.Functor.Functor` counterparts (i.e. they became more strict than before) ([CLC proposal #339](https://github.com/haskell/core-libraries-committee/issues/339))
@@ -37,7 +36,7 @@
* `GHC.TypeNats.Internal`
* `GHC.ExecutionStack.Internal`.
* Deprecate `GHC.JS.Prim.Internal.Build`, as per [CLC #329](https://github.com/haskell/core-libraries-committee/issues/329)
-
+ * `GHC.Exts.IOPort#` and its related operations have been removed ([CLC #213](https://github.com/haskell/core-libraries-committee/issues/213))
* Fix incorrect results of `integerPowMod` when the base is 0 and the exponent is negative, and `integerRecipMod` when the modulus is zero ([#26017](https://gitlab.haskell.org/ghc/ghc/-/issues/26017)).
* Fix the rewrite rule for `scanl'` not being strict in the first element of the output list ([#26143](https://gitlab.haskell.org/ghc/ghc/-/issues/26143)).
=====================================
libraries/ghci/GHCi/Message.hs
=====================================
@@ -89,7 +89,7 @@ data Message a where
LookupSymbol :: String -> Message (Maybe (RemotePtr ()))
LookupSymbolInDLL :: RemotePtr LoadedDLL -> String -> Message (Maybe (RemotePtr ()))
LookupClosure :: String -> Message (Maybe HValueRef)
- LoadDLL :: String -> Message (Either String (RemotePtr LoadedDLL))
+ LoadDLLs :: [String] -> Message (Either String [RemotePtr LoadedDLL])
LoadArchive :: String -> Message () -- error?
LoadObj :: String -> Message () -- error?
UnloadObj :: String -> Message () -- error?
@@ -448,7 +448,7 @@ data BreakModule
-- that type isn't available here.
data BreakUnitId
--- | A dummy type that tags pointers returned by 'LoadDLL'.
+-- | A dummy type that tags pointers returned by 'LoadDLLs'.
data LoadedDLL
-- SomeException can't be serialized because it contains dynamic
@@ -564,7 +564,7 @@ getMessage = do
1 -> Msg <$> return InitLinker
2 -> Msg <$> LookupSymbol <$> get
3 -> Msg <$> LookupClosure <$> get
- 4 -> Msg <$> LoadDLL <$> get
+ 4 -> Msg <$> LoadDLLs <$> get
5 -> Msg <$> LoadArchive <$> get
6 -> Msg <$> LoadObj <$> get
7 -> Msg <$> UnloadObj <$> get
@@ -610,7 +610,7 @@ putMessage m = case m of
InitLinker -> putWord8 1
LookupSymbol str -> putWord8 2 >> put str
LookupClosure str -> putWord8 3 >> put str
- LoadDLL str -> putWord8 4 >> put str
+ LoadDLLs strs -> putWord8 4 >> put strs
LoadArchive str -> putWord8 5 >> put str
LoadObj str -> putWord8 6 >> put str
UnloadObj str -> putWord8 7 >> put str
=====================================
libraries/ghci/GHCi/ObjLink.hs
=====================================
@@ -12,7 +12,7 @@
-- dynamic linker.
module GHCi.ObjLink
( initObjLinker, ShouldRetainCAFs(..)
- , loadDLL
+ , loadDLLs
, loadArchive
, loadObj
, unloadObj
@@ -31,6 +31,7 @@ import GHCi.RemoteTypes
import GHCi.Message (LoadedDLL)
import Control.Exception (throwIO, ErrorCall(..))
import Control.Monad ( when )
+import Data.Foldable
import Foreign.C
import Foreign.Marshal.Alloc ( alloca, free )
import Foreign ( nullPtr, peek )
@@ -43,6 +44,10 @@ import Control.Exception (catch, evaluate)
import GHC.Wasm.Prim
#endif
+#if defined(wasm32_HOST_ARCH)
+import Data.List (intercalate)
+#endif
+
-- ---------------------------------------------------------------------------
-- RTS Linker Interface
-- ---------------------------------------------------------------------------
@@ -67,20 +72,25 @@ data ShouldRetainCAFs
initObjLinker :: ShouldRetainCAFs -> IO ()
initObjLinker _ = pure ()
-loadDLL :: String -> IO (Either String (Ptr LoadedDLL))
-loadDLL f =
+-- Batch load multiple DLLs at once via dyld to enable a single
+-- dependency resolution and more parallel compilation. We pass a
+-- NUL-delimited JSString to avoid array marshalling on wasm.
+loadDLLs :: [String] -> IO (Either String [Ptr LoadedDLL])
+loadDLLs fs =
m `catch` \(err :: JSException) ->
- pure $ Left $ "loadDLL failed for " <> f <> ": " <> show err
+ pure $ Left $ "loadDLLs failed: " <> show err
where
+ packed :: JSString
+ packed = toJSString (intercalate ['\0'] fs)
m = do
- evaluate =<< js_loadDLL (toJSString f)
- pure $ Right nullPtr
+ evaluate =<< js_loadDLLs packed
+ pure $ Right (replicate (length fs) nullPtr)
-- See Note [Variable passing in JSFFI] for where
-- __ghc_wasm_jsffi_dyld comes from
-foreign import javascript safe "__ghc_wasm_jsffi_dyld.loadDLL($1)"
- js_loadDLL :: JSString -> IO ()
+foreign import javascript safe "__ghc_wasm_jsffi_dyld.loadDLLs($1)"
+ js_loadDLLs :: JSString -> IO ()
loadArchive :: String -> IO ()
loadArchive f = throwIO $ ErrorCall $ "loadArchive: unsupported on wasm for " <> f
@@ -241,6 +251,16 @@ resolveObjs = do
r <- c_resolveObjs
return (r /= 0)
+loadDLLs :: [String] -> IO (Either String [Ptr LoadedDLL])
+loadDLLs = foldrM load_one $ Right []
+ where
+ load_one _ err@(Left _) = pure err
+ load_one p (Right dlls) = do
+ r <- loadDLL p
+ pure $ case r of
+ Left err -> Left err
+ Right dll -> Right $ dll : dlls
+
-- ---------------------------------------------------------------------------
-- Foreign declarations to RTS entry points which does the real work;
-- ---------------------------------------------------------------------------
=====================================
libraries/ghci/GHCi/Run.hs
=====================================
@@ -57,7 +57,7 @@ run m = case m of
#if defined(javascript_HOST_ARCH)
LoadObj p -> withCString p loadJS
InitLinker -> notSupportedJS m
- LoadDLL {} -> notSupportedJS m
+ LoadDLLs {} -> notSupportedJS m
LoadArchive {} -> notSupportedJS m
UnloadObj {} -> notSupportedJS m
AddLibrarySearchPath {} -> notSupportedJS m
@@ -69,7 +69,7 @@ run m = case m of
LookupClosure str -> lookupJSClosure str
#else
InitLinker -> initObjLinker RetainCAFs
- LoadDLL str -> fmap toRemotePtr <$> loadDLL str
+ LoadDLLs strs -> fmap (map toRemotePtr) <$> loadDLLs strs
LoadArchive str -> loadArchive str
LoadObj str -> loadObj str
UnloadObj str -> unloadObj str
=====================================
rts/ExecPage.c
=====================================
@@ -10,15 +10,23 @@
#include "linker/MMap.h"
ExecPage *allocateExecPage(void) {
+#if defined(wasm32_HOST_ARCH)
+ return NULL;
+#else
ExecPage *page = (ExecPage *) mmapAnon(getPageSize());
return page;
+#endif
}
void freezeExecPage(ExecPage *page) {
+#if !defined(wasm32_HOST_ARCH)
mprotectForLinker(page, getPageSize(), MEM_READ_EXECUTE);
flushExec(getPageSize(), page);
+#endif
}
void freeExecPage(ExecPage *page) {
+#if !defined(wasm32_HOST_ARCH)
munmapForLinker(page, getPageSize(), "freeExecPage");
+#endif
}
=====================================
rts/Interpreter.c
=====================================
@@ -2599,11 +2599,11 @@ run_BCO:
#define SIZED_BIN_OP_TY_INT(op,ty) \
{ \
if(sizeof(ty) > sizeof(StgWord)) { \
- ty r = ((ty) ReadSpW64(0)) op ((ty) ReadSpW(2)); \
+ ty r = ((ty) ReadSpW64(0)) op ((StgInt) ReadSpW(2)); \
Sp_addW(1); \
SpW64(0) = (StgWord64) r; \
} else { \
- ty r = ((ty) ReadSpW(0)) op ((ty) ReadSpW(1)); \
+ ty r = ((ty) ReadSpW(0)) op ((StgInt) ReadSpW(1)); \
Sp_addW(1); \
SpW(0) = (StgWord) r; \
}; \
=====================================
rts/wasm/JSFFI.c
=====================================
@@ -5,6 +5,8 @@
#include "Threads.h"
#include "sm/Sanity.h"
+#include <sysexits.h>
+
#if defined(__wasm_reference_types__)
extern HsBool rts_JSFFI_flag;
@@ -12,21 +14,8 @@ extern HsStablePtr rts_threadDelay_impl;
extern StgClosure ghczminternal_GHCziInternalziWasmziPrimziImports_raiseJSException_closure;
extern StgClosure ghczminternal_GHCziInternalziWasmziPrimziConcziInternal_threadDelay_closure;
-int __main_void(void);
-
-int __main_argc_argv(int, char*[]);
-
-int __main_argc_argv(int argc, char *argv[]) {
- RtsConfig __conf = defaultRtsConfig;
- __conf.rts_opts_enabled = RtsOptsAll;
- __conf.rts_hs_main = false;
- hs_init_ghc(&argc, &argv, __conf);
- // See Note [threadDelay on wasm] for details.
- rts_JSFFI_flag = HS_BOOL_TRUE;
- getStablePtr((StgPtr)&ghczminternal_GHCziInternalziWasmziPrimziImports_raiseJSException_closure);
- rts_threadDelay_impl = getStablePtr((StgPtr)&ghczminternal_GHCziInternalziWasmziPrimziConcziInternal_threadDelay_closure);
- return 0;
-}
+__attribute__((__weak__))
+int __main_argc_argv(int argc, char *argv[]);
// Note [JSFFI initialization]
// ~~~~~~~~~~~~~~~~~~~~~~~~~~~
@@ -66,11 +55,69 @@ int __main_argc_argv(int argc, char *argv[]) {
// by the GHC codegen, and priority 102 to the initialization logic
// here to ensure hs_init_ghc() sees everything it needs to see.
__attribute__((constructor(102))) static void __ghc_wasm_jsffi_init(void) {
- // See
- // https://gitlab.haskell.org/ghc/wasi-libc/-/blob/master/libc-bottom-half/sou…
- // for its definition. It initializes some libc state, then calls
- // __main_argc_argv defined above.
- __main_void();
+ // If linking static code without -no-hs-main, then the driver
+ // emitted main() is in charge of its own RTS initialization, so
+ // skip.
+#if !defined(__PIC__)
+ if (__main_argc_argv) {
+ return;
+ }
+#endif
+
+ // Code below is mirrored from
+ // https://gitlab.haskell.org/haskell-wasm/wasi-libc/-/blob/master/libc-bottom…,
+ // fetches argc/argv using wasi api
+ __wasi_errno_t err;
+
+ // Get the sizes of the arrays we'll have to create to copy in the args.
+ size_t argv_buf_size;
+ size_t argc;
+ err = __wasi_args_sizes_get(&argc, &argv_buf_size);
+ if (err != __WASI_ERRNO_SUCCESS) {
+ _Exit(EX_OSERR);
+ }
+
+ // Add 1 for the NULL pointer to mark the end, and check for overflow.
+ size_t num_ptrs = argc + 1;
+ if (num_ptrs == 0) {
+ _Exit(EX_SOFTWARE);
+ }
+
+ // Allocate memory for storing the argument chars.
+ char *argv_buf = malloc(argv_buf_size);
+ if (argv_buf == NULL) {
+ _Exit(EX_SOFTWARE);
+ }
+
+ // Allocate memory for the array of pointers. This uses `calloc` both to
+ // handle overflow and to initialize the NULL pointer at the end.
+ char **argv = calloc(num_ptrs, sizeof(char *));
+ if (argv == NULL) {
+ free(argv_buf);
+ _Exit(EX_SOFTWARE);
+ }
+
+ // Fill the argument chars, and the argv array with pointers into those chars.
+ // TODO: Remove the casts on `argv_ptrs` and `argv_buf` once the witx is
+ // updated with char8 support.
+ err = __wasi_args_get((uint8_t **)argv, (uint8_t *)argv_buf);
+ if (err != __WASI_ERRNO_SUCCESS) {
+ free(argv_buf);
+ free(argv);
+ _Exit(EX_OSERR);
+ }
+
+ // Now that we have argc/argv, proceed to initialize the GHC RTS
+ RtsConfig __conf = defaultRtsConfig;
+ __conf.rts_opts_enabled = RtsOptsAll;
+ __conf.rts_hs_main = false;
+ hs_init_ghc((int *)&argc, &argv, __conf);
+ // See Note [threadDelay on wasm] for details.
+ rts_JSFFI_flag = HS_BOOL_TRUE;
+ getStablePtr((
+ StgPtr)&ghczminternal_GHCziInternalziWasmziPrimziImports_raiseJSException_closure);
+ rts_threadDelay_impl = getStablePtr((
+ StgPtr)&ghczminternal_GHCziInternalziWasmziPrimziConcziInternal_threadDelay_closure);
}
typedef __externref_t HsJSVal;
=====================================
testsuite/tests/rts/linker/T2615.hs
=====================================
@@ -4,7 +4,7 @@ library_name = "libfoo_script_T2615.so" -- this is really a linker script
main = do
initObjLinker RetainCAFs
- result <- loadDLL library_name
+ result <- loadDLLs [library_name]
case result of
Right _ -> putStrLn (library_name ++ " loaded successfully")
Left x -> putStrLn ("error: " ++ x)
=====================================
utils/jsffi/dyld.mjs
=====================================
@@ -9,7 +9,7 @@
// iserv (GHCi.Server.defaultServer). This part only runs in
// nodejs.
// 2. Dynamic linker: provide RTS linker interfaces like
-// loadDLL/lookupSymbol etc which are imported by wasm iserv. This
+// loadDLLs/lookupSymbol etc which are imported by wasm iserv. This
// part can run in browsers as well.
//
// When GHC starts external interpreter for the wasm target, it starts
@@ -50,7 +50,7 @@
//
// *** What works right now and what doesn't work yet?
//
-// loadDLL & bytecode interpreter work. Template Haskell & ghci work.
+// loadDLLs & bytecode interpreter work. Template Haskell & ghci work.
// Profiled dynamic code works. Compiled code and bytecode can all be
// loaded, though the side effects are constrained to what's supported
// by wasi preview1: we map the full host filesystem into wasm cause
@@ -777,17 +777,17 @@ class DyLD {
return this.#rpc.findSystemLibrary(f);
}
- // When we do loadDLL, we first perform "downsweep" which return a
+ // When we do loadDLLs, we first perform "downsweep" which return a
// toposorted array of dependencies up to itself, then sequentially
// load the downsweep result.
//
// The rationale of a separate downsweep phase, instead of a simple
- // recursive loadDLL function is: V8 delegates async
+ // recursive loadDLLs function is: V8 delegates async
// WebAssembly.compile to a background worker thread pool. To
// maintain consistent internal linker state, we *must* load each so
// file sequentially, but it's okay to kick off compilation asap,
// store the Promise in downsweep result and await for the actual
- // WebAssembly.Module in loadDLL logic. This way we can harness some
+ // WebAssembly.Module in loadDLLs logic. This way we can harness some
// background parallelism.
async #downsweep(p) {
const toks = p.split("/");
@@ -828,8 +828,26 @@ class DyLD {
return acc;
}
- // The real stuff
- async loadDLL(p) {
+ // Batch load multiple DLLs in one go.
+ // Accepts a NUL-delimited string of paths to avoid array marshalling.
+ // Each path can be absolute or a soname; dependency resolution is
+ // performed across the full set to enable maximal parallel compile
+ // while maintaining sequential instantiation order.
+ 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();
+
+ // Compute a single downsweep plan for the whole batch.
+ // Note: #downsweep mutates #loadedSos to break cycles and dedup.
+ const plan = [];
+ for (const p of paths) {
+ plan.push(...(await this.#downsweep(p)));
+ }
+
for (const {
memSize,
memP2Align,
@@ -837,7 +855,7 @@ class DyLD {
tableP2Align,
modp,
soname,
- } of await this.#downsweep(p)) {
+ } of plan) {
const import_obj = {
wasi_snapshot_preview1: this.#wasi.wasiImport,
env: {
@@ -1131,7 +1149,7 @@ export async function main({ rpc, libdir, ghciSoPath, args }) {
rpc,
});
await dyld.addLibrarySearchPath(libdir);
- await dyld.loadDLL(ghciSoPath);
+ await dyld.loadDLLs(ghciSoPath);
const reader = rpc.readStream.getReader();
const writer = rpc.writeStream.getWriter();
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/61264f284c101f2bfe5b71edcdb038…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/61264f284c101f2bfe5b71edcdb038…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/T26166-1] rts: Dynamically initialize built-in closures
by Ben Gamari (@bgamari) 29 Sep '25
by Ben Gamari (@bgamari) 29 Sep '25
29 Sep '25
Ben Gamari pushed to branch wip/T26166-1 at Glasgow Haskell Compiler / GHC
Commits:
757b4319 by Ben Gamari at 2025-09-29T15:27:57-04:00
rts: Dynamically initialize built-in closures
To resolve #26166 we need to eliminate references to undefined symbols
in the runtime system. One such source of these is the runtime's
static references to `I#` and `C#` due the `stg_INTLIKE` and
`stg_CHARLIKE` arrays.
To avoid this we make these dynamic, initializing them during RTS
start-up.
- - - - -
7 changed files:
- + rts/BuiltinClosures.c
- + rts/BuiltinClosures.h
- rts/RtsStartup.c
- rts/StgMiscClosures.cmm
- rts/include/rts/Constants.h
- rts/include/stg/MiscClosures.h
- rts/rts.cabal
Changes:
=====================================
rts/BuiltinClosures.c
=====================================
@@ -0,0 +1,30 @@
+#include "Rts.h"
+#include "Prelude.h"
+#include "BuiltinClosures.h"
+
+/*
+ * Note [CHARLIKE and INTLIKE closures]
+ * ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+ * These are static representations of Chars and small Ints, so that
+ * we can remove dynamic Chars and Ints during garbage collection and
+ * replace them with references to the static objects.
+ */
+
+StgIntCharlikeClosure stg_INTLIKE_closure[MAX_INTLIKE - MIN_INTLIKE + 1];
+StgIntCharlikeClosure stg_CHARLIKE_closure[MAX_CHARLIKE - MIN_CHARLIKE + 1];
+
+void initBuiltinClosures(void) {
+ // INTLIKE closures
+ for (int i = MIN_INTLIKE; i <= MAX_INTLIKE; i++) {
+ StgIntCharlikeClosure *c = &stg_INTLIKE_closure[i - MIN_INTLIKE];
+ SET_HDR((StgClosure* ) c, Izh_con_info, CCS_SYSTEM_OR_NULL);
+ c->data = i;
+ }
+
+ // CHARLIKE closures
+ for (int i = MIN_CHARLIKE; i <= MAX_CHARLIKE; i++) {
+ StgIntCharlikeClosure *c = &stg_CHARLIKE_closure[i - MIN_CHARLIKE];
+ SET_HDR((StgClosure* ) c, Czh_con_info, CCS_SYSTEM_OR_NULL);
+ c->data = i;
+ }
+}
=====================================
rts/BuiltinClosures.h
=====================================
@@ -0,0 +1,14 @@
+/*
+ * (c) The GHC Team, 2025-2026
+ *
+ * RTS/ghc-internal interface
+ *
+ */
+
+#pragma once
+
+#include "BeginPrivate.h"
+
+void initBuiltinClosures(void);
+
+#include "EndPrivate.h"
=====================================
rts/RtsStartup.c
=====================================
@@ -14,6 +14,7 @@
#include "linker/MMap.h"
#include "RtsFlags.h"
#include "RtsUtils.h"
+#include "BuiltinClosures.h"
#include "Prelude.h"
#include "Printer.h" /* DEBUG_LoadSymbols */
#include "Schedule.h" /* initScheduler */
@@ -373,6 +374,9 @@ hs_init_ghc(int *argc, char **argv[], RtsConfig rts_config)
traceInitEvent(traceOSProcessInfo);
flushTrace();
+ /* initialize INTLIKE and CHARLIKE closures */
+ initBuiltinClosures();
+
/* initialize the storage manager */
initStorage();
=====================================
rts/StgMiscClosures.cmm
=====================================
@@ -13,8 +13,6 @@
#include "Cmm.h"
import pthread_mutex_lock;
-import ghczminternal_GHCziInternalziTypes_Czh_info;
-import ghczminternal_GHCziInternalziTypes_Izh_info;
import AcquireSRWLockExclusive;
import ReleaseSRWLockExclusive;
@@ -23,7 +21,6 @@ import whitehole_lockClosure_spin;
import whitehole_lockClosure_yield;
#endif
-
#if !defined(UnregisterisedCompiler)
import CLOSURE CCS_SYSTEM;
import CLOSURE ENT_DYN_IND_ctr;
@@ -1031,554 +1028,3 @@ INFO_TABLE_CONSTR(stg_ASYNCIO_LIVE0,0,0,0,CONSTR_NOCAF,"ASYNCIO_LIVE0","ASYNCIO_
{ foreign "C" barf("ASYNCIO_LIVE0 object (%p) entered!", R1) never returns; }
CLOSURE(stg_ASYNCIO_LIVE0_closure,stg_ASYNCIO_LIVE0);
-
-/* ----------------------------------------------------------------------------
- Note [CHARLIKE and INTLIKE closures]
- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
- These are static representations of Chars and small Ints, so that
- we can remove dynamic Chars and Ints during garbage collection and
- replace them with references to the static objects.
- ------------------------------------------------------------------------- */
-
-#define Char_hash_con_info ghczminternal_GHCziInternalziTypes_Czh_con_info
-#define Int_hash_con_info ghczminternal_GHCziInternalziTypes_Izh_con_info
-
-#define CHARLIKE_HDR(n) CLOSURE(Char_hash_con_info, n)
-#define INTLIKE_HDR(n) CLOSURE(Int_hash_con_info, n)
-
-section "data" {
- stg_CHARLIKE_closure:
- CHARLIKE_HDR(0)
- CHARLIKE_HDR(1)
- CHARLIKE_HDR(2)
- CHARLIKE_HDR(3)
- CHARLIKE_HDR(4)
- CHARLIKE_HDR(5)
- CHARLIKE_HDR(6)
- CHARLIKE_HDR(7)
- CHARLIKE_HDR(8)
- CHARLIKE_HDR(9)
- CHARLIKE_HDR(10)
- CHARLIKE_HDR(11)
- CHARLIKE_HDR(12)
- CHARLIKE_HDR(13)
- CHARLIKE_HDR(14)
- CHARLIKE_HDR(15)
- CHARLIKE_HDR(16)
- CHARLIKE_HDR(17)
- CHARLIKE_HDR(18)
- CHARLIKE_HDR(19)
- CHARLIKE_HDR(20)
- CHARLIKE_HDR(21)
- CHARLIKE_HDR(22)
- CHARLIKE_HDR(23)
- CHARLIKE_HDR(24)
- CHARLIKE_HDR(25)
- CHARLIKE_HDR(26)
- CHARLIKE_HDR(27)
- CHARLIKE_HDR(28)
- CHARLIKE_HDR(29)
- CHARLIKE_HDR(30)
- CHARLIKE_HDR(31)
- CHARLIKE_HDR(32)
- CHARLIKE_HDR(33)
- CHARLIKE_HDR(34)
- CHARLIKE_HDR(35)
- CHARLIKE_HDR(36)
- CHARLIKE_HDR(37)
- CHARLIKE_HDR(38)
- CHARLIKE_HDR(39)
- CHARLIKE_HDR(40)
- CHARLIKE_HDR(41)
- CHARLIKE_HDR(42)
- CHARLIKE_HDR(43)
- CHARLIKE_HDR(44)
- CHARLIKE_HDR(45)
- CHARLIKE_HDR(46)
- CHARLIKE_HDR(47)
- CHARLIKE_HDR(48)
- CHARLIKE_HDR(49)
- CHARLIKE_HDR(50)
- CHARLIKE_HDR(51)
- CHARLIKE_HDR(52)
- CHARLIKE_HDR(53)
- CHARLIKE_HDR(54)
- CHARLIKE_HDR(55)
- CHARLIKE_HDR(56)
- CHARLIKE_HDR(57)
- CHARLIKE_HDR(58)
- CHARLIKE_HDR(59)
- CHARLIKE_HDR(60)
- CHARLIKE_HDR(61)
- CHARLIKE_HDR(62)
- CHARLIKE_HDR(63)
- CHARLIKE_HDR(64)
- CHARLIKE_HDR(65)
- CHARLIKE_HDR(66)
- CHARLIKE_HDR(67)
- CHARLIKE_HDR(68)
- CHARLIKE_HDR(69)
- CHARLIKE_HDR(70)
- CHARLIKE_HDR(71)
- CHARLIKE_HDR(72)
- CHARLIKE_HDR(73)
- CHARLIKE_HDR(74)
- CHARLIKE_HDR(75)
- CHARLIKE_HDR(76)
- CHARLIKE_HDR(77)
- CHARLIKE_HDR(78)
- CHARLIKE_HDR(79)
- CHARLIKE_HDR(80)
- CHARLIKE_HDR(81)
- CHARLIKE_HDR(82)
- CHARLIKE_HDR(83)
- CHARLIKE_HDR(84)
- CHARLIKE_HDR(85)
- CHARLIKE_HDR(86)
- CHARLIKE_HDR(87)
- CHARLIKE_HDR(88)
- CHARLIKE_HDR(89)
- CHARLIKE_HDR(90)
- CHARLIKE_HDR(91)
- CHARLIKE_HDR(92)
- CHARLIKE_HDR(93)
- CHARLIKE_HDR(94)
- CHARLIKE_HDR(95)
- CHARLIKE_HDR(96)
- CHARLIKE_HDR(97)
- CHARLIKE_HDR(98)
- CHARLIKE_HDR(99)
- CHARLIKE_HDR(100)
- CHARLIKE_HDR(101)
- CHARLIKE_HDR(102)
- CHARLIKE_HDR(103)
- CHARLIKE_HDR(104)
- CHARLIKE_HDR(105)
- CHARLIKE_HDR(106)
- CHARLIKE_HDR(107)
- CHARLIKE_HDR(108)
- CHARLIKE_HDR(109)
- CHARLIKE_HDR(110)
- CHARLIKE_HDR(111)
- CHARLIKE_HDR(112)
- CHARLIKE_HDR(113)
- CHARLIKE_HDR(114)
- CHARLIKE_HDR(115)
- CHARLIKE_HDR(116)
- CHARLIKE_HDR(117)
- CHARLIKE_HDR(118)
- CHARLIKE_HDR(119)
- CHARLIKE_HDR(120)
- CHARLIKE_HDR(121)
- CHARLIKE_HDR(122)
- CHARLIKE_HDR(123)
- CHARLIKE_HDR(124)
- CHARLIKE_HDR(125)
- CHARLIKE_HDR(126)
- CHARLIKE_HDR(127)
- CHARLIKE_HDR(128)
- CHARLIKE_HDR(129)
- CHARLIKE_HDR(130)
- CHARLIKE_HDR(131)
- CHARLIKE_HDR(132)
- CHARLIKE_HDR(133)
- CHARLIKE_HDR(134)
- CHARLIKE_HDR(135)
- CHARLIKE_HDR(136)
- CHARLIKE_HDR(137)
- CHARLIKE_HDR(138)
- CHARLIKE_HDR(139)
- CHARLIKE_HDR(140)
- CHARLIKE_HDR(141)
- CHARLIKE_HDR(142)
- CHARLIKE_HDR(143)
- CHARLIKE_HDR(144)
- CHARLIKE_HDR(145)
- CHARLIKE_HDR(146)
- CHARLIKE_HDR(147)
- CHARLIKE_HDR(148)
- CHARLIKE_HDR(149)
- CHARLIKE_HDR(150)
- CHARLIKE_HDR(151)
- CHARLIKE_HDR(152)
- CHARLIKE_HDR(153)
- CHARLIKE_HDR(154)
- CHARLIKE_HDR(155)
- CHARLIKE_HDR(156)
- CHARLIKE_HDR(157)
- CHARLIKE_HDR(158)
- CHARLIKE_HDR(159)
- CHARLIKE_HDR(160)
- CHARLIKE_HDR(161)
- CHARLIKE_HDR(162)
- CHARLIKE_HDR(163)
- CHARLIKE_HDR(164)
- CHARLIKE_HDR(165)
- CHARLIKE_HDR(166)
- CHARLIKE_HDR(167)
- CHARLIKE_HDR(168)
- CHARLIKE_HDR(169)
- CHARLIKE_HDR(170)
- CHARLIKE_HDR(171)
- CHARLIKE_HDR(172)
- CHARLIKE_HDR(173)
- CHARLIKE_HDR(174)
- CHARLIKE_HDR(175)
- CHARLIKE_HDR(176)
- CHARLIKE_HDR(177)
- CHARLIKE_HDR(178)
- CHARLIKE_HDR(179)
- CHARLIKE_HDR(180)
- CHARLIKE_HDR(181)
- CHARLIKE_HDR(182)
- CHARLIKE_HDR(183)
- CHARLIKE_HDR(184)
- CHARLIKE_HDR(185)
- CHARLIKE_HDR(186)
- CHARLIKE_HDR(187)
- CHARLIKE_HDR(188)
- CHARLIKE_HDR(189)
- CHARLIKE_HDR(190)
- CHARLIKE_HDR(191)
- CHARLIKE_HDR(192)
- CHARLIKE_HDR(193)
- CHARLIKE_HDR(194)
- CHARLIKE_HDR(195)
- CHARLIKE_HDR(196)
- CHARLIKE_HDR(197)
- CHARLIKE_HDR(198)
- CHARLIKE_HDR(199)
- CHARLIKE_HDR(200)
- CHARLIKE_HDR(201)
- CHARLIKE_HDR(202)
- CHARLIKE_HDR(203)
- CHARLIKE_HDR(204)
- CHARLIKE_HDR(205)
- CHARLIKE_HDR(206)
- CHARLIKE_HDR(207)
- CHARLIKE_HDR(208)
- CHARLIKE_HDR(209)
- CHARLIKE_HDR(210)
- CHARLIKE_HDR(211)
- CHARLIKE_HDR(212)
- CHARLIKE_HDR(213)
- CHARLIKE_HDR(214)
- CHARLIKE_HDR(215)
- CHARLIKE_HDR(216)
- CHARLIKE_HDR(217)
- CHARLIKE_HDR(218)
- CHARLIKE_HDR(219)
- CHARLIKE_HDR(220)
- CHARLIKE_HDR(221)
- CHARLIKE_HDR(222)
- CHARLIKE_HDR(223)
- CHARLIKE_HDR(224)
- CHARLIKE_HDR(225)
- CHARLIKE_HDR(226)
- CHARLIKE_HDR(227)
- CHARLIKE_HDR(228)
- CHARLIKE_HDR(229)
- CHARLIKE_HDR(230)
- CHARLIKE_HDR(231)
- CHARLIKE_HDR(232)
- CHARLIKE_HDR(233)
- CHARLIKE_HDR(234)
- CHARLIKE_HDR(235)
- CHARLIKE_HDR(236)
- CHARLIKE_HDR(237)
- CHARLIKE_HDR(238)
- CHARLIKE_HDR(239)
- CHARLIKE_HDR(240)
- CHARLIKE_HDR(241)
- CHARLIKE_HDR(242)
- CHARLIKE_HDR(243)
- CHARLIKE_HDR(244)
- CHARLIKE_HDR(245)
- CHARLIKE_HDR(246)
- CHARLIKE_HDR(247)
- CHARLIKE_HDR(248)
- CHARLIKE_HDR(249)
- CHARLIKE_HDR(250)
- CHARLIKE_HDR(251)
- CHARLIKE_HDR(252)
- CHARLIKE_HDR(253)
- CHARLIKE_HDR(254)
- CHARLIKE_HDR(255)
-}
-
-section "data" {
- stg_INTLIKE_closure:
- INTLIKE_HDR(-16) /* MIN_INTLIKE == -16 */
- INTLIKE_HDR(-15)
- INTLIKE_HDR(-14)
- INTLIKE_HDR(-13)
- INTLIKE_HDR(-12)
- INTLIKE_HDR(-11)
- INTLIKE_HDR(-10)
- INTLIKE_HDR(-9)
- INTLIKE_HDR(-8)
- INTLIKE_HDR(-7)
- INTLIKE_HDR(-6)
- INTLIKE_HDR(-5)
- INTLIKE_HDR(-4)
- INTLIKE_HDR(-3)
- INTLIKE_HDR(-2)
- INTLIKE_HDR(-1)
- INTLIKE_HDR(0)
- INTLIKE_HDR(1)
- INTLIKE_HDR(2)
- INTLIKE_HDR(3)
- INTLIKE_HDR(4)
- INTLIKE_HDR(5)
- INTLIKE_HDR(6)
- INTLIKE_HDR(7)
- INTLIKE_HDR(8)
- INTLIKE_HDR(9)
- INTLIKE_HDR(10)
- INTLIKE_HDR(11)
- INTLIKE_HDR(12)
- INTLIKE_HDR(13)
- INTLIKE_HDR(14)
- INTLIKE_HDR(15)
- INTLIKE_HDR(16)
- INTLIKE_HDR(17)
- INTLIKE_HDR(18)
- INTLIKE_HDR(19)
- INTLIKE_HDR(20)
- INTLIKE_HDR(21)
- INTLIKE_HDR(22)
- INTLIKE_HDR(23)
- INTLIKE_HDR(24)
- INTLIKE_HDR(25)
- INTLIKE_HDR(26)
- INTLIKE_HDR(27)
- INTLIKE_HDR(28)
- INTLIKE_HDR(29)
- INTLIKE_HDR(30)
- INTLIKE_HDR(31)
- INTLIKE_HDR(32)
- INTLIKE_HDR(33)
- INTLIKE_HDR(34)
- INTLIKE_HDR(35)
- INTLIKE_HDR(36)
- INTLIKE_HDR(37)
- INTLIKE_HDR(38)
- INTLIKE_HDR(39)
- INTLIKE_HDR(40)
- INTLIKE_HDR(41)
- INTLIKE_HDR(42)
- INTLIKE_HDR(43)
- INTLIKE_HDR(44)
- INTLIKE_HDR(45)
- INTLIKE_HDR(46)
- INTLIKE_HDR(47)
- INTLIKE_HDR(48)
- INTLIKE_HDR(49)
- INTLIKE_HDR(50)
- INTLIKE_HDR(51)
- INTLIKE_HDR(52)
- INTLIKE_HDR(53)
- INTLIKE_HDR(54)
- INTLIKE_HDR(55)
- INTLIKE_HDR(56)
- INTLIKE_HDR(57)
- INTLIKE_HDR(58)
- INTLIKE_HDR(59)
- INTLIKE_HDR(60)
- INTLIKE_HDR(61)
- INTLIKE_HDR(62)
- INTLIKE_HDR(63)
- INTLIKE_HDR(64)
- INTLIKE_HDR(65)
- INTLIKE_HDR(66)
- INTLIKE_HDR(67)
- INTLIKE_HDR(68)
- INTLIKE_HDR(69)
- INTLIKE_HDR(70)
- INTLIKE_HDR(71)
- INTLIKE_HDR(72)
- INTLIKE_HDR(73)
- INTLIKE_HDR(74)
- INTLIKE_HDR(75)
- INTLIKE_HDR(76)
- INTLIKE_HDR(77)
- INTLIKE_HDR(78)
- INTLIKE_HDR(79)
- INTLIKE_HDR(80)
- INTLIKE_HDR(81)
- INTLIKE_HDR(82)
- INTLIKE_HDR(83)
- INTLIKE_HDR(84)
- INTLIKE_HDR(85)
- INTLIKE_HDR(86)
- INTLIKE_HDR(87)
- INTLIKE_HDR(88)
- INTLIKE_HDR(89)
- INTLIKE_HDR(90)
- INTLIKE_HDR(91)
- INTLIKE_HDR(92)
- INTLIKE_HDR(93)
- INTLIKE_HDR(94)
- INTLIKE_HDR(95)
- INTLIKE_HDR(96)
- INTLIKE_HDR(97)
- INTLIKE_HDR(98)
- INTLIKE_HDR(99)
- INTLIKE_HDR(100)
- INTLIKE_HDR(101)
- INTLIKE_HDR(102)
- INTLIKE_HDR(103)
- INTLIKE_HDR(104)
- INTLIKE_HDR(105)
- INTLIKE_HDR(106)
- INTLIKE_HDR(107)
- INTLIKE_HDR(108)
- INTLIKE_HDR(109)
- INTLIKE_HDR(110)
- INTLIKE_HDR(111)
- INTLIKE_HDR(112)
- INTLIKE_HDR(113)
- INTLIKE_HDR(114)
- INTLIKE_HDR(115)
- INTLIKE_HDR(116)
- INTLIKE_HDR(117)
- INTLIKE_HDR(118)
- INTLIKE_HDR(119)
- INTLIKE_HDR(120)
- INTLIKE_HDR(121)
- INTLIKE_HDR(122)
- INTLIKE_HDR(123)
- INTLIKE_HDR(124)
- INTLIKE_HDR(125)
- INTLIKE_HDR(126)
- INTLIKE_HDR(127)
- INTLIKE_HDR(128)
- INTLIKE_HDR(129)
- INTLIKE_HDR(130)
- INTLIKE_HDR(131)
- INTLIKE_HDR(132)
- INTLIKE_HDR(133)
- INTLIKE_HDR(134)
- INTLIKE_HDR(135)
- INTLIKE_HDR(136)
- INTLIKE_HDR(137)
- INTLIKE_HDR(138)
- INTLIKE_HDR(139)
- INTLIKE_HDR(140)
- INTLIKE_HDR(141)
- INTLIKE_HDR(142)
- INTLIKE_HDR(143)
- INTLIKE_HDR(144)
- INTLIKE_HDR(145)
- INTLIKE_HDR(146)
- INTLIKE_HDR(147)
- INTLIKE_HDR(148)
- INTLIKE_HDR(149)
- INTLIKE_HDR(150)
- INTLIKE_HDR(151)
- INTLIKE_HDR(152)
- INTLIKE_HDR(153)
- INTLIKE_HDR(154)
- INTLIKE_HDR(155)
- INTLIKE_HDR(156)
- INTLIKE_HDR(157)
- INTLIKE_HDR(158)
- INTLIKE_HDR(159)
- INTLIKE_HDR(160)
- INTLIKE_HDR(161)
- INTLIKE_HDR(162)
- INTLIKE_HDR(163)
- INTLIKE_HDR(164)
- INTLIKE_HDR(165)
- INTLIKE_HDR(166)
- INTLIKE_HDR(167)
- INTLIKE_HDR(168)
- INTLIKE_HDR(169)
- INTLIKE_HDR(170)
- INTLIKE_HDR(171)
- INTLIKE_HDR(172)
- INTLIKE_HDR(173)
- INTLIKE_HDR(174)
- INTLIKE_HDR(175)
- INTLIKE_HDR(176)
- INTLIKE_HDR(177)
- INTLIKE_HDR(178)
- INTLIKE_HDR(179)
- INTLIKE_HDR(180)
- INTLIKE_HDR(181)
- INTLIKE_HDR(182)
- INTLIKE_HDR(183)
- INTLIKE_HDR(184)
- INTLIKE_HDR(185)
- INTLIKE_HDR(186)
- INTLIKE_HDR(187)
- INTLIKE_HDR(188)
- INTLIKE_HDR(189)
- INTLIKE_HDR(190)
- INTLIKE_HDR(191)
- INTLIKE_HDR(192)
- INTLIKE_HDR(193)
- INTLIKE_HDR(194)
- INTLIKE_HDR(195)
- INTLIKE_HDR(196)
- INTLIKE_HDR(197)
- INTLIKE_HDR(198)
- INTLIKE_HDR(199)
- INTLIKE_HDR(200)
- INTLIKE_HDR(201)
- INTLIKE_HDR(202)
- INTLIKE_HDR(203)
- INTLIKE_HDR(204)
- INTLIKE_HDR(205)
- INTLIKE_HDR(206)
- INTLIKE_HDR(207)
- INTLIKE_HDR(208)
- INTLIKE_HDR(209)
- INTLIKE_HDR(210)
- INTLIKE_HDR(211)
- INTLIKE_HDR(212)
- INTLIKE_HDR(213)
- INTLIKE_HDR(214)
- INTLIKE_HDR(215)
- INTLIKE_HDR(216)
- INTLIKE_HDR(217)
- INTLIKE_HDR(218)
- INTLIKE_HDR(219)
- INTLIKE_HDR(220)
- INTLIKE_HDR(221)
- INTLIKE_HDR(222)
- INTLIKE_HDR(223)
- INTLIKE_HDR(224)
- INTLIKE_HDR(225)
- INTLIKE_HDR(226)
- INTLIKE_HDR(227)
- INTLIKE_HDR(228)
- INTLIKE_HDR(229)
- INTLIKE_HDR(230)
- INTLIKE_HDR(231)
- INTLIKE_HDR(232)
- INTLIKE_HDR(233)
- INTLIKE_HDR(234)
- INTLIKE_HDR(235)
- INTLIKE_HDR(236)
- INTLIKE_HDR(237)
- INTLIKE_HDR(238)
- INTLIKE_HDR(239)
- INTLIKE_HDR(240)
- INTLIKE_HDR(241)
- INTLIKE_HDR(242)
- INTLIKE_HDR(243)
- INTLIKE_HDR(244)
- INTLIKE_HDR(245)
- INTLIKE_HDR(246)
- INTLIKE_HDR(247)
- INTLIKE_HDR(248)
- INTLIKE_HDR(249)
- INTLIKE_HDR(250)
- INTLIKE_HDR(251)
- INTLIKE_HDR(252)
- INTLIKE_HDR(253)
- INTLIKE_HDR(254)
- INTLIKE_HDR(255) /* MAX_INTLIKE == 255
- See #16961 for why 255 */
-}
=====================================
rts/include/rts/Constants.h
=====================================
@@ -57,11 +57,12 @@
#define MAX_SPEC_CONSTR_SIZE 2
/* Range of built-in table of static small int-like and char-like closures.
+ * Range is inclusive of both minimum and maximum.
*
* NB. This corresponds with the number of actual INTLIKE/CHARLIKE
* closures defined in rts/StgMiscClosures.cmm.
*/
-#define MAX_INTLIKE 255
+#define MAX_INTLIKE 255 /* See #16961 for why 255 */
#define MIN_INTLIKE (-16)
#define MAX_CHARLIKE 255
=====================================
rts/include/stg/MiscClosures.h
=====================================
@@ -277,8 +277,8 @@ RTS_ENTRY(stg_NO_FINALIZER);
extern StgWordArray stg_CHARLIKE_closure;
extern StgWordArray stg_INTLIKE_closure;
#else
-extern StgIntCharlikeClosure stg_CHARLIKE_closure[];
-extern StgIntCharlikeClosure stg_INTLIKE_closure[];
+extern StgIntCharlikeClosure stg_CHARLIKE_closure[MAX_CHARLIKE - MIN_CHARLIKE + 1];
+extern StgIntCharlikeClosure stg_INTLIKE_closure[MAX_INTLIKE - MIN_INTLIKE + 1];
#endif
/* StgStartup */
=====================================
rts/rts.cabal
=====================================
@@ -403,6 +403,7 @@ library
adjustor/AdjustorPool.c
ExecPage.c
Arena.c
+ BuiltinClosures.c
Capability.c
CheckUnload.c
CheckVectorSupport.c
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/757b4319d11bba64ff23be588b97d2f…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/757b4319d11bba64ff23be588b97d2f…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/rts-rm-c99-check] autoconf/ghc-toolchain: remove obsolete C99 check
by Cheng Shao (@TerrorJack) 29 Sep '25
by Cheng Shao (@TerrorJack) 29 Sep '25
29 Sep '25
Cheng Shao pushed to branch wip/rts-rm-c99-check at Glasgow Haskell Compiler / GHC
Commits:
3c9bcb37 by Cheng Shao at 2025-09-29T20:07:47+02: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.
- - - - -
6 changed files:
- configure.ac
- distrib/configure.ac.in
- m4/fp_cmm_cpp_cmd_with_args.m4
- − m4/fp_set_cflags_c99.m4
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cc.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cpp.hs
Changes:
=====================================
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])
=====================================
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 <<EOF
-#include <stdio.h>
-#if !defined __STDC_VERSION__ || __STDC_VERSION__ < 199901L
-# error "Compiler does not advertise C99 conformance"
-#endif
-EOF
-if "$CMM_CPP_CMD" $CMM_CPP_ARGS conftest.c -o conftest -g0 >/dev/null 2>&1; then
- AC_MSG_RESULT([yes])
-else
- # Try -std=gnu99
- if "$CMM_CPP_CMD" -std=gnu99 $CMM_CPP_ARGS conftest.c -o conftest -g0 >/dev/null 2>&1; then
- $3="-std=gnu99 $$3"
- AC_MSG_RESULT([needs -std=gnu99])
- else
- AC_MSG_ERROR([C99-compatible compiler needed])
- fi
-fi
-rm -f conftest.c conftest.o conftest
-
-
$2="$CMM_CPP_CMD"
$3="$$3 $CMM_CPP_ARGS"
@@ -85,4 +64,3 @@ unset CMM_CPP_CMD
unset CMM_CPP_ARGS
])
-
=====================================
m4/fp_set_cflags_c99.m4 deleted
=====================================
@@ -1,38 +0,0 @@
-# FP_SET_CFLAGS_C99
-# ----------------------------------
-# figure out which CFLAGS are needed to place the compiler into C99 mode
-# $1 is name of CC variable (unmodified)
-# $2 is name of CC flags variable (augmented if needed)
-# $3 is name of CPP flags variable (augmented if needed)
-AC_DEFUN([FP_SET_CFLAGS_C99],
-[
- dnl save current state of AC_PROG_CC_C99
- FP_COPY_SHELLVAR([CC],[fp_save_CC])
- FP_COPY_SHELLVAR([CFLAGS],[fp_save_CFLAGS])
- FP_COPY_SHELLVAR([CPPFLAGS],[fp_save_CPPFLAGS])
- FP_COPY_SHELLVAR([ac_cv_prog_cc_c99],[fp_save_cc_c99])
- dnl set local state
- CC="$$1"
- CFLAGS="$$2"
- CPPFLAGS="$$3"
- unset ac_cv_prog_cc_c99
- dnl perform detection
- AC_PROG_CC_C99
- fp_cc_c99="$ac_cv_prog_cc_c99"
- case "x$ac_cv_prog_cc_c99" in
- x) ;; # noop
- xno) AC_MSG_ERROR([C99-compatible compiler needed]) ;;
- *) $2="$$2 $ac_cv_prog_cc_c99"
- $3="$$3 $ac_cv_prog_cc_c99"
- ;;
- esac
- dnl restore saved state
- FP_COPY_SHELLVAR([fp_save_CC],[CC])
- FP_COPY_SHELLVAR([fp_save_CFLAGS],[CFLAGS])
- FP_COPY_SHELLVAR([fp_save_CPPFLAGS],[CPPFLAGS])
- FP_COPY_SHELLVAR([fp_save_cc_c99],[ac_cv_prog_cc_c99])
- dnl cleanup
- unset fp_save_CC
- unset fp_save_CFLAGS
- unset fp_save_cc_c99
-])
=====================================
utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cc.hs
=====================================
@@ -11,7 +11,6 @@ module GHC.Toolchain.Tools.Cc
, compileC
, compileAsm
, addPlatformDepCcFlags
- , checkC99Support
) where
import Control.Monad
@@ -51,12 +50,8 @@ findCc archOs llvmTarget progOpt = do
cc1 <- ignoreUnusedArgs cc0
cc2 <- ccSupportsTarget archOs llvmTarget cc1
checking "whether Cc works" $ checkCcWorks cc2
- cc3 <- oneOf "cc doesn't support C99" $ map checkC99Support
- [ cc2
- , cc2 & _ccFlags %++ "-std=gnu99"
- ]
- checkCcSupportsExtraViaCFlags cc3
- return cc3
+ checkCcSupportsExtraViaCFlags cc2
+ return cc2
checkCcWorks :: Cc -> M ()
checkCcWorks cc = withTempDir $ \dir -> do
@@ -88,17 +83,6 @@ ccSupportsTarget archOs target cc =
checking "whether Cc supports --target" $
supportsTarget archOs _ccProgram checkCcWorks target cc
-checkC99Support :: Cc -> M Cc
-checkC99Support cc = checking "for C99 support" $ withTempDir $ \dir -> do
- let test_o = dir </> "test.o"
- compileC cc test_o $ unlines
- [ "#include <stdio.h>"
- , "#if !defined __STDC_VERSION__ || __STDC_VERSION__ < 199901L"
- , "# error \"Compiler does not advertise C99 conformance\""
- , "#endif"
- ]
- return cc
-
checkCcSupportsExtraViaCFlags :: Cc -> M ()
checkCcSupportsExtraViaCFlags cc = checking "whether cc supports extra via-c flags" $ withTempDir $ \dir -> do
let test_o = dir </> "test.o"
=====================================
utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cpp.hs
=====================================
@@ -19,7 +19,7 @@ import GHC.Toolchain.Prelude
import GHC.Toolchain.Program
import GHC.Toolchain.Tools.Cc
-import GHC.Toolchain.Utils (withTempDir, oneOf, expectFileExists)
+import GHC.Toolchain.Utils (withTempDir, expectFileExists)
newtype Cpp = Cpp { cppProgram :: Program
}
@@ -160,13 +160,7 @@ findJsCpp progOpt cc = checking "for JavaScript C preprocessor" $ do
findCmmCpp :: ProgOpt -> Cc -> M CmmCpp
findCmmCpp progOpt cc = checking "for a Cmm preprocessor" $ do
-- Use the specified CPP or try to use the c compiler
- foundCppProg <- findProgram "Cmm preprocessor" progOpt [] <|> pure (programFromOpt progOpt (prgPath $ ccProgram cc) [])
- -- Check whether the C preprocessor needs -std=gnu99 (only very old toolchains need this)
- Cc cpp <- oneOf "cc doesn't support C99" $ map checkC99Support
- [ Cc foundCppProg
- , Cc (foundCppProg & _prgFlags %++ "-std=gnu99")
- ]
-
+ cpp <- findProgram "Cmm preprocessor" progOpt [] <|> pure (programFromOpt progOpt (prgPath $ ccProgram cc) [])
cmmCppSupportsG0 <- withTempDir $ \dir -> do
let conftest = dir </> "conftest.c"
writeFile conftest "int main(void) {}"
@@ -181,14 +175,9 @@ findCmmCpp progOpt cc = checking "for a Cmm preprocessor" $ do
findCpp :: ProgOpt -> Cc -> M Cpp
findCpp progOpt cc = checking "for C preprocessor" $ do
-- Use the specified CPP or try to use the c compiler
- foundCppProg <- findProgram "C preprocessor" progOpt [] <|> pure (programFromOpt progOpt (prgPath $ ccProgram cc) [])
- -- Check whether the C preprocessor needs -std=gnu99 (only very old toolchains need this)
- Cc cpp2 <- oneOf "cc doesn't support C99" $ map checkC99Support
- [ Cc foundCppProg
- , Cc (foundCppProg & _prgFlags %++ "-std=gnu99")
- ]
+ cpp <- findProgram "C preprocessor" progOpt [] <|> pure (programFromOpt progOpt (prgPath $ ccProgram cc) [])
-- Always add the -E flag to the CPP, regardless of the user options
- let cppProgram = addFlagIfNew "-E" cpp2
+ let cppProgram = addFlagIfNew "-E" cpp
return Cpp{cppProgram}
--------------------------------------------------------------------------------
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3c9bcb378efe476fed312fe4e12c6a5…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3c9bcb378efe476fed312fe4e12c6a5…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
29 Sep '25
Cheng Shao pushed new branch wip/rts-rm-c99-check at Glasgow Haskell Compiler / GHC
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/rts-rm-c99-check
You're receiving this email because of your account on gitlab.haskell.org.
1
0
29 Sep '25
Rodrigo Mesquita pushed new branch wip/romes/T26166 at Glasgow Haskell Compiler / GHC
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/romes/T26166
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/batch-loaddll] 53 commits: Enable TcM plugins in initTc
by Cheng Shao (@TerrorJack) 29 Sep '25
by Cheng Shao (@TerrorJack) 29 Sep '25
29 Sep '25
Cheng Shao pushed to branch wip/batch-loaddll at Glasgow Haskell Compiler / GHC
Commits:
de44e69e by sheaf at 2025-09-19T05:16:51-04:00
Enable TcM plugins in initTc
This commit ensures that we run typechecker plugins and defaulting
plugins whenever we call initTc.
In particular, this ensures that the pattern-match checker, which calls
'initTcDsForSolver' which calls 'initTc', runs with typechecker plugins
enabled. This matters for situations like:
merge :: Vec n a -> Vec n a -> Vec (2 * n) a
merge Nil Nil = Nil
merge (a <: as) (b <: bs) = a :< (b <: merge as bs)
in which we need the typechecker plugin to run in order to tell us that
the Givens would be inconsistent in the additional equation
merge (_ <: _) Nil
and thus that the equation is not needed.
Fixes #26395
- - - - -
2c378ad2 by Cheng Shao at 2025-09-19T05:17:33-04:00
rel-eng: update fedora image to 42
This patch is a part of #25876 and updates fedora image to 42.
- - - - -
0a9d9ffc by Sylvain Henry at 2025-09-19T13:12:14-04:00
Fix output of T14999 (#23685)
Fix output of T14999 to:
- take into account the +1 offset to DW_AT_low_pc (see Note [Info Offset])
- always use Intel's syntax to force consistency: it was reported that
sometimes GDB prints `jmpq` instead of `jmp` with the AT&T syntax
- - - - -
1480872a by Vladislav Zavialov at 2025-09-19T13:12:54-04:00
Fix PREP_MAYBE_LIBRARY in prep_target_file.m4
This change fixes a configure error introduced in:
commit 8235dd8c4945db9cb03e3be3c388d729d576ed1e
ghc-toolchain: Move UseLibdw to per-Target file
Now the build no longer fails with:
acghc-toolchain: Failed to read a valid Target value from hadrian/cfg/default.target
- - - - -
d1d9e39e by Ben Gamari at 2025-09-19T18:24:52-04:00
StgToByteCode: Don't assume that data con workers are nullary
Previously StgToByteCode assumed that all data-con workers were of a
nullary representation. This is not a valid assumption, as seen
in #23210, where an unsaturated application of a unary data
constructor's worker resulted in invalid bytecode. Sadly, I have not yet
been able to reduce a minimal testcase for this.
Fixes #23210.
- - - - -
3eeecd50 by Ben Gamari at 2025-09-19T18:24:53-04:00
testsuite: Mark T23146* as unbroken
- - - - -
2e73f342 by sheaf at 2025-09-19T18:24:53-04:00
Add test for #26216
- - - - -
c2efb912 by Sven Tennie at 2025-09-19T18:25:36-04:00
Generate correct test header
This increases convenience when copying & pasting...
- - - - -
d2fb811e by Sven Tennie at 2025-09-19T18:25:36-04:00
foundation test: Fix shift amount (#26248)
Shift primops' results are only defined for shift amounts of 0 to word
size - 1. The approach is similar to testing div-like operations (which
have a constraint regarding zero operands.)
This was partly vibe coded (https://github.com/supersven/ghc/pull/1) but
then heavily refactored.
- - - - -
a62ce115 by Andreas Klebinger at 2025-09-19T18:26:18-04:00
Tweak jspace test
I've given it a longer timeout, and tweaked the test file generation
to speed it up a bit. Hopefully that is enough to make it constentily pass.
Last but not least it now also always uses three threads.
- - - - -
0f034942 by Cheng Shao at 2025-09-19T18:26:59-04:00
rts: remove obsolete CC_SUPPORTS_TLS logic
This patch removes obsolete CC_SUPPORTS_TLS logic throughout the rts,
given __thread is now uniformly supported by C toolchains of all
platforms we currently support.
- - - - -
ef705655 by Cheng Shao at 2025-09-19T18:27:41-04:00
rts: remove obsolete HAS_VISIBILITY_HIDDEN logic
This patch removes obsolete HAS_VISIBILITY_HIDDEN logic throughout the
rts, given __attribute__((visibility("hidden"))) is uniformly
supported by C toolchains of all platforms we currently support.
- - - - -
9fdc1f7d by Cheng Shao at 2025-09-19T18:28:21-04:00
rts: remove -O3 pragma hack in Hash.c
This patch removes an obsolete gcc pragma to specify -O3 in Hash.c.
Hadrian already passes the right flag.
- - - - -
b8cfa8f7 by Cheng Shao at 2025-09-19T18:29:01-04:00
rts: remove obsolete COMPILING_WINDOWS_DLL logic
This patch removes obsolete COMPILING_WINDOWS_DLL logic throughout the
rts. They were once used for compiling to win32 DLLs, but we haven't
been able to compile Haskell units to win32 DLLs for many years now,
due to PE format's restriction of no more than 65536 exported symbols
in a single DLL.
- - - - -
bb760611 by Cheng Shao at 2025-09-19T18:29:42-04:00
wasm: bump browser_wasi_shim to 0.4.2
This patch bumps the browser_wasi_shim dependency of wasm dyld script
to 0.4.2.
- - - - -
8b0940db by Cheng Shao at 2025-09-20T06:48:05-04:00
compiler: move Binary instance of Map to GHC.Utils.Binary
This patch moves `Binary` instance of `Map` from `haddock-api` to
`GHC.Utils.Binary`. This also allows us to remove a redundant instance
defined for `NameEntityInfo`, which is a type synonym for `Map`.
- - - - -
4a8fed75 by Vladislav Zavialov at 2025-09-20T06:48:47-04:00
Fix keyword in ExplicitNamespaces error message (#26418)
Consider this module header and the resulting error:
{-# LANGUAGE NoExplicitNamespaces #-}
module T26418 (data HeadC) where
-- error: [GHC-47007]
-- Illegal keyword 'type'
Previously, the error message would mention 'type' (as shown above),
even though the user wrote 'data'. This has now been fixed.
The error location has also been corrected: it is now reported at the
keyword position rather than at the position of the associated
import/export item.
- - - - -
867c2675 by Cheng Shao at 2025-09-20T06:49:28-04:00
wasm: fix dyld handling for forward declared GOT.func items
This patch fixes wasm shared linker's handling of forward declared
GOT.func items, see linked issue for details. Also adds T26430 test to
witness the fix. Fixes #26430.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
e7df6cc0 by Simon Peyton Jones at 2025-09-23T14:34:39-04:00
Improve pretty printer for HsExpr
Given a very deeply-nested application, it just kept printing
deeper and deeper. This small change makes it cut off.
Test is in #26330, but we also get a dramatic decrease in compile
time for perf/compiler/InstanceMatching:
InstanceMatching 4,086,884,584 1,181,767,232 -71.1% GOOD
Why? Because before we got a GIGANTIC error message that took
ages to pretty-print; now we get this much more civilised message
(I have removed some whitespace.)
Match.hs:1007:1: error:
• No instance for ‘Show (F001 a)’ arising from a use of ‘showsPrec’
• In the second argument of ‘showString’, namely
‘(showsPrec
11 b1
(GHC.Internal.Show.showSpace
(showsPrec
11 b2
(GHC.Internal.Show.showSpace
(showsPrec
11 b3
(GHC.Internal.Show.showSpace
(showsPrec
11 b4
(GHC.Internal.Show.showSpace
(showsPrec
11 b5
(GHC.Internal.Show.showSpace
(showsPrec
11 b6
(GHC.Internal.Show.showSpace (showsPrec ...)))))))))))))’
-----------------------
The main payload is
* At the start of `pprExpr`
* In the defn of `pprApp`
A little bit of refactoring:
* It turned out that we were setting the default cut-off depth to a
fixed value in two places, so changing one didn't change the other.
See defaultSDocDepth and defaultSDocCols
* I refactored `pprDeeperList` a bit so I could understand it better.
Because the depth calculation has changed, there are lots of small
error message wibbles.
Metric Decrease:
InstanceMatching
- - - - -
209f0158 by Simon Peyton Jones at 2025-09-23T14:34:39-04:00
Use Outputable.ellipsis rather than text "..."
- - - - -
64bb0e37 by Sylvain Henry at 2025-09-23T14:35:56-04:00
deriveConstants: automatically pass -fcommon CC flag (#26393)
By mistake we tried to use deriveConstants without passing
`--gcc-flag -fcommon` (which Hadrian does) and it failed.
This patch:
1. adds parsing support for constants stored in the .bss section (i.e.
when -fcommon isn't passed)
2. enables passing `-fcommon` automatically to the C compiler because
Windows requires this for subtle reasons
3. Documents the subtle reasons
(1) isn't strictly necessary because we always do (2) but it does no
harm and it is still useful if the CC flags ever contain -fno-common
- - - - -
afcdf92f by Oleg Grenrus at 2025-09-23T14:36:41-04:00
Don't wrap spaces in <span>s
Doing similar comparison as in 63189b2ceca07edf4e179f4180ca60d470c62cb3
With this change the gzipped documentation is now 2% smaller (previously 1%)
12_694_206 Agda-2.9.0-docs-orig.tar.gz
12_436_829 Agda-2.9.0-docs.tar.gz
Unzipped docs are 5% smaller (previously 3%)
178M Agda-2.9.0-docs-orig
169M Agda-2.9.0-docs
Individual hyperlinked sources are around 7-10% smaller (previously 5%)
(`Parser` module is generated by happy and has relatively little whitespace)
14_230_117 Agda.Syntax.Parser.Parser.html
13_220_758 Agda.Syntax.Parser.Parser.html
Agda's hyperlinked sources are 9% smaller now:
121M Agda-2.9.0-docs-orig/src
110M Agda-2.9.0-docs/src
- - - - -
67de53a6 by Cheng Shao at 2025-09-23T14:37:31-04:00
rts: remove obsolete __GNUC__ related logic
This patch removes obsolete `__GNUC__` related logic, given on any
currently supported platform and toolchain, `__GNUC__ >= 4` is
universally true. Also pulls some other weeds and most notably, use
`__builtin___clear_cache` for clang as well, since clang has supported
this gcc intrinsic since 2014, see
https://github.com/llvm/llvm-project/commit/c491a8d4577052bc6b3b4c72a7db6a7….
- - - - -
c4d32493 by Sven Tennie at 2025-09-23T20:40:57-04:00
RV64: Fix: Add missing truncation to MO_S_Shr (#26248)
Sub-double word (<W64) registers need to be truncated after the
operation.
- - - - -
41dce477 by Sven Tennie at 2025-09-23T20:40:57-04:00
RV64: Cleanup shift emitting cases/code
Remove overlapping cases to make the shift logic easier to understand.
- - - - -
0a601c30 by Alex Washburn at 2025-09-23T20:41:41-04:00
Correcting LLVM linking of Intel BMI intrinsics pdep{8,16} and pext{8,16}.
This patch fixes #26065.
The LLVM interface does not expose bindings to:
- llvm.x86.bmi.pdep.8
- llvm.x86.bmi.pdep.16
- llvm.x86.bmi.pext.8
- llvm.x86.bmi.pext.16
So calls are instead made to llvm.x86.bmi.{pdep,pext}.32 in these cases,
with pre/post-operation truncation to constrain the logical value range.
- - - - -
89e8ff3d by Peng Fan at 2025-09-23T20:42:37-04:00
NCG/LA64: Implement MO_BSwap and MO_BRev with bit-manipulation Instructions
- - - - -
50f6be09 by Sylvain Henry at 2025-09-23T20:43:29-04:00
Allow Core plugins to access unoptimized Core (#23337)
Make the first simple optimization pass after desugaring a real CoreToDo
pass. This allows CorePlugins to decide whether they want to be executed
before or after this pass.
- - - - -
30ef0aac by Simon Hengel at 2025-09-23T20:44:12-04:00
docs: Fix typo in scoped_type_variables.rst
- - - - -
f8919262 by Cheng Shao at 2025-09-23T20:44:54-04:00
ghci: fix bootstrapping with 9.12.3-rc1 and above
This patch fixes bootstrapping GHC with 9.12.3-rc1 and above. ghci
defines `Binary` instance for `HalfWord` in `ghc-heap`, which is a
proper `newtype` in 9.14 and starting from 9.12.3. Given we don't
build `ghc-heap` in stage0, we need to fix this predicate so that it
corresponds to the boot ghc versions that contain the right version of
`ghc-heap`.
- - - - -
a7f15858 by sheaf at 2025-09-24T09:49:53-04:00
User's guide: clarify optimisation of INLINABLE unfoldings
This updates the user's guide section on INLINABLE pragmas to explain how
the unfoldings of inlineable functions are optimised. The user's guide incorrectly
stated that the RHS was not optimised at all, but this is not true. Instead, GHC
is careful about phase control to optmise the RHS while retaining the guarantee
that GHC behaves as if the original RHS had been written.
- - - - -
495886d9 by Rodrigo Mesquita at 2025-09-24T09:50:35-04:00
cleanup: Delete historical artifact of COMPILING_WINDOWS_DLL
Namely, drop the obsolete
- DLL_IMPORT_RTS
- DLL_IMPORT_DATA_VAR
- DLL_IMPORT_DATA_VARNAME
- DLL_IMPORT_DATA_REF
These macros were not doing anything and placed inconsistently
Looking at the git logs reveal these macros were used to support
dynamic libraries on Win32, a feature that was dropped
in b8cfa8f741729ef123569fb321c4b2ab4a1a941c
This allows us to get rid of the rts/DLL.h file too.
- - - - -
5ae89054 by Sylvain Henry at 2025-09-24T17:07:00-04:00
Allow disabling builtin rules (#20298)
Add a way to disable built-in rules programmatically and with a debug flag.
I also took the opportunity to add a debug flag to disable bignum rules,
which was only possible programmatically (e.g. in a plugin).
- - - - -
135242ca by Rodrigo Mesquita at 2025-09-24T17:07:44-04:00
Don't use build CFLAGS and friends as target settings
In the GHC in tree configure, `CFLAGS`, `CXXFLAGS`, and similar tool
configuration flags apply to the BUILD phase of the compiler, i.e. to
the tools run to compile GHC itself.
Notably, they should /not/ be carried over to the Target settings, i.e.
these flags should /not/ apply to the tool which GHC invokes at runtime.
Fixes #25637
- - - - -
b418408b by Irene Knapp at 2025-09-25T09:47:54-04:00
Document etymology of "bind" as the name for `>>=`
It took me twenty years of contemplation to realize why it's called that.
I therefore feel that it may not be obvious to beginners.
- - - - -
e9c5e46f by Brandon Chinn at 2025-09-25T09:48:36-04:00
Fix tabs in string gaps (#26415)
Tabs in string gaps were broken in bb030d0d because previously, string gaps were manually parsed, but now it's lexed by the usual Alex grammar and post-processed after successful lexing.
It broke because of a discrepancy between GHC's lexer grammar and the Haskell Report. The Haskell Report includes tabs in whitechar:
whitechar → newline | vertab | space | tab | uniWhite
$whitechar used to include tabs until 18 years ago, when it was removed in order to exclude tabs from $white_no_nl in order to warn on tabs: 6e202120. In this MR, I'm adding \t back into $whitechar, and explicitly excluding \t from the $white_no_nl+ rule ignoring all whitespace in source code, which more accurately colocates the "ignore all whitespace except tabs, which is handled in the next line" logic.
As a side effect of this MR, tabs are now allowed in pragmas; currently, a pragma written as {-# \t LANGUAGE ... #-} is interpreted as the tab character being the pragma name, and GHC warns "Unrecognized pragma". With this change, tabs are ignored as whitespace, which more closely matches the Report anyway.
- - - - -
8bf5b309 by Cheng Shao at 2025-09-25T09:49:18-04:00
wasm: remove the --no-turbo-fast-api-calls hack from dynamic linker shebang
This patch removes the `--no-turbo-fast-api-calls` hack from the dyld
script shebang; it was used to workaround v8 fast call coredumps in
nodejs and no longer needed, and comes with a performance penalty,
hence the removal.
- - - - -
c1cab0c3 by Sylvain Henry at 2025-09-26T10:36:30-04:00
Revert "Add necessary flag for js linking"
This reverts commit 84f68e2231b2eddb2e1dc4e90af394ef0f2e803f.
This commit didn't have the expected effect. See discussion in #26290.
Instead we export HEAP8 and HEAPU8 from rts/js/mem.js
- - - - -
0a434a80 by Sylvain Henry at 2025-09-26T10:36:30-04:00
JS: export HEAPU8 (#26290)
This is now required by newer Emscripten versions.
- - - - -
b10296a9 by Andreas Klebinger at 2025-09-26T10:37:11-04:00
sizeExpr: Improve Tick handling.
When determining if we scrutinize a function argument we
now properly look through ticks. Fixes #26444.
- - - - -
d9e2a9a7 by mniip at 2025-09-26T16:00:50-04:00
rts: Refactor parsing of -h flags
We have a nontrivial amount of heap profiling flags available in the
non-profiled runtime, so it makes sense to reuse the parsing code
between the profiled and the non-profiled runtime, only restricting
which flags are allowed.
- - - - -
089e45aa by mniip at 2025-09-26T16:00:50-04:00
rts: Fix parsing of -h options with braces
When the "filter by" -h options were introduced in
bc210f7d267e8351ccb66972f4b3a650eb9338bb, the braces were mandatory.
Then in 3c22fb21fb18e27ce8d941069a6915fce584a526, the braces were made
optional. Then in d1ce35d2271ac8b79cb5e37677b1a989749e611c the brace
syntax stopped working, and no one seems to have noticed.
- - - - -
423f1472 by mniip at 2025-09-26T16:00:50-04:00
rts: add -hT<type> and -hi<table id> heap filtering options (#26361)
They are available in non-profiled builds.
Along the way fixed a bug where combining -he<era> and -hr<retainer>
would ignore whether the retainer matches or not.
- - - - -
4cda4785 by mniip at 2025-09-26T16:00:50-04:00
docs: Document -hT<type> and -hi<addr>
- - - - -
982ad30f by mniip at 2025-09-26T16:00:50-04:00
rts: Refactor dumping the heap census
Always do the printing of the total size right next to where the bucket
label is printed. This prevents accidentally printing a label without
the corresponding amount.
Fixed a bug where exactly this happened for -hi profile and the 0x0
(uncategorized) info table.
There is now also much more symmetry between fprintf(hp_file,...) and
the corresponding traceHeapProfSampleString.
- - - - -
8cbe006a by Cheng Shao at 2025-09-26T16:01:34-04:00
hadrian: fix GHC.Platform.Host generation for cross stage1
This patch fixes incorrectly GHC.Platform.Host generation logic for
cross stage1 in hadrian (#26449). Also adds T26449 test case to
witness the fix.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
0ddd0fdc by soulomoon at 2025-09-28T19:24:10-04:00
Remove hptAllInstances usage during upsweep
Previously, during the upsweep phase when
checking safe imports, we were loading the module
interface with runTcInteractive, which in turn calls
hptAllInstances. This accesses non-below modules
from the home package table.
Change the implementation of checkSafeImports
to use initTcWithGbl and loadSysInterface to load the
module interface, since we already have TcGblEnv at hand.
This eliminates the unnecessary use of runTcInteractive
and hptAllInstances during the upsweep phase.
- - - - -
e05c496c by Ben Gamari at 2025-09-28T19:24:59-04:00
base: Update changelog to reflect timing of IOPort# removal
This change will make 9.14 afterall.
- - - - -
bdc9d130 by Cheng Shao at 2025-09-28T19:25:45-04:00
rts: fix wasm JSFFI initialization constructor code
This commit fixes wasm JSFFI initialization constructor code so that
the constructor is self-contained and avoids invoking a fake
__main_argc_argv function. The previous approach of reusing
__main_void logic in wasi-libc saves a tiny bit of code, at the
expense of link-time trouble whenever GHC links a wasm module without
-no-hs-main, in which case the driver-generated main function would
clash with the definition here, resulting in a linker error. It's
simply better to avoid messing with the main function, and it would
additionally allow linking wasm32-wasi command modules that does make
use of synchronous JSFFI.
- - - - -
5d59fc8f by Cheng Shao at 2025-09-28T19:26:27-04:00
rts: provide stub implementations of ExecPage functions for wasm
This patch provides stub implementations of ExecPage functions for
wasm. They are never actually invoked at runtime for any non-TNTC
platform, yet they can cause link-time errors of missing symbols when
the GHCi.InfoTable module gets linked into the final wasm module (e.g.
a GHC API program).
- - - - -
a4d664c7 by Cheng Shao at 2025-09-29T17:29:22+02:00
compiler/ghci: replace the LoadDLL message with LoadDLLs
As a part of #25407, this commit changes the LoadDLL message to
LoadDLLs, which takes a list of DLL paths to load and returns the list
of remote pointer handles. The wasm dyld is refactored to take
advantage of LoadDLLs and harvest background parallelism. On other
platforms, LoadDLLs is based on a fallback codepath that does
sequential loading.
The driver is not actually emitting singular LoadDLLs message with
multiple DLLs yet, this is left in subsequent commits.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
c7fc4bae by Cheng Shao at 2025-09-29T17:29:22+02:00
driver: separate downsweep/upsweep phase in loadPackages'
This commit refactors GHC.Linker.Loader.loadPackages' to be separated
into downsweep/upsweep phases:
- The downsweep phase performs dependency analysis and generates a
list of topologically sorted packages to load
- The upsweep phase sequentially loads these packages by calling
loadPackage
This is a necessary refactoring to make it possible to make loading of
DLLs concurrent.
- - - - -
ab180104 by Cheng Shao at 2025-09-29T17:57:19+02:00
driver: emit single LoadDLLs message to load multiple DLLs
This commit refactors the driver so that it emits a single LoadDLLs
message to load multiple DLLs in GHC.Linker.Loader.loadPackages'.
Closes #25407.
-------------------------
Metric Increase:
MultiLayerModulesTH_OneShot
TcPlugin_RewritePerf
-------------------------
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
221 changed files:
- .gitlab-ci.yml
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/CmmToAsm/LA64/CodeGen.hs
- compiler/GHC/CmmToAsm/LA64/Instr.hs
- compiler/GHC/CmmToAsm/LA64/Ppr.hs
- compiler/GHC/CmmToAsm/RV64/CodeGen.hs
- compiler/GHC/CmmToLlvm/CodeGen.hs
- compiler/GHC/Core/Opt/ConstantFold.hs
- compiler/GHC/Core/Opt/Pipeline.hs
- compiler/GHC/Core/Opt/Pipeline/Types.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Ppr.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/Rules/Config.hs
- compiler/GHC/Core/Unfold.hs
- compiler/GHC/Driver/Config/Core/Rules.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Plugins.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/HsToCore.hs
- compiler/GHC/HsToCore/Errors/Ppr.hs
- compiler/GHC/HsToCore/Monad.hs
- compiler/GHC/HsToCore/Pmc/Ppr.hs
- compiler/GHC/HsToCore/Pmc/Types.hs
- compiler/GHC/Iface/Ext/Types.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Linker/MacOS.hs
- compiler/GHC/Linker/Types.hs
- compiler/GHC/Llvm/Ppr.hs
- compiler/GHC/Llvm/Types.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Errors/Ppr.hs
- compiler/GHC/Parser/Errors/Types.hs
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/Lexer/String.x
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Parser/Types.hs
- compiler/GHC/Runtime/Heap/Inspect.hs
- compiler/GHC/Runtime/Interpreter.hs
- compiler/GHC/Runtime/Loader.hs
- compiler/GHC/StgToByteCode.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Tc/Utils/Monad.hs
- compiler/GHC/Types/Hint/Ppr.hs
- compiler/GHC/Utils/Binary.hs
- compiler/GHC/Utils/Outputable.hs
- compiler/GHC/Utils/Ppr.hs
- configure.ac
- docs/users_guide/debugging.rst
- docs/users_guide/exts/pragmas.rst
- docs/users_guide/exts/scoped_type_variables.rst
- docs/users_guide/profiling.rst
- hadrian/src/Rules/Generate.hs
- hadrian/src/Settings/Builders/DeriveConstants.hs
- libraries/base/changelog.md
- libraries/ghc-internal/cbits/atomic.c
- libraries/ghc-internal/cbits/ctz.c
- libraries/ghc-internal/src/GHC/Internal/Base.hs
- libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc
- libraries/ghci/GHCi/Message.hs
- libraries/ghci/GHCi/ObjLink.hs
- libraries/ghci/GHCi/Run.hs
- m4/fp_setup_windows_toolchain.m4
- − m4/fp_visibility_hidden.m4
- m4/fptools_set_c_ld_flags.m4
- m4/ghc_toolchain.m4
- m4/prep_target_file.m4
- rts/BeginPrivate.h
- rts/CloneStack.h
- rts/EndPrivate.h
- rts/ExecPage.c
- rts/Hash.c
- rts/Interpreter.c
- rts/Prelude.h
- rts/ProfHeap.c
- rts/RetainerSet.c
- − rts/RtsDllMain.c
- − rts/RtsDllMain.h
- rts/RtsFlags.c
- rts/RtsStartup.c
- rts/RtsSymbols.c
- rts/StgMiscClosures.cmm
- rts/Task.c
- rts/Task.h
- rts/configure.ac
- rts/include/Rts.h
- rts/include/RtsAPI.h
- rts/include/Stg.h
- rts/include/rts/Flags.h
- rts/include/rts/NonMoving.h
- rts/include/rts/OSThreads.h
- rts/include/rts/StableName.h
- rts/include/rts/StablePtr.h
- rts/include/rts/Types.h
- − rts/include/stg/DLL.h
- rts/include/stg/MiscClosures.h
- rts/js/mem.js
- rts/posix/OSThreads.c
- rts/rts.cabal
- rts/sm/BlockAlloc.c
- rts/sm/Evac.c
- rts/sm/Evac.h
- rts/sm/GCTDecl.h
- rts/sm/GCThread.h
- rts/sm/Storage.c
- rts/wasm/JSFFI.c
- rts/win32/OSThreads.c
- testsuite/driver/testlib.py
- testsuite/tests/arrows/gadt/T17423.stderr
- + testsuite/tests/bytecode/T26216.hs
- + testsuite/tests/bytecode/T26216.script
- + testsuite/tests/bytecode/T26216.stdout
- + testsuite/tests/bytecode/T26216_aux.hs
- testsuite/tests/bytecode/all.T
- testsuite/tests/codeGen/should_compile/Makefile
- testsuite/tests/codeGen/should_compile/T14999.stdout
- + testsuite/tests/codeGen/should_compile/T20298a.hs
- + testsuite/tests/codeGen/should_compile/T20298a.stderr
- + testsuite/tests/codeGen/should_compile/T20298b.hs
- + testsuite/tests/codeGen/should_compile/T20298b.stderr
- + testsuite/tests/codeGen/should_compile/T20298c.hs
- + testsuite/tests/codeGen/should_compile/T20298c.stderr
- testsuite/tests/codeGen/should_compile/all.T
- testsuite/tests/codeGen/should_run/T23146/all.T
- + testsuite/tests/cross/should_run/T26449.hs
- + testsuite/tests/cross/should_run/all.T
- testsuite/tests/driver/j-space/Makefile
- testsuite/tests/driver/j-space/all.T
- testsuite/tests/driver/j-space/genJspace
- + testsuite/tests/ghci-wasm/Makefile
- + testsuite/tests/ghci-wasm/T26430.hs
- + testsuite/tests/ghci-wasm/T26430A.c
- + testsuite/tests/ghci-wasm/T26430B.c
- + testsuite/tests/ghci-wasm/all.T
- testsuite/tests/indexed-types/should_compile/PushedInAsGivens.stderr
- testsuite/tests/indexed-types/should_fail/T26176.stderr
- testsuite/tests/indexed-types/should_fail/T2693.stderr
- testsuite/tests/indexed-types/should_fail/T4093b.stderr
- testsuite/tests/indexed-types/should_fail/T8518.stderr
- testsuite/tests/indexed-types/should_fail/T9662.stderr
- testsuite/tests/interface-stability/ghc-experimental-exports.stdout
- testsuite/tests/interface-stability/ghc-experimental-exports.stdout-mingw32
- testsuite/tests/linear/should_fail/Linear17.stderr
- testsuite/tests/linear/should_fail/LinearLet7.stderr
- + testsuite/tests/llvm/should_run/T26065.hs
- + testsuite/tests/llvm/should_run/T26065.stdout
- testsuite/tests/llvm/should_run/all.T
- testsuite/tests/numeric/should_run/foundation.hs
- testsuite/tests/parser/should_fail/RecordDotSyntaxFail10.stderr
- testsuite/tests/parser/should_fail/RecordDotSyntaxFail11.stderr
- testsuite/tests/parser/should_fail/RecordDotSyntaxFail13.stderr
- testsuite/tests/parser/should_fail/RecordDotSyntaxFail8.stderr
- testsuite/tests/parser/should_fail/T16270h.stderr
- + testsuite/tests/parser/should_fail/T26418.hs
- + testsuite/tests/parser/should_fail/T26418.stderr
- testsuite/tests/parser/should_fail/all.T
- + testsuite/tests/parser/should_run/T26415.hs
- + testsuite/tests/parser/should_run/T26415.stdout
- testsuite/tests/parser/should_run/all.T
- testsuite/tests/partial-sigs/should_compile/T21719.stderr
- testsuite/tests/plugins/annotation-plugin/SayAnnNames.hs
- testsuite/tests/plugins/late-plugin/LatePlugin.hs
- testsuite/tests/plugins/simple-plugin/Simple/ReplacePlugin.hs
- testsuite/tests/polykinds/T13393.stderr
- testsuite/tests/rep-poly/T12709.stderr
- testsuite/tests/rts/linker/T2615.hs
- testsuite/tests/simplCore/should_compile/simpl017.stderr
- + testsuite/tests/tcplugins/T26395.hs
- + testsuite/tests/tcplugins/T26395.stderr
- + testsuite/tests/tcplugins/T26395_Plugin.hs
- testsuite/tests/tcplugins/all.T
- testsuite/tests/th/T10945.stderr
- testsuite/tests/th/TH_StaticPointers02.stderr
- testsuite/tests/typecheck/should_compile/T11339.stderr
- testsuite/tests/typecheck/should_fail/DoExpansion3.stderr
- testsuite/tests/typecheck/should_fail/T12177.stderr
- testsuite/tests/typecheck/should_fail/T22707.stderr
- testsuite/tests/typecheck/should_fail/T24064.stderr
- + testsuite/tests/typecheck/should_fail/T26330.hs
- + testsuite/tests/typecheck/should_fail/T26330.stderr
- testsuite/tests/typecheck/should_fail/T8142.stderr
- testsuite/tests/typecheck/should_fail/T8603.stderr
- testsuite/tests/typecheck/should_fail/all.T
- testsuite/tests/typecheck/should_fail/tcfail128.stderr
- testsuite/tests/typecheck/should_fail/tcfail153.stderr
- testsuite/tests/typecheck/should_fail/tcfail168.stderr
- testsuite/tests/typecheck/should_fail/tcfail177.stderr
- testsuite/tests/typecheck/should_fail/tcfail185.stderr
- testsuite/tests/typecheck/should_run/Typeable1.stderr
- utils/deriveConstants/Main.hs
- utils/genprimopcode/Main.hs
- utils/genprimopcode/Syntax.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Link.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker/Renderer.hs
- utils/haddock/haddock-api/src/Haddock/InterfaceFile.hs
- utils/haddock/hypsrc-test/ref/src/Bug1091.html
- utils/haddock/hypsrc-test/ref/src/CPP.html
- utils/haddock/hypsrc-test/ref/src/Classes.html
- utils/haddock/hypsrc-test/ref/src/Constructors.html
- utils/haddock/hypsrc-test/ref/src/Identifiers.html
- utils/haddock/hypsrc-test/ref/src/LinkingIdentifiers.html
- utils/haddock/hypsrc-test/ref/src/Literals.html
- utils/haddock/hypsrc-test/ref/src/Operators.html
- utils/haddock/hypsrc-test/ref/src/Polymorphism.html
- utils/haddock/hypsrc-test/ref/src/PositionPragmas.html
- utils/haddock/hypsrc-test/ref/src/Quasiquoter.html
- utils/haddock/hypsrc-test/ref/src/Records.html
- utils/haddock/hypsrc-test/ref/src/TemplateHaskellQuasiquotes.html
- utils/haddock/hypsrc-test/ref/src/TemplateHaskellSplices.html
- utils/haddock/hypsrc-test/ref/src/Types.html
- utils/haddock/hypsrc-test/ref/src/UsingQuasiquotes.html
- utils/jsffi/dyld.mjs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9fa898187bec4fc1b1905078b7758f…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9fa898187bec4fc1b1905078b7758f…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
Ben Gamari pushed new branch wip/T26166-1 at Glasgow Haskell Compiler / GHC
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T26166-1
You're receiving this email because of your account on gitlab.haskell.org.
1
0