
[Git][ghc/ghc][master] 2 commits: Remove deprecated functions from the ghci package
by Marge Bot (@marge-bot) 20 Aug '25
by Marge Bot (@marge-bot) 20 Aug '25
20 Aug '25
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
f0a19d74 by fendor at 2025-08-20T19:55:00-04:00
Remove deprecated functions from the ghci package
- - - - -
ebeb991b by fendor at 2025-08-20T19:55:00-04:00
base: Remove unstable heap representation details from GHC.Exts
- - - - -
6 changed files:
- libraries/base/changelog.md
- libraries/base/src/GHC/Exts.hs
- libraries/ghci/GHCi/CreateBCO.hs
- libraries/ghci/GHCi/TH.hs
- libraries/ghci/ghci.cabal.in
- − testsuite/tests/module/T21752.stderr
Changes:
=====================================
libraries/base/changelog.md
=====================================
@@ -1,6 +1,7 @@
# Changelog for [`base` package](http://hackage.haskell.org/package/base)
## 4.23.0.0 *TBA*
+ * Remove deprecated, unstable heap representation details from `GHC.Exts` ([CLC proposal #212](https://github.com/haskell/core-libraries-committee/issues/212))
* Add `Data.List.NonEmpty.mapMaybe`. ([CLC proposal #337](https://github.com/haskell/core-libraries-committee/issues/337))
* 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))
* Modify the implementation of `Data.List.sortOn` to use `(>)` instead of `compare`. ([CLC proposal #332](https://github.com/haskell/core-libraries-committee/issues/332))
=====================================
libraries/base/src/GHC/Exts.hs
=====================================
@@ -26,12 +26,6 @@ module GHC.Exts
-- ** Legacy interface for arrays of arrays
module GHC.Internal.ArrayArray,
-- * Primitive operations
- {-# DEPRECATED ["The BCO, mkApUpd0#, and newBCO# re-exports from GHC.Exts have been deprecated and will be removed in 9.14", "These symbols should be imported from ghc-internal instead if needed."] #-}
- Prim.BCO,
- {-# DEPRECATED ["The BCO, mkApUpd0#, and newBCO# re-exports from GHC.Exts have been deprecated and will be removed in 9.14", "These symbols should be imported from ghc-internal instead if needed."] #-}
- Prim.mkApUpd0#,
- {-# DEPRECATED ["The BCO, mkApUpd0#, and newBCO# re-exports from GHC.Exts have been deprecated and will be removed in 9.14", "These symbols should be imported from ghc-internal instead if needed."] #-}
- Prim.newBCO#,
module GHC.Prim,
module GHC.Prim.Ext,
-- ** Running 'RealWorld' state thread
@@ -130,9 +124,6 @@ import GHC.Prim hiding
, whereFrom#
, isByteArrayWeaklyPinned#, isMutableByteArrayWeaklyPinned#
- -- deprecated
- , BCO, mkApUpd0#, newBCO#
-
-- Don't re-export vector FMA instructions
, fmaddFloatX4#
, fmsubFloatX4#
@@ -255,8 +246,6 @@ import GHC.Prim hiding
, minWord8X32#
, minWord8X64#
)
-import qualified GHC.Prim as Prim
- ( BCO, mkApUpd0#, newBCO# )
import GHC.Prim.Ext
=====================================
libraries/ghci/GHCi/CreateBCO.hs
=====================================
@@ -6,10 +6,6 @@
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE CPP #-}
-{-# OPTIONS_GHC -Wno-warnings-deprecations #-}
--- TODO We want to import GHC.Internal.Base (BCO, mkApUpd0#, newBCO#) instead
--- of from GHC.Exts when we can require of the bootstrap compiler to have
--- ghc-internal.
--
-- (c) The University of Glasgow 2002-2006
@@ -30,7 +26,8 @@ import Data.Array.Base
import Foreign hiding (newArray)
import Unsafe.Coerce (unsafeCoerce)
import GHC.Arr ( Array(..) )
-import GHC.Exts
+import GHC.Exts hiding ( BCO, mkApUpd0#, newBCO# )
+import GHC.Internal.Base ( BCO, mkApUpd0#, newBCO# )
import GHC.IO
import Control.Exception ( ErrorCall(..) )
=====================================
libraries/ghci/GHCi/TH.hs
=====================================
@@ -1,9 +1,6 @@
{-# LANGUAGE ScopedTypeVariables, StandaloneDeriving, DeriveGeneric,
TupleSections, RecordWildCards, InstanceSigs, CPP #-}
{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
-{-# OPTIONS_GHC -Wno-warnings-deprecations #-}
--- TODO We want to import GHC.Internal.Desugar instead of GHC.Desugar when we
--- can require of the bootstrap compiler to have ghc-internal.
-- |
-- Running TH splices
@@ -112,7 +109,7 @@ import Data.IORef
import Data.Map (Map)
import qualified Data.Map as M
import Data.Maybe
-import GHC.Desugar (AnnotationWrapper(..))
+import GHC.Internal.Desugar (AnnotationWrapper(..))
import qualified GHC.Boot.TH.Syntax as TH
import Unsafe.Coerce
=====================================
libraries/ghci/ghci.cabal.in
=====================================
@@ -86,11 +86,7 @@ library
rts,
array == 0.5.*,
base >= 4.8 && < 4.23,
- -- ghc-internal == @ProjectVersionForLib@.*
- -- TODO: Use GHC.Internal.Desugar and GHC.Internal.Base from
- -- ghc-internal instead of ignoring the deprecation warning in GHCi.TH
- -- and GHCi.CreateBCO when we require ghc-internal of the bootstrap
- -- compiler
+ ghc-internal >= 9.1001.0 && <=@ProjectVersionForLib@.0,
ghc-prim >= 0.5.0 && < 0.14,
binary == 0.8.*,
bytestring >= 0.10 && < 0.13,
=====================================
testsuite/tests/module/T21752.stderr deleted
=====================================
@@ -1,32 +0,0 @@
-T21752A.hs:4:5: warning: [GHC-68441] [-Wdeprecations (in -Wextended-warnings)]
- In the use of ‘newBCO#’ (imported from GHC.Exts):
- Deprecated: "The BCO, mkApUpd0#, and newBCO# re-exports from GHC.Exts have been deprecated and will be removed in 9.14
- These symbols should be imported from ghc-internal instead if needed."
-
-T21752A.hs:4:5: warning: [GHC-68441] [-Wdeprecations (in -Wextended-warnings)]
- In the use of ‘newBCO#’ (imported from GHC.Exts):
- Deprecated: "The BCO, mkApUpd0#, and newBCO# re-exports from GHC.Exts have been deprecated and will be removed in 9.14
- These symbols should be imported from ghc-internal instead if needed."
-
-T21752A.hs:4:5: warning: [GHC-68441] [-Wdeprecations (in -Wextended-warnings)]
- In the use of ‘mkApUpd0#’ (imported from GHC.Exts):
- Deprecated: "The BCO, mkApUpd0#, and newBCO# re-exports from GHC.Exts have been deprecated and will be removed in 9.14
- These symbols should be imported from ghc-internal instead if needed."
-
-T21752A.hs:4:5: warning: [GHC-68441] [-Wdeprecations (in -Wextended-warnings)]
- In the use of ‘mkApUpd0#’ (imported from GHC.Exts):
- Deprecated: "The BCO, mkApUpd0#, and newBCO# re-exports from GHC.Exts have been deprecated and will be removed in 9.14
- These symbols should be imported from ghc-internal instead if needed."
-
-T21752A.hs:4:5: warning: [GHC-68441] [-Wdeprecations (in -Wextended-warnings)]
- In the use of type constructor or class ‘BCO’
- (imported from GHC.Exts):
- Deprecated: "The BCO, mkApUpd0#, and newBCO# re-exports from GHC.Exts have been deprecated and will be removed in 9.14
- These symbols should be imported from ghc-internal instead if needed."
-
-T21752A.hs:4:5: warning: [GHC-68441] [-Wdeprecations (in -Wextended-warnings)]
- In the use of type constructor or class ‘BCO’
- (imported from GHC.Exts):
- Deprecated: "The BCO, mkApUpd0#, and newBCO# re-exports from GHC.Exts have been deprecated and will be removed in 9.14
- These symbols should be imported from ghc-internal instead if needed."
-
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c8882ed707c2542efe42d0967c74d2…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c8882ed707c2542efe42d0967c74d2…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/batch-loaddll] 2 commits: ghci: LoadDLL -> LoadDLLs
by Cheng Shao (@TerrorJack) 20 Aug '25
by Cheng Shao (@TerrorJack) 20 Aug '25
20 Aug '25
Cheng Shao pushed to branch wip/batch-loaddll at Glasgow Haskell Compiler / GHC
Commits:
f544c1c2 by Cheng Shao at 2025-08-21T01:23:03+02:00
ghci: LoadDLL -> LoadDLLs
Closes #25407.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
bf6d9da0 by Cheng Shao at 2025-08-21T01:23:07+02:00
loadPackages': separate downsweep/upsweep
- - - - -
8 changed files:
- compiler/GHC/Driver/Plugins.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Linker/MacOS.hs
- compiler/GHC/Runtime/Interpreter.hs
- libraries/ghci/GHCi/Message.hs
- libraries/ghci/GHCi/ObjLink.hs
- libraries/ghci/GHCi/Run.hs
- utils/jsffi/dyld.mjs
Changes:
=====================================
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
@@ -534,7 +535,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 ->
@@ -544,14 +545,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
@@ -891,7 +892,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)
@@ -1128,33 +1129,57 @@ 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
+ let link_one pkgs new_pkg_info = do
+ (hs_cls, extra_cls, loaded_dlls) <-
+ loadPackage
+ interp
+ hsc_env
+ new_pkg_info
+ evaluate $
+ 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_loaded' <- foldlM link_one pkgs_almost_loaded pkgs_info_list
+ evaluate $ pls {pkgs_loaded = pkgs_loaded'}
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)))
-
+ downsweep = foldlM downsweep_one
+
+ 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 pkg
@@ -1221,11 +1246,11 @@ loadPackage interp hsc_env pkg
loadFrameworks interp platform pkg
-- 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
+ loaded_dlls <- load_dyn interp hsc_env True 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 = []
#endif
@@ -1300,11 +1325,11 @@ restriction very easily.
-- 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
+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
@@ -1313,7 +1338,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
=====================================
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/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/ghci/GHCi/Message.hs
=====================================
@@ -84,7 +84,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?
@@ -441,7 +441,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
@@ -555,7 +555,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
@@ -601,7 +601,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
@@ -43,6 +43,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 +71,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 +250,16 @@ resolveObjs = do
r <- c_resolveObjs
return (r /= 0)
+loadDLLs :: [String] -> IO (Either String [Ptr LoadedDLL])
+loadDLLs = go []
+ where
+ go acc [] = pure (Right (reverse acc))
+ go acc (p:ps) = do
+ r <- loadDLL p
+ case r of
+ Left err -> pure (Left err)
+ Right h -> go (h:acc) ps
+
-- ---------------------------------------------------------------------------
-- 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
=====================================
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
@@ -801,17 +801,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("/");
@@ -852,8 +852,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);
+
+ // 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,
@@ -861,7 +879,7 @@ class DyLD {
tableP2Align,
modp,
soname,
- } of await this.#downsweep(p)) {
+ } of plan) {
const import_obj = {
wasi_snapshot_preview1: this.#wasi.wasiImport,
env: {
@@ -1138,7 +1156,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/d9a2d03b61cf843f6276340ac84a7a…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d9a2d03b61cf843f6276340ac84a7a…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/batch-loaddll] 2 commits: ghci: LoadDLL -> LoadDLLs
by Cheng Shao (@TerrorJack) 20 Aug '25
by Cheng Shao (@TerrorJack) 20 Aug '25
20 Aug '25
Cheng Shao pushed to branch wip/batch-loaddll at Glasgow Haskell Compiler / GHC
Commits:
22f896cc by Cheng Shao at 2025-08-21T00:52:46+02:00
ghci: LoadDLL -> LoadDLLs
Closes #25407.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
d9a2d03b by Cheng Shao at 2025-08-21T00:52:50+02:00
loadPackages': separate downsweep/upsweep
- - - - -
8 changed files:
- compiler/GHC/Driver/Plugins.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Linker/MacOS.hs
- compiler/GHC/Runtime/Interpreter.hs
- libraries/ghci/GHCi/Message.hs
- libraries/ghci/GHCi/ObjLink.hs
- libraries/ghci/GHCi/Run.hs
- utils/jsffi/dyld.mjs
Changes:
=====================================
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
@@ -534,9 +535,10 @@ 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)
- case maybe_errstr of
- Right _ -> maybePutStrLn logger "done"
+ res_e <- loadDLLs interp [platformSOName platform dll_unadorned]
+ case res_e of
+ Right [_] -> maybePutStrLn logger "done"
+ Right _ -> preloadFailed "unexpected LoadDLLs response" lib_paths lib_spec
Left mm | platformOS platform /= OSDarwin ->
preloadFailed mm lib_paths lib_spec
Left mm | otherwise -> do
@@ -544,17 +546,19 @@ 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
- case err2 of
- Right _ -> maybePutStrLn logger "done"
- Left _ -> preloadFailed mm lib_paths lib_spec
+ err2_e <- loadDLLs interp [libfile]
+ case err2_e of
+ Right [_] -> maybePutStrLn logger "done"
+ Right _ -> preloadFailed mm lib_paths lib_spec
+ Left _ -> preloadFailed mm lib_paths lib_spec
return pls
DLLPath dll_path -> do
- do maybe_errstr <- loadDLL interp dll_path
- case maybe_errstr of
- Right _ -> maybePutStrLn logger "done"
- Left mm -> preloadFailed mm lib_paths lib_spec
+ do res_e <- loadDLLs interp [dll_path]
+ case res_e of
+ Right [_] -> maybePutStrLn logger "done"
+ Left mm -> preloadFailed mm lib_paths lib_spec
+ _ -> preloadFailed "unexpected LoadDLLs response" lib_paths lib_spec
return pls
Framework framework ->
@@ -891,10 +895,11 @@ 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
- case m of
- Right _ -> return $! pls { temp_sos = (libPath, libName) : temp_sos }
- Left err -> linkFail msg (text err)
+ res <- loadDLLs interp [soFile]
+ case res of
+ Right [_] -> return $! pls { temp_sos = (libPath, libName) : temp_sos }
+ Left err -> linkFail msg (text err)
+ _ -> linkFail msg (text "unexpected LoadDLLs response")
where
msg = "GHC.Linker.Loader.dynLoadObjs: Loading temp shared object failed"
@@ -1128,33 +1133,57 @@ 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
+ let link_one pkgs new_pkg_info = do
+ (hs_cls, extra_cls, loaded_dlls) <-
+ loadPackage
+ interp
+ hsc_env
+ new_pkg_info
+ evaluate $
+ 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_loaded' <- foldlM link_one pkgs_almost_loaded pkgs_info_list
+ evaluate $ pls {pkgs_loaded = pkgs_loaded'}
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)))
-
+ downsweep = foldlM downsweep_one
+
+ 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 pkg
@@ -1221,11 +1250,16 @@ loadPackage interp hsc_env pkg
loadFrameworks interp platform pkg
-- 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
+ -- Batch-load Haskell package DLLs to allow downstream
+ -- interpreters/linkers to parallelize work (#25407).
+ res_loaded_dlls <- loadDLLs interp known_hs_dlls
+ loaded_dlls <- case res_loaded_dlls of
+ Right ds -> pure ds
+ Left e -> cmdLineErrorIO e
-- 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 = []
#endif
@@ -1300,11 +1334,11 @@ restriction very easily.
-- 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
- case r of
- Right loaded_dll -> pure (Just loaded_dll)
+load_dyn :: Interp -> HscEnv -> Bool -> [FilePath] -> IO (Maybe [RemotePtr LoadedDLL])
+load_dyn interp hsc_env crash_early dlls = do
+ rs <- loadDLLs interp dlls
+ case rs of
+ Right loaded_dlls -> pure (Just loaded_dlls)
Left err ->
if crash_early
then cmdLineErrorIO err
=====================================
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,8 +170,9 @@ 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)
- ; case dll of
- Right _ -> return Nothing
- Left err -> findLoadDLL ps ((p ++ ": " ++ err):errs)
+ do { res <- loadDLLs interp [p </> fwk_file]
+ ; case res of
+ Right [_] -> return Nothing
+ Left err -> findLoadDLL ps ((p ++ ": " ++ err):errs)
+ _ -> findLoadDLL ps ((p ++ ": unexpected LoadDLLs response"):errs)
}
=====================================
compiler/GHC/Runtime/Interpreter.hs
=====================================
@@ -38,7 +38,7 @@ module GHC.Runtime.Interpreter
, lookupSymbol
, lookupSymbolInDLL
, lookupClosure
- , loadDLL
+ , loadDLLs
, loadArchive
, loadObj
, unloadObj
@@ -559,13 +559,10 @@ 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
--- (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)
+-- | Load multiple DLLs in one batch. Returns either an error (if any DLL fails)
+-- or the list of successfully loaded DLL handles.
+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 +758,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/ghci/GHCi/Message.hs
=====================================
@@ -84,7 +84,8 @@ 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))
+ -- | Load multiple DLLs in one batch
+ LoadDLLs :: [String] -> Message (Either String [RemotePtr LoadedDLL])
LoadArchive :: String -> Message () -- error?
LoadObj :: String -> Message () -- error?
UnloadObj :: String -> Message () -- error?
@@ -441,7 +442,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
@@ -555,7 +556,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
@@ -601,7 +602,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
@@ -43,6 +43,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 +71,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 +250,17 @@ resolveObjs = do
r <- c_resolveObjs
return (r /= 0)
+-- | Portable batch load: map 'loadDLL' and collect results.
+loadDLLs :: [String] -> IO (Either String [Ptr LoadedDLL])
+loadDLLs = go []
+ where
+ go acc [] = pure (Right (reverse acc))
+ go acc (p:ps) = do
+ r <- loadDLL p
+ case r of
+ Left err -> pure (Left err)
+ Right h -> go (h:acc) ps
+
-- ---------------------------------------------------------------------------
-- 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,9 @@ run m = case m of
LookupClosure str -> lookupJSClosure str
#else
InitLinker -> initObjLinker RetainCAFs
- LoadDLL str -> fmap toRemotePtr <$> loadDLL str
+ LoadDLLs strs -> do
+ -- Always go through batch API. On non-wasm this falls back to per-DLL loads.
+ fmap (map toRemotePtr) <$> loadDLLs strs
LoadArchive str -> loadArchive str
LoadObj str -> loadObj str
UnloadObj str -> unloadObj str
=====================================
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
@@ -801,17 +801,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("/");
@@ -852,8 +852,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);
+
+ // 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,
@@ -861,7 +879,7 @@ class DyLD {
tableP2Align,
modp,
soname,
- } of await this.#downsweep(p)) {
+ } of plan) {
const import_obj = {
wasi_snapshot_preview1: this.#wasi.wasiImport,
env: {
@@ -1138,7 +1156,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/98c839ddd9ea9beeef0fe2dda49ac4…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/98c839ddd9ea9beeef0fe2dda49ac4…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/batch-loaddll] 23 commits: configure: Allow use of LLVM 20
by Cheng Shao (@TerrorJack) 20 Aug '25
by Cheng Shao (@TerrorJack) 20 Aug '25
20 Aug '25
Cheng Shao pushed to branch wip/batch-loaddll at Glasgow Haskell Compiler / GHC
Commits:
ca03226d by Ben Gamari at 2025-08-18T13:43:20+00:00
configure: Allow use of LLVM 20
- - - - -
783cd7d6 by Cheng Shao at 2025-08-18T20:13:14-04:00
compiler: use `UniqMap` instead of `Map` for `BCEnv` in bytecode compiler
The bytecode compiler maintains a `BCEnv` which was previously `Map Id
StackDepth`. Given `Id` is `Uniquable`, we might as well use `UniqMap`
here as a more efficient data structure, hence this patch.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
58e46da9 by fendor at 2025-08-18T20:13:56-04:00
rts: Strip lower three bits when hashing Word instead of lower eight bits
- - - - -
45dbfa23 by Cheng Shao at 2025-08-18T20:14:37-04:00
libffi: update to 3.5.2
Bumps libffi submodule.
- - - - -
54be78ef by Ben Gamari at 2025-08-19T16:28:05-04:00
testsuite: Fix T20006b
This test is supposed to fail for non-threaded ways yet it
was previously marked as only failing in `normal`.
Fix this.
- - - - -
f4bac607 by Simon Peyton Jones at 2025-08-19T16:28:47-04:00
Take yet more care with reporting redundant constraints
This small patch fixes #25992, which relates to reporting redundant
constraints on default-method declarations.
See (TRC5) in Note [Tracking redundant constraints]
- - - - -
ab130fec by fendor at 2025-08-19T16:29:29-04:00
Bump dependencies of hadrian-bootstrap-gen to use GHC 9.6.7
- - - - -
6d02ac6f by fendor at 2025-08-19T16:29:29-04:00
Bump required GHC version for test-bootstrap jobs to 9.10.1
Include test-bootstrap job for GHC 9.12.2.
Update hadrian bootstrap plans use GHC 9.10 and 9.12
Remove older GHC bootstrap configurations.
We require at least GHC 9.10.1 to build GHC.
Adds plans for:
* 9.10.1
* 9.10.2
* 9.12.1
* 9.12.2
- - - - -
9e857171 by Brandon Chinn at 2025-08-20T11:47:46-04:00
Don't warn unused-imports with used generated imports
Fixes #21730
* The old notion of "implicit" import has been renamed to "generated". See Note [Generated imports] in GHC.Hs.ImpExp.
* ImportMap now keeps track of generated and user-written imports separately. This avoids the fake SrcSpan we used to give the implicit Prelude import, and the hack that went with it.
* -ddump-minimal-imports now considers generated imports (but still only
warns on + prints user-written imports)
* bestImport considers generated imports to take priority over user-written imports.
- - - - -
9fb3bad4 by Ben Gamari at 2025-08-20T11:48:31-04:00
mailmap: Use ben(a)well-typed.com more liberally
Nearly all of this work was done while working for Well-Typed.
- - - - -
774fec37 by Ben Gamari at 2025-08-20T11:49:15-04:00
Add primop to annotate the call stack with arbitrary data
We introduce a new primop `annotateStack#` which allows us to push
arbitrary data onto the call-stack.
This allows us to extract the data later when decoding the stack, for
example when an exception is thrown, showing more information to the
user without having to annotate the full call-stack with `HasCallStack`
constraints.
A new stack frame value is introduced `AnnFrame`, which consists of
nothing but a generic payload.
The primop has a small wrapper API that allows users to annotate their
call-stack in programs.
There is a pure API and an IO-based one. The former is a little bit
dubious, as it affects the evaluation of a program, so use with care.
The latter is "safe", as it doesn't change the evaluation of the
program.
The stack annotation mechanism is similarly implemented to the
`ExceptionAnnotation` and `Exception`, there is a typeclass to indicate
something can be pushed onto the call-stack and all values are wrapped
in the existential `SomeStackAnnotation`, which recover the type of the
annotation payload.
There is currently no builtin way to show the stack annotations when
`Backtraces` are displayed (i.e., when showing stack traces to the user),
which we will address in a follow-up MR.
-------------------------
Metric Increase:
ghc_experimental_so
-------------------------
We increase the size of the package, so this is not unreasonable.
Co-Authored-By: fendor <fendor(a)posteo.de>
Co-Authored-By: Ben Gamari <bgamari.foss(a)gmail.com>
- - - - -
fdfa3892 by Ben Gamari at 2025-08-20T11:49:57-04:00
testsuite: Add regression test for #24606
- - - - -
39b2e382 by Cheng Shao at 2025-08-20T11:50:40-04:00
compiler: only use `Name` instead of `Id` in `SptEntry`
As a part of #26298, this patch refactors `SptEntry` to only carry a
`Name` instead of `Id`: we do not care about extra information like
caffyness or type at all in any static pointer related codegen logic.
This is necessary to make `SptEntry` serializable, as a part of the
grand plan of serializable bytecode.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
276f8ea8 by Vekhir -- at 2025-08-20T11:51:35-04:00
Bump Cabal dependency
- - - - -
0b9c7437 by Zubin Duggal at 2025-08-20T11:52:18-04:00
ci: Teach ci.sh to fetch FreeBSD artifacts from ghcup unofficial bindists and bootstrap compiler on FreeBSD to 9.10.1
Also refactor fetch_ghc logic in ci.sh, renaming the GHC_VERSION enviorment configuration variable to FETCH_GHC_VERSION,
making it clear that it is intended for use on platforms like Windows and FreeBSD where we don't want to use the GHC
excecutable from the platform environment and instead need to download and install GHC-$FETCH_GHC_VERSION from a release
bindist.
Fixes #26296
- - - - -
b2914797 by Cheng Shao at 2025-08-20T11:53:00-04:00
driver: use UniqSet for hiddenModules in DynFlags/FinderOpts
This patch replaces Set ModuleName with UniqSet ModuleName in
DynFlags.hiddenModules and FinderOpts.finder_hiddenModules for
improved efficiency.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
0335d899 by Cheng Shao at 2025-08-20T11:53:00-04:00
driver: use UniqMap ModuleName in the finder
This patch replaces Map ModuleName with UniqMap ModuleName in the
finder for improved efficiency.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
91f4faaa by Cheng Shao at 2025-08-20T11:53:43-04:00
configure: check python3 version and require minimal 3.7
Since !9515, the testsuite driver requires python3 version to be at
least 3.7, though this has never been checked by configure logic. This
patch implements the version check. Fixes #23234.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
df4ee9b4 by Cheng Shao at 2025-08-20T11:54:25-04:00
compiler: use zero cost coerce in GHC.CmmToAsm.CFG.loopInfo
This patch refactors GHC.CmmToAsm.CFG.loopInfo to use zero cost coerce
and thus addresses the TODO. For coerce to work, constructors of
Label/LabelMap/LabelSet from GHC.Cmm.Dataflow.Label are exposed,
though I believe it's a worthy tradeoff to avoid unnecessary runtime
cost without using unsafeCoerce, since the latter could be a landmine
for future refactoring.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
ccda188d by Simon Peyton Jones at 2025-08-20T11:55:07-04:00
Start with empty inerts in shortcut solving
When short-cut solving we were starting with an inert set that had
unsolved Wanteds. This caused an infinite loop (#26314), because a
typechecker plugin kept being given that unsolved Wanted.
It's better just to start with an empty inert set
- - - - -
c8882ed7 by Ben Gamari at 2025-08-20T11:55:49-04:00
configure: Bump minimal bootstrap GHC version to 9.8
- - - - -
5a462246 by Cheng Shao at 2025-08-21T00:22:32+02:00
ghci: LoadDLL -> LoadDLLs
Closes #25407.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
98c839dd by Cheng Shao at 2025-08-21T00:22:37+02:00
loadPackages': separate downsweep/upsweep
- - - - -
172 changed files:
- .gitlab-ci.yml
- .gitlab/ci.sh
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .mailmap
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/Cmm/Dataflow/Label.hs
- compiler/GHC/CmmToAsm/CFG.hs
- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Driver/Config/Finder.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Plugins.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/HsToCore/Docs.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Iface/Tidy/StaticPtrTable.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Linker/MacOS.hs
- compiler/GHC/Parser/Header.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/Runtime/Interpreter.hs
- compiler/GHC/StgToByteCode.hs
- compiler/GHC/StgToCmm/Prim.hs
- compiler/GHC/StgToJS/Prim.hs
- compiler/GHC/StgToJS/StaticPtr.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Tc/Solver/Dict.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Solver/Solve.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/Types/Name/Reader.hs
- compiler/GHC/Types/SptEntry.hs
- compiler/GHC/Unit/Finder.hs
- compiler/GHC/Unit/Finder/Types.hs
- configure.ac
- ghc/GHCi/UI.hs
- hadrian/bootstrap/generate_bootstrap_plans
- hadrian/bootstrap/hadrian-bootstrap-gen.cabal
- hadrian/bootstrap/plan-9_10_1.json
- hadrian/bootstrap/plan-9_6_5.json → hadrian/bootstrap/plan-9_10_2.json
- hadrian/bootstrap/plan-9_6_6.json → hadrian/bootstrap/plan-9_12_1.json
- hadrian/bootstrap/plan-9_6_4.json → hadrian/bootstrap/plan-9_12_2.json
- − hadrian/bootstrap/plan-9_6_1.json
- − hadrian/bootstrap/plan-9_6_2.json
- − hadrian/bootstrap/plan-9_6_3.json
- − hadrian/bootstrap/plan-9_8_1.json
- − hadrian/bootstrap/plan-9_8_2.json
- hadrian/bootstrap/plan-bootstrap-9_10_1.json
- hadrian/bootstrap/plan-bootstrap-9_6_5.json → hadrian/bootstrap/plan-bootstrap-9_10_2.json
- hadrian/bootstrap/plan-bootstrap-9_6_6.json → hadrian/bootstrap/plan-bootstrap-9_12_1.json
- hadrian/bootstrap/plan-bootstrap-9_8_1.json → hadrian/bootstrap/plan-bootstrap-9_12_2.json
- − hadrian/bootstrap/plan-bootstrap-9_6_1.json
- − hadrian/bootstrap/plan-bootstrap-9_6_2.json
- − hadrian/bootstrap/plan-bootstrap-9_6_3.json
- − hadrian/bootstrap/plan-bootstrap-9_6_4.json
- − hadrian/bootstrap/plan-bootstrap-9_8_2.json
- hadrian/bootstrap/src/Main.hs
- hadrian/hadrian.cabal
- libffi-tarballs
- libraries/ghc-experimental/ghc-experimental.cabal.in
- + libraries/ghc-experimental/src/GHC/Stack/Annotation/Experimental.hs
- libraries/ghc-heap/GHC/Exts/Heap/ClosureTypes.hs
- libraries/ghc-heap/GHC/Exts/Heap/Closures.hs
- libraries/ghc-heap/GHC/Exts/Stack.hs
- libraries/ghc-heap/GHC/Exts/Stack/Constants.hsc
- libraries/ghc-heap/GHC/Exts/Stack/Decode.hs
- + libraries/ghc-heap/tests/stack-annotation/Makefile
- + libraries/ghc-heap/tests/stack-annotation/TestUtils.hs
- + libraries/ghc-heap/tests/stack-annotation/all.T
- + libraries/ghc-heap/tests/stack-annotation/ann_frame001.hs
- + libraries/ghc-heap/tests/stack-annotation/ann_frame001.stdout
- + libraries/ghc-heap/tests/stack-annotation/ann_frame002.hs
- + libraries/ghc-heap/tests/stack-annotation/ann_frame002.stdout
- + libraries/ghc-heap/tests/stack-annotation/ann_frame003.hs
- + libraries/ghc-heap/tests/stack-annotation/ann_frame003.stdout
- + libraries/ghc-heap/tests/stack-annotation/ann_frame004.hs
- + libraries/ghc-heap/tests/stack-annotation/ann_frame004.stdout
- libraries/ghc-internal/src/GHC/Internal/ClosureTypes.hs
- libraries/ghci/GHCi/Message.hs
- libraries/ghci/GHCi/ObjLink.hs
- libraries/ghci/GHCi/Run.hs
- m4/find_python.m4
- rts/ClosureFlags.c
- rts/Hash.c
- rts/LdvProfile.c
- rts/PrimOps.cmm
- rts/Printer.c
- rts/RetainerProfile.c
- rts/RtsSymbols.c
- rts/TraverseHeap.c
- rts/include/rts/storage/ClosureTypes.h
- rts/include/rts/storage/Closures.h
- rts/include/stg/MiscClosures.h
- rts/js/profiling.js
- rts/sm/Compact.c
- rts/sm/Evac.c
- rts/sm/NonMovingMark.c
- rts/sm/Sanity.c
- rts/sm/Scav.c
- testsuite/tests/gadt/T12468.stderr
- testsuite/tests/ghc-e/should_fail/T24172.stderr
- testsuite/tests/ghci/scripts/T8353.stderr
- testsuite/tests/ghci/scripts/ghci038.stdout
- testsuite/tests/interface-stability/base-exports.stdout
- testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
- testsuite/tests/interface-stability/base-exports.stdout-mingw32
- testsuite/tests/interface-stability/base-exports.stdout-ws-32
- testsuite/tests/interface-stability/ghc-experimental-exports.stdout
- testsuite/tests/interface-stability/ghc-experimental-exports.stdout-mingw32
- testsuite/tests/interface-stability/ghc-prim-exports.stdout
- testsuite/tests/interface-stability/ghc-prim-exports.stdout-mingw32
- testsuite/tests/module/mod150.stderr
- testsuite/tests/module/mod151.stderr
- testsuite/tests/module/mod152.stderr
- testsuite/tests/module/mod153.stderr
- testsuite/tests/overloadedrecflds/should_fail/T18999_NoDisambiguateRecordFields.stderr
- testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
- testsuite/tests/parser/should_compile/T14189.stderr
- testsuite/tests/parser/should_compile/T19082.stderr
- testsuite/tests/perf/compiler/hard_hole_fits.stderr
- testsuite/tests/plugins/Makefile
- + testsuite/tests/plugins/T21730-plugin/Makefile
- + testsuite/tests/plugins/T21730-plugin/Setup.hs
- + testsuite/tests/plugins/T21730-plugin/T21730-plugin.cabal
- + testsuite/tests/plugins/T21730-plugin/T21730_Plugin.hs
- + testsuite/tests/plugins/T21730.hs
- testsuite/tests/plugins/all.T
- testsuite/tests/quotes/LiftErrMsg.stderr
- testsuite/tests/quotes/LiftErrMsgDefer.stderr
- testsuite/tests/quotes/LiftErrMsgTyped.stderr
- testsuite/tests/rename/should_compile/T22513d.stderr
- testsuite/tests/rename/should_compile/T22513e.stderr
- testsuite/tests/rename/should_compile/T22513f.stderr
- testsuite/tests/rename/should_compile/T22513g.stderr
- testsuite/tests/rename/should_compile/T22513h.stderr
- testsuite/tests/rename/should_compile/T22513i.stderr
- testsuite/tests/rename/should_compile/rn039.ghc.stderr
- testsuite/tests/rename/should_fail/T15487.stderr
- testsuite/tests/rename/should_fail/T18740a.stderr
- testsuite/tests/rename/should_fail/rnfail044.stderr
- testsuite/tests/rts/flags/all.T
- testsuite/tests/safeHaskell/flags/SafeFlags17.stderr
- + testsuite/tests/simplCore/should_compile/T24606.hs
- testsuite/tests/simplCore/should_compile/all.T
- testsuite/tests/th/T10267.stderr
- testsuite/tests/th/T14627.stderr
- testsuite/tests/th/T15321.stderr
- testsuite/tests/typecheck/should_compile/T13050.stderr
- testsuite/tests/typecheck/should_compile/T14273.stderr
- testsuite/tests/typecheck/should_compile/T14590.stderr
- testsuite/tests/typecheck/should_compile/T25180.stderr
- + testsuite/tests/typecheck/should_compile/T25992a.hs
- testsuite/tests/typecheck/should_compile/T9497a.stderr
- testsuite/tests/typecheck/should_compile/all.T
- testsuite/tests/typecheck/should_compile/refinement_hole_fits.stderr
- testsuite/tests/typecheck/should_compile/subsumption_sort_hole_fits.stderr
- testsuite/tests/typecheck/should_fail/T14884.stderr
- testsuite/tests/typecheck/should_fail/T21130.stderr
- testsuite/tests/typecheck/should_fail/T23739b.stderr
- testsuite/tests/typecheck/should_fail/T23739c.stderr
- testsuite/tests/typecheck/should_fail/T9497d.stderr
- testsuite/tests/typecheck/should_fail/tcfail037.stderr
- testsuite/tests/typecheck/should_run/T9497a-run.stderr
- testsuite/tests/typecheck/should_run/T9497b-run.stderr
- testsuite/tests/typecheck/should_run/T9497c-run.stderr
- testsuite/tests/vdq-rta/should_fail/T23738_fail_pun.stderr
- utils/deriveConstants/Main.hs
- 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/a7e3f3d43331d9c8bc53b863e2d82b…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a7e3f3d43331d9c8bc53b863e2d82b…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

20 Aug '25
Cheng Shao pushed new branch wip/use-uniq-map-set at Glasgow Haskell Compiler / GHC
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/use-uniq-map-set
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 16 commits: Don't warn unused-imports with used generated imports
by Marge Bot (@marge-bot) 20 Aug '25
by Marge Bot (@marge-bot) 20 Aug '25
20 Aug '25
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
9e857171 by Brandon Chinn at 2025-08-20T11:47:46-04:00
Don't warn unused-imports with used generated imports
Fixes #21730
* The old notion of "implicit" import has been renamed to "generated". See Note [Generated imports] in GHC.Hs.ImpExp.
* ImportMap now keeps track of generated and user-written imports separately. This avoids the fake SrcSpan we used to give the implicit Prelude import, and the hack that went with it.
* -ddump-minimal-imports now considers generated imports (but still only
warns on + prints user-written imports)
* bestImport considers generated imports to take priority over user-written imports.
- - - - -
9fb3bad4 by Ben Gamari at 2025-08-20T11:48:31-04:00
mailmap: Use ben(a)well-typed.com more liberally
Nearly all of this work was done while working for Well-Typed.
- - - - -
774fec37 by Ben Gamari at 2025-08-20T11:49:15-04:00
Add primop to annotate the call stack with arbitrary data
We introduce a new primop `annotateStack#` which allows us to push
arbitrary data onto the call-stack.
This allows us to extract the data later when decoding the stack, for
example when an exception is thrown, showing more information to the
user without having to annotate the full call-stack with `HasCallStack`
constraints.
A new stack frame value is introduced `AnnFrame`, which consists of
nothing but a generic payload.
The primop has a small wrapper API that allows users to annotate their
call-stack in programs.
There is a pure API and an IO-based one. The former is a little bit
dubious, as it affects the evaluation of a program, so use with care.
The latter is "safe", as it doesn't change the evaluation of the
program.
The stack annotation mechanism is similarly implemented to the
`ExceptionAnnotation` and `Exception`, there is a typeclass to indicate
something can be pushed onto the call-stack and all values are wrapped
in the existential `SomeStackAnnotation`, which recover the type of the
annotation payload.
There is currently no builtin way to show the stack annotations when
`Backtraces` are displayed (i.e., when showing stack traces to the user),
which we will address in a follow-up MR.
-------------------------
Metric Increase:
ghc_experimental_so
-------------------------
We increase the size of the package, so this is not unreasonable.
Co-Authored-By: fendor <fendor(a)posteo.de>
Co-Authored-By: Ben Gamari <bgamari.foss(a)gmail.com>
- - - - -
fdfa3892 by Ben Gamari at 2025-08-20T11:49:57-04:00
testsuite: Add regression test for #24606
- - - - -
39b2e382 by Cheng Shao at 2025-08-20T11:50:40-04:00
compiler: only use `Name` instead of `Id` in `SptEntry`
As a part of #26298, this patch refactors `SptEntry` to only carry a
`Name` instead of `Id`: we do not care about extra information like
caffyness or type at all in any static pointer related codegen logic.
This is necessary to make `SptEntry` serializable, as a part of the
grand plan of serializable bytecode.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
276f8ea8 by Vekhir -- at 2025-08-20T11:51:35-04:00
Bump Cabal dependency
- - - - -
0b9c7437 by Zubin Duggal at 2025-08-20T11:52:18-04:00
ci: Teach ci.sh to fetch FreeBSD artifacts from ghcup unofficial bindists and bootstrap compiler on FreeBSD to 9.10.1
Also refactor fetch_ghc logic in ci.sh, renaming the GHC_VERSION enviorment configuration variable to FETCH_GHC_VERSION,
making it clear that it is intended for use on platforms like Windows and FreeBSD where we don't want to use the GHC
excecutable from the platform environment and instead need to download and install GHC-$FETCH_GHC_VERSION from a release
bindist.
Fixes #26296
- - - - -
b2914797 by Cheng Shao at 2025-08-20T11:53:00-04:00
driver: use UniqSet for hiddenModules in DynFlags/FinderOpts
This patch replaces Set ModuleName with UniqSet ModuleName in
DynFlags.hiddenModules and FinderOpts.finder_hiddenModules for
improved efficiency.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
0335d899 by Cheng Shao at 2025-08-20T11:53:00-04:00
driver: use UniqMap ModuleName in the finder
This patch replaces Map ModuleName with UniqMap ModuleName in the
finder for improved efficiency.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
91f4faaa by Cheng Shao at 2025-08-20T11:53:43-04:00
configure: check python3 version and require minimal 3.7
Since !9515, the testsuite driver requires python3 version to be at
least 3.7, though this has never been checked by configure logic. This
patch implements the version check. Fixes #23234.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
df4ee9b4 by Cheng Shao at 2025-08-20T11:54:25-04:00
compiler: use zero cost coerce in GHC.CmmToAsm.CFG.loopInfo
This patch refactors GHC.CmmToAsm.CFG.loopInfo to use zero cost coerce
and thus addresses the TODO. For coerce to work, constructors of
Label/LabelMap/LabelSet from GHC.Cmm.Dataflow.Label are exposed,
though I believe it's a worthy tradeoff to avoid unnecessary runtime
cost without using unsafeCoerce, since the latter could be a landmine
for future refactoring.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
ccda188d by Simon Peyton Jones at 2025-08-20T11:55:07-04:00
Start with empty inerts in shortcut solving
When short-cut solving we were starting with an inert set that had
unsolved Wanteds. This caused an infinite loop (#26314), because a
typechecker plugin kept being given that unsolved Wanted.
It's better just to start with an empty inert set
- - - - -
c8882ed7 by Ben Gamari at 2025-08-20T11:55:49-04:00
configure: Bump minimal bootstrap GHC version to 9.8
- - - - -
d4305a5e by fendor at 2025-08-20T16:03:54-04:00
Remove deprecated functions from the ghci package
- - - - -
64d4e8e5 by fendor at 2025-08-20T16:03:54-04:00
base: Remove unstable heap representation details from GHC.Exts
- - - - -
1bfe8128 by Rodrigo Mesquita at 2025-08-20T16:03:58-04:00
bytecode: Use 32bits for breakpoint index
Fixes #26325
- - - - -
143 changed files:
- .gitlab/ci.sh
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .mailmap
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/ByteCode/Asm.hs
- compiler/GHC/Cmm/Dataflow/Label.hs
- compiler/GHC/CmmToAsm/CFG.hs
- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Driver/Config/Finder.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/HsToCore/Docs.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Iface/Tidy/StaticPtrTable.hs
- compiler/GHC/Parser/Header.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/StgToCmm/Prim.hs
- compiler/GHC/StgToJS/Prim.hs
- compiler/GHC/StgToJS/StaticPtr.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Tc/Solver/Dict.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Solver/Solve.hs
- compiler/GHC/Types/Name/Reader.hs
- compiler/GHC/Types/SptEntry.hs
- compiler/GHC/Unit/Finder.hs
- compiler/GHC/Unit/Finder/Types.hs
- configure.ac
- ghc/GHCi/UI.hs
- hadrian/hadrian.cabal
- libraries/base/changelog.md
- libraries/base/src/GHC/Exts.hs
- libraries/ghc-experimental/ghc-experimental.cabal.in
- + libraries/ghc-experimental/src/GHC/Stack/Annotation/Experimental.hs
- libraries/ghc-heap/GHC/Exts/Heap/ClosureTypes.hs
- libraries/ghc-heap/GHC/Exts/Heap/Closures.hs
- libraries/ghc-heap/GHC/Exts/Stack.hs
- libraries/ghc-heap/GHC/Exts/Stack/Constants.hsc
- libraries/ghc-heap/GHC/Exts/Stack/Decode.hs
- + libraries/ghc-heap/tests/stack-annotation/Makefile
- + libraries/ghc-heap/tests/stack-annotation/TestUtils.hs
- + libraries/ghc-heap/tests/stack-annotation/all.T
- + libraries/ghc-heap/tests/stack-annotation/ann_frame001.hs
- + libraries/ghc-heap/tests/stack-annotation/ann_frame001.stdout
- + libraries/ghc-heap/tests/stack-annotation/ann_frame002.hs
- + libraries/ghc-heap/tests/stack-annotation/ann_frame002.stdout
- + libraries/ghc-heap/tests/stack-annotation/ann_frame003.hs
- + libraries/ghc-heap/tests/stack-annotation/ann_frame003.stdout
- + libraries/ghc-heap/tests/stack-annotation/ann_frame004.hs
- + libraries/ghc-heap/tests/stack-annotation/ann_frame004.stdout
- libraries/ghc-internal/src/GHC/Internal/ClosureTypes.hs
- libraries/ghci/GHCi/CreateBCO.hs
- libraries/ghci/GHCi/TH.hs
- libraries/ghci/ghci.cabal.in
- m4/find_python.m4
- rts/ClosureFlags.c
- rts/Disassembler.c
- rts/Interpreter.c
- rts/LdvProfile.c
- rts/PrimOps.cmm
- rts/Printer.c
- rts/RetainerProfile.c
- rts/RtsSymbols.c
- rts/TraverseHeap.c
- rts/include/rts/storage/ClosureTypes.h
- rts/include/rts/storage/Closures.h
- rts/include/stg/MiscClosures.h
- rts/js/profiling.js
- rts/sm/Compact.c
- rts/sm/Evac.c
- rts/sm/NonMovingMark.c
- rts/sm/Sanity.c
- rts/sm/Scav.c
- testsuite/tests/gadt/T12468.stderr
- testsuite/tests/ghc-e/should_fail/T24172.stderr
- testsuite/tests/ghci/scripts/T8353.stderr
- testsuite/tests/ghci/scripts/ghci038.stdout
- testsuite/tests/interface-stability/base-exports.stdout
- testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
- testsuite/tests/interface-stability/base-exports.stdout-mingw32
- testsuite/tests/interface-stability/base-exports.stdout-ws-32
- testsuite/tests/interface-stability/ghc-experimental-exports.stdout
- testsuite/tests/interface-stability/ghc-experimental-exports.stdout-mingw32
- testsuite/tests/interface-stability/ghc-prim-exports.stdout
- testsuite/tests/interface-stability/ghc-prim-exports.stdout-mingw32
- − testsuite/tests/module/T21752.stderr
- testsuite/tests/module/mod150.stderr
- testsuite/tests/module/mod151.stderr
- testsuite/tests/module/mod152.stderr
- testsuite/tests/module/mod153.stderr
- testsuite/tests/overloadedrecflds/should_fail/T18999_NoDisambiguateRecordFields.stderr
- testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
- testsuite/tests/parser/should_compile/T14189.stderr
- testsuite/tests/parser/should_compile/T19082.stderr
- testsuite/tests/perf/compiler/hard_hole_fits.stderr
- testsuite/tests/plugins/Makefile
- + testsuite/tests/plugins/T21730-plugin/Makefile
- + testsuite/tests/plugins/T21730-plugin/Setup.hs
- + testsuite/tests/plugins/T21730-plugin/T21730-plugin.cabal
- + testsuite/tests/plugins/T21730-plugin/T21730_Plugin.hs
- + testsuite/tests/plugins/T21730.hs
- testsuite/tests/plugins/all.T
- testsuite/tests/quotes/LiftErrMsg.stderr
- testsuite/tests/quotes/LiftErrMsgDefer.stderr
- testsuite/tests/quotes/LiftErrMsgTyped.stderr
- testsuite/tests/rename/should_compile/T22513d.stderr
- testsuite/tests/rename/should_compile/T22513e.stderr
- testsuite/tests/rename/should_compile/T22513f.stderr
- testsuite/tests/rename/should_compile/T22513g.stderr
- testsuite/tests/rename/should_compile/T22513h.stderr
- testsuite/tests/rename/should_compile/T22513i.stderr
- testsuite/tests/rename/should_compile/rn039.ghc.stderr
- testsuite/tests/rename/should_fail/T15487.stderr
- testsuite/tests/rename/should_fail/T18740a.stderr
- testsuite/tests/rename/should_fail/rnfail044.stderr
- testsuite/tests/safeHaskell/flags/SafeFlags17.stderr
- + testsuite/tests/simplCore/should_compile/T24606.hs
- testsuite/tests/simplCore/should_compile/all.T
- testsuite/tests/th/T10267.stderr
- testsuite/tests/th/T14627.stderr
- testsuite/tests/th/T15321.stderr
- testsuite/tests/typecheck/should_compile/T13050.stderr
- testsuite/tests/typecheck/should_compile/T14273.stderr
- testsuite/tests/typecheck/should_compile/T14590.stderr
- testsuite/tests/typecheck/should_compile/T25180.stderr
- testsuite/tests/typecheck/should_compile/T9497a.stderr
- testsuite/tests/typecheck/should_compile/refinement_hole_fits.stderr
- testsuite/tests/typecheck/should_compile/subsumption_sort_hole_fits.stderr
- testsuite/tests/typecheck/should_fail/T14884.stderr
- testsuite/tests/typecheck/should_fail/T21130.stderr
- testsuite/tests/typecheck/should_fail/T23739b.stderr
- testsuite/tests/typecheck/should_fail/T23739c.stderr
- testsuite/tests/typecheck/should_fail/T9497d.stderr
- testsuite/tests/typecheck/should_fail/tcfail037.stderr
- testsuite/tests/typecheck/should_run/T9497a-run.stderr
- testsuite/tests/typecheck/should_run/T9497b-run.stderr
- testsuite/tests/typecheck/should_run/T9497c-run.stderr
- testsuite/tests/vdq-rta/should_fail/T23738_fail_pun.stderr
- utils/deriveConstants/Main.hs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7fe235f6a029d0bf555f3ec23d6985…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7fe235f6a029d0bf555f3ec23d6985…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
Cheng Shao pushed new branch wip/14554-5 at Glasgow Haskell Compiler / GHC
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/14554-5
You're receiving this email because of your account on gitlab.haskell.org.
1
0

20 Aug '25
Cheng Shao deleted branch wip/hiddenmodules-uniqset at Glasgow Haskell Compiler / GHC
--
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/bytecode-serialize-3] 59 commits: Kill IOPort#
by Cheng Shao (@TerrorJack) 20 Aug '25
by Cheng Shao (@TerrorJack) 20 Aug '25
20 Aug '25
Cheng Shao pushed to branch wip/bytecode-serialize-3 at Glasgow Haskell Compiler / GHC
Commits:
34fc50c1 by Ben Gamari at 2025-08-11T13:36:25-04:00
Kill IOPort#
This type is unnecessary, having been superceded by `MVar` and a rework
of WinIO's blocking logic.
See #20947.
See https://github.com/haskell/core-libraries-committee/issues/213.
- - - - -
56b32c5a by sheaf at 2025-08-12T10:00:19-04:00
Improve deep subsumption
This commit improves the DeepSubsumption sub-typing implementation
in GHC.Tc.Utils.Unify.tc_sub_type_deep by being less eager to fall back
to unification.
For example, we now are properly able to prove the subtyping relationship
((∀ a. a->a) -> Int) -> Bool <= β[tau] Bool
for an unfilled metavariable β. In this case (with an AppTy on the right),
we used to fall back to unification. No longer: now, given that the LHS
is a FunTy and that the RHS is a deep rho type (does not need any instantiation),
we try to make the RHS into a FunTy, viz.
β := (->) γ
We can then continue using covariance & contravariance of the function
arrow, which allows us to prove the subtyping relationship, instead of
trying to unify which would cause us to error out with:
Couldn't match expected type ‘β’ with actual type ‘(->) ((∀ a. a -> a) -> Int)
See Note [FunTy vs non-FunTy case in tc_sub_type_deep] in GHC.Tc.Utils.Unify.
The other main improvement in this patch concerns type inference.
The main subsumption logic happens (before & after this patch) in
GHC.Tc.Gen.App.checkResultTy. However, before this patch, all of the
DeepSubsumption logic only kicked in in 'check' mode, not in 'infer' mode.
This patch adds deep instantiation in the 'infer' mode of checkResultTy
when we are doing deep subsumption, which allows us to accept programs
such as:
f :: Int -> (forall a. a->a)
g :: Int -> Bool -> Bool
test1 b =
case b of
True -> f
False -> g
test2 b =
case b of
True -> g
False -> f
See Note [Deeply instantiate in checkResultTy when inferring].
Finally, we add representation-polymorphism checks to ensure that the
lambda abstractions we introduce when doing subsumption obey the
representation polymorphism invariants of Note [Representation polymorphism invariants]
in GHC.Core. See Note [FunTy vs FunTy case in tc_sub_type_deep].
This is accompanied by a courtesy change to `(<.>) :: HsWrapper -> HsWrapper -> HsWrapper`,
adding the equation:
WpCast c1 <.> WpCast c2 = WpCast (c1 `mkTransCo` c2)
This is useful because mkWpFun does not introduce an eta-expansion when
both of the argument & result wrappers are casts; so this change allows
us to avoid introducing lambda abstractions when casts suffice.
Fixes #26225
- - - - -
d175aff8 by Sylvain Henry at 2025-08-12T10:01:31-04:00
Add regression test for #18619
- - - - -
a3983a26 by Sylvain Henry at 2025-08-12T10:02:20-04:00
RTS: remove some TSAN annotations (#20464)
Use RELAXED_LOAD_ALWAYS macro instead.
- - - - -
0434af81 by Ben Gamari at 2025-08-12T10:03:02-04:00
Bump time submodule to 1.15
Also required bumps of Cabal, directory, and hpc.
- - - - -
62899117 by Florian Ragwitz at 2025-08-13T21:01:34-04:00
Extend record-selector usage ticking to all binds using a record field
This extends the previous handling of ticking for RecordWildCards and
NamedFieldPuns to all var bindings that involve record selectors.
Note that certain patterns such as `Foo{foo = 42}` will currently not tick the
`foo` selector, as ticking is triggered by `HsVar`s.
Closes #26191.
- - - - -
b37b3af7 by Florian Ragwitz at 2025-08-13T21:01:34-04:00
Add release notes for 9.16.1 and move description of latest HPC changes there.
- - - - -
a5e4b7d9 by Ben Gamari at 2025-08-13T21:02:18-04:00
rts: Clarify rationale for undefined atomic wrappers
Since c06e3f46d24ef69f3a3d794f5f604cb8c2a40cbc the RTS has declared
various atomic operation wrappers defined by ghc-internal as undefined.
While the rationale for this isn't clear from the commit message, I
believe that this is necessary due to the unregisterised backend.
Specifically, the code generator will reference these symbols when
compiling RTS Cmm sources.
- - - - -
50842f83 by Andreas Klebinger at 2025-08-13T21:03:01-04:00
Make unexpected LLVM versions a warning rather than an error.
Typically a newer LLVM version *will* work so erroring out if
a user uses a newer LLVM version is too aggressive.
Fixes #25915
- - - - -
c91e2650 by fendor at 2025-08-13T21:03:43-04:00
Store `StackTrace` and `StackSnapshot` in `Backtraces`
Instead of decoding the stack traces when collecting the `Backtraces`,
defer this decoding until actually showing the `Backtraces`.
This allows users to customise how `Backtraces` are displayed by
using a custom implementation of `displayExceptionWithInfo`, overwriting
the default implementation for `Backtraces` (`displayBacktraces`).
- - - - -
dee28cdd by fendor at 2025-08-13T21:03:43-04:00
Allow users to customise the collection of exception annotations
Add a global `CollectExceptionAnnotationMechanism` which determines how
`ExceptionAnnotation`s are collected upon throwing an `Exception`.
This API is exposed via `ghc-experimental`.
By overriding how we collect `Backtraces`, we can control how the
`Backtraces` are displayed to the user by newtyping `Backtraces` and
giving a different instance for `ExceptionAnnotation`.
A concrete use-case for this feature is allowing us to experiment with
alternative stack decoders, without having to modify `base`, which take
additional information from the stack frames.
This commit does not modify how `Backtraces` are currently
collected or displayed.
- - - - -
66024722 by fendor at 2025-08-13T21:03:43-04:00
Expose Backtraces internals from ghc-experimental
Additionally, expose the same API `base:Control.Exception.Backtrace`
to make it easier to use as a drop-in replacement.
- - - - -
a766286f by Reed Mullanix at 2025-08-13T21:04:36-04:00
ghc-internal: Fix naturalAndNot for NB/NS case
When the first argument to `naturalAndNot` is larger than a `Word` and the second is `Word`-sized, `naturalAndNot` will truncate the
result:
```
>>> naturalAndNot ((2 ^ 65) .|. (2 ^ 3)) (2 ^ 3)
0
```
In contrast, `naturalAndNot` does not truncate when both arguments are larger than a `Word`, so this appears to be a bug.
Luckily, the fix is pretty easy: we just need to call `bigNatAndNotWord#` instead of truncating.
Fixes #26230
- - - - -
3506fa7d by Simon Hengel at 2025-08-13T21:05:18-04:00
Report -pgms as a deprecated flag
(instead of reporting an unspecific warning)
Before:
on the commandline: warning:
Object splitting was removed in GHC 8.8
After:
on the commandline: warning: [GHC-53692] [-Wdeprecated-flags]
-pgms is deprecated: Object splitting was removed in GHC 8.8
- - - - -
51c701fe by Zubin Duggal at 2025-08-13T21:06:00-04:00
testsuite: Be more permissive when filtering out GNU_PROPERTY_TYPE linker warnings
The warning text is slightly different with ld.bfd.
Fixes #26249
- - - - -
dfe6f464 by Simon Hengel at 2025-08-13T21:06:43-04:00
Refactoring: Don't misuse `MCDiagnostic` for lint messages
`MCDiagnostic` is meant to be used for compiler diagnostics.
Any code that creates `MCDiagnostic` directly, without going through
`GHC.Driver.Errors.printMessage`, side steps `-fdiagnostics-as-json`
(see e.g. !14475, !14492 !14548).
To avoid this in the future I want to control more narrowly who creates
`MCDiagnostic` (see #24113).
Some parts of the compiler use `MCDiagnostic` purely for formatting
purposes, without creating any real compiler diagnostics. This change
introduces a helper function, `formatDiagnostic`, that can be used in
such cases instead of constructing `MCDiagnostic`.
- - - - -
a8b2fbae by Teo Camarasu at 2025-08-13T21:07:24-04:00
rts: ensure MessageBlackHole.link is always a valid closure
We turn a MessageBlackHole into an StgInd in wakeBlockingQueue().
Therefore it's important that the link field, which becomes the
indirection field, always points to a valid closure.
It's unclear whether it's currently possible for the previous behaviour
to lead to a crash, but it's good to be consistent about this invariant nonetheless.
Co-authored-by: Andreas Klebinger <klebinger.andreas(a)gmx.at>
- - - - -
4021181e by Teo Camarasu at 2025-08-13T21:07:24-04:00
rts: spin if we see a WHITEHOLE in messageBlackHole
When a BLACKHOLE gets cancelled in raiseAsync, we indirect to a THUNK.
GC can then shortcut this, replacing our BLACKHOLE with a fresh THUNK.
This THUNK is not guaranteed to have a valid indirectee field.
If at the same time, a message intended for the previous BLACKHOLE is
processed and concurrently we BLACKHOLE the THUNK, thus temporarily
turning it into a WHITEHOLE, we can get a segfault, since we look at the
undefined indirectee field of the THUNK
The fix is simple: spin if we see a WHITEHOLE, and it will soon be
replaced with a valid BLACKHOLE.
Resolves #26205
- - - - -
1107af89 by Oleg Grenrus at 2025-08-13T21:08:06-04:00
Allow defining HasField instances for naughty fields
Resolves #26295
... as HasField solver doesn't solve for fields with "naughty"
selectors, we could as well allow defining HasField instances for these
fields.
- - - - -
020e7587 by Sylvain Henry at 2025-08-13T21:09:00-04:00
Fix Data.List unqualified import warning
- - - - -
fd811ded by Simon Peyton Jones at 2025-08-14T17:56:47-04:00
Make injecting implicit bindings into its own pass
Previously we were injecting "impliicit bindings" (data constructor
worker and wrappers etc)
- both at the end of CoreTidy,
- and at the start of CorePrep
This is unpleasant and confusing. This patch puts it it its own pass,
addImplicitBinds, which runs between the two.
The function `GHC.CoreToStg.AddImplicitBinds.addImplicitBinds` now takes /all/
TyCons, not just the ones for algebraic data types. That change ripples
through to
- corePrepPgm
- doCodeGen
- byteCodeGen
All take [TyCon] which includes all TyCons
- - - - -
9bd7fcc5 by Simon Peyton Jones at 2025-08-14T17:56:47-04:00
Implement unary classes
The big change is described exhaustively in
Note [Unary class magic] in GHC.Core.TyCon
Other changes
* We never unbox class dictionaries in worker/wrapper. This has been true for some
time now, but the logic is now centralised in functions in
GHC.Core.Opt.WorkWrap.Utils, namely `canUnboxTyCon`, and `canUnboxArg`
See Note [Do not unbox class dictionaries] in GHC.Core.Opt.WorkWrap.Utils.
* Refactored the `notWorthFloating` logic in GHc.Core.Opt.SetLevels.
I can't remember if I actually changed any behaviour here, but if so it's
only in a corner cases.
* Fixed a bug in `GHC.Core.TyCon.isEnumerationTyCon`, which was wrongly returning
True for (##).
* Remove redundant Role argument to `liftCoSubstWithEx`. It was always
Representational.
* I refactored evidence generation in the constraint solver:
* Made GHC.Tc.Types.Evidence contain better abstactions for evidence
generation.
* I deleted the file `GHC.Tc.Types.EvTerm` and merged its (small) contents
elsewhere. It wasn't paying its way.
* Made evidence for implicit parameters go via a proper abstraction.
* Fix inlineBoringOk; see (IB6) in Note [inlineBoringOk]
This fixes a slowdown in `countdownEffectfulDynLocal`
in the `effectful` library.
Smaller things
* Rename `isDataTyCon` to `isBoxedDataTyCon`.
* GHC.Core.Corecion.liftCoSubstWithEx was only called with Representational role,
so I baked that into the function and removed the argument.
* Get rid of `GHC.Core.TyCon.tyConSingleAlgDataCon_maybe` in favour of calling
`not isNewTyCon` at the call sites; more explicit.
* Refatored `GHC.Core.TyCon.isInjectiveTyCon`; but I don't think I changed its
behaviour
* Moved `decomposeIPPred` to GHC.Core.Predicate
Compile time performance changes:
geo. mean +0.1%
minimum -6.8%
maximum +14.4%
The +14% one is in T21839c, where it seems that a bit more inlining
is taking place. That seems acceptable; and the average change is small
Metric Decrease:
LargeRecord
T12227
T12707
T16577
T21839r
T5642
Metric Increase:
T15164
T21839c
T3294
T5321FD
T5321Fun
WWRec
- - - - -
b4075d71 by Simon Peyton Jones at 2025-08-14T17:56:47-04:00
Slight improvement to pre/postInlineUnconditionally
Avoids an extra simplifier iteration
- - - - -
9e443596 by Simon Peyton Jones at 2025-08-14T17:56:47-04:00
Fix a long-standing assertion error in normSplitTyConApp_maybe
- - - - -
91310ad0 by Simon Peyton Jones at 2025-08-14T17:56:47-04:00
Add comment to coercion optimiser
- - - - -
5b841d82 by Teo Camarasu at 2025-08-14T17:57:56-04:00
template-haskell: move some identifiers from ghc-internal to template-haskell
These identifiers are not used internally by the compiler. Therefore we
have no reason for them to be in ghc-internal.
By moving them to template-haskell, we benefit from it being easier to
change them and we avoid having to build them in stage0.
Resolves #26048
- - - - -
33e2c7e5 by Teo Camarasu at 2025-08-14T17:57:56-04:00
template-haskell: transfer $infix note to public module
This Haddock note should be in the public facing module
- - - - -
2a411fc4 by Sylvain Henry at 2025-08-14T17:59:09-04:00
JS: export HEAP8 symbol (#26290)
Newer Emscripten requires this.
- - - - -
248f78ca by Ben Gamari at 2025-08-14T17:59:51-04:00
users-guide: Drop the THREAD_RUNNABLE event
As of f361281c89fbce42865d8b8b27b0957205366186 it is no longer emitted.
- - - - -
706d33e3 by Recursion Ninja at 2025-08-15T04:12:12-04:00
Resolving issues #20645 and #26109
Correctly sign extending and casting smaller bit width types for LLVM operations:
- bitReverse8#
- bitReverse16#
- bitReverse32#
- byteSwap16#
- byteSwap32#
- pdep8#
- pdep16#
- pext8#
- pext16#
- - - - -
1cdc6f46 by Cheng Shao at 2025-08-15T04:12:56-04:00
hadrian: enforce have_llvm=False for wasm32/js
This patch fixes hadrian to always pass have_llvm=False to the
testsuite driver for wasm32/js targets. These targets don't really
support the LLVM backend, and the optllvm test way doesn't work. We
used to special-case wasm32/js to avoid auto-adding optllvm way in
testsuite/config/ghc, but this is still problematic if someone writes
a new LLVM-related test and uses something like when(have_llvm(),
extra_ways(["optllvm"])). So better just enforce have_llvm=False for
these targets here.
- - - - -
ca03226d by Ben Gamari at 2025-08-18T13:43:20+00:00
configure: Allow use of LLVM 20
- - - - -
783cd7d6 by Cheng Shao at 2025-08-18T20:13:14-04:00
compiler: use `UniqMap` instead of `Map` for `BCEnv` in bytecode compiler
The bytecode compiler maintains a `BCEnv` which was previously `Map Id
StackDepth`. Given `Id` is `Uniquable`, we might as well use `UniqMap`
here as a more efficient data structure, hence this patch.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
58e46da9 by fendor at 2025-08-18T20:13:56-04:00
rts: Strip lower three bits when hashing Word instead of lower eight bits
- - - - -
45dbfa23 by Cheng Shao at 2025-08-18T20:14:37-04:00
libffi: update to 3.5.2
Bumps libffi submodule.
- - - - -
54be78ef by Ben Gamari at 2025-08-19T16:28:05-04:00
testsuite: Fix T20006b
This test is supposed to fail for non-threaded ways yet it
was previously marked as only failing in `normal`.
Fix this.
- - - - -
f4bac607 by Simon Peyton Jones at 2025-08-19T16:28:47-04:00
Take yet more care with reporting redundant constraints
This small patch fixes #25992, which relates to reporting redundant
constraints on default-method declarations.
See (TRC5) in Note [Tracking redundant constraints]
- - - - -
ab130fec by fendor at 2025-08-19T16:29:29-04:00
Bump dependencies of hadrian-bootstrap-gen to use GHC 9.6.7
- - - - -
6d02ac6f by fendor at 2025-08-19T16:29:29-04:00
Bump required GHC version for test-bootstrap jobs to 9.10.1
Include test-bootstrap job for GHC 9.12.2.
Update hadrian bootstrap plans use GHC 9.10 and 9.12
Remove older GHC bootstrap configurations.
We require at least GHC 9.10.1 to build GHC.
Adds plans for:
* 9.10.1
* 9.10.2
* 9.12.1
* 9.12.2
- - - - -
9e857171 by Brandon Chinn at 2025-08-20T11:47:46-04:00
Don't warn unused-imports with used generated imports
Fixes #21730
* The old notion of "implicit" import has been renamed to "generated". See Note [Generated imports] in GHC.Hs.ImpExp.
* ImportMap now keeps track of generated and user-written imports separately. This avoids the fake SrcSpan we used to give the implicit Prelude import, and the hack that went with it.
* -ddump-minimal-imports now considers generated imports (but still only
warns on + prints user-written imports)
* bestImport considers generated imports to take priority over user-written imports.
- - - - -
9fb3bad4 by Ben Gamari at 2025-08-20T11:48:31-04:00
mailmap: Use ben(a)well-typed.com more liberally
Nearly all of this work was done while working for Well-Typed.
- - - - -
774fec37 by Ben Gamari at 2025-08-20T11:49:15-04:00
Add primop to annotate the call stack with arbitrary data
We introduce a new primop `annotateStack#` which allows us to push
arbitrary data onto the call-stack.
This allows us to extract the data later when decoding the stack, for
example when an exception is thrown, showing more information to the
user without having to annotate the full call-stack with `HasCallStack`
constraints.
A new stack frame value is introduced `AnnFrame`, which consists of
nothing but a generic payload.
The primop has a small wrapper API that allows users to annotate their
call-stack in programs.
There is a pure API and an IO-based one. The former is a little bit
dubious, as it affects the evaluation of a program, so use with care.
The latter is "safe", as it doesn't change the evaluation of the
program.
The stack annotation mechanism is similarly implemented to the
`ExceptionAnnotation` and `Exception`, there is a typeclass to indicate
something can be pushed onto the call-stack and all values are wrapped
in the existential `SomeStackAnnotation`, which recover the type of the
annotation payload.
There is currently no builtin way to show the stack annotations when
`Backtraces` are displayed (i.e., when showing stack traces to the user),
which we will address in a follow-up MR.
-------------------------
Metric Increase:
ghc_experimental_so
-------------------------
We increase the size of the package, so this is not unreasonable.
Co-Authored-By: fendor <fendor(a)posteo.de>
Co-Authored-By: Ben Gamari <bgamari.foss(a)gmail.com>
- - - - -
fdfa3892 by Ben Gamari at 2025-08-20T11:49:57-04:00
testsuite: Add regression test for #24606
- - - - -
39b2e382 by Cheng Shao at 2025-08-20T11:50:40-04:00
compiler: only use `Name` instead of `Id` in `SptEntry`
As a part of #26298, this patch refactors `SptEntry` to only carry a
`Name` instead of `Id`: we do not care about extra information like
caffyness or type at all in any static pointer related codegen logic.
This is necessary to make `SptEntry` serializable, as a part of the
grand plan of serializable bytecode.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
276f8ea8 by Vekhir -- at 2025-08-20T11:51:35-04:00
Bump Cabal dependency
- - - - -
0b9c7437 by Zubin Duggal at 2025-08-20T11:52:18-04:00
ci: Teach ci.sh to fetch FreeBSD artifacts from ghcup unofficial bindists and bootstrap compiler on FreeBSD to 9.10.1
Also refactor fetch_ghc logic in ci.sh, renaming the GHC_VERSION enviorment configuration variable to FETCH_GHC_VERSION,
making it clear that it is intended for use on platforms like Windows and FreeBSD where we don't want to use the GHC
excecutable from the platform environment and instead need to download and install GHC-$FETCH_GHC_VERSION from a release
bindist.
Fixes #26296
- - - - -
b2914797 by Cheng Shao at 2025-08-20T11:53:00-04:00
driver: use UniqSet for hiddenModules in DynFlags/FinderOpts
This patch replaces Set ModuleName with UniqSet ModuleName in
DynFlags.hiddenModules and FinderOpts.finder_hiddenModules for
improved efficiency.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
0335d899 by Cheng Shao at 2025-08-20T11:53:00-04:00
driver: use UniqMap ModuleName in the finder
This patch replaces Map ModuleName with UniqMap ModuleName in the
finder for improved efficiency.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
91f4faaa by Cheng Shao at 2025-08-20T11:53:43-04:00
configure: check python3 version and require minimal 3.7
Since !9515, the testsuite driver requires python3 version to be at
least 3.7, though this has never been checked by configure logic. This
patch implements the version check. Fixes #23234.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
df4ee9b4 by Cheng Shao at 2025-08-20T11:54:25-04:00
compiler: use zero cost coerce in GHC.CmmToAsm.CFG.loopInfo
This patch refactors GHC.CmmToAsm.CFG.loopInfo to use zero cost coerce
and thus addresses the TODO. For coerce to work, constructors of
Label/LabelMap/LabelSet from GHC.Cmm.Dataflow.Label are exposed,
though I believe it's a worthy tradeoff to avoid unnecessary runtime
cost without using unsafeCoerce, since the latter could be a landmine
for future refactoring.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
ccda188d by Simon Peyton Jones at 2025-08-20T11:55:07-04:00
Start with empty inerts in shortcut solving
When short-cut solving we were starting with an inert set that had
unsolved Wanteds. This caused an infinite loop (#26314), because a
typechecker plugin kept being given that unsolved Wanted.
It's better just to start with an empty inert set
- - - - -
c8882ed7 by Ben Gamari at 2025-08-20T11:55:49-04:00
configure: Bump minimal bootstrap GHC version to 9.8
- - - - -
cdcfcd9d by Rodrigo Mesquita at 2025-08-20T19:43:19+02:00
cleanup: Move dehydrateCgBreakInfo to Stg2Bc
This no longer has anything to do with Core.
- - - - -
227dbb4e by Rodrigo Mesquita at 2025-08-20T19:43:19+02:00
rts/Disassembler: Fix spacing of BRK_FUN
- - - - -
5cde3660 by Rodrigo Mesquita at 2025-08-20T19:43:19+02:00
debugger: Fix bciPtr in Step-out
We need to use `BCO_NEXT` to move bciPtr to ix=1, because ix=0 points to
the instruction itself!
I do not understand how this didn't crash before.
- - - - -
e89edf00 by Rodrigo Mesquita at 2025-08-20T19:43:20+02:00
debugger: Allow BRK_FUNs to head case continuation BCOs
When we start executing a BCO, we may want to yield to the scheduler:
this may be triggered by a heap/stack check, context switch, or a
breakpoint. To yield, we need to put the stack in a state such that
when execution is resumed we are back to where we yielded from.
Previously, a BKR_FUN could only head a function BCO because we only
knew how to construct a valid stack for yielding from one -- simply add
`apply_interp_info` + the BCO to resume executing. This is valid because
the stack at the start of run_BCO is headed by that BCO's arguments.
However, in case continuation BCOs (as per Note [Case continuation BCOs]),
we couldn't easily reconstruct a valid stack that could be resumed
because we dropped too soon the stack frames regarding the value
returned (stg_ret) and received (stg_ctoi) by that continuation.
This is especially tricky because of the variable type and size return
frames (e.g. pointer ret_p/ctoi_R1p vs a tuple ret_t/ctoi_t2).
The trick to being able to yield from a BRK_FUN at the start of a case
cont BCO is to stop removing the ret frame headers eagerly and instead
keep them until the BCO starts executing. The new layout at the start of
a case cont. BCO is described by the new Note [Stack layout when entering run_BCO].
Now, we keep the ret_* and ctoi_* frames when entering run_BCO.
A BRK_FUN is then executed if found, and the stack is yielded as-is with
the preserved ret and ctoi frames.
Then, a case cont BCO's instructions always SLIDE off the headers of the
ret and ctoi frames, in StgToByteCode.doCase, turning a stack like
| .... |
+---------------+
| fv2 |
+---------------+
| fv1 |
+---------------+
| BCO |
+---------------+
| stg_ctoi_ret_ |
+---------------+
| retval |
+---------------+
| stg_ret_..... |
+---------------+
into
| .... |
+---------------+
| fv2 |
+---------------+
| fv1 |
+---------------+
| retval |
+---------------+
for the remainder of the BCO.
Moreover, this more uniform approach of keeping the ret and ctoi frames
means we need less ad-hoc logic concerning the variable size of
ret_tuple vs ret_p/np frames in the code generator and interpreter:
Always keep the return to cont. stack intact at the start of run_BCO,
and the statically generated instructions will take care of adjusting
it.
Unlocks BRK_FUNs at the start of case cont. BCOs which will enable a
better user-facing step-out (#26042) which is free of the bugs the
current BRK_ALTS implementation suffers from (namely, using BRK_FUN
rather than BRK_ALTS in a case cont. means we'll never accidentally end
up in a breakpoint "deeper" than the continuation, because we stop at
the case cont itself rather than on the first breakpoint we evaluate
after it).
- - - - -
1df87e94 by Rodrigo Mesquita at 2025-08-20T19:43:20+02:00
BRK_FUN with InternalBreakLocs for code-generation time breakpoints
At the start of a case continuation BCO, place a BRK_FUN.
This BRK_FUN uses the new "internal breakpoint location" -- allowing us
to come up with a valid source location for this breakpoint that is not associated with a source-level tick.
For case continuation BCOs, we use the last tick seen before it as the
source location. The reasoning is described in Note [Debugger: Stepout internal break locs].
Note how T26042c, which was broken because it displayed the incorrect
behavior of the previous step out when we'd end up at a deeper level
than the one from which we initiated step-out, is now fixed.
As of this commit, BRK_ALTS is now dead code and is thus dropped.
Note [Debugger: Stepout internal break locs]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Step-out tells the interpreter to run until the current function
returns to where it was called from, and stop there.
This is achieved by enabling the BRK_FUN found on the first RET_BCO
frame on the stack (See [Note Debugger: Step-out]).
Case continuation BCOs (which select an alternative branch) must
therefore be headed by a BRK_FUN. An example:
f x = case g x of <--- end up here
1 -> ...
2 -> ...
g y = ... <--- step out from here
- `g` will return a value to the case continuation BCO in `f`
- The case continuation BCO will receive the value returned from g
- Match on it and push the alternative continuation for that branch
- And then enter that alternative.
If we step-out of `g`, the first RET_BCO on the stack is the case
continuation of `f` -- execution should stop at its start, before
selecting an alternative. (One might ask, "why not enable the breakpoint
in the alternative instead?", because the alternative continuation is
only pushed to the stack *after* it is selected by the case cont. BCO)
However, the case cont. BCO is not associated with any source-level
tick, it is merely the glue code which selects alternatives which do
have source level ticks. Therefore, we have to come up at code
generation time with a breakpoint location ('InternalBreakLoc') to
display to the user when it is stopped there.
Our solution is to use the last tick seen just before reaching the case
continuation. This is robust because a case continuation will thus
always have a relevant breakpoint location:
- The source location will be the last source-relevant expression
executed before the continuation is pushed
- So the source location will point to the thing you've just stepped
out of
- Doing :step-local from there will put you on the selected
alternative (which at the source level may also be the e.g. next
line in a do-block)
Examples, using angle brackets (<<...>>) to denote the breakpoint span:
f x = case <<g x>> {- step in here -} of
1 -> ...
2 -> ...>
g y = <<...>> <--- step out from here
...
f x = <<case g x of <--- end up here, whole case highlighted
1 -> ...
2 -> ...>>
doing :step-local ...
f x = case g x of
1 -> <<...>> <--- stop in the alternative
2 -> ...
A second example based on T26042d2, where the source is a do-block IO
action, optimised to a chain of `case expressions`.
main = do
putStrLn "hello1"
<<f>> <--- step-in here
putStrLn "hello3"
putStrLn "hello4"
f = do
<<putStrLn "hello2.1">> <--- step-out from here
putStrLn "hello2.2"
...
main = do
putStrLn "hello1"
<<f>> <--- end up here again, the previously executed expression
putStrLn "hello3"
putStrLn "hello4"
doing step/step-local ...
main = do
putStrLn "hello1"
f
<<putStrLn "hello3">> <--- straight to the next line
putStrLn "hello4"
Finishes #26042
- - - - -
d101ba07 by Rodrigo Mesquita at 2025-08-20T19:43:20+02:00
debugger: Re-use the last BreakpointId whole in step-out
Previously, to come up with a location to stop at for `:stepout`, we
would store the location of the last BreakpointId surrounding the
continuation, as described by Note [Debugger: Stepout internal break locs].
However, re-using just the location from the last source breakpoint
isn't sufficient to provide the necessary information in the break
location. Specifically, it wouldn't bind any variables at that location.
Really, there is no reason not to re-use the last breakpoint wholesale,
and re-use all the information we had there. Step-out should behave just
as if we had stopped at the call, but s.t. continuing will not
re-execute the call.
This commit updates the CgBreakInfo to always store a BreakpointId, be
it the original one or the one we're emulating (for step-out).
It makes variable bindings on :stepout work
- - - - -
99a522ac by Cheng Shao at 2025-08-20T19:50:36+02:00
compiler: implement and test bytecode serialization logic
- - - - -
419 changed files:
- .gitlab-ci.yml
- .gitlab/ci.sh
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .mailmap
- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Builtin/PrimOps.hs
- compiler/GHC/Builtin/PrimOps/Ids.hs
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/Types/Prim.hs
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/ByteCode/Asm.hs
- compiler/GHC/ByteCode/Breakpoints.hs
- compiler/GHC/ByteCode/InfoTable.hs
- compiler/GHC/ByteCode/Instr.hs
- + compiler/GHC/ByteCode/Serialize.hs
- compiler/GHC/ByteCode/Types.hs
- compiler/GHC/Cmm/Dataflow/Label.hs
- compiler/GHC/CmmToAsm/CFG.hs
- compiler/GHC/CmmToLlvm/CodeGen.hs
- compiler/GHC/Core/Class.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/Coercion/Opt.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/FamInstEnv.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/OccurAnal.hs
- compiler/GHC/Core/Opt/SetLevels.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/Specialise.hs
- compiler/GHC/Core/Opt/WorkWrap/Utils.hs
- compiler/GHC/Core/Predicate.hs
- compiler/GHC/Core/TyCo/Rep.hs
- compiler/GHC/Core/TyCon.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Unfold.hs
- compiler/GHC/Core/Unfold/Make.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/CoreToStg.hs
- + compiler/GHC/CoreToStg/AddImplicitBinds.hs
- compiler/GHC/CoreToStg/Prep.hs
- compiler/GHC/Data/FlatBag.hs
- compiler/GHC/Data/SmallArray.hs
- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Driver/Config/Finder.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Errors/Ppr.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/HsToCore.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Breakpoints.hs
- compiler/GHC/HsToCore/Docs.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Foreign/Call.hs
- compiler/GHC/HsToCore/Ticks.hs
- compiler/GHC/Iface/Decl.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/Iface/Tidy.hs
- compiler/GHC/Iface/Tidy/StaticPtrTable.hs
- compiler/GHC/IfaceToCore.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Parser/Header.hs
- compiler/GHC/Rename/Module.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/Runtime/Debugger/Breakpoints.hs
- compiler/GHC/Runtime/Eval.hs
- compiler/GHC/Stg/Lint.hs
- compiler/GHC/StgToByteCode.hs
- compiler/GHC/StgToCmm.hs
- compiler/GHC/StgToCmm/Prim.hs
- compiler/GHC/StgToJS/Prim.hs
- compiler/GHC/StgToJS/StaticPtr.hs
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Gen/App.hs
- compiler/GHC/Tc/Gen/Bind.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/HsType.hs
- compiler/GHC/Tc/Instance/Class.hs
- compiler/GHC/Tc/Instance/Family.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Tc/Solver/Default.hs
- compiler/GHC/Tc/Solver/Dict.hs
- compiler/GHC/Tc/Solver/Equality.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Solver/Solve.hs
- compiler/GHC/Tc/TyCl.hs
- compiler/GHC/Tc/TyCl/Build.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/GHC/Tc/TyCl/PatSyn.hs
- compiler/GHC/Tc/TyCl/Utils.hs
- − compiler/GHC/Tc/Types/EvTerm.hs
- compiler/GHC/Tc/Types/Evidence.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/Tc/Utils/Concrete.hs
- compiler/GHC/Tc/Utils/TcMType.hs
- compiler/GHC/Tc/Utils/Unify.hs
- compiler/GHC/Tc/Validity.hs
- compiler/GHC/Types/Demand.hs
- compiler/GHC/Types/Error.hs
- compiler/GHC/Types/Id.hs
- compiler/GHC/Types/Id/Make.hs
- compiler/GHC/Types/Name/Reader.hs
- compiler/GHC/Types/RepType.hs
- compiler/GHC/Types/SptEntry.hs
- compiler/GHC/Types/Tickish.hs
- compiler/GHC/Types/TyThing.hs
- compiler/GHC/Unit/Finder.hs
- compiler/GHC/Unit/Finder/Types.hs
- compiler/GHC/Utils/Binary.hs
- compiler/GHC/Utils/Error.hs
- compiler/ghc.cabal.in
- configure.ac
- − docs/users_guide/9.14.1-notes.rst
- + docs/users_guide/9.16.1-notes.rst
- docs/users_guide/eventlog-formats.rst
- docs/users_guide/release-notes.rst
- ghc/GHCi/UI.hs
- ghc/ghc-bin.cabal.in
- hadrian/bootstrap/generate_bootstrap_plans
- hadrian/bootstrap/hadrian-bootstrap-gen.cabal
- hadrian/bootstrap/plan-9_10_1.json
- hadrian/bootstrap/plan-9_6_5.json → hadrian/bootstrap/plan-9_10_2.json
- hadrian/bootstrap/plan-9_6_6.json → hadrian/bootstrap/plan-9_12_1.json
- hadrian/bootstrap/plan-9_6_4.json → hadrian/bootstrap/plan-9_12_2.json
- − hadrian/bootstrap/plan-9_6_1.json
- − hadrian/bootstrap/plan-9_6_2.json
- − hadrian/bootstrap/plan-9_6_3.json
- − hadrian/bootstrap/plan-9_8_1.json
- − hadrian/bootstrap/plan-9_8_2.json
- hadrian/bootstrap/plan-bootstrap-9_10_1.json
- hadrian/bootstrap/plan-bootstrap-9_6_5.json → hadrian/bootstrap/plan-bootstrap-9_10_2.json
- hadrian/bootstrap/plan-bootstrap-9_6_6.json → hadrian/bootstrap/plan-bootstrap-9_12_1.json
- hadrian/bootstrap/plan-bootstrap-9_8_1.json → hadrian/bootstrap/plan-bootstrap-9_12_2.json
- − hadrian/bootstrap/plan-bootstrap-9_6_1.json
- − hadrian/bootstrap/plan-bootstrap-9_6_2.json
- − hadrian/bootstrap/plan-bootstrap-9_6_3.json
- − hadrian/bootstrap/plan-bootstrap-9_6_4.json
- − hadrian/bootstrap/plan-bootstrap-9_8_2.json
- hadrian/bootstrap/src/Main.hs
- hadrian/hadrian.cabal
- hadrian/src/Settings/Builders/RunTest.hs
- libffi-tarballs
- libraries/Cabal
- libraries/base/base.cabal.in
- libraries/base/changelog.md
- libraries/base/src/GHC/Exts.hs
- − libraries/base/src/GHC/IOPort.hs
- libraries/directory
- libraries/ghc-bignum/changelog.md
- libraries/ghc-experimental/ghc-experimental.cabal.in
- + libraries/ghc-experimental/src/GHC/Exception/Backtrace/Experimental.hs
- + libraries/ghc-experimental/src/GHC/Stack/Annotation/Experimental.hs
- libraries/ghc-heap/GHC/Exts/Heap/ClosureTypes.hs
- libraries/ghc-heap/GHC/Exts/Heap/Closures.hs
- libraries/ghc-heap/GHC/Exts/Stack.hs
- libraries/ghc-heap/GHC/Exts/Stack/Constants.hsc
- libraries/ghc-heap/GHC/Exts/Stack/Decode.hs
- + libraries/ghc-heap/tests/stack-annotation/Makefile
- + libraries/ghc-heap/tests/stack-annotation/TestUtils.hs
- + libraries/ghc-heap/tests/stack-annotation/all.T
- + libraries/ghc-heap/tests/stack-annotation/ann_frame001.hs
- + libraries/ghc-heap/tests/stack-annotation/ann_frame001.stdout
- + libraries/ghc-heap/tests/stack-annotation/ann_frame002.hs
- + libraries/ghc-heap/tests/stack-annotation/ann_frame002.stdout
- + libraries/ghc-heap/tests/stack-annotation/ann_frame003.hs
- + libraries/ghc-heap/tests/stack-annotation/ann_frame003.stdout
- + libraries/ghc-heap/tests/stack-annotation/ann_frame004.hs
- + libraries/ghc-heap/tests/stack-annotation/ann_frame004.stdout
- libraries/ghc-internal/cbits/pdep.c
- libraries/ghc-internal/cbits/pext.c
- libraries/ghc-internal/ghc-internal.cabal.in
- libraries/ghc-internal/src/GHC/Internal/Bignum/Natural.hs
- libraries/ghc-internal/src/GHC/Internal/ClosureTypes.hs
- libraries/ghc-internal/src/GHC/Internal/Event/Windows.hsc
- libraries/ghc-internal/src/GHC/Internal/Event/Windows/Thread.hs
- libraries/ghc-internal/src/GHC/Internal/Exception.hs
- libraries/ghc-internal/src/GHC/Internal/Exception/Backtrace.hs
- libraries/ghc-internal/src/GHC/Internal/Exception/Backtrace.hs-boot
- libraries/ghc-internal/src/GHC/Internal/Exts.hs
- libraries/ghc-internal/src/GHC/Internal/IO/Buffer.hs
- libraries/ghc-internal/src/GHC/Internal/IO/Windows/Handle.hsc
- − libraries/ghc-internal/src/GHC/Internal/IOPort.hs
- libraries/ghc-internal/src/GHC/Internal/Prim/PtrEq.hs
- libraries/ghc-internal/src/GHC/Internal/TH/Lib.hs
- libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs
- libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs
- + libraries/ghc-internal/tests/Makefile
- + libraries/ghc-internal/tests/all.T
- + libraries/ghc-internal/tests/backtraces/Makefile
- + libraries/ghc-internal/tests/backtraces/T14532a.hs
- + libraries/ghc-internal/tests/backtraces/T14532a.stdout
- + libraries/ghc-internal/tests/backtraces/T14532b.hs
- + libraries/ghc-internal/tests/backtraces/T14532b.stdout
- + libraries/ghc-internal/tests/backtraces/all.T
- libraries/ghc-prim/changelog.md
- libraries/ghci/GHCi/Run.hs
- libraries/hpc
- libraries/template-haskell/Language/Haskell/TH/Lib.hs
- libraries/template-haskell/Language/Haskell/TH/Quote.hs
- libraries/template-haskell/Language/Haskell/TH/Syntax.hs
- libraries/template-haskell/tests/all.T
- libraries/time
- libraries/unix
- m4/find_python.m4
- rts/ClosureFlags.c
- rts/Disassembler.c
- rts/Hash.c
- rts/Interpreter.c
- rts/LdvProfile.c
- rts/Messages.c
- rts/Prelude.h
- rts/PrimOps.cmm
- rts/Printer.c
- rts/Profiling.c
- rts/RetainerProfile.c
- rts/RtsSymbols.c
- rts/StgMiscClosures.cmm
- rts/TraverseHeap.c
- rts/Updates.h
- rts/external-symbols.list.in
- rts/include/rts/Bytecodes.h
- rts/include/rts/storage/ClosureTypes.h
- rts/include/rts/storage/Closures.h
- rts/include/stg/MiscClosures.h
- rts/include/stg/SMP.h
- rts/js/mem.js
- rts/js/profiling.js
- rts/posix/ticker/Pthread.c
- rts/posix/ticker/TimerFd.c
- rts/rts.cabal
- rts/sm/Compact.c
- rts/sm/Evac.c
- rts/sm/NonMovingMark.c
- rts/sm/Sanity.c
- rts/sm/Scav.c
- rts/win32/AsyncWinIO.c
- rts/win32/libHSghc-internal.def
- testsuite/config/ghc
- testsuite/driver/testlib.py
- testsuite/tests/arrows/should_compile/T21301.stderr
- testsuite/tests/core-to-stg/T24124.stderr
- testsuite/tests/corelint/LintEtaExpand.stderr
- testsuite/tests/count-deps/CountDepsAst.stdout
- testsuite/tests/count-deps/CountDepsParser.stdout
- testsuite/tests/deSugar/should_compile/T2431.stderr
- testsuite/tests/deSugar/should_fail/DsStrictFail.stderr
- testsuite/tests/deSugar/should_run/T20024.stderr
- testsuite/tests/deSugar/should_run/dsrun005.stderr
- testsuite/tests/deSugar/should_run/dsrun007.stderr
- testsuite/tests/deSugar/should_run/dsrun008.stderr
- testsuite/tests/deriving/should_run/T9576.stderr
- testsuite/tests/dmdanal/should_compile/T16029.stdout
- testsuite/tests/dmdanal/sigs/T21119.stderr
- testsuite/tests/dmdanal/sigs/T21888.stderr
- testsuite/tests/gadt/T12468.stderr
- testsuite/tests/ghc-e/should_fail/T24172.stderr
- testsuite/tests/ghci.debugger/scripts/T26042b.script
- testsuite/tests/ghci.debugger/scripts/T26042b.stdout
- testsuite/tests/ghci.debugger/scripts/T26042c.script
- testsuite/tests/ghci.debugger/scripts/T26042c.stdout
- + testsuite/tests/ghci.debugger/scripts/T26042d2.hs
- + testsuite/tests/ghci.debugger/scripts/T26042d2.script
- + testsuite/tests/ghci.debugger/scripts/T26042d2.stdout
- testsuite/tests/ghci.debugger/scripts/T26042e.stdout
- testsuite/tests/ghci.debugger/scripts/T26042f.script
- testsuite/tests/ghci.debugger/scripts/T26042f1.stdout
- testsuite/tests/ghci.debugger/scripts/T26042f2.stdout
- testsuite/tests/ghci.debugger/scripts/T26042g.stdout
- testsuite/tests/ghci.debugger/scripts/all.T
- testsuite/tests/ghci.debugger/scripts/break011.stdout
- testsuite/tests/ghci.debugger/scripts/break024.stdout
- testsuite/tests/ghci/scripts/Defer02.stderr
- testsuite/tests/ghci/scripts/T15325.stderr
- testsuite/tests/ghci/scripts/T8353.stderr
- testsuite/tests/ghci/scripts/ghci038.stdout
- testsuite/tests/hpc/recsel/recsel.hs
- testsuite/tests/hpc/recsel/recsel.stdout
- testsuite/tests/indexed-types/should_compile/T2238.hs
- testsuite/tests/indexed-types/should_fail/T5439.stderr
- testsuite/tests/interface-stability/base-exports.stdout
- testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
- testsuite/tests/interface-stability/base-exports.stdout-mingw32
- testsuite/tests/interface-stability/base-exports.stdout-ws-32
- testsuite/tests/interface-stability/ghc-experimental-exports.stdout
- testsuite/tests/interface-stability/ghc-experimental-exports.stdout-mingw32
- testsuite/tests/interface-stability/ghc-prim-exports.stdout
- testsuite/tests/interface-stability/ghc-prim-exports.stdout-mingw32
- testsuite/tests/interface-stability/template-haskell-exports.stdout
- + testsuite/tests/llvm/should_run/T20645.hs
- + testsuite/tests/llvm/should_run/T20645.stdout
- testsuite/tests/llvm/should_run/all.T
- testsuite/tests/module/mod150.stderr
- testsuite/tests/module/mod151.stderr
- testsuite/tests/module/mod152.stderr
- testsuite/tests/module/mod153.stderr
- testsuite/tests/numeric/should_compile/T15547.stderr
- testsuite/tests/numeric/should_compile/T23907.stderr
- + testsuite/tests/numeric/should_run/T18619.hs
- + testsuite/tests/numeric/should_run/T18619.stderr
- + testsuite/tests/numeric/should_run/T26230.hs
- + testsuite/tests/numeric/should_run/T26230.stdout
- testsuite/tests/numeric/should_run/all.T
- testsuite/tests/numeric/should_run/foundation.hs
- testsuite/tests/overloadedrecflds/should_fail/T18999_NoDisambiguateRecordFields.stderr
- + testsuite/tests/overloadedrecflds/should_run/T26295.hs
- + testsuite/tests/overloadedrecflds/should_run/T26295.stdout
- testsuite/tests/overloadedrecflds/should_run/all.T
- testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
- testsuite/tests/parser/should_compile/T14189.stderr
- testsuite/tests/parser/should_compile/T19082.stderr
- testsuite/tests/partial-sigs/should_compile/T10403.stderr
- testsuite/tests/partial-sigs/should_fail/T10615.stderr
- testsuite/tests/patsyn/should_run/ghci.stderr
- testsuite/tests/perf/compiler/hard_hole_fits.stderr
- testsuite/tests/plugins/Makefile
- + testsuite/tests/plugins/T21730-plugin/Makefile
- + testsuite/tests/plugins/T21730-plugin/Setup.hs
- + testsuite/tests/plugins/T21730-plugin/T21730-plugin.cabal
- + testsuite/tests/plugins/T21730-plugin/T21730_Plugin.hs
- + testsuite/tests/plugins/T21730.hs
- testsuite/tests/plugins/all.T
- testsuite/tests/primops/should_run/UnliftedIOPort.hs
- testsuite/tests/primops/should_run/all.T
- testsuite/tests/quasiquotation/T4491/test.T
- testsuite/tests/quotes/LiftErrMsg.stderr
- testsuite/tests/quotes/LiftErrMsgDefer.stderr
- testsuite/tests/quotes/LiftErrMsgTyped.stderr
- testsuite/tests/rename/should_compile/T22513d.stderr
- testsuite/tests/rename/should_compile/T22513e.stderr
- testsuite/tests/rename/should_compile/T22513f.stderr
- testsuite/tests/rename/should_compile/T22513g.stderr
- testsuite/tests/rename/should_compile/T22513h.stderr
- testsuite/tests/rename/should_compile/T22513i.stderr
- testsuite/tests/rename/should_compile/rn039.ghc.stderr
- testsuite/tests/rename/should_fail/T15487.stderr
- testsuite/tests/rename/should_fail/T18740a.stderr
- testsuite/tests/rename/should_fail/rnfail044.stderr
- + testsuite/tests/rep-poly/NoEtaRequired.hs
- testsuite/tests/rep-poly/T21906.stderr
- testsuite/tests/rep-poly/all.T
- testsuite/tests/roles/should_compile/Roles14.stderr
- testsuite/tests/roles/should_compile/Roles3.stderr
- testsuite/tests/roles/should_compile/Roles4.stderr
- testsuite/tests/rts/flags/all.T
- testsuite/tests/safeHaskell/flags/SafeFlags17.stderr
- testsuite/tests/safeHaskell/safeLanguage/SafeLang15.stderr
- testsuite/tests/simplCore/should_compile/DataToTagFamilyScrut.stderr
- testsuite/tests/simplCore/should_compile/T15205.stderr
- testsuite/tests/simplCore/should_compile/T17366.stderr
- testsuite/tests/simplCore/should_compile/T17966.stderr
- testsuite/tests/simplCore/should_compile/T22309.stderr
- testsuite/tests/simplCore/should_compile/T22375DataFamily.stderr
- testsuite/tests/simplCore/should_compile/T23307.stderr
- testsuite/tests/simplCore/should_compile/T23307a.stderr
- + testsuite/tests/simplCore/should_compile/T24606.hs
- testsuite/tests/simplCore/should_compile/T25389.stderr
- testsuite/tests/simplCore/should_compile/T25713.stderr
- testsuite/tests/simplCore/should_compile/T7360.stderr
- testsuite/tests/simplCore/should_compile/all.T
- testsuite/tests/simplStg/should_compile/T15226b.stderr
- testsuite/tests/tcplugins/CtIdPlugin.hs
- testsuite/tests/th/Makefile
- testsuite/tests/th/T10267.stderr
- testsuite/tests/th/T14627.stderr
- testsuite/tests/th/T15321.stderr
- testsuite/tests/type-data/should_run/T22332a.stderr
- testsuite/tests/typecheck/should_compile/Makefile
- testsuite/tests/typecheck/should_compile/T12763.stderr
- testsuite/tests/typecheck/should_compile/T13050.stderr
- testsuite/tests/typecheck/should_compile/T14273.stderr
- testsuite/tests/typecheck/should_compile/T14590.stderr
- testsuite/tests/typecheck/should_compile/T14774.stdout
- testsuite/tests/typecheck/should_compile/T18406b.stderr
- testsuite/tests/typecheck/should_compile/T18529.stderr
- testsuite/tests/typecheck/should_compile/T25180.stderr
- + testsuite/tests/typecheck/should_compile/T25992a.hs
- + testsuite/tests/typecheck/should_compile/T26225.hs
- + testsuite/tests/typecheck/should_compile/T26225b.hs
- testsuite/tests/typecheck/should_compile/T9497a.stderr
- testsuite/tests/typecheck/should_compile/all.T
- testsuite/tests/typecheck/should_compile/refinement_hole_fits.stderr
- testsuite/tests/typecheck/should_compile/subsumption_sort_hole_fits.stderr
- − testsuite/tests/typecheck/should_fail/T12563.stderr
- testsuite/tests/typecheck/should_fail/T14618.stderr
- testsuite/tests/typecheck/should_fail/T14884.stderr
- testsuite/tests/typecheck/should_fail/T21130.stderr
- testsuite/tests/typecheck/should_fail/T23739b.stderr
- testsuite/tests/typecheck/should_fail/T23739c.stderr
- testsuite/tests/typecheck/should_fail/T6022.stderr
- testsuite/tests/typecheck/should_fail/T8883.stderr
- testsuite/tests/typecheck/should_fail/T9497d.stderr
- testsuite/tests/typecheck/should_fail/all.T
- testsuite/tests/typecheck/should_fail/tcfail037.stderr
- testsuite/tests/typecheck/should_fail/tcfail140.stderr
- testsuite/tests/typecheck/should_run/T10284.stderr
- testsuite/tests/typecheck/should_run/T13838.stderr
- testsuite/tests/typecheck/should_run/T9497a-run.stderr
- testsuite/tests/typecheck/should_run/T9497b-run.stderr
- testsuite/tests/typecheck/should_run/T9497c-run.stderr
- testsuite/tests/unboxedsums/unpack_sums_7.stdout
- testsuite/tests/unsatisfiable/T23816.stderr
- testsuite/tests/unsatisfiable/UnsatDefer.stderr
- testsuite/tests/vdq-rta/should_fail/T23738_fail_pun.stderr
- testsuite/tests/wasm/should_run/control-flow/LoadCmmGroup.hs
- testsuite/tests/wasm/should_run/control-flow/RunWasm.hs
- utils/deriveConstants/Main.hs
- utils/genprimopcode/Lexer.x
- utils/genprimopcode/Main.hs
- utils/genprimopcode/Parser.y
- utils/genprimopcode/ParserM.hs
- utils/genprimopcode/Syntax.hs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ad864ef9004cc7bffc617ec9480def…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ad864ef9004cc7bffc617ec9480def…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/fix-spt-stub] 22 commits: configure: Allow use of LLVM 20
by Cheng Shao (@TerrorJack) 20 Aug '25
by Cheng Shao (@TerrorJack) 20 Aug '25
20 Aug '25
Cheng Shao pushed to branch wip/fix-spt-stub at Glasgow Haskell Compiler / GHC
Commits:
ca03226d by Ben Gamari at 2025-08-18T13:43:20+00:00
configure: Allow use of LLVM 20
- - - - -
783cd7d6 by Cheng Shao at 2025-08-18T20:13:14-04:00
compiler: use `UniqMap` instead of `Map` for `BCEnv` in bytecode compiler
The bytecode compiler maintains a `BCEnv` which was previously `Map Id
StackDepth`. Given `Id` is `Uniquable`, we might as well use `UniqMap`
here as a more efficient data structure, hence this patch.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
58e46da9 by fendor at 2025-08-18T20:13:56-04:00
rts: Strip lower three bits when hashing Word instead of lower eight bits
- - - - -
45dbfa23 by Cheng Shao at 2025-08-18T20:14:37-04:00
libffi: update to 3.5.2
Bumps libffi submodule.
- - - - -
54be78ef by Ben Gamari at 2025-08-19T16:28:05-04:00
testsuite: Fix T20006b
This test is supposed to fail for non-threaded ways yet it
was previously marked as only failing in `normal`.
Fix this.
- - - - -
f4bac607 by Simon Peyton Jones at 2025-08-19T16:28:47-04:00
Take yet more care with reporting redundant constraints
This small patch fixes #25992, which relates to reporting redundant
constraints on default-method declarations.
See (TRC5) in Note [Tracking redundant constraints]
- - - - -
ab130fec by fendor at 2025-08-19T16:29:29-04:00
Bump dependencies of hadrian-bootstrap-gen to use GHC 9.6.7
- - - - -
6d02ac6f by fendor at 2025-08-19T16:29:29-04:00
Bump required GHC version for test-bootstrap jobs to 9.10.1
Include test-bootstrap job for GHC 9.12.2.
Update hadrian bootstrap plans use GHC 9.10 and 9.12
Remove older GHC bootstrap configurations.
We require at least GHC 9.10.1 to build GHC.
Adds plans for:
* 9.10.1
* 9.10.2
* 9.12.1
* 9.12.2
- - - - -
9e857171 by Brandon Chinn at 2025-08-20T11:47:46-04:00
Don't warn unused-imports with used generated imports
Fixes #21730
* The old notion of "implicit" import has been renamed to "generated". See Note [Generated imports] in GHC.Hs.ImpExp.
* ImportMap now keeps track of generated and user-written imports separately. This avoids the fake SrcSpan we used to give the implicit Prelude import, and the hack that went with it.
* -ddump-minimal-imports now considers generated imports (but still only
warns on + prints user-written imports)
* bestImport considers generated imports to take priority over user-written imports.
- - - - -
9fb3bad4 by Ben Gamari at 2025-08-20T11:48:31-04:00
mailmap: Use ben(a)well-typed.com more liberally
Nearly all of this work was done while working for Well-Typed.
- - - - -
774fec37 by Ben Gamari at 2025-08-20T11:49:15-04:00
Add primop to annotate the call stack with arbitrary data
We introduce a new primop `annotateStack#` which allows us to push
arbitrary data onto the call-stack.
This allows us to extract the data later when decoding the stack, for
example when an exception is thrown, showing more information to the
user without having to annotate the full call-stack with `HasCallStack`
constraints.
A new stack frame value is introduced `AnnFrame`, which consists of
nothing but a generic payload.
The primop has a small wrapper API that allows users to annotate their
call-stack in programs.
There is a pure API and an IO-based one. The former is a little bit
dubious, as it affects the evaluation of a program, so use with care.
The latter is "safe", as it doesn't change the evaluation of the
program.
The stack annotation mechanism is similarly implemented to the
`ExceptionAnnotation` and `Exception`, there is a typeclass to indicate
something can be pushed onto the call-stack and all values are wrapped
in the existential `SomeStackAnnotation`, which recover the type of the
annotation payload.
There is currently no builtin way to show the stack annotations when
`Backtraces` are displayed (i.e., when showing stack traces to the user),
which we will address in a follow-up MR.
-------------------------
Metric Increase:
ghc_experimental_so
-------------------------
We increase the size of the package, so this is not unreasonable.
Co-Authored-By: fendor <fendor(a)posteo.de>
Co-Authored-By: Ben Gamari <bgamari.foss(a)gmail.com>
- - - - -
fdfa3892 by Ben Gamari at 2025-08-20T11:49:57-04:00
testsuite: Add regression test for #24606
- - - - -
39b2e382 by Cheng Shao at 2025-08-20T11:50:40-04:00
compiler: only use `Name` instead of `Id` in `SptEntry`
As a part of #26298, this patch refactors `SptEntry` to only carry a
`Name` instead of `Id`: we do not care about extra information like
caffyness or type at all in any static pointer related codegen logic.
This is necessary to make `SptEntry` serializable, as a part of the
grand plan of serializable bytecode.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
276f8ea8 by Vekhir -- at 2025-08-20T11:51:35-04:00
Bump Cabal dependency
- - - - -
0b9c7437 by Zubin Duggal at 2025-08-20T11:52:18-04:00
ci: Teach ci.sh to fetch FreeBSD artifacts from ghcup unofficial bindists and bootstrap compiler on FreeBSD to 9.10.1
Also refactor fetch_ghc logic in ci.sh, renaming the GHC_VERSION enviorment configuration variable to FETCH_GHC_VERSION,
making it clear that it is intended for use on platforms like Windows and FreeBSD where we don't want to use the GHC
excecutable from the platform environment and instead need to download and install GHC-$FETCH_GHC_VERSION from a release
bindist.
Fixes #26296
- - - - -
b2914797 by Cheng Shao at 2025-08-20T11:53:00-04:00
driver: use UniqSet for hiddenModules in DynFlags/FinderOpts
This patch replaces Set ModuleName with UniqSet ModuleName in
DynFlags.hiddenModules and FinderOpts.finder_hiddenModules for
improved efficiency.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
0335d899 by Cheng Shao at 2025-08-20T11:53:00-04:00
driver: use UniqMap ModuleName in the finder
This patch replaces Map ModuleName with UniqMap ModuleName in the
finder for improved efficiency.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
91f4faaa by Cheng Shao at 2025-08-20T11:53:43-04:00
configure: check python3 version and require minimal 3.7
Since !9515, the testsuite driver requires python3 version to be at
least 3.7, though this has never been checked by configure logic. This
patch implements the version check. Fixes #23234.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
df4ee9b4 by Cheng Shao at 2025-08-20T11:54:25-04:00
compiler: use zero cost coerce in GHC.CmmToAsm.CFG.loopInfo
This patch refactors GHC.CmmToAsm.CFG.loopInfo to use zero cost coerce
and thus addresses the TODO. For coerce to work, constructors of
Label/LabelMap/LabelSet from GHC.Cmm.Dataflow.Label are exposed,
though I believe it's a worthy tradeoff to avoid unnecessary runtime
cost without using unsafeCoerce, since the latter could be a landmine
for future refactoring.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
ccda188d by Simon Peyton Jones at 2025-08-20T11:55:07-04:00
Start with empty inerts in shortcut solving
When short-cut solving we were starting with an inert set that had
unsolved Wanteds. This caused an infinite loop (#26314), because a
typechecker plugin kept being given that unsolved Wanted.
It's better just to start with an empty inert set
- - - - -
c8882ed7 by Ben Gamari at 2025-08-20T11:55:49-04:00
configure: Bump minimal bootstrap GHC version to 9.8
- - - - -
d2eb9e93 by Cheng Shao at 2025-08-20T18:16:33+02:00
compiler: fix closure C type in SPT init code
This patch fixes the closure C type in SPT init code to StgClosure,
instead of the previously incorrect StgPtr. Having an incorrect C type
makes SPT init code not compatible with other foreign stub generation
logic, which may also emit their own extern declarations for the same
closure symbols and thus will clash with the incorrect prototypes in
SPT init code.
- - - - -
164 changed files:
- .gitlab-ci.yml
- .gitlab/ci.sh
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .mailmap
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/Cmm/Dataflow/Label.hs
- compiler/GHC/CmmToAsm/CFG.hs
- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Driver/Config/Finder.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/HsToCore/Docs.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Iface/Tidy/StaticPtrTable.hs
- compiler/GHC/Parser/Header.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/StgToByteCode.hs
- compiler/GHC/StgToCmm/Prim.hs
- compiler/GHC/StgToJS/Prim.hs
- compiler/GHC/StgToJS/StaticPtr.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Tc/Solver/Dict.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Solver/Solve.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/Types/Name/Reader.hs
- compiler/GHC/Types/SptEntry.hs
- compiler/GHC/Unit/Finder.hs
- compiler/GHC/Unit/Finder/Types.hs
- configure.ac
- ghc/GHCi/UI.hs
- hadrian/bootstrap/generate_bootstrap_plans
- hadrian/bootstrap/hadrian-bootstrap-gen.cabal
- hadrian/bootstrap/plan-9_10_1.json
- hadrian/bootstrap/plan-9_6_5.json → hadrian/bootstrap/plan-9_10_2.json
- hadrian/bootstrap/plan-9_6_6.json → hadrian/bootstrap/plan-9_12_1.json
- hadrian/bootstrap/plan-9_6_4.json → hadrian/bootstrap/plan-9_12_2.json
- − hadrian/bootstrap/plan-9_6_1.json
- − hadrian/bootstrap/plan-9_6_2.json
- − hadrian/bootstrap/plan-9_6_3.json
- − hadrian/bootstrap/plan-9_8_1.json
- − hadrian/bootstrap/plan-9_8_2.json
- hadrian/bootstrap/plan-bootstrap-9_10_1.json
- hadrian/bootstrap/plan-bootstrap-9_6_5.json → hadrian/bootstrap/plan-bootstrap-9_10_2.json
- hadrian/bootstrap/plan-bootstrap-9_6_6.json → hadrian/bootstrap/plan-bootstrap-9_12_1.json
- hadrian/bootstrap/plan-bootstrap-9_8_1.json → hadrian/bootstrap/plan-bootstrap-9_12_2.json
- − hadrian/bootstrap/plan-bootstrap-9_6_1.json
- − hadrian/bootstrap/plan-bootstrap-9_6_2.json
- − hadrian/bootstrap/plan-bootstrap-9_6_3.json
- − hadrian/bootstrap/plan-bootstrap-9_6_4.json
- − hadrian/bootstrap/plan-bootstrap-9_8_2.json
- hadrian/bootstrap/src/Main.hs
- hadrian/hadrian.cabal
- libffi-tarballs
- libraries/ghc-experimental/ghc-experimental.cabal.in
- + libraries/ghc-experimental/src/GHC/Stack/Annotation/Experimental.hs
- libraries/ghc-heap/GHC/Exts/Heap/ClosureTypes.hs
- libraries/ghc-heap/GHC/Exts/Heap/Closures.hs
- libraries/ghc-heap/GHC/Exts/Stack.hs
- libraries/ghc-heap/GHC/Exts/Stack/Constants.hsc
- libraries/ghc-heap/GHC/Exts/Stack/Decode.hs
- + libraries/ghc-heap/tests/stack-annotation/Makefile
- + libraries/ghc-heap/tests/stack-annotation/TestUtils.hs
- + libraries/ghc-heap/tests/stack-annotation/all.T
- + libraries/ghc-heap/tests/stack-annotation/ann_frame001.hs
- + libraries/ghc-heap/tests/stack-annotation/ann_frame001.stdout
- + libraries/ghc-heap/tests/stack-annotation/ann_frame002.hs
- + libraries/ghc-heap/tests/stack-annotation/ann_frame002.stdout
- + libraries/ghc-heap/tests/stack-annotation/ann_frame003.hs
- + libraries/ghc-heap/tests/stack-annotation/ann_frame003.stdout
- + libraries/ghc-heap/tests/stack-annotation/ann_frame004.hs
- + libraries/ghc-heap/tests/stack-annotation/ann_frame004.stdout
- libraries/ghc-internal/src/GHC/Internal/ClosureTypes.hs
- m4/find_python.m4
- rts/ClosureFlags.c
- rts/Hash.c
- rts/LdvProfile.c
- rts/PrimOps.cmm
- rts/Printer.c
- rts/RetainerProfile.c
- rts/RtsSymbols.c
- rts/TraverseHeap.c
- rts/include/rts/storage/ClosureTypes.h
- rts/include/rts/storage/Closures.h
- rts/include/stg/MiscClosures.h
- rts/js/profiling.js
- rts/sm/Compact.c
- rts/sm/Evac.c
- rts/sm/NonMovingMark.c
- rts/sm/Sanity.c
- rts/sm/Scav.c
- testsuite/tests/gadt/T12468.stderr
- testsuite/tests/ghc-e/should_fail/T24172.stderr
- testsuite/tests/ghci/scripts/T8353.stderr
- testsuite/tests/ghci/scripts/ghci038.stdout
- testsuite/tests/interface-stability/base-exports.stdout
- testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
- testsuite/tests/interface-stability/base-exports.stdout-mingw32
- testsuite/tests/interface-stability/base-exports.stdout-ws-32
- testsuite/tests/interface-stability/ghc-experimental-exports.stdout
- testsuite/tests/interface-stability/ghc-experimental-exports.stdout-mingw32
- testsuite/tests/interface-stability/ghc-prim-exports.stdout
- testsuite/tests/interface-stability/ghc-prim-exports.stdout-mingw32
- testsuite/tests/module/mod150.stderr
- testsuite/tests/module/mod151.stderr
- testsuite/tests/module/mod152.stderr
- testsuite/tests/module/mod153.stderr
- testsuite/tests/overloadedrecflds/should_fail/T18999_NoDisambiguateRecordFields.stderr
- testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
- testsuite/tests/parser/should_compile/T14189.stderr
- testsuite/tests/parser/should_compile/T19082.stderr
- testsuite/tests/perf/compiler/hard_hole_fits.stderr
- testsuite/tests/plugins/Makefile
- + testsuite/tests/plugins/T21730-plugin/Makefile
- + testsuite/tests/plugins/T21730-plugin/Setup.hs
- + testsuite/tests/plugins/T21730-plugin/T21730-plugin.cabal
- + testsuite/tests/plugins/T21730-plugin/T21730_Plugin.hs
- + testsuite/tests/plugins/T21730.hs
- testsuite/tests/plugins/all.T
- testsuite/tests/quotes/LiftErrMsg.stderr
- testsuite/tests/quotes/LiftErrMsgDefer.stderr
- testsuite/tests/quotes/LiftErrMsgTyped.stderr
- testsuite/tests/rename/should_compile/T22513d.stderr
- testsuite/tests/rename/should_compile/T22513e.stderr
- testsuite/tests/rename/should_compile/T22513f.stderr
- testsuite/tests/rename/should_compile/T22513g.stderr
- testsuite/tests/rename/should_compile/T22513h.stderr
- testsuite/tests/rename/should_compile/T22513i.stderr
- testsuite/tests/rename/should_compile/rn039.ghc.stderr
- testsuite/tests/rename/should_fail/T15487.stderr
- testsuite/tests/rename/should_fail/T18740a.stderr
- testsuite/tests/rename/should_fail/rnfail044.stderr
- testsuite/tests/rts/flags/all.T
- testsuite/tests/safeHaskell/flags/SafeFlags17.stderr
- + testsuite/tests/simplCore/should_compile/T24606.hs
- testsuite/tests/simplCore/should_compile/all.T
- testsuite/tests/th/T10267.stderr
- testsuite/tests/th/T14627.stderr
- testsuite/tests/th/T15321.stderr
- testsuite/tests/typecheck/should_compile/T13050.stderr
- testsuite/tests/typecheck/should_compile/T14273.stderr
- testsuite/tests/typecheck/should_compile/T14590.stderr
- testsuite/tests/typecheck/should_compile/T25180.stderr
- + testsuite/tests/typecheck/should_compile/T25992a.hs
- testsuite/tests/typecheck/should_compile/T9497a.stderr
- testsuite/tests/typecheck/should_compile/all.T
- testsuite/tests/typecheck/should_compile/refinement_hole_fits.stderr
- testsuite/tests/typecheck/should_compile/subsumption_sort_hole_fits.stderr
- testsuite/tests/typecheck/should_fail/T14884.stderr
- testsuite/tests/typecheck/should_fail/T21130.stderr
- testsuite/tests/typecheck/should_fail/T23739b.stderr
- testsuite/tests/typecheck/should_fail/T23739c.stderr
- testsuite/tests/typecheck/should_fail/T9497d.stderr
- testsuite/tests/typecheck/should_fail/tcfail037.stderr
- testsuite/tests/typecheck/should_run/T9497a-run.stderr
- testsuite/tests/typecheck/should_run/T9497b-run.stderr
- testsuite/tests/typecheck/should_run/T9497c-run.stderr
- testsuite/tests/vdq-rta/should_fail/T23738_fail_pun.stderr
- utils/deriveConstants/Main.hs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4ded6c63b366737da2c9d94ed6931f…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4ded6c63b366737da2c9d94ed6931f…
You're receiving this email because of your account on gitlab.haskell.org.
1
0