18 Sep '25
Rodrigo Mesquita pushed new branch wip/romes/24985 at Glasgow Haskell Compiler / GHC
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/romes/24985
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 4 commits: compiler/ghci: replace the LoadDLL message with LoadDLLs
by Marge Bot (@marge-bot) 18 Sep '25
by Marge Bot (@marge-bot) 18 Sep '25
18 Sep '25
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
ca6864df by Cheng Shao at 2025-09-18T13:41:57+02:00
compiler/ghci: replace the LoadDLL message with LoadDLLs
As a part of #25407, this commit changes the LoadDLL message to
LoadDLLs, which takes a list of DLL paths to load and returns the list
of remote pointer handles. The wasm dyld is refactored to take
advantage of LoadDLLs and harvest background parallelism. On other
platforms, LoadDLLs is based on a fallback codepath that does
sequential loading.
The driver is not actually emitting singular LoadDLLs message with
multiple DLLs yet, this is left in subsequent commits.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
193509d0 by Cheng Shao at 2025-09-18T13:41:57+02:00
driver: separate downsweep/upsweep phase in loadPackages'
This commit refactors GHC.Linker.Loader.loadPackages' to be separated
into downsweep/upsweep phases:
- The downsweep phase performs dependency analysis and generates a
list of topologically sorted packages to load
- The upsweep phase sequentially loads these packages by calling
loadPackage
This is a necessary refactoring to make it possible to make loading of
DLLs concurrent.
- - - - -
9fa89818 by Cheng Shao at 2025-09-18T13:46:10+02:00
driver: emit single LoadDLLs message to load multiple DLLs
This commit refactors the driver so that it emits a single LoadDLLs
message to load multiple DLLs in GHC.Linker.Loader.loadPackages'.
Closes #25407.
-------------------------
Metric Increase:
MultiLayerModulesTH_OneShot
TcPlugin_RewritePerf
-------------------------
- - - - -
59c36504 by sheaf at 2025-09-18T12:32:30-04:00
Enable TcM plugins in initTc
This commit ensures that we run typechecker plugins and defaulting
plugins whenever we call initTc.
In particular, this ensures that the pattern-match checker, which calls
'initTcDsForSolver' which calls 'initTc', runs with typechecker plugins
enabled. This matters for situations like:
merge :: Vec n a -> Vec n a -> Vec (2 * n) a
merge Nil Nil = Nil
merge (a <: as) (b <: bs) = a :< (b <: merge as bs)
in which we need the typechecker plugin to run in order to tell us that
the Givens would be inconsistent in the additional equation
merge (_ <: _) Nil
and thus that the equation is not needed.
Fixes #26395
- - - - -
17 changed files:
- compiler/GHC/Driver/Plugins.hs
- compiler/GHC/HsToCore/Monad.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Linker/MacOS.hs
- compiler/GHC/Linker/Types.hs
- compiler/GHC/Runtime/Interpreter.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Tc/Utils/Monad.hs
- libraries/ghci/GHCi/Message.hs
- libraries/ghci/GHCi/ObjLink.hs
- libraries/ghci/GHCi/Run.hs
- testsuite/tests/rts/linker/T2615.hs
- + testsuite/tests/tcplugins/T26395.hs
- + testsuite/tests/tcplugins/T26395.stderr
- + testsuite/tests/tcplugins/T26395_Plugin.hs
- testsuite/tests/tcplugins/all.T
- 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/HsToCore/Monad.hs
=====================================
@@ -58,6 +58,7 @@ module GHC.HsToCore.Monad (
import GHC.Prelude
import GHC.Driver.Env
+import GHC.Driver.Env.KnotVars
import GHC.Driver.DynFlags
import GHC.Driver.Ppr
import GHC.Driver.Config.Diagnostic
@@ -117,7 +118,7 @@ import GHC.Utils.Panic
import qualified GHC.Data.Strict as Strict
import Data.IORef
-import GHC.Driver.Env.KnotVars
+
import GHC.IO.Unsafe (unsafeInterleaveIO)
{-
=====================================
compiler/GHC/Linker/Loader.hs
=====================================
@@ -1,6 +1,7 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE ViewPatterns #-}
--
-- (c) The University of Glasgow 2002-2006
@@ -535,7 +536,7 @@ preloadLib interp hsc_env lib_paths framework_paths pls lib_spec = do
return pls
DLL dll_unadorned -> do
- maybe_errstr <- loadDLL interp (platformSOName platform dll_unadorned)
+ maybe_errstr <- loadDLLs interp [platformSOName platform dll_unadorned]
case maybe_errstr of
Right _ -> maybePutStrLn logger "done"
Left mm | platformOS platform /= OSDarwin ->
@@ -545,14 +546,14 @@ preloadLib interp hsc_env lib_paths framework_paths pls lib_spec = do
-- since (apparently) some things install that way - see
-- ticket #8770.
let libfile = ("lib" ++ dll_unadorned) <.> "so"
- err2 <- loadDLL interp libfile
+ err2 <- loadDLLs interp [libfile]
case err2 of
Right _ -> maybePutStrLn logger "done"
Left _ -> preloadFailed mm lib_paths lib_spec
return pls
DLLPath dll_path -> do
- do maybe_errstr <- loadDLL interp dll_path
+ do maybe_errstr <- loadDLLs interp [dll_path]
case maybe_errstr of
Right _ -> maybePutStrLn logger "done"
Left mm -> preloadFailed mm lib_paths lib_spec
@@ -892,7 +893,7 @@ dynLoadObjs interp hsc_env pls@LoaderState{..} objs = do
-- if we got this far, extend the lifetime of the library file
changeTempFilesLifetime tmpfs TFL_GhcSession [soFile]
- m <- loadDLL interp soFile
+ m <- loadDLLs interp [soFile]
case m of
Right _ -> return $! pls { temp_sos = (libPath, libName) : temp_sos }
Left err -> linkFail msg (text err)
@@ -1129,51 +1130,91 @@ loadPackages interp hsc_env new_pkgs = do
loadPackages' :: Interp -> HscEnv -> [UnitId] -> LoaderState -> IO LoaderState
loadPackages' interp hsc_env new_pks pls = do
- pkgs' <- link (pkgs_loaded pls) new_pks
- return $! pls { pkgs_loaded = pkgs'
- }
+ (reverse -> pkgs_info_list, pkgs_almost_loaded) <-
+ downsweep
+ ([], pkgs_loaded pls)
+ new_pks
+ loaded_pkgs_info_list <- loadPackage interp hsc_env pkgs_info_list
+ evaluate $
+ pls
+ { pkgs_loaded =
+ foldl'
+ ( \pkgs (new_pkg_info, (hs_cls, extra_cls, loaded_dlls)) ->
+ adjustUDFM
+ ( \old_pkg_info ->
+ old_pkg_info
+ { loaded_pkg_hs_objs = hs_cls,
+ loaded_pkg_non_hs_objs = extra_cls,
+ loaded_pkg_hs_dlls = loaded_dlls
+ }
+ )
+ pkgs
+ (Packages.unitId new_pkg_info)
+ )
+ pkgs_almost_loaded
+ (zip pkgs_info_list loaded_pkgs_info_list)
+ }
where
- link :: PkgsLoaded -> [UnitId] -> IO PkgsLoaded
- link pkgs new_pkgs =
- foldM link_one pkgs new_pkgs
-
- link_one pkgs new_pkg
- | new_pkg `elemUDFM` pkgs -- Already linked
- = return pkgs
-
- | Just pkg_cfg <- lookupUnitId (hsc_units hsc_env) new_pkg
- = do { let deps = unitDepends pkg_cfg
- -- Link dependents first
- ; pkgs' <- link pkgs deps
- -- Now link the package itself
- ; (hs_cls, extra_cls, loaded_dlls) <- loadPackage interp hsc_env pkg_cfg
- ; let trans_deps = unionManyUniqDSets [ addOneToUniqDSet (loaded_pkg_trans_deps loaded_pkg_info) dep_pkg
- | dep_pkg <- deps
- , Just loaded_pkg_info <- pure (lookupUDFM pkgs' dep_pkg)
- ]
- ; return (addToUDFM pkgs' new_pkg (LoadedPkgInfo new_pkg hs_cls extra_cls loaded_dlls trans_deps)) }
-
- | otherwise
- = throwGhcExceptionIO (CmdLineError ("unknown package: " ++ unpackFS (unitIdFS new_pkg)))
-
-
-loadPackage :: Interp -> HscEnv -> UnitInfo -> IO ([LibrarySpec], [LibrarySpec], [RemotePtr LoadedDLL])
-loadPackage interp hsc_env pkg
+ -- The downsweep process takes an initial 'PkgsLoaded' and uses it
+ -- to memoize new packages to load when recursively downsweeping
+ -- the dependencies. The returned 'PkgsLoaded' is popularized with
+ -- placeholder 'LoadedPkgInfo' for new packages yet to be loaded,
+ -- which need to be modified later to fill in the missing fields.
+ --
+ -- The [UnitInfo] list is an accumulated *reverse* topologically
+ -- sorted list of new packages to load: 'downsweep_one' appends a
+ -- package to its head after that package's transitive
+ -- dependencies go into that list. There are no duplicate items in
+ -- this list due to memoization.
+ downsweep ::
+ ([UnitInfo], PkgsLoaded) -> [UnitId] -> IO ([UnitInfo], PkgsLoaded)
+ downsweep = foldlM downsweep_one
+
+ downsweep_one ::
+ ([UnitInfo], PkgsLoaded) -> UnitId -> IO ([UnitInfo], PkgsLoaded)
+ downsweep_one (pkgs_info_list, pkgs) new_pkg
+ | new_pkg `elemUDFM` pkgs = pure (pkgs_info_list, pkgs)
+ | Just new_pkg_info <- lookupUnitId (hsc_units hsc_env) new_pkg = do
+ let new_pkg_deps = unitDepends new_pkg_info
+ (pkgs_info_list', pkgs') <- downsweep (pkgs_info_list, pkgs) new_pkg_deps
+ let new_pkg_trans_deps =
+ unionManyUniqDSets
+ [ addOneToUniqDSet (loaded_pkg_trans_deps loaded_pkg_info) dep_pkg
+ | dep_pkg <- new_pkg_deps,
+ loaded_pkg_info <- maybeToList $ pkgs' `lookupUDFM` dep_pkg
+ ]
+ pure
+ ( new_pkg_info : pkgs_info_list',
+ addToUDFM pkgs' new_pkg $
+ LoadedPkgInfo
+ { loaded_pkg_uid = new_pkg,
+ loaded_pkg_hs_objs = [],
+ loaded_pkg_non_hs_objs = [],
+ loaded_pkg_hs_dlls = [],
+ loaded_pkg_trans_deps = new_pkg_trans_deps
+ }
+ )
+ | otherwise =
+ throwGhcExceptionIO
+ (CmdLineError ("unknown package: " ++ unpackFS (unitIdFS new_pkg)))
+
+loadPackage :: Interp -> HscEnv -> [UnitInfo] -> IO [([LibrarySpec], [LibrarySpec], [RemotePtr LoadedDLL])]
+loadPackage interp hsc_env pkgs
= do
let dflags = hsc_dflags hsc_env
let logger = hsc_logger hsc_env
platform = targetPlatform dflags
is_dyn = interpreterDynamic interp
- dirs | is_dyn = map ST.unpack $ Packages.unitLibraryDynDirs pkg
- | otherwise = map ST.unpack $ Packages.unitLibraryDirs pkg
+ dirs | is_dyn = [map ST.unpack $ Packages.unitLibraryDynDirs pkg | pkg <- pkgs]
+ | otherwise = [map ST.unpack $ Packages.unitLibraryDirs pkg | pkg <- pkgs]
- let hs_libs = map ST.unpack $ Packages.unitLibraries pkg
+ let hs_libs = [map ST.unpack $ Packages.unitLibraries pkg | pkg <- pkgs]
-- The FFI GHCi import lib isn't needed as
-- GHC.Linker.Loader + rts/Linker.c link the
-- interpreted references to FFI to the compiled FFI.
-- We therefore filter it out so that we don't get
-- duplicate symbol errors.
- hs_libs' = filter ("HSffi" /=) hs_libs
+ hs_libs' = filter ("HSffi" /=) <$> hs_libs
-- Because of slight differences between the GHC dynamic linker and
-- the native system linker some packages have to link with a
@@ -1182,51 +1223,60 @@ loadPackage interp hsc_env pkg
-- libs do not exactly match the .so/.dll equivalents. So if the
-- package file provides an "extra-ghci-libraries" field then we use
-- that instead of the "extra-libraries" field.
- extdeplibs = map ST.unpack (if null (Packages.unitExtDepLibsGhc pkg)
+ extdeplibs = [map ST.unpack (if null (Packages.unitExtDepLibsGhc pkg)
then Packages.unitExtDepLibsSys pkg
- else Packages.unitExtDepLibsGhc pkg)
- linkerlibs = [ lib | '-':'l':lib <- (map ST.unpack $ Packages.unitLinkerOptions pkg) ]
- extra_libs = extdeplibs ++ linkerlibs
+ else Packages.unitExtDepLibsGhc pkg) | pkg <- pkgs]
+ linkerlibs = [[ lib | '-':'l':lib <- (map ST.unpack $ Packages.unitLinkerOptions pkg) ] | pkg <- pkgs]
+ extra_libs = zipWith (++) extdeplibs linkerlibs
-- See Note [Fork/Exec Windows]
gcc_paths <- getGCCPaths logger dflags (platformOS platform)
- dirs_env <- addEnvPaths "LIBRARY_PATH" dirs
+ dirs_env <- traverse (addEnvPaths "LIBRARY_PATH") dirs
hs_classifieds
- <- mapM (locateLib interp hsc_env True dirs_env gcc_paths) hs_libs'
+ <- sequenceA [mapM (locateLib interp hsc_env True dirs_env_ gcc_paths) hs_libs'_ | (dirs_env_, hs_libs'_) <- zip dirs_env hs_libs' ]
extra_classifieds
- <- mapM (locateLib interp hsc_env False dirs_env gcc_paths) extra_libs
- let classifieds = hs_classifieds ++ extra_classifieds
+ <- sequenceA [mapM (locateLib interp hsc_env False dirs_env_ gcc_paths) extra_libs_ | (dirs_env_, extra_libs_) <- zip dirs_env extra_libs]
+ let classifieds = zipWith (++) hs_classifieds extra_classifieds
-- Complication: all the .so's must be loaded before any of the .o's.
- let known_hs_dlls = [ dll | DLLPath dll <- hs_classifieds ]
- known_extra_dlls = [ dll | DLLPath dll <- extra_classifieds ]
- known_dlls = known_hs_dlls ++ known_extra_dlls
+ let known_hs_dlls = [[ dll | DLLPath dll <- hs_classifieds_ ] | hs_classifieds_ <- hs_classifieds]
+ known_extra_dlls = [ dll | extra_classifieds_ <- extra_classifieds, DLLPath dll <- extra_classifieds_ ]
+ known_dlls = concat known_hs_dlls ++ known_extra_dlls
#if defined(CAN_LOAD_DLL)
- dlls = [ dll | DLL dll <- classifieds ]
+ dlls = [ dll | classifieds_ <- classifieds, DLL dll <- classifieds_ ]
#endif
- objs = [ obj | Objects objs <- classifieds
- , obj <- objs ]
- archs = [ arch | Archive arch <- classifieds ]
+ objs = [ obj | classifieds_ <- classifieds, Objects objs <- classifieds_
+ , obj <- objs]
+ archs = [ arch | classifieds_ <- classifieds, Archive arch <- classifieds_ ]
-- Add directories to library search paths
let dll_paths = map takeDirectory known_dlls
- all_paths = nub $ map normalise $ dll_paths ++ dirs
+ all_paths = nub $ map normalise $ dll_paths ++ concat dirs
all_paths_env <- addEnvPaths "LD_LIBRARY_PATH" all_paths
pathCache <- mapM (addLibrarySearchPath interp) all_paths_env
maybePutSDoc logger
- (text "Loading unit " <> pprUnitInfoForUser pkg <> text " ... ")
+ (text "Loading units " <> vcat (map pprUnitInfoForUser pkgs) <> text " ... ")
#if defined(CAN_LOAD_DLL)
- loadFrameworks interp platform pkg
+ forM_ pkgs $ loadFrameworks interp platform
-- See Note [Crash early load_dyn and locateLib]
-- Crash early if can't load any of `known_dlls`
- mapM_ (load_dyn interp hsc_env True) known_extra_dlls
- loaded_dlls <- mapMaybeM (load_dyn interp hsc_env True) known_hs_dlls
+ _ <- load_dyn interp hsc_env True known_extra_dlls
+
+ -- We pass [[FilePath]] of dlls to load and flattens the list
+ -- before doing a LoadDLLs. The returned list of RemotePtrs
+ -- would need to be regrouped to the same shape of the input
+ -- [[FilePath]], each group's [RemotePtr LoadedDLL]
+ -- corresponds to the DLL handles of a Haskell unit.
+ let regroup :: [[a]] -> [b] -> [[b]]
+ regroup [] _ = []
+ regroup (l:ls) xs = xs0: regroup ls xs1 where (xs0, xs1) = splitAt (length l) xs
+ loaded_dlls <- regroup known_hs_dlls <$> load_dyn interp hsc_env True (concat known_hs_dlls)
-- For remaining `dlls` crash early only when there is surely
-- no package's DLL around ... (not is_dyn)
- mapM_ (load_dyn interp hsc_env (not is_dyn) . platformSOName platform) dlls
+ _ <- load_dyn interp hsc_env (not is_dyn) $ map (platformSOName platform) dlls
#else
let loaded_dlls = []
#endif
@@ -1248,9 +1298,9 @@ loadPackage interp hsc_env pkg
if succeeded ok
then do
maybePutStrLn logger "done."
- return (hs_classifieds, extra_classifieds, loaded_dlls)
- else let errmsg = text "unable to load unit `"
- <> pprUnitInfoForUser pkg <> text "'"
+ pure $ zip3 hs_classifieds extra_classifieds loaded_dlls
+ else let errmsg = text "unable to load units `"
+ <> vcat (map pprUnitInfoForUser pkgs) <> text "'"
in throwGhcExceptionIO (InstallationError (showSDoc dflags errmsg))
{-
@@ -1300,12 +1350,12 @@ restriction very easily.
-- we have already searched the filesystem; the strings passed to load_dyn
-- can be passed directly to loadDLL. They are either fully-qualified
-- ("/usr/lib/libfoo.so"), or unqualified ("libfoo.so"). In the latter case,
--- loadDLL is going to search the system paths to find the library.
-load_dyn :: Interp -> HscEnv -> Bool -> FilePath -> IO (Maybe (RemotePtr LoadedDLL))
-load_dyn interp hsc_env crash_early dll = do
- r <- loadDLL interp dll
+-- loadDLLs is going to search the system paths to find the library.
+load_dyn :: Interp -> HscEnv -> Bool -> [FilePath] -> IO [RemotePtr LoadedDLL]
+load_dyn interp hsc_env crash_early dlls = do
+ r <- loadDLLs interp dlls
case r of
- Right loaded_dll -> pure (Just loaded_dll)
+ Right loaded_dlls -> pure loaded_dlls
Left err ->
if crash_early
then cmdLineErrorIO err
@@ -1314,7 +1364,7 @@ load_dyn interp hsc_env crash_early dll = do
$ reportDiagnostic logger
neverQualify diag_opts
noSrcSpan (WarningWithFlag Opt_WarnMissedExtraSharedLib) $ withPprStyle defaultUserStyle (note err)
- pure Nothing
+ pure []
where
diag_opts = initDiagOpts (hsc_dflags hsc_env)
logger = hsc_logger hsc_env
@@ -1370,7 +1420,7 @@ locateLib interp hsc_env is_hs lib_dirs gcc_dirs lib0
-- then look in library-dirs and inplace GCC for a static library (libfoo.a)
-- then try "gcc --print-file-name" to search gcc's search path
-- for a dynamic library (#5289)
- -- otherwise, assume loadDLL can find it
+ -- otherwise, assume loadDLLs can find it
--
-- The logic is a bit complicated, but the rationale behind it is that
-- loading a shared library for us is O(1) while loading an archive is
=====================================
compiler/GHC/Linker/MacOS.hs
=====================================
@@ -162,7 +162,7 @@ loadFramework interp extraPaths rootname
-- sorry for the hardcoded paths, I hope they won't change anytime soon:
defaultFrameworkPaths = ["/Library/Frameworks", "/System/Library/Frameworks"]
- -- Try to call loadDLL for each candidate path.
+ -- Try to call loadDLLs for each candidate path.
--
-- See Note [macOS Big Sur dynamic libraries]
findLoadDLL [] errs =
@@ -170,7 +170,7 @@ loadFramework interp extraPaths rootname
-- has no built-in paths for frameworks: give up
return $ Just errs
findLoadDLL (p:ps) errs =
- do { dll <- loadDLL interp (p </> fwk_file)
+ do { dll <- loadDLLs interp [p </> fwk_file]
; case dll of
Right _ -> return Nothing
Left err -> findLoadDLL ps ((p ++ ": " ++ err):errs)
=====================================
compiler/GHC/Linker/Types.hs
=====================================
@@ -494,7 +494,7 @@ data LibrarySpec
| DLL String -- "Unadorned" name of a .DLL/.so
-- e.g. On unix "qt" denotes "libqt.so"
-- On Windows "burble" denotes "burble.DLL" or "libburble.dll"
- -- loadDLL is platform-specific and adds the lib/.so/.DLL
+ -- loadDLLs is platform-specific and adds the lib/.so/.DLL
-- suffixes platform-dependently
| DLLPath FilePath -- Absolute or relative pathname to a dynamic library
=====================================
compiler/GHC/Runtime/Interpreter.hs
=====================================
@@ -38,7 +38,7 @@ module GHC.Runtime.Interpreter
, lookupSymbol
, lookupSymbolInDLL
, lookupClosure
- , loadDLL
+ , loadDLLs
, loadArchive
, loadObj
, unloadObj
@@ -559,13 +559,13 @@ withSymbolCache interp str determine_addr = do
purgeLookupSymbolCache :: Interp -> IO ()
purgeLookupSymbolCache interp = purgeInterpSymbolCache (interpSymbolCache interp)
--- | loadDLL loads a dynamic library using the OS's native linker
+-- | 'loadDLLs' loads dynamic libraries using the OS's native linker
-- (i.e. dlopen() on Unix, LoadLibrary() on Windows). It takes either
--- an absolute pathname to the file, or a relative filename
--- (e.g. "libfoo.so" or "foo.dll"). In the latter case, loadDLL
--- searches the standard locations for the appropriate library.
-loadDLL :: Interp -> String -> IO (Either String (RemotePtr LoadedDLL))
-loadDLL interp str = interpCmd interp (LoadDLL str)
+-- absolute pathnames to the files, or relative filenames
+-- (e.g. "libfoo.so" or "foo.dll"). In the latter case, 'loadDLLs'
+-- searches the standard locations for the appropriate libraries.
+loadDLLs :: Interp -> [String] -> IO (Either String [RemotePtr LoadedDLL])
+loadDLLs interp strs = interpCmd interp (LoadDLLs strs)
loadArchive :: Interp -> String -> IO ()
loadArchive interp path = do
@@ -761,4 +761,3 @@ readIModModBreaks hug mod = imodBreaks_modBreaks . expectJust <$> readIModBreaks
fromEvalResult :: EvalResult a -> IO a
fromEvalResult (EvalException e) = throwIO (fromSerializableException e)
fromEvalResult (EvalSuccess a) = return a
-
=====================================
compiler/GHC/Tc/Module.hs
=====================================
@@ -26,6 +26,7 @@ module GHC.Tc.Module (
runTcInteractive, -- Used by GHC API clients (#8878)
withTcPlugins, -- Used by GHC API clients (#20499)
withHoleFitPlugins, -- Used by GHC API clients (#20499)
+ withDefaultingPlugins,
tcRnLookupName,
tcRnGetInfo,
tcRnModule, tcRnModuleTcRnM,
@@ -53,7 +54,6 @@ import GHC.Driver.DynFlags
import GHC.Driver.Config.Diagnostic
import GHC.IO.Unsafe ( unsafeInterleaveIO )
-import GHC.Tc.Errors.Hole.Plugin ( HoleFitPluginR (..) )
import GHC.Tc.Errors.Types
import {-# SOURCE #-} GHC.Tc.Gen.Splice ( finishTH, runRemoteModFinalizers )
import GHC.Tc.Gen.HsType
@@ -141,7 +141,6 @@ import GHC.Types.Id as Id
import GHC.Types.Id.Info( IdDetails(..) )
import GHC.Types.Var.Env
import GHC.Types.TypeEnv
-import GHC.Types.Unique.FM
import GHC.Types.Name
import GHC.Types.Name.Env
import GHC.Types.Name.Set
@@ -212,10 +211,6 @@ tcRnModule hsc_env mod_sum save_rn_syntax
(text "Renamer/typechecker"<+>brackets (ppr this_mod))
(const ()) $
initTc hsc_env hsc_src save_rn_syntax this_mod real_loc $
- withTcPlugins hsc_env $
- withDefaultingPlugins hsc_env $
- withHoleFitPlugins hsc_env $
-
tcRnModuleTcRnM hsc_env mod_sum parsedModule this_mod
| otherwise
@@ -3182,72 +3177,11 @@ hasTopUserName x
{-
********************************************************************************
-Type Checker Plugins
+ Running plugins
********************************************************************************
-}
-withTcPlugins :: HscEnv -> TcM a -> TcM a
-withTcPlugins hsc_env m =
- case catMaybes $ mapPlugins (hsc_plugins hsc_env) tcPlugin of
- [] -> m -- Common fast case
- plugins -> do
- (solvers, rewriters, stops) <-
- unzip3 `fmap` mapM start_plugin plugins
- let
- rewritersUniqFM :: UniqFM TyCon [TcPluginRewriter]
- !rewritersUniqFM = sequenceUFMList rewriters
- -- The following ensures that tcPluginStop is called even if a type
- -- error occurs during compilation (Fix of #10078)
- eitherRes <- tryM $
- updGblEnv (\e -> e { tcg_tc_plugin_solvers = solvers
- , tcg_tc_plugin_rewriters = rewritersUniqFM }) m
- mapM_ runTcPluginM stops
- case eitherRes of
- Left _ -> failM
- Right res -> return res
- where
- start_plugin (TcPlugin start solve rewrite stop) =
- do s <- runTcPluginM start
- return (solve s, rewrite s, stop s)
-
-withDefaultingPlugins :: HscEnv -> TcM a -> TcM a
-withDefaultingPlugins hsc_env m =
- do case catMaybes $ mapPlugins (hsc_plugins hsc_env) defaultingPlugin of
- [] -> m -- Common fast case
- plugins -> do (plugins,stops) <- mapAndUnzipM start_plugin plugins
- -- This ensures that dePluginStop is called even if a type
- -- error occurs during compilation
- eitherRes <- tryM $ do
- updGblEnv (\e -> e { tcg_defaulting_plugins = plugins }) m
- mapM_ runTcPluginM stops
- case eitherRes of
- Left _ -> failM
- Right res -> return res
- where
- start_plugin (DefaultingPlugin start fill stop) =
- do s <- runTcPluginM start
- return (fill s, stop s)
-
-withHoleFitPlugins :: HscEnv -> TcM a -> TcM a
-withHoleFitPlugins hsc_env m =
- case catMaybes $ mapPlugins (hsc_plugins hsc_env) holeFitPlugin of
- [] -> m -- Common fast case
- plugins -> do (plugins,stops) <- mapAndUnzipM start_plugin plugins
- -- This ensures that hfPluginStop is called even if a type
- -- error occurs during compilation.
- eitherRes <- tryM $
- updGblEnv (\e -> e { tcg_hf_plugins = plugins }) m
- sequence_ stops
- case eitherRes of
- Left _ -> failM
- Right res -> return res
- where
- start_plugin (HoleFitPluginR init plugin stop) =
- do ref <- init
- return (plugin ref, stop ref)
-
-
runRenamerPlugin :: TcGblEnv
-> HsGroup GhcRn
-> TcM (TcGblEnv, HsGroup GhcRn)
=====================================
compiler/GHC/Tc/Utils/Monad.hs
=====================================
@@ -31,6 +31,9 @@ module GHC.Tc.Utils.Monad(
updateEps, updateEps_,
getHpt, getEpsAndHug,
+ -- * Initialising TcM plugins
+ withTcPlugins, withDefaultingPlugins, withHoleFitPlugins,
+
-- * Arrow scopes
newArrowScope, escapeArrowScope,
@@ -163,6 +166,7 @@ import GHC.Builtin.Names
import GHC.Builtin.Types( zonkAnyTyCon )
import GHC.Tc.Errors.Types
+import GHC.Tc.Errors.Hole.Plugin ( HoleFitPluginR (..) )
import GHC.Tc.Types -- Re-export all
import GHC.Tc.Types.Constraint
import GHC.Tc.Types.CtLoc
@@ -183,13 +187,17 @@ import GHC.Unit.Module.Warnings
import GHC.Unit.Home.PackageTable
import GHC.Core.UsageEnv
+
+import GHC.Core.Coercion ( isReflCo )
import GHC.Core.Multiplicity
import GHC.Core.InstEnv
import GHC.Core.FamInstEnv
import GHC.Core.Type( mkNumLitTy )
+import GHC.Core.TyCon ( TyCon )
import GHC.Driver.Env
import GHC.Driver.Env.KnotVars
+import GHC.Driver.Plugins ( Plugin(..), mapPlugins )
import GHC.Driver.Session
import GHC.Driver.Config.Diagnostic
@@ -226,7 +234,7 @@ import GHC.Types.SrcLoc
import GHC.Types.Name.Env
import GHC.Types.Name.Set
import GHC.Types.Name.Ppr
-import GHC.Types.Unique.FM ( emptyUFM )
+import GHC.Types.Unique.FM ( UniqFM, emptyUFM, sequenceUFMList )
import GHC.Types.Unique.DFM
import GHC.Types.Unique.Supply
import GHC.Types.Annotations
@@ -240,8 +248,6 @@ import Data.IORef
import Control.Monad
import qualified Data.Map as Map
-import GHC.Core.Coercion (isReflCo)
-
{-
************************************************************************
@@ -263,129 +269,139 @@ initTc :: HscEnv
-- (error messages should have been printed already)
initTc hsc_env hsc_src keep_rn_syntax mod loc do_this
- = do { keep_var <- newIORef emptyNameSet ;
- used_gre_var <- newIORef [] ;
- th_var <- newIORef False ;
- infer_var <- newIORef True ;
- infer_reasons_var <- newIORef emptyMessages ;
- dfun_n_var <- newIORef emptyOccSet ;
- zany_n_var <- newIORef 0 ;
- let { type_env_var = hsc_type_env_vars hsc_env };
-
- dependent_files_var <- newIORef [] ;
- dependent_dirs_var <- newIORef [] ;
- static_wc_var <- newIORef emptyWC ;
- cc_st_var <- newIORef newCostCentreState ;
- th_topdecls_var <- newIORef [] ;
- th_foreign_files_var <- newIORef [] ;
- th_topnames_var <- newIORef emptyNameSet ;
- th_modfinalizers_var <- newIORef [] ;
- th_coreplugins_var <- newIORef [] ;
- th_state_var <- newIORef Map.empty ;
- th_remote_state_var <- newIORef Nothing ;
- th_docs_var <- newIORef Map.empty ;
- th_needed_deps_var <- newIORef ([], emptyUDFM) ;
- next_wrapper_num <- newIORef emptyModuleEnv ;
- let {
- -- bangs to avoid leaking the env (#19356)
- !dflags = hsc_dflags hsc_env ;
- !mhome_unit = hsc_home_unit_maybe hsc_env;
- !logger = hsc_logger hsc_env ;
-
- maybe_rn_syntax :: forall a. a -> Maybe a ;
- maybe_rn_syntax empty_val
- | logHasDumpFlag logger Opt_D_dump_rn_ast = Just empty_val
-
- | gopt Opt_WriteHie dflags = Just empty_val
-
- -- We want to serialize the documentation in the .hi-files,
- -- and need to extract it from the renamed syntax first.
- -- See 'GHC.HsToCore.Docs.extractDocs'.
- | gopt Opt_Haddock dflags = Just empty_val
-
- | keep_rn_syntax = Just empty_val
- | otherwise = Nothing ;
-
- gbl_env = TcGblEnv {
- tcg_th_topdecls = th_topdecls_var,
- tcg_th_foreign_files = th_foreign_files_var,
- tcg_th_topnames = th_topnames_var,
- tcg_th_modfinalizers = th_modfinalizers_var,
- tcg_th_coreplugins = th_coreplugins_var,
- tcg_th_state = th_state_var,
- tcg_th_remote_state = th_remote_state_var,
- tcg_th_docs = th_docs_var,
-
- tcg_mod = mod,
- tcg_semantic_mod = homeModuleInstantiation mhome_unit mod,
- tcg_src = hsc_src,
- tcg_rdr_env = emptyGlobalRdrEnv,
- tcg_fix_env = emptyNameEnv,
- tcg_default = emptyDefaultEnv,
- tcg_default_exports = emptyDefaultEnv,
- tcg_type_env = emptyNameEnv,
- tcg_type_env_var = type_env_var,
- tcg_inst_env = emptyInstEnv,
- tcg_fam_inst_env = emptyFamInstEnv,
- tcg_ann_env = emptyAnnEnv,
- tcg_complete_match_env = [],
- tcg_th_used = th_var,
- tcg_th_needed_deps = th_needed_deps_var,
- tcg_exports = [],
- tcg_imports = emptyImportAvails,
- tcg_import_decls = [],
- tcg_used_gres = used_gre_var,
- tcg_dus = emptyDUs,
-
- tcg_rn_imports = [],
- tcg_rn_exports =
- if hsc_src == HsigFile
- -- Always retain renamed syntax, so that we can give
- -- better errors. (TODO: how?)
- then Just []
- else maybe_rn_syntax [],
- tcg_rn_decls = maybe_rn_syntax emptyRnGroup,
- tcg_tr_module = Nothing,
- tcg_binds = emptyLHsBinds,
- tcg_imp_specs = [],
- tcg_sigs = emptyNameSet,
- tcg_ksigs = emptyNameSet,
- tcg_ev_binds = emptyBag,
- tcg_warns = emptyWarn,
- tcg_anns = [],
- tcg_tcs = [],
- tcg_insts = [],
- tcg_fam_insts = [],
- tcg_rules = [],
- tcg_fords = [],
- tcg_patsyns = [],
- tcg_merged = [],
- tcg_dfun_n = dfun_n_var,
- tcg_zany_n = zany_n_var,
- tcg_keep = keep_var,
- tcg_hdr_info = (Nothing,Nothing),
- tcg_main = Nothing,
- tcg_self_boot = NoSelfBoot,
- tcg_safe_infer = infer_var,
- tcg_safe_infer_reasons = infer_reasons_var,
- tcg_dependent_files = dependent_files_var,
- tcg_dependent_dirs = dependent_dirs_var,
- tcg_tc_plugin_solvers = [],
- tcg_tc_plugin_rewriters = emptyUFM,
- tcg_defaulting_plugins = [],
- tcg_hf_plugins = [],
- tcg_top_loc = loc,
- tcg_static_wc = static_wc_var,
- tcg_complete_matches = [],
- tcg_cc_st = cc_st_var,
- tcg_next_wrapper_num = next_wrapper_num
- } ;
- } ;
+ = do { gbl_env <- initTcGblEnv hsc_env hsc_src keep_rn_syntax mod loc
-- OK, here's the business end!
- initTcWithGbl hsc_env gbl_env loc do_this
+ ; initTcWithGbl hsc_env gbl_env loc $
+
+ -- Make sure to initialise all TcM plugins from the ambient HscEnv.
+ --
+ -- This ensures that all callers of 'initTc' enable plugins (#26395).
+ withTcPlugins hsc_env $
+ withDefaultingPlugins hsc_env $
+ withHoleFitPlugins hsc_env $
+
+ do_this
}
+-- | Create an empty 'TcGblEnv'.
+initTcGblEnv :: HscEnv -> HscSource -> Bool -> Module -> RealSrcSpan -> IO TcGblEnv
+initTcGblEnv hsc_env hsc_src keep_rn_syntax mod loc =
+ do { keep_var <- newIORef emptyNameSet
+ ; used_gre_var <- newIORef []
+ ; th_var <- newIORef False
+ ; infer_var <- newIORef True
+ ; infer_reasons_var <- newIORef emptyMessages
+ ; dfun_n_var <- newIORef emptyOccSet
+ ; zany_n_var <- newIORef 0
+ ; dependent_files_var <- newIORef []
+ ; dependent_dirs_var <- newIORef []
+ ; static_wc_var <- newIORef emptyWC
+ ; cc_st_var <- newIORef newCostCentreState
+ ; th_topdecls_var <- newIORef []
+ ; th_foreign_files_var <- newIORef []
+ ; th_topnames_var <- newIORef emptyNameSet
+ ; th_modfinalizers_var <- newIORef []
+ ; th_coreplugins_var <- newIORef []
+ ; th_state_var <- newIORef Map.empty
+ ; th_remote_state_var <- newIORef Nothing
+ ; th_docs_var <- newIORef Map.empty
+ ; th_needed_deps_var <- newIORef ([], emptyUDFM)
+ ; next_wrapper_num <- newIORef emptyModuleEnv
+ ; let
+ -- bangs to avoid leaking the env (#19356)
+ !dflags = hsc_dflags hsc_env
+ !mhome_unit = hsc_home_unit_maybe hsc_env
+ !logger = hsc_logger hsc_env
+
+ maybe_rn_syntax :: forall a. a -> Maybe a ;
+ maybe_rn_syntax empty_val
+ | logHasDumpFlag logger Opt_D_dump_rn_ast = Just empty_val
+
+ | gopt Opt_WriteHie dflags = Just empty_val
+
+ -- We want to serialize the documentation in the .hi-files,
+ -- and need to extract it from the renamed syntax first.
+ -- See 'GHC.HsToCore.Docs.extractDocs'.
+ | gopt Opt_Haddock dflags = Just empty_val
+
+ | keep_rn_syntax = Just empty_val
+ | otherwise = Nothing ;
+
+ ; return $ TcGblEnv
+ { tcg_th_topdecls = th_topdecls_var
+ , tcg_th_foreign_files = th_foreign_files_var
+ , tcg_th_topnames = th_topnames_var
+ , tcg_th_modfinalizers = th_modfinalizers_var
+ , tcg_th_coreplugins = th_coreplugins_var
+ , tcg_th_state = th_state_var
+ , tcg_th_remote_state = th_remote_state_var
+ , tcg_th_docs = th_docs_var
+
+ , tcg_mod = mod
+ , tcg_semantic_mod = homeModuleInstantiation mhome_unit mod
+ , tcg_src = hsc_src
+ , tcg_rdr_env = emptyGlobalRdrEnv
+ , tcg_fix_env = emptyNameEnv
+ , tcg_default = emptyDefaultEnv
+ , tcg_default_exports = emptyDefaultEnv
+ , tcg_type_env = emptyNameEnv
+ , tcg_type_env_var = hsc_type_env_vars hsc_env
+ , tcg_inst_env = emptyInstEnv
+ , tcg_fam_inst_env = emptyFamInstEnv
+ , tcg_ann_env = emptyAnnEnv
+ , tcg_complete_match_env = []
+ , tcg_th_used = th_var
+ , tcg_th_needed_deps = th_needed_deps_var
+ , tcg_exports = []
+ , tcg_imports = emptyImportAvails
+ , tcg_import_decls = []
+ , tcg_used_gres = used_gre_var
+ , tcg_dus = emptyDUs
+
+ , tcg_rn_imports = []
+ , tcg_rn_exports = if hsc_src == HsigFile
+ -- Always retain renamed syntax, so that we can give
+ -- better errors. (TODO: how?)
+ then Just []
+ else maybe_rn_syntax []
+ , tcg_rn_decls = maybe_rn_syntax emptyRnGroup
+ , tcg_tr_module = Nothing
+ , tcg_binds = emptyLHsBinds
+ , tcg_imp_specs = []
+ , tcg_sigs = emptyNameSet
+ , tcg_ksigs = emptyNameSet
+ , tcg_ev_binds = emptyBag
+ , tcg_warns = emptyWarn
+ , tcg_anns = []
+ , tcg_tcs = []
+ , tcg_insts = []
+ , tcg_fam_insts = []
+ , tcg_rules = []
+ , tcg_fords = []
+ , tcg_patsyns = []
+ , tcg_merged = []
+ , tcg_dfun_n = dfun_n_var
+ , tcg_zany_n = zany_n_var
+ , tcg_keep = keep_var
+ , tcg_hdr_info = (Nothing,Nothing)
+ , tcg_main = Nothing
+ , tcg_self_boot = NoSelfBoot
+ , tcg_safe_infer = infer_var
+ , tcg_safe_infer_reasons = infer_reasons_var
+ , tcg_dependent_files = dependent_files_var
+ , tcg_dependent_dirs = dependent_dirs_var
+ , tcg_tc_plugin_solvers = []
+ , tcg_tc_plugin_rewriters = emptyUFM
+ , tcg_defaulting_plugins = []
+ , tcg_hf_plugins = []
+ , tcg_top_loc = loc
+ , tcg_static_wc = static_wc_var
+ , tcg_complete_matches = []
+ , tcg_cc_st = cc_st_var
+ , tcg_next_wrapper_num = next_wrapper_num
+ } }
+
-- | Run a 'TcM' action in the context of an existing 'GblEnv'.
initTcWithGbl :: HscEnv
-> TcGblEnv
@@ -686,6 +702,83 @@ withIfaceErr ctx do_this = do
liftIO $ throwGhcExceptionIO (ProgramError (renderWithContext ctx msg))
Succeeded result -> return result
+{-
+************************************************************************
+* *
+ Initialising plugins for TcM
+* *
+************************************************************************
+-}
+
+-- | Initialise typechecker plugins, run the inner action, then stop
+-- the typechecker plugins.
+withTcPlugins :: HscEnv -> TcM a -> TcM a
+withTcPlugins hsc_env m =
+ case catMaybes $ mapPlugins (hsc_plugins hsc_env) tcPlugin of
+ [] -> m -- Common fast case
+ plugins -> do
+ (solvers, rewriters, stops) <-
+ unzip3 `fmap` mapM start_plugin plugins
+ let
+ rewritersUniqFM :: UniqFM TyCon [TcPluginRewriter]
+ !rewritersUniqFM = sequenceUFMList rewriters
+ -- The following ensures that tcPluginStop is called even if a type
+ -- error occurs during compilation (Fix of #10078)
+ eitherRes <- tryM $
+ updGblEnv (\e -> e { tcg_tc_plugin_solvers = solvers
+ , tcg_tc_plugin_rewriters = rewritersUniqFM })
+ m
+ mapM_ runTcPluginM stops
+ case eitherRes of
+ Left _ -> failM
+ Right res -> return res
+ where
+ start_plugin (TcPlugin start solve rewrite stop) =
+ do s <- runTcPluginM start
+ return (solve s, rewrite s, stop s)
+
+-- | Initialise defaulting plugins, run the inner action, then stop
+-- the defaulting plugins.
+withDefaultingPlugins :: HscEnv -> TcM a -> TcM a
+withDefaultingPlugins hsc_env m =
+ do case catMaybes $ mapPlugins (hsc_plugins hsc_env) defaultingPlugin of
+ [] -> m -- Common fast case
+ plugins -> do (plugins,stops) <- mapAndUnzipM start_plugin plugins
+ -- This ensures that dePluginStop is called even if a type
+ -- error occurs during compilation
+ eitherRes <- tryM $ do
+ updGblEnv (\e -> e { tcg_defaulting_plugins = plugins })
+ m
+ mapM_ runTcPluginM stops
+ case eitherRes of
+ Left _ -> failM
+ Right res -> return res
+ where
+ start_plugin (DefaultingPlugin start fill stop) =
+ do s <- runTcPluginM start
+ return (fill s, stop s)
+
+-- | Initialise hole fit plugins, run the inner action, then stop
+-- the hole fit plugins.
+withHoleFitPlugins :: HscEnv -> TcM a -> TcM a
+withHoleFitPlugins hsc_env m =
+ case catMaybes $ mapPlugins (hsc_plugins hsc_env) holeFitPlugin of
+ [] -> m -- Common fast case
+ plugins -> do (plugins,stops) <- mapAndUnzipM start_plugin plugins
+ -- This ensures that hfPluginStop is called even if a type
+ -- error occurs during compilation.
+ eitherRes <- tryM $
+ updGblEnv (\e -> e { tcg_hf_plugins = plugins })
+ m
+ sequence_ stops
+ case eitherRes of
+ Left _ -> failM
+ Right res -> return res
+ where
+ start_plugin (HoleFitPluginR init plugin stop) =
+ do ref <- init
+ return (plugin ref, stop ref)
+
{-
************************************************************************
* *
=====================================
libraries/ghci/GHCi/Message.hs
=====================================
@@ -89,7 +89,7 @@ data Message a where
LookupSymbol :: String -> Message (Maybe (RemotePtr ()))
LookupSymbolInDLL :: RemotePtr LoadedDLL -> String -> Message (Maybe (RemotePtr ()))
LookupClosure :: String -> Message (Maybe HValueRef)
- LoadDLL :: String -> Message (Either String (RemotePtr LoadedDLL))
+ LoadDLLs :: [String] -> Message (Either String [RemotePtr LoadedDLL])
LoadArchive :: String -> Message () -- error?
LoadObj :: String -> Message () -- error?
UnloadObj :: String -> Message () -- error?
@@ -448,7 +448,7 @@ data BreakModule
-- that type isn't available here.
data BreakUnitId
--- | A dummy type that tags pointers returned by 'LoadDLL'.
+-- | A dummy type that tags pointers returned by 'LoadDLLs'.
data LoadedDLL
-- SomeException can't be serialized because it contains dynamic
@@ -564,7 +564,7 @@ getMessage = do
1 -> Msg <$> return InitLinker
2 -> Msg <$> LookupSymbol <$> get
3 -> Msg <$> LookupClosure <$> get
- 4 -> Msg <$> LoadDLL <$> get
+ 4 -> Msg <$> LoadDLLs <$> get
5 -> Msg <$> LoadArchive <$> get
6 -> Msg <$> LoadObj <$> get
7 -> Msg <$> UnloadObj <$> get
@@ -610,7 +610,7 @@ putMessage m = case m of
InitLinker -> putWord8 1
LookupSymbol str -> putWord8 2 >> put str
LookupClosure str -> putWord8 3 >> put str
- LoadDLL str -> putWord8 4 >> put str
+ LoadDLLs strs -> putWord8 4 >> put strs
LoadArchive str -> putWord8 5 >> put str
LoadObj str -> putWord8 6 >> put str
UnloadObj str -> putWord8 7 >> put str
=====================================
libraries/ghci/GHCi/ObjLink.hs
=====================================
@@ -12,7 +12,7 @@
-- dynamic linker.
module GHCi.ObjLink
( initObjLinker, ShouldRetainCAFs(..)
- , loadDLL
+ , loadDLLs
, loadArchive
, loadObj
, unloadObj
@@ -31,6 +31,7 @@ import GHCi.RemoteTypes
import GHCi.Message (LoadedDLL)
import Control.Exception (throwIO, ErrorCall(..))
import Control.Monad ( when )
+import Data.Foldable
import Foreign.C
import Foreign.Marshal.Alloc ( alloca, free )
import Foreign ( nullPtr, peek )
@@ -43,6 +44,10 @@ import Control.Exception (catch, evaluate)
import GHC.Wasm.Prim
#endif
+#if defined(wasm32_HOST_ARCH)
+import Data.List (intercalate)
+#endif
+
-- ---------------------------------------------------------------------------
-- RTS Linker Interface
-- ---------------------------------------------------------------------------
@@ -67,20 +72,25 @@ data ShouldRetainCAFs
initObjLinker :: ShouldRetainCAFs -> IO ()
initObjLinker _ = pure ()
-loadDLL :: String -> IO (Either String (Ptr LoadedDLL))
-loadDLL f =
+-- Batch load multiple DLLs at once via dyld to enable a single
+-- dependency resolution and more parallel compilation. We pass a
+-- NUL-delimited JSString to avoid array marshalling on wasm.
+loadDLLs :: [String] -> IO (Either String [Ptr LoadedDLL])
+loadDLLs fs =
m `catch` \(err :: JSException) ->
- pure $ Left $ "loadDLL failed for " <> f <> ": " <> show err
+ pure $ Left $ "loadDLLs failed: " <> show err
where
+ packed :: JSString
+ packed = toJSString (intercalate ['\0'] fs)
m = do
- evaluate =<< js_loadDLL (toJSString f)
- pure $ Right nullPtr
+ evaluate =<< js_loadDLLs packed
+ pure $ Right (replicate (length fs) nullPtr)
-- See Note [Variable passing in JSFFI] for where
-- __ghc_wasm_jsffi_dyld comes from
-foreign import javascript safe "__ghc_wasm_jsffi_dyld.loadDLL($1)"
- js_loadDLL :: JSString -> IO ()
+foreign import javascript safe "__ghc_wasm_jsffi_dyld.loadDLLs($1)"
+ js_loadDLLs :: JSString -> IO ()
loadArchive :: String -> IO ()
loadArchive f = throwIO $ ErrorCall $ "loadArchive: unsupported on wasm for " <> f
@@ -241,6 +251,16 @@ resolveObjs = do
r <- c_resolveObjs
return (r /= 0)
+loadDLLs :: [String] -> IO (Either String [Ptr LoadedDLL])
+loadDLLs = foldrM load_one $ Right []
+ where
+ load_one _ err@(Left _) = pure err
+ load_one p (Right dlls) = do
+ r <- loadDLL p
+ pure $ case r of
+ Left err -> Left err
+ Right dll -> Right $ dll : dlls
+
-- ---------------------------------------------------------------------------
-- Foreign declarations to RTS entry points which does the real work;
-- ---------------------------------------------------------------------------
=====================================
libraries/ghci/GHCi/Run.hs
=====================================
@@ -57,7 +57,7 @@ run m = case m of
#if defined(javascript_HOST_ARCH)
LoadObj p -> withCString p loadJS
InitLinker -> notSupportedJS m
- LoadDLL {} -> notSupportedJS m
+ LoadDLLs {} -> notSupportedJS m
LoadArchive {} -> notSupportedJS m
UnloadObj {} -> notSupportedJS m
AddLibrarySearchPath {} -> notSupportedJS m
@@ -69,7 +69,7 @@ run m = case m of
LookupClosure str -> lookupJSClosure str
#else
InitLinker -> initObjLinker RetainCAFs
- LoadDLL str -> fmap toRemotePtr <$> loadDLL str
+ LoadDLLs strs -> fmap (map toRemotePtr) <$> loadDLLs strs
LoadArchive str -> loadArchive str
LoadObj str -> loadObj str
UnloadObj str -> unloadObj str
=====================================
testsuite/tests/rts/linker/T2615.hs
=====================================
@@ -4,7 +4,7 @@ library_name = "libfoo_script_T2615.so" -- this is really a linker script
main = do
initObjLinker RetainCAFs
- result <- loadDLL library_name
+ result <- loadDLLs [library_name]
case result of
Right _ -> putStrLn (library_name ++ " loaded successfully")
Left x -> putStrLn ("error: " ++ x)
=====================================
testsuite/tests/tcplugins/T26395.hs
=====================================
@@ -0,0 +1,51 @@
+
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE GADTs #-}
+{-# LANGUAGE StandaloneKindSignatures #-}
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE TypeOperators #-}
+{-# LANGUAGE UnliftedDatatypes #-}
+
+{-# OPTIONS_GHC -fplugin=T26395_Plugin #-}
+
+{-# OPTIONS_GHC -Wincomplete-patterns #-}
+{-# OPTIONS_GHC -Winaccessible-code #-}
+{-# OPTIONS_GHC -Woverlapping-patterns #-}
+
+module T26395 where
+
+import Data.Kind
+import GHC.TypeNats
+import GHC.Exts ( UnliftedType )
+
+-- This test verifies that typechecker plugins are enabled
+-- when we run the solver for pattern-match checking.
+
+type Peano :: Nat -> UnliftedType
+data Peano n where
+ Z :: Peano 0
+ S :: Peano n -> Peano (1 + n)
+
+test1 :: Peano n -> Peano n -> Int
+test1 Z Z = 0
+test1 (S n) (S m) = 1 + test1 n m
+
+{-
+The following test doesn't work properly due to #26401:
+the pattern-match checker reports a missing equation
+
+ Z (S _) _
+
+but there is no invocation of the solver of the form
+
+ [G] n ~ 0
+ [G] m ~ 1 + m1
+ [G] (n-m) ~ m2
+
+for which we could report the Givens as contradictory.
+
+test2 :: Peano n -> Peano m -> Peano (n - m) -> Int
+test2 Z Z Z = 0
+test2 (S _) (S _) _ = 1
+test2 (S _) Z (S _) = 2
+-}
=====================================
testsuite/tests/tcplugins/T26395.stderr
=====================================
@@ -0,0 +1,2 @@
+[1 of 2] Compiling T26395_Plugin ( T26395_Plugin.hs, T26395_Plugin.o )
+[2 of 2] Compiling T26395 ( T26395.hs, T26395.o )
=====================================
testsuite/tests/tcplugins/T26395_Plugin.hs
=====================================
@@ -0,0 +1,208 @@
+{-# LANGUAGE RecordWildCards #-}
+{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE MultiWayIf #-}
+{-# LANGUAGE BlockArguments #-}
+{-# LANGUAGE ViewPatterns #-}
+
+{-# OPTIONS_GHC -Wall -Wno-orphans #-}
+
+module T26395_Plugin where
+
+-- base
+import Prelude hiding ( (<>) )
+import qualified Data.Semigroup as S
+import Data.List ( partition )
+import Data.Maybe
+import GHC.TypeNats
+
+-- ghc
+import GHC.Builtin.Types.Literals
+import GHC.Core.Predicate
+import GHC.Core.TyCo.Rep
+import GHC.Plugins
+import GHC.Tc.Plugin
+import GHC.Tc.Types
+import GHC.Tc.Types.Constraint
+import GHC.Tc.Types.Evidence
+import GHC.Tc.Utils.TcType
+import GHC.Types.Unique.Map
+
+--------------------------------------------------------------------------------
+
+plugin :: Plugin
+plugin =
+ defaultPlugin
+ { pluginRecompile = purePlugin
+ , tcPlugin = \ _-> Just $
+ TcPlugin
+ { tcPluginInit = pure ()
+ , tcPluginSolve = \ _ -> solve
+ , tcPluginRewrite = \ _ -> emptyUFM
+ , tcPluginStop = \ _ -> pure ()
+ }
+ }
+
+solve :: EvBindsVar -> [Ct] -> [Ct] -> TcPluginM TcPluginSolveResult
+solve _ givens wanteds
+ -- This plugin only reports inconsistencies among Given constraints.
+ | not $ null wanteds
+ = pure $ TcPluginOk [] []
+ | otherwise
+ = do { let givenLinearExprs = mapMaybe linearExprCt_maybe givens
+ sols = solutions givenLinearExprs
+
+ ; tcPluginTrace "solveLinearExprs" $
+ vcat [ text "givens:" <+> ppr givens
+ , text "linExprs:" <+> ppr givenLinearExprs
+ , text "sols:" <+> ppr (take 1 sols)
+ ]
+ ; return $
+ if null sols
+ then TcPluginContradiction givens
+ else TcPluginOk [] []
+ }
+
+data LinearExpr =
+ LinearExpr
+ { constant :: Integer
+ , coeffs :: UniqMap TyVar Integer
+ }
+instance Semigroup LinearExpr where
+ LinearExpr c xs <> LinearExpr d ys =
+ LinearExpr ( c + d ) ( plusMaybeUniqMap_C comb xs ys )
+ where
+ comb a1 a2 =
+ let a = a1 + a2
+ in if a == 0
+ then Nothing
+ else Just a
+
+instance Monoid LinearExpr where
+ mempty = LinearExpr 0 emptyUniqMap
+
+mapLinearExpr :: (Integer -> Integer) -> LinearExpr -> LinearExpr
+mapLinearExpr f (LinearExpr c xs) = LinearExpr (f c) (mapUniqMap f xs)
+
+minusLinearExpr :: LinearExpr -> LinearExpr -> LinearExpr
+minusLinearExpr a b = a S.<> mapLinearExpr negate b
+
+instance Outputable LinearExpr where
+ ppr ( LinearExpr c xs ) =
+ hcat $ punctuate ( text " + " ) $
+ ( ppr c : map ppr_var ( nonDetUniqMapToList xs ) )
+ where
+ ppr_var ( tv, i )
+ | i == 1
+ = ppr tv
+ | i < 0
+ = parens ( text "-" <> ppr (abs i) ) <> text "*" <> ppr tv
+ | otherwise
+ = ppr i <> text "*" <> ppr tv
+
+maxCoeff :: LinearExpr -> Double
+maxCoeff ( LinearExpr c xs ) =
+ maximum ( map fromInteger ( c : nonDetEltsUniqMap xs ) )
+
+
+linearExprCt_maybe :: Ct -> Maybe LinearExpr
+linearExprCt_maybe ct =
+ case classifyPredType (ctPred ct) of
+ EqPred NomEq lhs rhs
+ | all isNaturalTy [ typeKind lhs, typeKind rhs ]
+ , Just e1 <- linearExprTy_maybe lhs
+ , Just e2 <- linearExprTy_maybe rhs
+ -> Just $ e1 `minusLinearExpr` e2
+ _ -> Nothing
+
+isNat :: Type -> Maybe Integer
+isNat ty
+ | Just (NumTyLit n) <- isLitTy ty
+ = Just n
+ | otherwise
+ = Nothing
+
+linearExprTy_maybe :: Type -> Maybe LinearExpr
+linearExprTy_maybe ty
+ | Just n <- isNat ty
+ = Just $ LinearExpr n emptyUniqMap
+ | Just (tc, args) <- splitTyConApp_maybe ty
+ = if | tc == typeNatAddTyCon
+ , [x, y] <- args
+ , Just e1 <- linearExprTy_maybe x
+ , Just e2 <- linearExprTy_maybe y
+ -> Just $ e1 S.<> e2
+ | tc == typeNatSubTyCon
+ , [x,y] <- args
+ , Just e1 <- linearExprTy_maybe x
+ , Just e2 <- linearExprTy_maybe y
+ -> Just $ e1 `minusLinearExpr` e2
+ | tc == typeNatMulTyCon
+ , [x, y] <- args
+ ->
+ if | Just ( LinearExpr n xs ) <- linearExprTy_maybe x
+ , isNullUniqMap xs
+ , Just e <- linearExprTy_maybe y
+ -> Just $
+ if n == 0
+ then mempty
+ else mapLinearExpr (n *) e
+ | Just ( LinearExpr n ys ) <- linearExprTy_maybe y
+ , isNullUniqMap ys
+ , Just e <- linearExprTy_maybe x
+ -> Just $
+ if n == 0
+ then mempty
+ else mapLinearExpr (fromIntegral n *) e
+ | otherwise
+ -> Nothing
+ | otherwise
+ -> Nothing
+ | Just tv <- getTyVar_maybe ty
+ = Just $ LinearExpr 0 ( unitUniqMap tv 1 )
+ | otherwise
+ = Nothing
+
+-- Brute force algorithm to check whether a system of Diophantine
+-- linear equations is solvable in natural numbers.
+solutions :: [ LinearExpr ] -> [ UniqMap TyVar Natural ]
+solutions eqs =
+ let
+ (constEqs, realEqs) = partition (isNullUniqMap . coeffs) eqs
+ d = length realEqs
+ fvs = nonDetKeysUniqMap $ plusUniqMapList ( map coeffs realEqs )
+ in
+ if | any ( ( /= 0 ) . evalLinearExpr emptyUniqMap ) constEqs
+ -> []
+ | d == 0
+ -> [ emptyUniqMap ]
+ | otherwise
+ ->
+ let
+ m = maximum $ map maxCoeff realEqs
+ hadamardBound = sqrt ( fromIntegral $ d ^ d ) * m ^ d
+ tests = mkAssignments ( floor hadamardBound ) fvs
+ in
+ filter ( \ test -> isSolution test realEqs ) tests
+
+
+mkAssignments :: Natural -> [ TyVar ] -> [ UniqMap TyVar Natural ]
+mkAssignments _ [] = [ emptyUniqMap ]
+mkAssignments b (v : vs) =
+ [ addToUniqMap rest v n
+ | n <- [ 0 .. b ]
+ , rest <- mkAssignments b vs
+ ]
+
+isSolution :: UniqMap TyVar Natural -> [ LinearExpr ] -> Bool
+isSolution assig =
+ all ( \ expr -> evalLinearExpr assig expr == 0 )
+
+evalLinearExpr :: UniqMap TyVar Natural -> LinearExpr -> Integer
+evalLinearExpr vals ( LinearExpr c xs ) = nonDetFoldUniqMap aux c xs
+ where
+ aux ( tv, coeff ) !acc = acc + coeff * val
+ where
+ val :: Integer
+ val = case lookupUniqMap vals tv of
+ Nothing -> pprPanic "evalLinearExpr: missing tv" (ppr tv)
+ Just v -> fromIntegral v
=====================================
testsuite/tests/tcplugins/all.T
=====================================
@@ -110,6 +110,19 @@ test('TcPlugin_CtId'
, '-dynamic -package ghc' if have_dynamic() else '-package ghc' ]
)
+# Checks that we run type-checker plugins for pattern-match warnings.
+test('T26395'
+ , [ extra_files(
+ [ 'T26395_Plugin.hs'
+ , 'T26395.hs'
+ ])
+ , req_th
+ ]
+ , multimod_compile
+ , [ 'T26395.hs'
+ , '-dynamic -package ghc' if have_dynamic() else '-package ghc' ]
+ )
+
test('T11462', [js_broken(22261), req_th, req_plugins], multi_compile,
[None, [('T11462_Plugin.hs', '-package ghc'), ('T11462.hs', '')],
'-dynamic' if have_dynamic() else ''])
=====================================
utils/jsffi/dyld.mjs
=====================================
@@ -9,7 +9,7 @@
// iserv (GHCi.Server.defaultServer). This part only runs in
// nodejs.
// 2. Dynamic linker: provide RTS linker interfaces like
-// loadDLL/lookupSymbol etc which are imported by wasm iserv. This
+// loadDLLs/lookupSymbol etc which are imported by wasm iserv. This
// part can run in browsers as well.
//
// When GHC starts external interpreter for the wasm target, it starts
@@ -50,7 +50,7 @@
//
// *** What works right now and what doesn't work yet?
//
-// loadDLL & bytecode interpreter work. Template Haskell & ghci work.
+// loadDLLs & bytecode interpreter work. Template Haskell & ghci work.
// Profiled dynamic code works. Compiled code and bytecode can all be
// loaded, though the side effects are constrained to what's supported
// by wasi preview1: we map the full host filesystem into wasm cause
@@ -777,17 +777,17 @@ class DyLD {
return this.#rpc.findSystemLibrary(f);
}
- // When we do loadDLL, we first perform "downsweep" which return a
+ // When we do loadDLLs, we first perform "downsweep" which return a
// toposorted array of dependencies up to itself, then sequentially
// load the downsweep result.
//
// The rationale of a separate downsweep phase, instead of a simple
- // recursive loadDLL function is: V8 delegates async
+ // recursive loadDLLs function is: V8 delegates async
// WebAssembly.compile to a background worker thread pool. To
// maintain consistent internal linker state, we *must* load each so
// file sequentially, but it's okay to kick off compilation asap,
// store the Promise in downsweep result and await for the actual
- // WebAssembly.Module in loadDLL logic. This way we can harness some
+ // WebAssembly.Module in loadDLLs logic. This way we can harness some
// background parallelism.
async #downsweep(p) {
const toks = p.split("/");
@@ -828,8 +828,26 @@ class DyLD {
return acc;
}
- // The real stuff
- async loadDLL(p) {
+ // Batch load multiple DLLs in one go.
+ // Accepts a NUL-delimited string of paths to avoid array marshalling.
+ // Each path can be absolute or a soname; dependency resolution is
+ // performed across the full set to enable maximal parallel compile
+ // while maintaining sequential instantiation order.
+ async loadDLLs(packed) {
+ // Normalize input to an array of strings. When called from Haskell
+ // we pass a single JSString containing NUL-separated paths.
+ const paths = (typeof packed === "string"
+ ? (packed.length === 0 ? [] : packed.split("\0"))
+ : [packed] // tolerate an accidental single path object
+ ).filter((s) => s.length > 0).reverse();
+
+ // Compute a single downsweep plan for the whole batch.
+ // Note: #downsweep mutates #loadedSos to break cycles and dedup.
+ const plan = [];
+ for (const p of paths) {
+ plan.push(...(await this.#downsweep(p)));
+ }
+
for (const {
memSize,
memP2Align,
@@ -837,7 +855,7 @@ class DyLD {
tableP2Align,
modp,
soname,
- } of await this.#downsweep(p)) {
+ } of plan) {
const import_obj = {
wasi_snapshot_preview1: this.#wasi.wasiImport,
env: {
@@ -1128,7 +1146,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/e018feaf03aabf017f791687fab071…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e018feaf03aabf017f791687fab071…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/fedora42] 44 commits: Handle heap allocation failure in I/O primops
by Cheng Shao (@TerrorJack) 18 Sep '25
by Cheng Shao (@TerrorJack) 18 Sep '25
18 Sep '25
Cheng Shao pushed to branch wip/fedora42 at Glasgow Haskell Compiler / GHC
Commits:
62ae97de by Duncan Coutts at 2025-09-12T13:23:33-04:00
Handle heap allocation failure in I/O primops
The current I/O managers do not use allocateMightFail, but future ones
will. To support this properly we need to be able to return to the
primop with a failure. We simply use a bool return value.
Currently however, we will just throw an exception rather than calling
the GC because that's what all the other primops do too.
For the general issue of primops invoking GC and retrying, see
https://gitlab.haskell.org/ghc/ghc/-/issues/24105
- - - - -
cb9093f5 by Duncan Coutts at 2025-09-12T13:23:33-04:00
Move (and rename) scheduleStartSignalHandlers into RtsSignals.h
Previously it was a local helper (static) function in Schedule.c.
Rename it to startPendingSignalHandlers and deifine it as an inline
header function in RtsSignals.h. So it should still be fast.
Each (new style) I/O manager is going to need to do the same, so eliminating
the duplication now makes sense.
- - - - -
9736d44a by Duncan Coutts at 2025-09-12T13:23:33-04:00
Reduce detail in printThreadBlockage I/O blocking cases
The printThreadBlockage is used in debug tracing output.
For the cases BlockedOn{Read,Write,Delay} the output previously included
the fd that was being waited on, and the delay target wake time.
Superficially this sounds useful, but it's clearly not that useful
because it was already wrong for the Win32 non-threaded I/O manager. In
that situation it will print garbage (the async_result pointer, cast to
a fd or a time).
So given that it apparently never mattered that the information was
accurate, then it's hardly a big jump to say it doesn't matter if it is
present at all.
A good reason to remove it is that otherwise we have to make a new
API and a per-I/O manager implementation to fetch the information. And
for some I/O manager implementations, this information is not available.
It is not available in the win32 non-threaded I/O manager. And for some
future Linux ones, there is no need for the fd to be stored, so storing
it would be just extra space used for very little gain.
So the simplest thing is to just remove the detail.
- - - - -
bc0f2d5d by Duncan Coutts at 2025-09-12T13:23:33-04:00
Add TimeoutQueue.{c,h} and corresponding tests
A data structure used to efficiently manage a collection of timeouts.
It is a priority queue based on absolute expiry time. It uses 64bit
high-precision Time for the keys. The values are normal closures which
allows for example using MVars for unblocking.
It is common in many applications for timeouts to be created and then
deleted or altered before they expire. Thus the choice of data structure
for timeouts should support this efficiently. The implementation choice
here is a leftist heap with the extra feature that it supports deleting
arbitrary elements, provided the caller retain a pointer to the element.
While the deleteMin operation takes O(log n) time, as in all heap
structures, the delete operation for arbitrary elements /typically/
takes O(1), and only O(log n) in the worst case. In practice, when
managing thousands of timeouts it can be a factor of 10 faster to delete
a random timeout queue element than to remove the minimum element. This
supports the common use case.
The plan is to use it in some of the RTS-side I/O managers to support
their timer functionality. In this use case the heap value will be an
MVar used for each timeout to unblock waiting threads.
- - - - -
d1679c9d by Duncan Coutts at 2025-09-12T13:23:33-04:00
Add ClosureTable.{c,h} and corresponding tests
A table of pointers to closures on the GC heap with stable indexes.
It provides O(1) alloc, free and lookup. The table can be expanded
using a simple doubling strategy: in which case allocation is typically
O(1) and occasionally O(n) for overall amortised O(1). No shrinking is
used.
The table itself is heap allocated, and points to other heap objects.
As such it's necessary to use markClosureTable to ensure the table is
used as a GC root to keep the table entries alive, and maintain proper
pointers to them as the GC moves heap objects about.
It is designed to be allocated and accesses exclusively from a single
capability, enabling it to work without any locking. It is thus similar
to the StablePtr table, but per-capability which removes the need for
locking. It _should_ also provide lower GC pause times with the
non-moving GC by spending only O(1) time in markClosureTable, vs O(n)
for markStablePtrTable.
The plan is to use it in some of the I/O managers to keep track of
in-flight I/O operations (but not timers). This allows the tracking
info to be kept on the (unpinned) GC heap, and shared with Haskell
code, and by putting a pointer to the tracking information in a table,
the index remains stable and can be passed via foreign code (like the
kernel).
- - - - -
78cb8dd5 by Duncan Coutts at 2025-09-12T13:23:33-04:00
Add the StgAsyncIOOp closure type
This is intended to be used by multiple I/O managers to help with
tracking in-flight I/O operations.
It is called asynchronous because from the point of view of the RTS we
have many such operations in progress at once. From the point of view of
a Haskell thread of course it can look synchronous.
- - - - -
a2839896 by Duncan Coutts at 2025-09-12T13:23:33-04:00
Add StgAsyncIOOp and StgTimeoutQueue to tso->block_info
These will be used by new I/O managers, for threads blocked on I/O or
timeouts.
- - - - -
fdc2451c by Duncan Coutts at 2025-09-12T13:23:33-04:00
Add a new I/O manager based on poll()
This is a proof of concept I/O manager, to show how to add new ones
neatly, using the ClosureTable and TimeoutQueue infrastructure.
It uses the old unix poll() API, so it is of course limited in
performance by that, but it should have the benefit of wide
compatibility. Also we neatly avoid a name clash with the existing
select() I/O manager.
Compared to the select() I/O manager:
1. beause it uses poll() it is not limited to 1024 file descriptors
(but it's still O(n) so don't expect great performance);
2. it should have much faster threadDelay (when using it in lots of
threads at once) because it's based on the new TimeoutQueue which is
O(log n) rather than O(n).
Some of the code related to timers/timouts is put into a shared module
rts/posix/Timeout.{h,c} since it is intended to be shared with other
similar I/O managers.
- - - - -
6c273b76 by Duncan Coutts at 2025-09-12T13:23:34-04:00
Document the I/O managers in the user guide
and note the new poll I/O manager in the release notes.
- - - - -
824fab74 by Duncan Coutts at 2025-09-12T13:23:34-04:00
Use the poll() I/O manager by default
That is, for the non-threaded RTS, prefer the poll I/O manager over the
legacy select() one, if both can be enabled.
This patch is primarily for CI testing, so we should probably remove
this patch before merging. We can change defaults later after wider
testing and feedback.
- - - - -
39392532 by Luite Stegeman at 2025-09-12T13:24:16-04:00
Support larger unboxed sums
Change known constructor encoding for sums in interfaces to use
11 bits for both the arity and the alternative (up from 8 and 6,
respectively)
- - - - -
2af12e21 by Luite Stegeman at 2025-09-12T13:24:16-04:00
Decompose padding smallest-first in Cmm toplevel data constructors
This makes each individual padding value aligned
- - - - -
418fa78f by Luite Stegeman at 2025-09-12T13:24:16-04:00
Use slots smaller than word as tag for smaller unboxed sums
This packs unboxed sums more efficiently by allowing
Word8, Word16 and Word32 for the tag field if the number of
constructors is small enough
- - - - -
8d7e912f by Rodrigo Mesquita at 2025-09-12T17:57:24-04:00
ghc-toolchain: Use ByteOrder rather than new Endianness
Don't introduce a duplicate datatype when the previous one is equivalent
and already used elsewhere. This avoids unnecessary translation between
the two.
- - - - -
7d378476 by Rodrigo Mesquita at 2025-09-12T17:57:24-04:00
Read Toolchain.Target files rather than 'settings'
This commit makes GHC read `lib/targets/default.target`, a file with a
serialized value of `ghc-toolchain`'s `GHC.Toolchain.Target`.
Moreover, it removes all the now-redundant entries from `lib/settings`
that are configured as part of a `Target` but were being written into
`settings`.
This makes it easier to support multiple targets from the same compiler
(aka runtime retargetability). `ghc-toolchain` can be re-run many times
standalone to produce a `Target` description for different targets, and,
in the future, GHC will be able to pick at runtime amongst different
`Target` files.
This commit only makes it read the default `Target` configured in-tree
or configured when installing the bindist.
The remaining bits of `settings` need to be moved to `Target` in follow
up commits, but ultimately they all should be moved since they are
per-target relevant.
Fixes #24212
On Windows, the constant overhead of parsing a slightly more complex
data structure causes some small-allocation tests to wiggle around 1 to
2 extra MB (1-2% in these cases).
-------------------------
Metric Increase:
MultiLayerModulesTH_OneShot
T10421
T10547
T12234
T12425
T13035
T18140
T18923
T9198
TcPlugin_RewritePerf
-------------------------
- - - - -
e0780a16 by Rodrigo Mesquita at 2025-09-12T17:57:24-04:00
ghc-toolchain: Move TgtHasLibm to per-Target file
TargetHasLibm is now part of the per-target configuration
Towards #26227
- - - - -
8235dd8c by Rodrigo Mesquita at 2025-09-12T17:57:24-04:00
ghc-toolchain: Move UseLibdw to per-Target file
To support DWARF unwinding, the RTS must be built with the -f+libdw flag
and with the -DUSE_LIBDW macro definition. These flags are passed on
build by Hadrian when --enable-dwarf-unwinding is specified at configure
time.
Whether the RTS was built with support for DWARF is a per-target
property, and as such, it was moved to the per-target
GHC.Toolchain.Target.Target file.
Additionally, we keep in the target file the include and library paths
for finding libdw, since libdw should be checked at configure time (be
it by configure, or ghc-toolchain, that libdw is properly available).
Preserving the user-given include paths for libdw facilitates in the
future building the RTS on demand for a given target (if we didn't keep
that user input, we couldn't)
Towards #26227
- - - - -
d5ecf2e8 by Rodrigo Mesquita at 2025-09-12T17:57:25-04:00
ghc-toolchain: Make "Support SMP" a query on a Toolchain.Target
"Support SMP" is merely a function of target, so we can represent it as
such in `ghc-toolchain`.
Hadrian queries the Target using this predicate to determine how to
build GHC, and GHC queries the Target similarly to report under --info
whether it "Support SMP"
Towards #26227
- - - - -
e07b031a by Rodrigo Mesquita at 2025-09-12T17:57:25-04:00
ghc-toolchain: Make "tgt rts linker only supports shared libs" function on Target
Just like with "Support SMP", "target RTS linker only supports shared
libraries" is a predicate on a `Target` so we can just compute it when
necessary from the given `Target`.
Towards #26227
- - - - -
14123ee6 by Simon Peyton Jones at 2025-09-12T17:58:07-04:00
Solve forall-constraints via an implication, again
In this earlier commit:
commit 953fd8f1dc080f1c56e3a60b4b7157456949be29
Author: Simon Peyton Jones <simon.peytonjones(a)gmail.com>
Date: Mon Jul 21 10:06:43 2025 +0100
Solve forall-constraints immediately, or not at all
I used a all-or-nothing strategy for quantified constraints
(aka forall-constraints). But alas that fell foul of #26315,
and #26376.
So this MR goes back to solving a quantified constraint by
turning it into an implication; UNLESS we are simplifying
constraints from a SPECIALISE pragma, in which case the
all-or-nothing strategy is great. See:
Note [Solving a Wanted forall-constraint]
Other stuff in this MR:
* TcSMode becomes a record of flags, rather than an enumeration
type; much nicer.
* Some fancy footwork to avoid error messages worsening again
(The above MR made them better; we want to retain that.)
See `GHC.Tc.Errors.Ppr.pprQCOriginExtra`.
-------------------------
Metric Decrease:
T24471
-------------------------
- - - - -
e6c192e2 by Simon Peyton Jones at 2025-09-12T17:58:07-04:00
Add a test case for #26396
...same bug ast #26315
- - - - -
8f3d80ff by Luite Stegeman at 2025-09-13T08:43:09+02:00
Use mkVirtHeapOffsets for reconstructing terms in RTTI
This makes mkVirtHeapOffsets the single source of truth for
finding field offsets in closures.
- - - - -
eb389338 by Luite Stegeman at 2025-09-13T08:43:09+02:00
Sort non-pointer fields by size for more efficient packing
This sorts non-pointer fields in mkVirtHeapOffsets, always
storing the largest field first. The relative order of
equally sized fields remains unchanged.
This reduces wasted padding/alignment space in closures with
differently sized fields.
- - - - -
99b233f4 by Alison at 2025-09-13T16:51:04-04:00
ghc-heap: Fix race condition with profiling builds
Apply the same fix from Closures.hs (64fd0fac83) to Heap.hs by adding
empty imports to make way-dependent dependencies visible to `ghc -M`.
Fixes #15197, #26407
- - - - -
77deaa7a by Cheng Shao at 2025-09-14T21:29:45-04:00
hadrian: build in-tree gmp with -fvisibility=hidden
When hadrian builds in-tree gmp, it should build the shared objects
with -fvisibility=hidden. The gmp symbols are only used by bignum
logic in ghc-internal and shouldn't be exported by the ghc-internal
shared library. We should always strive to keep shared library symbol
table lean, which benefits platforms with slow dynamic linker or even
hard limits about how many symbols can be exported (e.g. macos dyld,
win32 dll and wasm dyld).
- - - - -
42a18960 by Cheng Shao at 2025-09-14T21:30:26-04:00
Revert "wasm: add brotli compression for ghci browser mode"
This reverts commit 731217ce68a1093b5f9e26a07d5bd2cdade2b352.
Benchmarks show non-negligible overhead when browser runs on the same
host, which is the majority of actual use cases.
- - - - -
e6755b9f by Cheng Shao at 2025-09-14T21:30:26-04:00
wasm: remove etag logic in ghci browser mode web server
This commit removes the etag logic in dyld script's ghci browser mode
web server. It was meant to support caching logic of wasm shared
libraries, but even if the port is manually specified to make caching
even relevant, for localhost the extra overhead around etag logic is
simply not worth it according to benchmarks.
- - - - -
ac5859b9 by sheaf at 2025-09-16T14:58:38-04:00
Add 'Outputable Natural' instance
This commit adds an Outputable instance for the Natural natural-number type,
as well as a "natural :: Natural -> SDoc" function that mirrors the existing
"integer" function.
- - - - -
d48ebc23 by Cheng Shao at 2025-09-16T14:59:18-04:00
autoconf: emit warning instead of error for FIND_PYTHON logic
This patch makes FIND_PYTHON logic emit warning instead of error, so
when the user doesn't expect to run the testsuite driver (especially
when installing a bindist), python would not be mandatory. Fixes #26347.
- - - - -
54b5950e by Sylvain Henry at 2025-09-17T04:45:18-04:00
Print fully qualified unit names in name mismatch
It's more user-friendly to directly print the right thing instead of
requiring the user to retry with the additional `-dppr-debug` flag.
- - - - -
403cb665 by Ben Gamari at 2025-09-17T04:46:00-04:00
configure: Fix consistency between distrib and source CC check
Previously distrib/configure.ac did not
include `cc`.
Closes #26394.
- - - - -
2dcd4cb9 by Oleg Grenrus at 2025-09-17T04:46:41-04:00
Use isPrint in showUnique
The comment say
```
-- Avoid emitting non-printable characters in pretty uniques. See #25989.
```
so let the code do exactly that.
There are tags (at least : and 0 .. 9) which weren't in A .. z range.
- - - - -
e5dd754b by Oleg Grenrus at 2025-09-17T04:46:42-04:00
Shorten in-module links in hyperlinked source
Instead of href="This.Module#ident" to just "#ident"
- - - - -
63189b2c by Oleg Grenrus at 2025-09-17T04:46:42-04:00
Use showUnique in internalAnchorIdent
Showing the key of Unique as a number is generally not a great idea.
GHC Unique has a tag in high bits, so the raw number is unnecessarily
big.
So now we have
```html
<a href="#l-rvgK"><span class="hs-identifier hs-var hs-var">bar</span></a>
```
instead of
```html
<a href="#local-6989586621679015689"><span class="hs-identifier hs-var hs-var">bar</span></a>
```
Together with previous changes of shorter intra-module links the effect
on compressed files is not huge, that is expected as we simply remove
repetitive contents which pack well.
```
12_694_206 Agda-2.9.0-docs-orig.tar.gz
12_566_065 Agda-2.9.0-docs.tar.gz
```
However when unpacked, the difference can be significant,
e.g. Agda's largest module source got 5% reduction:
```
14_230_117 Agda.Syntax.Parser.Parser.html
13_422_109 Agda.Syntax.Parser.Parser.html
```
The whole hyperlinked source code directory got similar reduction
```
121M Agda-2.9.0-docs-orig/src
114M Agda-2.9.0-docs/src
```
For the reference, sources are about 2/3 of the generated haddocks
```
178M Agda-2.9.0-docs-old
172M Agda-2.9.0-docs
```
so we get around 3.5% size reduction overall. Not bad for a small local
changes.
- - - - -
6f63f57b by Stefan Schulze Frielinghaus at 2025-09-17T04:47:22-04:00
rts: Fix alignment for gen_workspace #26334
After a0fa4941903272c48b050d24e93eec819eff51bd bootstrap is broken on
s390x and errors out with
rts/sm/GCThread.h:207:5: error:
error: alignment of array elements is greater than element size
207 | gen_workspace gens[];
| ^~~~~~~~~~~~~
The alignment constraint is applied via the attribute to the type
gen_workspace and leaves the underlying type struct gen_workspace_
untouched. On Aarch64, x86, and s390x the struct has a size of 128
bytes. On Aarch64 and x86 the alignments of 128 and 64 are divisors of
the size, respectively, which is why the type is a viable member type
for an array. However, on s390x, the alignment is 256 and therefore is
not a divisor of the size and hence cannot be used for arrays.
Basically I see two fixes here. Either decrease the alignment
requirement on s390x, or by applying the alignment constraint on the
struct itself. The former might affect performance as noted in
a0fa4941903272c48b050d24e93eec819eff51bd. The latter introduces padding
bits whenever necessary in order to ensure that
sizeof(gen_workspace[N])==N*sizeof(gen_workspace) holds which is done by
this patch.
- - - - -
06d25623 by Cheng Shao at 2025-09-17T19:32:27-04:00
ghci: add :shell command
This patch adds a new :shell command to ghci which works similarly to
:!, except it guarantees to run the command via sh -c. On POSIX hosts
the behavior is identical to :!, but on Windows it uses the msys2
shell instead of system cmd.exe shell. This is convenient when writing
simple ghci scripts that run simple POSIX commands, and the behavior
can be expected to be coherent on both Windows and POSIX.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
186054f7 by Cheng Shao at 2025-09-17T19:32:27-04:00
testsuite: remove legacy :shell trick
This commit makes use of the built-in :shell functionality in ghci in
the test cases, and remove the legacy :shell trick.
- - - - -
0a3a4aa3 by Cheng Shao at 2025-09-17T19:32:27-04:00
docs: document :shell in ghci
This commit documents the :shell command in ghci.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
a4ff12bb by Cheng Shao at 2025-09-17T19:33:09-04:00
ghc-internal: fix codepages program
codepages was not properly updated during the base -> ghc-internal
migration, this commit fixes it.
- - - - -
7e094def by Cheng Shao at 2025-09-17T19:33:09-04:00
ghc-internal: relax ucd2haskell cabal upper bounds
This commit relaxes ucd2haskell cabal upper bounds to make it runnable
via ghc 9.12/9.14.
- - - - -
7077c9f7 by Cheng Shao at 2025-09-17T19:33:09-04:00
ghc-internal: update to unicode 17.0.0
This commit updates the generated code in ghc-internal to match
unicode 17.0.0.
- - - - -
cef8938f by sheaf at 2025-09-17T19:34:09-04:00
Bad record update msg: allow out-of-scope datacons
This commit ensures that, when we encounter an invalid record update
(because no constructor exists which contains all of the record fields
mentioned in the record update), we graciously handle the situation in
which the constructors themselves are not in scope. In that case,
instead of looking up the constructors in the GlobalRdrEnv, directly
look up their GREInfo using the lookupGREInfo function.
Fixes #26391
- - - - -
a2d9d7c2 by sheaf at 2025-09-17T19:34:09-04:00
Improve Notes about disambiguating record updates
This commit updates the notes [Disambiguating record updates] and
[Type-directed record disambiguation], in particular adding more
information about the deprecation status of type-directed disambiguation
of record updates.
- - - - -
2f3c3905 by Cheng Shao at 2025-09-18T17:11:31+02:00
rel-eng: update fedora image to 42
This patch is a part of #25876 and updates fedora image to 42.
- - - - -
223 changed files:
- .gitlab-ci.yml
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- compiler/GHC/Builtin/Uniques.hs
- compiler/GHC/Cmm/Utils.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/Iface/Errors/Ppr.hs
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/Pat.hs
- compiler/GHC/Runtime/Heap/Inspect.hs
- compiler/GHC/Settings.hs
- compiler/GHC/Settings/IO.hs
- compiler/GHC/Stg/Unarise.hs
- compiler/GHC/StgToCmm/DataCon.hs
- compiler/GHC/StgToCmm/Layout.hs
- compiler/GHC/SysTools/BaseDir.hs
- compiler/GHC/Tc/Deriv/Utils.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/Sig.hs
- compiler/GHC/Tc/Solver.hs
- compiler/GHC/Tc/Solver/Default.hs
- compiler/GHC/Tc/Solver/Dict.hs
- compiler/GHC/Tc/Solver/Equality.hs
- compiler/GHC/Tc/Solver/InertSet.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Solver/Solve.hs
- compiler/GHC/Tc/Solver/Solve.hs-boot
- compiler/GHC/Tc/Types/Constraint.hs
- compiler/GHC/Tc/Types/Evidence.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/Tc/Utils/Monad.hs
- compiler/GHC/Tc/Zonk/TcType.hs
- compiler/GHC/Tc/Zonk/Type.hs
- compiler/GHC/Types/RepType.hs
- compiler/GHC/Types/Unique.hs
- compiler/GHC/Unit/State.hs
- compiler/GHC/Utils/Outputable.hs
- compiler/ghc.cabal.in
- configure.ac
- distrib/configure.ac.in
- docs/users_guide/9.16.1-notes.rst
- docs/users_guide/ghci.rst
- docs/users_guide/runtime_control.rst
- ghc/GHCi/UI.hs
- hadrian/bindist/Makefile
- hadrian/bindist/config.mk.in
- hadrian/cfg/default.host.target.in
- hadrian/cfg/default.target.in
- hadrian/cfg/system.config.in
- hadrian/src/Base.hs
- hadrian/src/Oracles/Flag.hs
- hadrian/src/Oracles/Setting.hs
- hadrian/src/Rules/Generate.hs
- hadrian/src/Rules/Gmp.hs
- hadrian/src/Settings/Packages.hs
- libraries/base/src/GHC/RTS/Flags.hs
- libraries/base/tests/unicode002.stdout
- libraries/base/tests/unicode003.stdout
- libraries/ghc-boot/GHC/Settings/Utils.hs
- libraries/ghc-boot/ghc-boot.cabal.in
- libraries/ghc-heap/GHC/Exts/Heap.hs
- libraries/ghc-internal/codepages/MakeTable.hs
- libraries/ghc-internal/codepages/Makefile
- libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc
- libraries/ghc-internal/src/GHC/Internal/ResponseFile.hs
- libraries/ghc-internal/src/GHC/Internal/Unicode/Char/DerivedCoreProperties.hs
- libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/GeneralCategory.hs
- libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleLowerCaseMapping.hs
- libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleTitleCaseMapping.hs
- libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleUpperCaseMapping.hs
- libraries/ghc-internal/src/GHC/Internal/Unicode/Version.hs
- libraries/ghc-internal/tools/ucd2haskell/ucd.sh
- libraries/ghc-internal/tools/ucd2haskell/ucd2haskell.cabal
- libraries/ghc-internal/tools/ucd2haskell/unicode_version
- m4/find_python.m4
- m4/fp_find_libdw.m4
- − m4/fp_settings.m4
- m4/fp_setup_windows_toolchain.m4
- m4/ghc_toolchain.m4
- m4/prep_target_file.m4
- + m4/subst_tooldir.m4
- mk/hsc2hs.in
- + rts/ClosureTable.c
- + rts/ClosureTable.h
- rts/IOManager.c
- rts/IOManager.h
- rts/IOManagerInternals.h
- rts/PrimOps.cmm
- rts/RtsSignals.h
- rts/Schedule.c
- rts/StgMiscClosures.cmm
- rts/Threads.c
- + rts/TimeoutQueue.c
- + rts/TimeoutQueue.h
- rts/configure.ac
- rts/include/rts/Constants.h
- rts/include/rts/Flags.h
- rts/include/rts/storage/Closures.h
- rts/include/rts/storage/TSO.h
- rts/include/stg/MiscClosures.h
- + rts/posix/Poll.c
- + rts/posix/Poll.h
- + rts/posix/Timeout.c
- + rts/posix/Timeout.h
- rts/rts.cabal
- rts/sm/GCThread.h
- testsuite/tests/backpack/should_fail/bkpfail11.stderr
- testsuite/tests/backpack/should_fail/bkpfail43.stderr
- testsuite/tests/codeGen/should_compile/T25166.stdout → testsuite/tests/codeGen/should_compile/T25166.stdout-ws-32
- + testsuite/tests/codeGen/should_compile/T25166.stdout-ws-64
- testsuite/tests/codeGen/should_run/T13825-unit.hs
- + testsuite/tests/deriving/should_compile/T26396.hs
- testsuite/tests/deriving/should_compile/all.T
- testsuite/tests/deriving/should_fail/T12768.stderr
- testsuite/tests/deriving/should_fail/T1496.stderr
- testsuite/tests/deriving/should_fail/T21302.stderr
- testsuite/tests/deriving/should_fail/T22696b.stderr
- testsuite/tests/deriving/should_fail/T5498.stderr
- testsuite/tests/deriving/should_fail/T7148.stderr
- testsuite/tests/deriving/should_fail/T7148a.stderr
- testsuite/tests/driver/multipleHomeUnits/all.T
- testsuite/tests/ghc-api/T20757.hs
- testsuite/tests/ghc-api/settings-escape/T24265.hs
- testsuite/tests/ghc-api/settings-escape/T24265.stderr
- + testsuite/tests/ghc-api/settings-escape/ghc-install-folder/lib with spaces/targets/.gitkeep
- testsuite/tests/ghci.debugger/scripts/break022/all.T
- testsuite/tests/ghci.debugger/scripts/break022/break022.script
- testsuite/tests/ghci.debugger/scripts/break023/all.T
- testsuite/tests/ghci.debugger/scripts/break023/break023.script
- testsuite/tests/ghci/prog001/prog001.T
- testsuite/tests/ghci/prog001/prog001.script
- testsuite/tests/ghci/prog002/prog002.T
- testsuite/tests/ghci/prog002/prog002.script
- testsuite/tests/ghci/prog003/prog003.T
- testsuite/tests/ghci/prog003/prog003.script
- testsuite/tests/ghci/prog005/prog005.T
- testsuite/tests/ghci/prog005/prog005.script
- testsuite/tests/ghci/prog010/all.T
- testsuite/tests/ghci/prog010/ghci.prog010.script
- testsuite/tests/ghci/prog012/all.T
- testsuite/tests/ghci/prog012/prog012.script
- testsuite/tests/ghci/recompTHghci/all.T
- testsuite/tests/ghci/recompTHghci/recompTHghci.script
- testsuite/tests/ghci/scripts/T18330.script
- testsuite/tests/ghci/scripts/T18330.stdout
- testsuite/tests/ghci/scripts/T1914.script
- testsuite/tests/ghci/scripts/T20587.script
- testsuite/tests/ghci/scripts/T6106.script
- testsuite/tests/ghci/scripts/T8353.script
- testsuite/tests/ghci/scripts/all.T
- testsuite/tests/ghci/scripts/ghci038.script
- testsuite/tests/ghci/scripts/ghci058.script
- testsuite/tests/ghci/scripts/ghci063.script
- − testsuite/tests/ghci/shell.hs
- testsuite/tests/impredicative/T17332.stderr
- testsuite/tests/interface-stability/ghc-experimental-exports.stdout
- testsuite/tests/interface-stability/ghc-experimental-exports.stdout-mingw32
- + testsuite/tests/overloadedrecflds/should_fail/T26391.hs
- + testsuite/tests/overloadedrecflds/should_fail/T26391.stderr
- testsuite/tests/overloadedrecflds/should_fail/all.T
- testsuite/tests/perf/compiler/MultiLayerModulesDefsGhci.script
- testsuite/tests/perf/compiler/all.T
- testsuite/tests/quantified-constraints/T19690.stderr
- testsuite/tests/quantified-constraints/T19921.stderr
- testsuite/tests/quantified-constraints/T21006.stderr
- testsuite/tests/roles/should_fail/RolesIArray.stderr
- + testsuite/tests/rts/ClosureTable.hs
- + testsuite/tests/rts/ClosureTable_c.c
- + testsuite/tests/rts/TimeoutQueue.c
- + testsuite/tests/rts/TimeoutQueue.stdout
- testsuite/tests/rts/all.T
- testsuite/tests/simplCore/should_compile/DsSpecPragmas.hs
- testsuite/tests/simplCore/should_compile/DsSpecPragmas.stderr
- testsuite/tests/typecheck/should_compile/T14434.hs
- + testsuite/tests/typecheck/should_compile/T26376.hs
- testsuite/tests/typecheck/should_compile/all.T
- testsuite/tests/typecheck/should_fail/T15801.stderr
- testsuite/tests/typecheck/should_fail/T19627.stderr
- testsuite/tests/typecheck/should_fail/T20666.stderr
- testsuite/tests/typecheck/should_fail/T20666a.stderr
- testsuite/tests/typecheck/should_fail/T20666b.stderr
- testsuite/tests/typecheck/should_fail/T22912.stderr
- testsuite/tests/typecheck/should_fail/T23427.stderr
- + testsuite/tests/unboxedsums/UbxSumUnpackedSize.hs
- + testsuite/tests/unboxedsums/UbxSumUnpackedSize.stdout
- + testsuite/tests/unboxedsums/UbxSumUnpackedSize.stdout-ws-32
- testsuite/tests/unboxedsums/all.T
- testsuite/tests/unboxedsums/unboxedsums_unit_tests.hs
- utils/ghc-pkg/Main.hs
- utils/ghc-pkg/ghc-pkg.cabal.in
- utils/ghc-toolchain/exe/Main.hs
- utils/ghc-toolchain/ghc-toolchain.cabal
- + utils/ghc-toolchain/src/GHC/Toolchain/Library.hs
- utils/ghc-toolchain/src/GHC/Toolchain/PlatformDetails.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Target.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cc.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cpp.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cxx.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker/Renderer.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker/Utils.hs
- utils/haddock/hypsrc-test/Main.hs
- utils/haddock/hypsrc-test/ref/src/CPP.html
- utils/haddock/hypsrc-test/ref/src/Classes.html
- utils/haddock/hypsrc-test/ref/src/Constructors.html
- utils/haddock/hypsrc-test/ref/src/Identifiers.html
- utils/haddock/hypsrc-test/ref/src/LinkingIdentifiers.html
- utils/haddock/hypsrc-test/ref/src/Literals.html
- utils/haddock/hypsrc-test/ref/src/Operators.html
- utils/haddock/hypsrc-test/ref/src/Polymorphism.html
- utils/haddock/hypsrc-test/ref/src/PositionPragmas.html
- utils/haddock/hypsrc-test/ref/src/Quasiquoter.html
- utils/haddock/hypsrc-test/ref/src/Records.html
- utils/haddock/hypsrc-test/ref/src/TemplateHaskellQuasiquotes.html
- utils/haddock/hypsrc-test/ref/src/TemplateHaskellSplices.html
- utils/haddock/hypsrc-test/ref/src/Types.html
- utils/haddock/hypsrc-test/ref/src/UsingQuasiquotes.html
- utils/jsffi/dyld.mjs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/591e5d355ce7e4ca6277e6633d01c9…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/591e5d355ce7e4ca6277e6633d01c9…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
18 Sep '25
Rodrigo Mesquita pushed new branch wip/romes/25637 at Glasgow Haskell Compiler / GHC
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/romes/25637
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/T26330] 9 commits: ghci: add :shell command
by Simon Peyton Jones (@simonpj) 18 Sep '25
by Simon Peyton Jones (@simonpj) 18 Sep '25
18 Sep '25
Simon Peyton Jones pushed to branch wip/T26330 at Glasgow Haskell Compiler / GHC
Commits:
06d25623 by Cheng Shao at 2025-09-17T19:32:27-04:00
ghci: add :shell command
This patch adds a new :shell command to ghci which works similarly to
:!, except it guarantees to run the command via sh -c. On POSIX hosts
the behavior is identical to :!, but on Windows it uses the msys2
shell instead of system cmd.exe shell. This is convenient when writing
simple ghci scripts that run simple POSIX commands, and the behavior
can be expected to be coherent on both Windows and POSIX.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
186054f7 by Cheng Shao at 2025-09-17T19:32:27-04:00
testsuite: remove legacy :shell trick
This commit makes use of the built-in :shell functionality in ghci in
the test cases, and remove the legacy :shell trick.
- - - - -
0a3a4aa3 by Cheng Shao at 2025-09-17T19:32:27-04:00
docs: document :shell in ghci
This commit documents the :shell command in ghci.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
a4ff12bb by Cheng Shao at 2025-09-17T19:33:09-04:00
ghc-internal: fix codepages program
codepages was not properly updated during the base -> ghc-internal
migration, this commit fixes it.
- - - - -
7e094def by Cheng Shao at 2025-09-17T19:33:09-04:00
ghc-internal: relax ucd2haskell cabal upper bounds
This commit relaxes ucd2haskell cabal upper bounds to make it runnable
via ghc 9.12/9.14.
- - - - -
7077c9f7 by Cheng Shao at 2025-09-17T19:33:09-04:00
ghc-internal: update to unicode 17.0.0
This commit updates the generated code in ghc-internal to match
unicode 17.0.0.
- - - - -
cef8938f by sheaf at 2025-09-17T19:34:09-04:00
Bad record update msg: allow out-of-scope datacons
This commit ensures that, when we encounter an invalid record update
(because no constructor exists which contains all of the record fields
mentioned in the record update), we graciously handle the situation in
which the constructors themselves are not in scope. In that case,
instead of looking up the constructors in the GlobalRdrEnv, directly
look up their GREInfo using the lookupGREInfo function.
Fixes #26391
- - - - -
a2d9d7c2 by sheaf at 2025-09-17T19:34:09-04:00
Improve Notes about disambiguating record updates
This commit updates the notes [Disambiguating record updates] and
[Type-directed record disambiguation], in particular adding more
information about the deprecation status of type-directed disambiguation
of record updates.
- - - - -
6acb5e18 by Simon Peyton Jones at 2025-09-18T15:12:25+01:00
Improve pretty printer for HsExpr
Given a very deeply-nested application, it just kept printing
deeper and deeper. This small change makes it cut off.
Test is in #26330, but we also get a dramatic decrease in compile
time for perf/compiler/InstanceMatching:
InstanceMatching 4,086,884,584 1,181,767,232 -71.1% GOOD
Why? Because before we got a GIGANTIC error message that took
ages to pretty-print; now we get this much more civilised message
(I have removed some whitespace.)
Match.hs:1007:1: error:
• No instance for ‘Show (F001 a)’ arising from a use of ‘showsPrec’
• In the second argument of ‘showString’, namely
‘(showsPrec
11 b1
(GHC.Internal.Show.showSpace
(showsPrec
11 b2
(GHC.Internal.Show.showSpace
(showsPrec
11 b3
(GHC.Internal.Show.showSpace
(showsPrec
11 b4
(GHC.Internal.Show.showSpace
(showsPrec
11 b5
(GHC.Internal.Show.showSpace
(showsPrec
11 b6
(GHC.Internal.Show.showSpace (showsPrec ...)))))))))))))’
-----------------------
The main payload is
* At the start of `pprExpr`
* In the defn of `pprApp`
A little bit of refactoring:
* It turned out that we were setting the default cut-off depth to a
fixed value in two places, so changing one didn't change the other.
See defaultSDocDepth and defaultSDocCols
* I refactored `pprDeeperList` a bit so I could understand it better.
Because the depth calculation has changed, there are lots of small
error message wibbles.
Metric Decrease:
InstanceMatching
- - - - -
93 changed files:
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/Pat.hs
- compiler/GHC/Runtime/Heap/Inspect.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Utils/Outputable.hs
- docs/users_guide/9.16.1-notes.rst
- docs/users_guide/ghci.rst
- ghc/GHCi/UI.hs
- libraries/base/tests/unicode002.stdout
- libraries/base/tests/unicode003.stdout
- libraries/ghc-internal/codepages/MakeTable.hs
- libraries/ghc-internal/codepages/Makefile
- libraries/ghc-internal/src/GHC/Internal/Unicode/Char/DerivedCoreProperties.hs
- libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/GeneralCategory.hs
- libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleLowerCaseMapping.hs
- libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleTitleCaseMapping.hs
- libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleUpperCaseMapping.hs
- libraries/ghc-internal/src/GHC/Internal/Unicode/Version.hs
- libraries/ghc-internal/tools/ucd2haskell/ucd.sh
- libraries/ghc-internal/tools/ucd2haskell/ucd2haskell.cabal
- libraries/ghc-internal/tools/ucd2haskell/unicode_version
- testsuite/tests/arrows/gadt/T17423.stderr
- testsuite/tests/driver/multipleHomeUnits/all.T
- testsuite/tests/ghci.debugger/scripts/break022/all.T
- testsuite/tests/ghci.debugger/scripts/break022/break022.script
- testsuite/tests/ghci.debugger/scripts/break023/all.T
- testsuite/tests/ghci.debugger/scripts/break023/break023.script
- testsuite/tests/ghci/prog001/prog001.T
- testsuite/tests/ghci/prog001/prog001.script
- testsuite/tests/ghci/prog002/prog002.T
- testsuite/tests/ghci/prog002/prog002.script
- testsuite/tests/ghci/prog003/prog003.T
- testsuite/tests/ghci/prog003/prog003.script
- testsuite/tests/ghci/prog005/prog005.T
- testsuite/tests/ghci/prog005/prog005.script
- testsuite/tests/ghci/prog010/all.T
- testsuite/tests/ghci/prog010/ghci.prog010.script
- testsuite/tests/ghci/prog012/all.T
- testsuite/tests/ghci/prog012/prog012.script
- testsuite/tests/ghci/recompTHghci/all.T
- testsuite/tests/ghci/recompTHghci/recompTHghci.script
- testsuite/tests/ghci/scripts/T18330.script
- testsuite/tests/ghci/scripts/T18330.stdout
- testsuite/tests/ghci/scripts/T1914.script
- testsuite/tests/ghci/scripts/T20587.script
- testsuite/tests/ghci/scripts/T6106.script
- testsuite/tests/ghci/scripts/T8353.script
- testsuite/tests/ghci/scripts/all.T
- testsuite/tests/ghci/scripts/ghci038.script
- testsuite/tests/ghci/scripts/ghci058.script
- testsuite/tests/ghci/scripts/ghci063.script
- − testsuite/tests/ghci/shell.hs
- testsuite/tests/indexed-types/should_compile/PushedInAsGivens.stderr
- testsuite/tests/indexed-types/should_fail/T26176.stderr
- testsuite/tests/indexed-types/should_fail/T2693.stderr
- testsuite/tests/indexed-types/should_fail/T4093b.stderr
- testsuite/tests/indexed-types/should_fail/T8518.stderr
- testsuite/tests/indexed-types/should_fail/T9662.stderr
- testsuite/tests/linear/should_fail/Linear17.stderr
- testsuite/tests/linear/should_fail/LinearLet7.stderr
- + testsuite/tests/overloadedrecflds/should_fail/T26391.hs
- + testsuite/tests/overloadedrecflds/should_fail/T26391.stderr
- testsuite/tests/overloadedrecflds/should_fail/all.T
- testsuite/tests/parser/should_fail/RecordDotSyntaxFail10.stderr
- testsuite/tests/parser/should_fail/RecordDotSyntaxFail11.stderr
- testsuite/tests/parser/should_fail/RecordDotSyntaxFail13.stderr
- testsuite/tests/parser/should_fail/RecordDotSyntaxFail8.stderr
- testsuite/tests/partial-sigs/should_compile/T21719.stderr
- testsuite/tests/perf/compiler/MultiLayerModulesDefsGhci.script
- testsuite/tests/perf/compiler/all.T
- testsuite/tests/polykinds/T13393.stderr
- testsuite/tests/rep-poly/T12709.stderr
- testsuite/tests/simplCore/should_compile/simpl017.stderr
- testsuite/tests/th/T10945.stderr
- testsuite/tests/th/TH_StaticPointers02.stderr
- testsuite/tests/typecheck/should_compile/T11339.stderr
- testsuite/tests/typecheck/should_fail/DoExpansion3.stderr
- testsuite/tests/typecheck/should_fail/T12177.stderr
- testsuite/tests/typecheck/should_fail/T22707.stderr
- testsuite/tests/typecheck/should_fail/T24064.stderr
- + testsuite/tests/typecheck/should_fail/T26330.hs
- + testsuite/tests/typecheck/should_fail/T26330.stderr
- testsuite/tests/typecheck/should_fail/T8142.stderr
- testsuite/tests/typecheck/should_fail/T8603.stderr
- testsuite/tests/typecheck/should_fail/all.T
- testsuite/tests/typecheck/should_fail/tcfail128.stderr
- testsuite/tests/typecheck/should_fail/tcfail153.stderr
- testsuite/tests/typecheck/should_fail/tcfail168.stderr
- testsuite/tests/typecheck/should_fail/tcfail177.stderr
- testsuite/tests/typecheck/should_fail/tcfail185.stderr
- testsuite/tests/typecheck/should_run/Typeable1.stderr
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4a03551be9697c5cce416560c2e606…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4a03551be9697c5cce416560c2e606…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/9.12.3-backports] 2 commits: Bump Cabal submodule to 3.14.2.0
by Zubin (@wz1000) 18 Sep '25
by Zubin (@wz1000) 18 Sep '25
18 Sep '25
Zubin pushed to branch wip/9.12.3-backports at Glasgow Haskell Compiler / GHC
Commits:
593b5049 by Zubin Duggal at 2025-09-18T18:17:46+05:30
Bump Cabal submodule to 3.14.2.0
- - - - -
8d2bf5bd by Zubin Duggal at 2025-09-18T18:17:46+05:30
Prepare 9.12.3
- - - - -
10 changed files:
- .gitlab-ci.yml
- configure.ac
- docs/users_guide/9.12.3-notes.rst
- libraries/Cabal
- libraries/base/base.cabal.in
- libraries/base/changelog.md
- testsuite/driver/testlib.py
- testsuite/tests/backpack/cabal/bkpcabal08/bkpcabal08.stdout
- testsuite/tests/driver/T20604/T20604.stdout
- testsuite/tests/polykinds/T14172.stderr
Changes:
=====================================
.gitlab-ci.yml
=====================================
@@ -315,6 +315,7 @@ lint-ci-config:
- .gitlab/jobs-metadata.json
- .gitlab/jobs.yaml
dependencies: []
+ allow_failure: true
lint-submods:
extends: .lint-submods
=====================================
configure.ac
=====================================
@@ -22,7 +22,7 @@ AC_INIT([The Glorious Glasgow Haskell Compilation System], [9.12.2], [glasgow-ha
AC_CONFIG_MACRO_DIRS([m4])
# Set this to YES for a released version, otherwise NO
-: ${RELEASE=YES}
+: ${RELEASE=NO}
# The primary version (e.g. 7.5, 7.4.1) is set in the AC_INIT line
# above. If this is not a released version, then we will append the
=====================================
docs/users_guide/9.12.3-notes.rst
=====================================
@@ -13,6 +13,83 @@ Compiler
- Fixed re-exports of ``MkSolo`` and ``MkSolo#`` (:ghc-ticket:`25182`)
- Fixed the behavior of ``Language.Haskell.TH.mkName "FUN"`` (:ghc-ticket:`25174`)
+- Fixed miscompilation involving ``zonkEqTypes`` on ``AppTy/AppTy`` (:ghc-ticket:`26256`)
+- Fixed CprAnal to detect recursive newtypes (:ghc-ticket:`25944`)
+- Fixed specialisation of incoherent instances (:ghc-ticket:`25883`)
+- Fixed bytecode generation for ``tagToEnum# <LITERAL>`` (:ghc-ticket:`25975`)
+- Fixed panic with EmptyCase and RequiredTypeArguments (:ghc-ticket:`25004`)
+- Fixed ``tyConStupidTheta`` to handle ``PromotedDataCon`` (:ghc-ticket:`25739`)
+- Fixed unused import warnings for duplicate record fields (:ghc-ticket:`24035`)
+- Fixed lexing of ``"\^\"`` (:ghc-ticket:`25937`)
+- Fixed string gap collapsing (:ghc-ticket:`25784`)
+- Fixed lexing of comments in multiline strings (:ghc-ticket:`25609`)
+- Made unexpected LLVM versions a warning rather than an error (:ghc-ticket:`25915`)
+- Disabled ``-fprof-late-overloaded-calls`` for join points to avoid invalid transformations
+- Fixed bugs in ``integerRecipMod`` and ``integerPowMod`` (:ghc-ticket:`26017`)
+- Fixed ``naturalAndNot`` for NB/NS case (:ghc-ticket:`26230`)
+- Fixed ``ds_ev_typeable`` to use ``mkTrAppChecked`` (:ghc-ticket:`25998`)
+- Fixed GHC settings to always unescape escaped spaces (:ghc-ticket:`25204`)
+- Fixed issue with HasCallStack constraint caching (:ghc-ticket:`25529`)
+- Fixed archive member size writing logic in ``GHC.SysTools.Ar`` (:ghc-ticket:`26120`, :ghc-ticket:`22586`)
+
+Runtime System
+~~~~~~~~~~~~~~
+
+- Fixed ``MessageBlackHole.link`` to always be a valid closure
+- Fixed handling of WHITEHOLE in ``messageBlackHole`` (:ghc-ticket:`26205`)
+- Fixed ``rts_clearMemory`` logic when sanity checks are enabled (:ghc-ticket:`26011`)
+- Fixed underflow frame lookups in the bytecode interpreter (:ghc-ticket:`25750`)
+- Fixed overflows and reentrancy in interpreter statistics calculation (:ghc-ticket:`25756`)
+- Fixed INTERP_STATS profiling code (:ghc-ticket:`25695`)
+- Removed problematic ``n_free`` variable from nonmovingGC (:ghc-ticket:`26186`)
+- Fixed incorrect format specifiers in era profiling
+- Improved documentation of SLIDE and PACK bytecode instructions
+- Eliminated redundant ``SLIDE x 0`` bytecode instructions
+- Fixed compile issues on powerpc64 ELF v1
+
+Code Generation
+~~~~~~~~~~~~~~~
+
+- Fixed LLVM built-in variable predicate (was checking ``$llvm`` instead of ``@llvm``)
+- Fixed linkage of built-in arrays for LLVM (:ghc-ticket:`25769`)
+- Fixed code generation for SSE vector operations (:ghc-ticket:`25859`)
+- Fixed ``bswap64`` code generation on i386 (:ghc-ticket:`25601`)
+- Fixed sub-word arithmetic right shift on AArch64 (:ghc-ticket:`26061`)
+- Fixed LLVM vector literal emission to include type information
+- Fixed LLVM version detection
+- Fixed typo in ``padLiveArgs`` that caused segfaults (:ghc-ticket:`25770`, :ghc-ticket:`25773`)
+- Fixed constant-folding for Word->Float bitcasts
+- Added surface syntax for Word/Float bitcast operations
+- Fixed ``MOVD`` format in x86 NCG for ``unpackInt64X2#``
+- Added ``-finter-module-far-jumps`` flag for AArch64
+- Fixed RV64 J instruction handling for non-local jumps (:ghc-ticket:`25738`)
+- Reapplied division by constants optimization
+- Fixed TNTC to set CmmProc entry_label properly (:ghc-ticket:`25565`)
+
+Linker
+~~~~~~
+
+- Improved efficiency of proddable blocks structure (:ghc-ticket:`26009`)
+- Fixed Windows DLL loading to avoid redundant ``LoadLibraryEx`` calls (:ghc-ticket:`26009`)
+- Fixed incorrect use of ``break`` in nested for loop (:ghc-ticket:`26052`)
+- Fixed linker to not fail due to ``RTLD_NOW`` (:ghc-ticket:`25943`)
+- Dropped obsolete Windows XP compatibility checks
+
+GHCi
+~~~~
+
+- Fixed ``mkTopLevEnv`` to use ``loadInterfaceForModule`` instead of ``loadSrcInterface`` (:ghc-ticket:`25951`)
+
+Template Haskell
+~~~~~~~~~~~~~~~~
+
+- Added explicit export lists to all remaining template-haskell modules
+
+Build system
+~~~~~~~~~~~~~~~~
+
+- Exposed all of Backtraces' internals for ghc-internal (:ghc-ticket:`26049`)
+- Fixed cross-compilation configuration override (:ghc-ticket:`26236`)
Included libraries
~~~~~~~~~~~~~~~~~~
=====================================
libraries/Cabal
=====================================
@@ -1 +1 @@
-Subproject commit 269fd808e5d80223a229b6b19edfe6f5b109007a
+Subproject commit d265cc2d02f7d4a6b114a9ee6f903cc0a5984608
=====================================
libraries/base/base.cabal.in
=====================================
@@ -4,7 +4,7 @@ cabal-version: 3.0
-- Make sure you are editing ghc-experimental.cabal.in, not ghc-experimental.cabal
name: base
-version: 4.21.0.0
+version: 4.21.1.0
-- NOTE: Don't forget to update ./changelog.md
license: BSD-3-Clause
=====================================
libraries/base/changelog.md
=====================================
@@ -1,10 +1,8 @@
# Changelog for [`base` package](http://hackage.haskell.org/package/base)
-## 4.21.2.0 *Sept 2024*
- * Fix bug where `naturalAndNot` was incorrectly truncating results ([CLC proposal #350](github.com/haskell/core-libraries-committee/issues/350))
-
## 4.21.1.0 *Sept 2024*
* Fix incorrect results of `integerPowMod` when the base is 0 and the exponent is negative, and `integerRecipMod` when the modulus is zero ([#26017](https://gitlab.haskell.org/ghc/ghc/-/issues/26017)).
+ * Fix bug where `naturalAndNot` was incorrectly truncating results ([CLC proposal #350](github.com/haskell/core-libraries-committee/issues/350))
## 4.21.0.0 *December 2024*
* Shipped with GHC 9.12.1
=====================================
testsuite/driver/testlib.py
=====================================
@@ -1725,7 +1725,7 @@ async def do_test(name: TestName,
dst_makefile = in_testdir('Makefile')
if src_makefile.exists():
makefile = src_makefile.read_text(encoding='UTF-8')
- makefile = re.sub('TOP=.*', 'TOP=%s' % config.top, makefile, 1)
+ makefile = re.sub('TOP=.*', 'TOP=%s' % config.top, makefile, count=1)
dst_makefile.write_text(makefile, encoding='UTF-8')
if opts.pre_cmd:
=====================================
testsuite/tests/backpack/cabal/bkpcabal08/bkpcabal08.stdout
=====================================
@@ -13,13 +13,13 @@ Building library 'q' instantiated with
for bkpcabal08-0.1.0.0...
[2 of 4] Compiling B[sig] ( q/B.hsig, nothing )
[3 of 4] Compiling M ( q/M.hs, nothing ) [A changed]
-[4 of 4] Instantiating bkpcabal08-0.1.0.0-CoQJNXLfoYQ4TyvApzFHv-p
+[4 of 4] Instantiating bkpcabal08-0.1.0.0-Kp9zfG3ziUqEJBaLAu1d32-p
Preprocessing library 'q' for bkpcabal08-0.1.0.0...
Building library 'q' instantiated with
- A = bkpcabal08-0.1.0.0-5HJrxUERN7CD204UZeT4Ws-impl:A
- B = bkpcabal08-0.1.0.0-5HJrxUERN7CD204UZeT4Ws-impl:B
+ A = bkpcabal08-0.1.0.0-D4vXaroNoDaJMvvAtgjdtX-impl:A
+ B = bkpcabal08-0.1.0.0-D4vXaroNoDaJMvvAtgjdtX-impl:B
for bkpcabal08-0.1.0.0...
-[1 of 3] Compiling A[sig] ( q/A.hsig, dist/build/bkpcabal08-0.1.0.0-1DQJ9DKc4h59P07qcb0kBc-q+J5mAfRWG9IgLmFQVftCb8t/A.o ) [Prelude package changed]
-[2 of 3] Compiling B[sig] ( q/B.hsig, dist/build/bkpcabal08-0.1.0.0-1DQJ9DKc4h59P07qcb0kBc-q+J5mAfRWG9IgLmFQVftCb8t/B.o ) [Prelude package changed]
+[1 of 3] Compiling A[sig] ( q/A.hsig, dist/build/bkpcabal08-0.1.0.0-6DurfqyJQywFVtea63QYmb-q+22gYsRiIDs71N0vTkoa781/A.o ) [Prelude package changed]
+[2 of 3] Compiling B[sig] ( q/B.hsig, dist/build/bkpcabal08-0.1.0.0-6DurfqyJQywFVtea63QYmb-q+22gYsRiIDs71N0vTkoa781/B.o ) [Prelude package changed]
Preprocessing library 'r' for bkpcabal08-0.1.0.0...
Building library 'r' for bkpcabal08-0.1.0.0...
=====================================
testsuite/tests/driver/T20604/T20604.stdout
=====================================
@@ -1,11 +1,5 @@
A1
A
-addDependentFile "/home/zubin/ghcs/unicode-lex/_build_devel2/stage1/lib/../lib/x86_64-linux-ghc-9.10.2.20250728/ghc-prim-0.12.0-inplace/libHSghc-prim-0.12.0-inplace.a" 019a1208b8742850eeb197adcf0445f3
-addDependentFile "/home/zubin/ghcs/unicode-lex/_build_devel2/stage1/lib/../lib/x86_64-linux-ghc-9.10.2.20250728/ghc-bignum-1.3-inplace/libHSghc-bignum-1.3-inplace.a" ca54044c2ea501531ac3016a72a9d92b
-addDependentFile "/home/zubin/ghcs/unicode-lex/_build_devel2/stage1/lib/../lib/x86_64-linux-ghc-9.10.2.20250728/ghc-internal-9.1002.0-inplace/libHSghc-internal-9.1002.0-inplace.a" 1c2b59e426d6ae9172eb46d890155e19
-addDependentFile "/home/zubin/ghcs/unicode-lex/_build_devel2/stage1/lib/../lib/x86_64-linux-ghc-9.10.2.20250728/base-4.20.2.0-inplace/libHSbase-4.20.2.0-inplace.a" 820a64d9cb81281e10660ded650e973f
-addDependentFile "/home/zubin/ghcs/unicode-lex/_build_devel2/stage1/lib/../lib/x86_64-linux-ghc-9.10.2.20250728/ghc-boot-th-9.10.2.20250728-inplace/libHSghc-boot-th-9.10.2.20250728-inplace.a" 47565629d3614763d649bde91000bf42
-addDependentFile "/home/zubin/ghcs/unicode-lex/_build_devel2/stage1/lib/../lib/x86_64-linux-ghc-9.10.2.20250728/array-0.5.8.0-inplace/libHSarray-0.5.8.0-inplace.a" 7fb37d6d03900a689d24212e83d3f729
-addDependentFile "/home/zubin/ghcs/unicode-lex/_build_devel2/stage1/lib/../lib/x86_64-linux-ghc-9.10.2.20250728/deepseq-1.5.0.0-inplace/libHSdeepseq-1.5.0.0-inplace.a" 316be3ed9f3b5e893b2eb9924f8bb698
-addDependentFile "/home/zubin/ghcs/unicode-lex/_build_devel2/stage1/lib/../lib/x86_64-linux-ghc-9.10.2.20250728/pretty-1.1.3.6-inplace/libHSpretty-1.1.3.6-inplace.a" ab975b458837cd4dd7a38be2c7e71603
-addDependentFile "/home/zubin/ghcs/unicode-lex/_build_devel2/stage1/lib/../lib/x86_64-linux-ghc-9.10.2.20250728/template-haskell-2.22.0.0-inplace/libHStemplate-haskell-2.22.0.0-inplace.a" 8520e0f59701ce4073df664d176ade9c
+addDependentFile "/home/zubin/ghcs/exprType/_build_release/stage1/lib/../lib/x86_64-linux-ghc-9.12.2.20250917-inplace/libHSghc-prim-0.13.0-inplace-ghc9.12.2.20250917.so" 8803d0bdafc63e06222615bea8dc353d
+addDependentFile "/home/zubin/ghcs/exprType/_build_release/stage1/lib/../lib/x86_64-linux-ghc-9.12.2.20250917-inplace/libHSghc-bignum-1.3-inplace-ghc9.12.2.20250917.so" f17f0d2b06181c46da6178e187b358e0
+addDependentFile "/home/zubin/ghcs/exprType/_build_release/stage1/lib/../lib/x86_64-linux-ghc-9.12.2.20250917-inplace/libHSghc-internal-9.1202.0-inplace-ghc9.12.2.20250917.so" ec33682bace30c3a503fa37c72640d1c
=====================================
testsuite/tests/polykinds/T14172.stderr
=====================================
@@ -1,6 +1,6 @@
T14172.hs:7:46: error: [GHC-88464]
- • Found type wildcard ‘_’ standing for ‘a'1 :: k0’
- Where: ‘k0’ is an ambiguous type variable
+ • Found type wildcard ‘_’ standing for ‘a'1 :: k30’
+ Where: ‘k30’ is an ambiguous type variable
‘a'1’ is an ambiguous type variable
To use the inferred type, enable PartialTypeSignatures
• In the first argument of ‘h’, namely ‘_’
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/35866ae93502c05b1e1c9dcf89d89f…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/35866ae93502c05b1e1c9dcf89d89f…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/batch-loaddll] 11 commits: ghci: add :shell command
by Cheng Shao (@TerrorJack) 18 Sep '25
by Cheng Shao (@TerrorJack) 18 Sep '25
18 Sep '25
Cheng Shao pushed to branch wip/batch-loaddll at Glasgow Haskell Compiler / GHC
Commits:
06d25623 by Cheng Shao at 2025-09-17T19:32:27-04:00
ghci: add :shell command
This patch adds a new :shell command to ghci which works similarly to
:!, except it guarantees to run the command via sh -c. On POSIX hosts
the behavior is identical to :!, but on Windows it uses the msys2
shell instead of system cmd.exe shell. This is convenient when writing
simple ghci scripts that run simple POSIX commands, and the behavior
can be expected to be coherent on both Windows and POSIX.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
186054f7 by Cheng Shao at 2025-09-17T19:32:27-04:00
testsuite: remove legacy :shell trick
This commit makes use of the built-in :shell functionality in ghci in
the test cases, and remove the legacy :shell trick.
- - - - -
0a3a4aa3 by Cheng Shao at 2025-09-17T19:32:27-04:00
docs: document :shell in ghci
This commit documents the :shell command in ghci.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
a4ff12bb by Cheng Shao at 2025-09-17T19:33:09-04:00
ghc-internal: fix codepages program
codepages was not properly updated during the base -> ghc-internal
migration, this commit fixes it.
- - - - -
7e094def by Cheng Shao at 2025-09-17T19:33:09-04:00
ghc-internal: relax ucd2haskell cabal upper bounds
This commit relaxes ucd2haskell cabal upper bounds to make it runnable
via ghc 9.12/9.14.
- - - - -
7077c9f7 by Cheng Shao at 2025-09-17T19:33:09-04:00
ghc-internal: update to unicode 17.0.0
This commit updates the generated code in ghc-internal to match
unicode 17.0.0.
- - - - -
cef8938f by sheaf at 2025-09-17T19:34:09-04:00
Bad record update msg: allow out-of-scope datacons
This commit ensures that, when we encounter an invalid record update
(because no constructor exists which contains all of the record fields
mentioned in the record update), we graciously handle the situation in
which the constructors themselves are not in scope. In that case,
instead of looking up the constructors in the GlobalRdrEnv, directly
look up their GREInfo using the lookupGREInfo function.
Fixes #26391
- - - - -
a2d9d7c2 by sheaf at 2025-09-17T19:34:09-04:00
Improve Notes about disambiguating record updates
This commit updates the notes [Disambiguating record updates] and
[Type-directed record disambiguation], in particular adding more
information about the deprecation status of type-directed disambiguation
of record updates.
- - - - -
ca6864df by Cheng Shao at 2025-09-18T13:41:57+02:00
compiler/ghci: replace the LoadDLL message with LoadDLLs
As a part of #25407, this commit changes the LoadDLL message to
LoadDLLs, which takes a list of DLL paths to load and returns the list
of remote pointer handles. The wasm dyld is refactored to take
advantage of LoadDLLs and harvest background parallelism. On other
platforms, LoadDLLs is based on a fallback codepath that does
sequential loading.
The driver is not actually emitting singular LoadDLLs message with
multiple DLLs yet, this is left in subsequent commits.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
193509d0 by Cheng Shao at 2025-09-18T13:41:57+02:00
driver: separate downsweep/upsweep phase in loadPackages'
This commit refactors GHC.Linker.Loader.loadPackages' to be separated
into downsweep/upsweep phases:
- The downsweep phase performs dependency analysis and generates a
list of topologically sorted packages to load
- The upsweep phase sequentially loads these packages by calling
loadPackage
This is a necessary refactoring to make it possible to make loading of
DLLs concurrent.
- - - - -
9fa89818 by Cheng Shao at 2025-09-18T13:46:10+02:00
driver: emit single LoadDLLs message to load multiple DLLs
This commit refactors the driver so that it emits a single LoadDLLs
message to load multiple DLLs in GHC.Linker.Loader.loadPackages'.
Closes #25407.
-------------------------
Metric Increase:
MultiLayerModulesTH_OneShot
TcPlugin_RewritePerf
-------------------------
- - - - -
64 changed files:
- compiler/GHC/Driver/Plugins.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Linker/MacOS.hs
- compiler/GHC/Linker/Types.hs
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/Pat.hs
- compiler/GHC/Runtime/Interpreter.hs
- compiler/GHC/Tc/Gen/Expr.hs
- docs/users_guide/9.16.1-notes.rst
- docs/users_guide/ghci.rst
- ghc/GHCi/UI.hs
- libraries/base/tests/unicode002.stdout
- libraries/base/tests/unicode003.stdout
- libraries/ghc-internal/codepages/MakeTable.hs
- libraries/ghc-internal/codepages/Makefile
- libraries/ghc-internal/src/GHC/Internal/Unicode/Char/DerivedCoreProperties.hs
- libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/GeneralCategory.hs
- libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleLowerCaseMapping.hs
- libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleTitleCaseMapping.hs
- libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleUpperCaseMapping.hs
- libraries/ghc-internal/src/GHC/Internal/Unicode/Version.hs
- libraries/ghc-internal/tools/ucd2haskell/ucd.sh
- libraries/ghc-internal/tools/ucd2haskell/ucd2haskell.cabal
- libraries/ghc-internal/tools/ucd2haskell/unicode_version
- libraries/ghci/GHCi/Message.hs
- libraries/ghci/GHCi/ObjLink.hs
- libraries/ghci/GHCi/Run.hs
- testsuite/tests/driver/multipleHomeUnits/all.T
- testsuite/tests/ghci.debugger/scripts/break022/all.T
- testsuite/tests/ghci.debugger/scripts/break022/break022.script
- testsuite/tests/ghci.debugger/scripts/break023/all.T
- testsuite/tests/ghci.debugger/scripts/break023/break023.script
- testsuite/tests/ghci/prog001/prog001.T
- testsuite/tests/ghci/prog001/prog001.script
- testsuite/tests/ghci/prog002/prog002.T
- testsuite/tests/ghci/prog002/prog002.script
- testsuite/tests/ghci/prog003/prog003.T
- testsuite/tests/ghci/prog003/prog003.script
- testsuite/tests/ghci/prog005/prog005.T
- testsuite/tests/ghci/prog005/prog005.script
- testsuite/tests/ghci/prog010/all.T
- testsuite/tests/ghci/prog010/ghci.prog010.script
- testsuite/tests/ghci/prog012/all.T
- testsuite/tests/ghci/prog012/prog012.script
- testsuite/tests/ghci/recompTHghci/all.T
- testsuite/tests/ghci/recompTHghci/recompTHghci.script
- testsuite/tests/ghci/scripts/T18330.script
- testsuite/tests/ghci/scripts/T18330.stdout
- testsuite/tests/ghci/scripts/T1914.script
- testsuite/tests/ghci/scripts/T20587.script
- testsuite/tests/ghci/scripts/T6106.script
- testsuite/tests/ghci/scripts/T8353.script
- testsuite/tests/ghci/scripts/all.T
- testsuite/tests/ghci/scripts/ghci038.script
- testsuite/tests/ghci/scripts/ghci058.script
- testsuite/tests/ghci/scripts/ghci063.script
- − testsuite/tests/ghci/shell.hs
- + testsuite/tests/overloadedrecflds/should_fail/T26391.hs
- + testsuite/tests/overloadedrecflds/should_fail/T26391.stderr
- testsuite/tests/overloadedrecflds/should_fail/all.T
- testsuite/tests/perf/compiler/MultiLayerModulesDefsGhci.script
- testsuite/tests/perf/compiler/all.T
- testsuite/tests/rts/linker/T2615.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/c598a52ef4307751c2b7da8d196e5e…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c598a52ef4307751c2b7da8d196e5e…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 2 commits: Enable TcM plugins in initTc
by Marge Bot (@marge-bot) 18 Sep '25
by Marge Bot (@marge-bot) 18 Sep '25
18 Sep '25
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
7720420a by sheaf at 2025-09-18T06:59:28-04:00
Enable TcM plugins in initTc
This commit ensures that we run typechecker plugins and defaulting
plugins whenever we call initTc.
In particular, this ensures that the pattern-match checker, which calls
'initTcDsForSolver' which calls 'initTc', runs with typechecker plugins
enabled. This matters for situations like:
merge :: Vec n a -> Vec n a -> Vec (2 * n) a
merge Nil Nil = Nil
merge (a <: as) (b <: bs) = a :< (b <: merge as bs)
in which we need the typechecker plugin to run in order to tell us that
the Givens would be inconsistent in the additional equation
merge (_ <: _) Nil
and thus that the equation is not needed.
Fixes #26395
- - - - -
e018feaf by Cheng Shao at 2025-09-18T06:59:29-04:00
rel-eng: update fedora image to 42
This patch is a part of #25876 and updates fedora image to 42.
- - - - -
12 changed files:
- .gitlab-ci.yml
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- compiler/GHC/HsToCore/Monad.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Tc/Utils/Monad.hs
- + testsuite/tests/tcplugins/T26395.hs
- + testsuite/tests/tcplugins/T26395.stderr
- + testsuite/tests/tcplugins/T26395_Plugin.hs
- testsuite/tests/tcplugins/all.T
Changes:
=====================================
.gitlab-ci.yml
=====================================
@@ -2,7 +2,7 @@ variables:
GIT_SSL_NO_VERIFY: "1"
# Commit of ghc/ci-images repository from which to pull Docker images
- DOCKER_REV: be4ac2cd18f38e63b263e2a27c76a7c279385796
+ DOCKER_REV: a97d5c67d803c6b3811c6cccdf33dc8e9d7eafe3
# Sequential version number of all cached things.
# Bump to invalidate GitLab CI cache.
@@ -433,14 +433,14 @@ hadrian-ghc-in-ghci:
hadrian-multi:
stage: testing
needs:
- - job: x86_64-linux-fedora33-release
+ - job: x86_64-linux-fedora42-release
optional: true
- - job: nightly-x86_64-linux-fedora33-release
+ - job: nightly-x86_64-linux-fedora42-release
optional: true
- - job: release-x86_64-linux-fedora33-release
+ - job: release-x86_64-linux-fedora42-release
optional: true
dependencies: null
- image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora33:$DOCKER_REV"
+ image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora42:$DOCKER_REV"
before_script:
# workaround for docker permissions
- sudo chown ghc:ghc -R .
@@ -460,7 +460,7 @@ hadrian-multi:
- ls
- |
mkdir tmp
- tar -xf ghc-x86_64-linux-fedora33-release.tar.xz -C tmp
+ tar -xf ghc-x86_64-linux-fedora42-release.tar.xz -C tmp
pushd tmp/ghc-*/
./configure --prefix=$root
make install
@@ -522,17 +522,17 @@ test-cabal-reinstall-x86_64-linux-deb10:
abi-test-nightly:
stage: full-build
needs:
- - job: nightly-x86_64-linux-fedora33-release-hackage
- - job: nightly-x86_64-linux-fedora33-release
+ - job: nightly-x86_64-linux-fedora42-release-hackage
+ - job: nightly-x86_64-linux-fedora42-release
tags:
- x86_64-linux
- image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora33:$DOCKER_REV"
+ image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora42:$DOCKER_REV"
dependencies: null
before_script:
- mkdir -p normal
- mkdir -p hackage
- - tar -xf ghc-x86_64-linux-fedora33-release.tar.xz -C normal/
- - tar -xf ghc-x86_64-linux-fedora33-release-hackage_docs.tar.xz -C hackage/
+ - tar -xf ghc-x86_64-linux-fedora42-release.tar.xz -C normal/
+ - tar -xf ghc-x86_64-linux-fedora42-release-hackage_docs.tar.xz -C hackage/
script:
- .gitlab/ci.sh compare_interfaces_of "normal/ghc-*" "hackage/ghc-*"
artifacts:
@@ -609,9 +609,9 @@ doc-tarball:
hackage-doc-tarball:
stage: packaging
needs:
- - job: nightly-x86_64-linux-fedora33-release-hackage
+ - job: nightly-x86_64-linux-fedora42-release-hackage
optional: true
- - job: release-x86_64-linux-fedora33-release-hackage
+ - job: release-x86_64-linux-fedora42-release-hackage
optional: true
- job: source-tarball
tags:
@@ -628,7 +628,7 @@ hackage-doc-tarball:
- hackage_docs
before_script:
- tar -xf ghc-*[0-9]-src.tar.xz
- - tar -xf ghc-x86_64-linux-fedora33-release.tar.xz -C ghc*/
+ - tar -xf ghc-x86_64-linux-fedora42-release.tar.xz -C ghc*/
script:
- cd ghc*/
- mv .gitlab/rel_eng/upload_ghc_libs.py .
@@ -754,7 +754,7 @@ test-bootstrap:
# Triggering jobs in the ghc/head.hackage project requires that we have a job
# token for that repository. Furthermore the head.hackage CI job must have
# access to an unprivileged access token with the ability to query the ghc/ghc
-# project such that it can find the job ID of the fedora33 job for the current
+# project such that it can find the job ID of the fedora42 job for the current
# pipeline.
#
# hackage-lint: Can be triggered on any MR, normal validate pipeline or nightly build.
@@ -841,7 +841,7 @@ nightly-hackage-lint:
nightly-hackage-perf:
needs:
- - job: nightly-x86_64-linux-fedora33-release
+ - job: nightly-x86_64-linux-fedora42-release
optional: true
artifacts: false
- job: nightly-aarch64-linux-deb12-validate
@@ -860,7 +860,7 @@ nightly-hackage-perf:
release-hackage-lint:
needs:
- - job: release-x86_64-linux-fedora33-release
+ - job: release-x86_64-linux-fedora42-release
optional: true
artifacts: false
- job: release-aarch64-linux-deb12-release+no_split_sections
@@ -946,13 +946,13 @@ perf-nofib:
allow_failure: true
stage: testing
needs:
- - job: x86_64-linux-fedora33-release
+ - job: x86_64-linux-fedora42-release
optional: true
- - job: nightly-x86_64-linux-fedora33-release
+ - job: nightly-x86_64-linux-fedora42-release
optional: true
- - job: release-x86_64-linux-fedora33-release
+ - job: release-x86_64-linux-fedora42-release
optional: true
- image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora33:$DOCKER_REV"
+ image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora42:$DOCKER_REV"
rules:
- when: never
- *full-ci
@@ -965,7 +965,7 @@ perf-nofib:
- root=$(pwd)/ghc
- |
mkdir tmp
- tar -xf ../ghc-x86_64-linux-fedora33-release.tar.xz -C tmp
+ tar -xf ../ghc-x86_64-linux-fedora42-release.tar.xz -C tmp
pushd tmp/ghc-*/
./configure --prefix=$root
make install
@@ -989,21 +989,21 @@ perf-nofib:
perf:
stage: testing
needs:
- - job: x86_64-linux-fedora33-release
+ - job: x86_64-linux-fedora42-release
optional: true
- - job: nightly-x86_64-linux-fedora33-release
+ - job: nightly-x86_64-linux-fedora42-release
optional: true
- - job: release-x86_64-linux-fedora33-release
+ - job: release-x86_64-linux-fedora42-release
optional: true
dependencies: null
- image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora33:$DOCKER_REV"
+ image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora42:$DOCKER_REV"
tags:
- x86_64-linux-perf
script:
- root=$(pwd)/ghc
- |
mkdir tmp
- tar -xf ghc-x86_64-linux-fedora33-release.tar.xz -C tmp
+ tar -xf ghc-x86_64-linux-fedora42-release.tar.xz -C tmp
pushd tmp/ghc-*/
./configure --prefix=$root
make install
@@ -1027,14 +1027,14 @@ perf:
abi-test:
stage: testing
needs:
- - job: x86_64-linux-fedora33-release
+ - job: x86_64-linux-fedora42-release
optional: true
- - job: nightly-x86_64-linux-fedora33-release
+ - job: nightly-x86_64-linux-fedora42-release
optional: true
- - job: release-x86_64-linux-fedora33-release
+ - job: release-x86_64-linux-fedora42-release
optional: true
dependencies: null
- image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora33:$DOCKER_REV"
+ image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora42:$DOCKER_REV"
rules:
- if: $CI_MERGE_REQUEST_ID
- if: '$CI_COMMIT_BRANCH == "master"'
@@ -1045,7 +1045,7 @@ abi-test:
- root=$(pwd)/ghc
- |
mkdir tmp
- tar -xf ghc-x86_64-linux-fedora33-release.tar.xz -C tmp
+ tar -xf ghc-x86_64-linux-fedora42-release.tar.xz -C tmp
pushd tmp/ghc-*/
./configure --prefix=$root
make install
@@ -1200,7 +1200,7 @@ ghcup-metadata-nightly:
extends: .ghcup-metadata
# Explicit needs for validate pipeline because we only need certain bindists
needs:
- - job: nightly-x86_64-linux-fedora33-release
+ - job: nightly-x86_64-linux-fedora42-release
artifacts: false
- job: nightly-x86_64-linux-ubuntu24_04-validate
artifacts: false
@@ -1251,7 +1251,7 @@ ghcup-metadata-nightly:
# Update the ghcup metadata with information about this nightly pipeline
ghcup-metadata-nightly-push:
stage: deploy
- image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora33:$DOCKER_REV"
+ image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora42:$DOCKER_REV"
dependencies: null
tags:
- x86_64-linux
=====================================
.gitlab/generate-ci/gen_ci.hs
=====================================
@@ -82,7 +82,7 @@ The generated names for the jobs is important as there are a few downstream cons
of the jobs artifacts. Therefore some care should be taken if changing the generated
names of jobs to update these other places.
-1. Fedora33 jobs are required by head.hackage
+1. fedora42 jobs are required by head.hackage
2. The fetch-gitlab release utility pulls release artifacts from the
3. The ghc-head-from script downloads release artifacts based on a pipeline change.
4. Some subsequent CI jobs have explicit dependencies (for example docs-tarball, perf, perf-nofib)
@@ -118,8 +118,7 @@ data LinuxDistro
| Debian11Js
| Debian10
| Debian9
- | Fedora33
- | Fedora38
+ | Fedora42
| Ubuntu2404LoongArch64
| Ubuntu2404
| Ubuntu2204
@@ -319,8 +318,7 @@ distroName Debian12Riscv = "deb12-riscv"
distroName Debian12Wine = "deb12-wine"
distroName Debian10 = "deb10"
distroName Debian9 = "deb9"
-distroName Fedora33 = "fedora33"
-distroName Fedora38 = "fedora38"
+distroName Fedora42 = "fedora42"
distroName Ubuntu2404LoongArch64 = "ubuntu24_04-loongarch"
distroName Ubuntu1804 = "ubuntu18_04"
distroName Ubuntu2004 = "ubuntu20_04"
@@ -501,14 +499,6 @@ alpineVariables arch = mconcat $
distroVariables :: Arch -> LinuxDistro -> Variables
distroVariables arch Alpine312 = alpineVariables arch
distroVariables arch Alpine322 = alpineVariables arch
-distroVariables _ Fedora33 = mconcat
- -- LLC/OPT do not work for some reason in our fedora images
- -- These tests fail with this error: T11649 T5681 T7571 T8131b
- -- +/opt/llvm/bin/opt: /lib64/libtinfo.so.5: no version information available (required by /opt/llvm/bin/opt)
- -- +/opt/llvm/bin/llc: /lib64/libtinfo.so.5: no version information available (required by /opt/llvm/bin/llc)
- [ "LLC" =: "/bin/false"
- , "OPT" =: "/bin/false"
- ]
distroVariables _ _ = mempty
-----------------------------------------------------------------------------
@@ -1207,13 +1197,13 @@ rhel_x86 =
fedora_x86 :: [JobGroup Job]
fedora_x86 =
- [ -- Fedora33 job is always built with perf so there's one job in the normal
+ [ -- Fedora42 job is always built with perf so there's one job in the normal
-- validate pipeline which is built with perf.
- fastCI (standardBuildsWithConfig Amd64 (Linux Fedora33) releaseConfig)
+ fastCI (standardBuildsWithConfig Amd64 (Linux Fedora42) releaseConfig)
-- This job is only for generating head.hackage docs
- , hackage_doc_job (disableValidate (standardBuildsWithConfig Amd64 (Linux Fedora33) releaseConfig))
- , disableValidate (standardBuildsWithConfig Amd64 (Linux Fedora33) dwarf)
- , disableValidate (standardBuilds Amd64 (Linux Fedora38))
+ , hackage_doc_job (disableValidate (standardBuildsWithConfig Amd64 (Linux Fedora42) releaseConfig))
+ , disableValidate (standardBuildsWithConfig Amd64 (Linux Fedora42) dwarf)
+ , disableValidate (standardBuilds Amd64 (Linux Fedora42))
]
where
hackage_doc_job = rename (<> "-hackage") . modifyJobs (addVariable "HADRIAN_ARGS" "--haddock-for-hackage")
@@ -1375,7 +1365,7 @@ platform_mapping = Map.map go combined_result
, "x86_64-linux-deb11-validate"
, "x86_64-linux-deb12-validate"
, "x86_64-linux-deb10-validate+debug_info"
- , "x86_64-linux-fedora33-release"
+ , "x86_64-linux-fedora42-release"
, "x86_64-linux-deb11-cross_aarch64-linux-gnu-validate"
, "x86_64-windows-validate"
, "aarch64-linux-deb12-validate"
@@ -1390,13 +1380,13 @@ platform_mapping = Map.map go combined_result
, "nightly-aarch64-linux-deb12-wine-int_native-cross_aarch64-unknown-mingw32-validate"
, "nightly-x86_64-linux-alpine3_12-validate+fully_static"
, "nightly-x86_64-linux-deb10-validate"
- , "nightly-x86_64-linux-fedora33-release"
+ , "nightly-x86_64-linux-fedora42-release"
, "nightly-x86_64-windows-validate"
, "release-x86_64-linux-alpine3_12-release+fully_static+no_split_sections"
, "release-x86_64-linux-deb10-release"
, "release-x86_64-linux-deb11-release"
, "release-x86_64-linux-deb12-release"
- , "release-x86_64-linux-fedora33-release"
+ , "release-x86_64-linux-fedora42-release"
, "release-x86_64-windows-release"
]
=====================================
.gitlab/jobs.yaml
=====================================
@@ -2942,7 +2942,7 @@
"XZ_OPT": "-9"
}
},
- "nightly-x86_64-linux-fedora33-release": {
+ "nightly-x86_64-linux-fedora42-release": {
"after_script": [
".gitlab/ci.sh save_cache",
".gitlab/ci.sh save_test_output",
@@ -2953,7 +2953,7 @@
"artifacts": {
"expire_in": "8 weeks",
"paths": [
- "ghc-x86_64-linux-fedora33-release.tar.xz",
+ "ghc-x86_64-linux-fedora42-release.tar.xz",
"junit.xml",
"unexpected-test-output.tar.gz"
],
@@ -2963,14 +2963,14 @@
"when": "always"
},
"cache": {
- "key": "x86_64-linux-fedora33-$CACHE_REV",
+ "key": "x86_64-linux-fedora42-$CACHE_REV",
"paths": [
"cabal-cache",
"toolchain"
]
},
"dependencies": [],
- "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora33:$DOCKER_REV",
+ "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora42:$DOCKER_REV",
"needs": [
{
"artifacts": false,
@@ -2996,18 +2996,16 @@
],
"variables": {
"BIGNUM_BACKEND": "gmp",
- "BIN_DIST_NAME": "ghc-x86_64-linux-fedora33-release",
+ "BIN_DIST_NAME": "ghc-x86_64-linux-fedora42-release",
"BUILD_FLAVOUR": "release",
"CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
"INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
- "LLC": "/bin/false",
- "OPT": "/bin/false",
"RUNTEST_ARGS": "",
- "TEST_ENV": "x86_64-linux-fedora33-release",
+ "TEST_ENV": "x86_64-linux-fedora42-release",
"XZ_OPT": "-9"
}
},
- "nightly-x86_64-linux-fedora33-release-hackage": {
+ "nightly-x86_64-linux-fedora42-release-hackage": {
"after_script": [
".gitlab/ci.sh save_cache",
".gitlab/ci.sh save_test_output",
@@ -3018,7 +3016,7 @@
"artifacts": {
"expire_in": "8 weeks",
"paths": [
- "ghc-x86_64-linux-fedora33-release.tar.xz",
+ "ghc-x86_64-linux-fedora42-release.tar.xz",
"junit.xml",
"unexpected-test-output.tar.gz"
],
@@ -3028,14 +3026,14 @@
"when": "always"
},
"cache": {
- "key": "x86_64-linux-fedora33-$CACHE_REV",
+ "key": "x86_64-linux-fedora42-$CACHE_REV",
"paths": [
"cabal-cache",
"toolchain"
]
},
"dependencies": [],
- "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora33:$DOCKER_REV",
+ "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora42:$DOCKER_REV",
"needs": [
{
"artifacts": false,
@@ -3061,19 +3059,17 @@
],
"variables": {
"BIGNUM_BACKEND": "gmp",
- "BIN_DIST_NAME": "ghc-x86_64-linux-fedora33-release",
+ "BIN_DIST_NAME": "ghc-x86_64-linux-fedora42-release",
"BUILD_FLAVOUR": "release",
"CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
"HADRIAN_ARGS": "--haddock-for-hackage",
"INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
- "LLC": "/bin/false",
- "OPT": "/bin/false",
"RUNTEST_ARGS": "",
- "TEST_ENV": "x86_64-linux-fedora33-release",
+ "TEST_ENV": "x86_64-linux-fedora42-release",
"XZ_OPT": "-9"
}
},
- "nightly-x86_64-linux-fedora33-validate+debug_info": {
+ "nightly-x86_64-linux-fedora42-validate": {
"after_script": [
".gitlab/ci.sh save_cache",
".gitlab/ci.sh save_test_output",
@@ -3084,7 +3080,7 @@
"artifacts": {
"expire_in": "8 weeks",
"paths": [
- "ghc-x86_64-linux-fedora33-validate+debug_info.tar.xz",
+ "ghc-x86_64-linux-fedora42-validate.tar.xz",
"junit.xml",
"unexpected-test-output.tar.gz"
],
@@ -3094,14 +3090,14 @@
"when": "always"
},
"cache": {
- "key": "x86_64-linux-fedora33-$CACHE_REV",
+ "key": "x86_64-linux-fedora42-$CACHE_REV",
"paths": [
"cabal-cache",
"toolchain"
]
},
"dependencies": [],
- "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora33:$DOCKER_REV",
+ "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora42:$DOCKER_REV",
"needs": [
{
"artifacts": false,
@@ -3127,18 +3123,16 @@
],
"variables": {
"BIGNUM_BACKEND": "gmp",
- "BIN_DIST_NAME": "ghc-x86_64-linux-fedora33-validate+debug_info",
- "BUILD_FLAVOUR": "validate+debug_info",
+ "BIN_DIST_NAME": "ghc-x86_64-linux-fedora42-validate",
+ "BUILD_FLAVOUR": "validate",
"CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
"INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
- "LLC": "/bin/false",
- "OPT": "/bin/false",
"RUNTEST_ARGS": "",
- "TEST_ENV": "x86_64-linux-fedora33-validate+debug_info",
+ "TEST_ENV": "x86_64-linux-fedora42-validate",
"XZ_OPT": "-9"
}
},
- "nightly-x86_64-linux-fedora38-validate": {
+ "nightly-x86_64-linux-fedora42-validate+debug_info": {
"after_script": [
".gitlab/ci.sh save_cache",
".gitlab/ci.sh save_test_output",
@@ -3149,7 +3143,7 @@
"artifacts": {
"expire_in": "8 weeks",
"paths": [
- "ghc-x86_64-linux-fedora38-validate.tar.xz",
+ "ghc-x86_64-linux-fedora42-validate+debug_info.tar.xz",
"junit.xml",
"unexpected-test-output.tar.gz"
],
@@ -3159,14 +3153,14 @@
"when": "always"
},
"cache": {
- "key": "x86_64-linux-fedora38-$CACHE_REV",
+ "key": "x86_64-linux-fedora42-$CACHE_REV",
"paths": [
"cabal-cache",
"toolchain"
]
},
"dependencies": [],
- "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora38:$DOCKER_REV",
+ "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora42:$DOCKER_REV",
"needs": [
{
"artifacts": false,
@@ -3192,12 +3186,12 @@
],
"variables": {
"BIGNUM_BACKEND": "gmp",
- "BIN_DIST_NAME": "ghc-x86_64-linux-fedora38-validate",
- "BUILD_FLAVOUR": "validate",
+ "BIN_DIST_NAME": "ghc-x86_64-linux-fedora42-validate+debug_info",
+ "BUILD_FLAVOUR": "validate+debug_info",
"CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
"INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
"RUNTEST_ARGS": "",
- "TEST_ENV": "x86_64-linux-fedora38-validate",
+ "TEST_ENV": "x86_64-linux-fedora42-validate+debug_info",
"XZ_OPT": "-9"
}
},
@@ -4814,7 +4808,7 @@
"XZ_OPT": "-9"
}
},
- "release-x86_64-linux-fedora33-release": {
+ "release-x86_64-linux-fedora42-release": {
"after_script": [
".gitlab/ci.sh save_cache",
".gitlab/ci.sh save_test_output",
@@ -4825,7 +4819,7 @@
"artifacts": {
"expire_in": "1 year",
"paths": [
- "ghc-x86_64-linux-fedora33-release.tar.xz",
+ "ghc-x86_64-linux-fedora42-release.tar.xz",
"junit.xml",
"unexpected-test-output.tar.gz"
],
@@ -4835,14 +4829,14 @@
"when": "always"
},
"cache": {
- "key": "x86_64-linux-fedora33-$CACHE_REV",
+ "key": "x86_64-linux-fedora42-$CACHE_REV",
"paths": [
"cabal-cache",
"toolchain"
]
},
"dependencies": [],
- "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora33:$DOCKER_REV",
+ "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora42:$DOCKER_REV",
"needs": [
{
"artifacts": false,
@@ -4868,19 +4862,17 @@
],
"variables": {
"BIGNUM_BACKEND": "gmp",
- "BIN_DIST_NAME": "ghc-x86_64-linux-fedora33-release",
+ "BIN_DIST_NAME": "ghc-x86_64-linux-fedora42-release",
"BUILD_FLAVOUR": "release",
"CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
"IGNORE_PERF_FAILURES": "all",
"INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
- "LLC": "/bin/false",
- "OPT": "/bin/false",
"RUNTEST_ARGS": "",
- "TEST_ENV": "x86_64-linux-fedora33-release",
+ "TEST_ENV": "x86_64-linux-fedora42-release",
"XZ_OPT": "-9"
}
},
- "release-x86_64-linux-fedora33-release+debug_info": {
+ "release-x86_64-linux-fedora42-release+debug_info": {
"after_script": [
".gitlab/ci.sh save_cache",
".gitlab/ci.sh save_test_output",
@@ -4891,7 +4883,7 @@
"artifacts": {
"expire_in": "1 year",
"paths": [
- "ghc-x86_64-linux-fedora33-release+debug_info.tar.xz",
+ "ghc-x86_64-linux-fedora42-release+debug_info.tar.xz",
"junit.xml",
"unexpected-test-output.tar.gz"
],
@@ -4901,14 +4893,14 @@
"when": "always"
},
"cache": {
- "key": "x86_64-linux-fedora33-$CACHE_REV",
+ "key": "x86_64-linux-fedora42-$CACHE_REV",
"paths": [
"cabal-cache",
"toolchain"
]
},
"dependencies": [],
- "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora33:$DOCKER_REV",
+ "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora42:$DOCKER_REV",
"needs": [
{
"artifacts": false,
@@ -4934,19 +4926,17 @@
],
"variables": {
"BIGNUM_BACKEND": "gmp",
- "BIN_DIST_NAME": "ghc-x86_64-linux-fedora33-release+debug_info",
+ "BIN_DIST_NAME": "ghc-x86_64-linux-fedora42-release+debug_info",
"BUILD_FLAVOUR": "release+debug_info",
"CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
"IGNORE_PERF_FAILURES": "all",
"INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
- "LLC": "/bin/false",
- "OPT": "/bin/false",
"RUNTEST_ARGS": "",
- "TEST_ENV": "x86_64-linux-fedora33-release+debug_info",
+ "TEST_ENV": "x86_64-linux-fedora42-release+debug_info",
"XZ_OPT": "-9"
}
},
- "release-x86_64-linux-fedora33-release-hackage": {
+ "release-x86_64-linux-fedora42-release-hackage": {
"after_script": [
".gitlab/ci.sh save_cache",
".gitlab/ci.sh save_test_output",
@@ -4957,7 +4947,7 @@
"artifacts": {
"expire_in": "1 year",
"paths": [
- "ghc-x86_64-linux-fedora33-release.tar.xz",
+ "ghc-x86_64-linux-fedora42-release.tar.xz",
"junit.xml",
"unexpected-test-output.tar.gz"
],
@@ -4967,14 +4957,14 @@
"when": "always"
},
"cache": {
- "key": "x86_64-linux-fedora33-$CACHE_REV",
+ "key": "x86_64-linux-fedora42-$CACHE_REV",
"paths": [
"cabal-cache",
"toolchain"
]
},
"dependencies": [],
- "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora33:$DOCKER_REV",
+ "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora42:$DOCKER_REV",
"needs": [
{
"artifacts": false,
@@ -5000,80 +4990,14 @@
],
"variables": {
"BIGNUM_BACKEND": "gmp",
- "BIN_DIST_NAME": "ghc-x86_64-linux-fedora33-release",
+ "BIN_DIST_NAME": "ghc-x86_64-linux-fedora42-release",
"BUILD_FLAVOUR": "release",
"CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
"HADRIAN_ARGS": "--haddock-for-hackage",
"IGNORE_PERF_FAILURES": "all",
"INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
- "LLC": "/bin/false",
- "OPT": "/bin/false",
- "RUNTEST_ARGS": "",
- "TEST_ENV": "x86_64-linux-fedora33-release",
- "XZ_OPT": "-9"
- }
- },
- "release-x86_64-linux-fedora38-release": {
- "after_script": [
- ".gitlab/ci.sh save_cache",
- ".gitlab/ci.sh save_test_output",
- ".gitlab/ci.sh clean",
- "cat ci_timings.txt"
- ],
- "allow_failure": false,
- "artifacts": {
- "expire_in": "1 year",
- "paths": [
- "ghc-x86_64-linux-fedora38-release.tar.xz",
- "junit.xml",
- "unexpected-test-output.tar.gz"
- ],
- "reports": {
- "junit": "junit.xml"
- },
- "when": "always"
- },
- "cache": {
- "key": "x86_64-linux-fedora38-$CACHE_REV",
- "paths": [
- "cabal-cache",
- "toolchain"
- ]
- },
- "dependencies": [],
- "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora38:$DOCKER_REV",
- "needs": [
- {
- "artifacts": false,
- "job": "hadrian-ghc-in-ghci"
- }
- ],
- "rules": [
- {
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB == \"yes\") && ($NIGHTLY == null)",
- "when": "on_success"
- }
- ],
- "script": [
- "sudo chown ghc:ghc -R .",
- ".gitlab/ci.sh setup",
- ".gitlab/ci.sh configure",
- ".gitlab/ci.sh build_hadrian",
- ".gitlab/ci.sh test_hadrian"
- ],
- "stage": "full-build",
- "tags": [
- "x86_64-linux"
- ],
- "variables": {
- "BIGNUM_BACKEND": "gmp",
- "BIN_DIST_NAME": "ghc-x86_64-linux-fedora38-release",
- "BUILD_FLAVOUR": "release",
- "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
- "IGNORE_PERF_FAILURES": "all",
- "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
"RUNTEST_ARGS": "",
- "TEST_ENV": "x86_64-linux-fedora38-release",
+ "TEST_ENV": "x86_64-linux-fedora42-release",
"XZ_OPT": "-9"
}
},
@@ -7108,7 +7032,7 @@
"TEST_ENV": "x86_64-linux-deb9-validate"
}
},
- "x86_64-linux-fedora33-release": {
+ "x86_64-linux-fedora42-release": {
"after_script": [
".gitlab/ci.sh save_cache",
".gitlab/ci.sh save_test_output",
@@ -7119,7 +7043,7 @@
"artifacts": {
"expire_in": "2 weeks",
"paths": [
- "ghc-x86_64-linux-fedora33-release.tar.xz",
+ "ghc-x86_64-linux-fedora42-release.tar.xz",
"junit.xml",
"unexpected-test-output.tar.gz"
],
@@ -7129,14 +7053,14 @@
"when": "always"
},
"cache": {
- "key": "x86_64-linux-fedora33-$CACHE_REV",
+ "key": "x86_64-linux-fedora42-$CACHE_REV",
"paths": [
"cabal-cache",
"toolchain"
]
},
"dependencies": [],
- "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora33:$DOCKER_REV",
+ "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora42:$DOCKER_REV",
"needs": [
{
"artifacts": false,
@@ -7145,7 +7069,7 @@
],
"rules": [
{
- "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-fedora33-release(\\s|$).*/)) || (($ONLY_JOBS == null) && ((\"true\" == \"true\")))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+ "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-fedora42-release(\\s|$).*/)) || (($ONLY_JOBS == null) && ((\"true\" == \"true\")))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
"when": "on_success"
}
],
@@ -7162,17 +7086,15 @@
],
"variables": {
"BIGNUM_BACKEND": "gmp",
- "BIN_DIST_NAME": "ghc-x86_64-linux-fedora33-release",
+ "BIN_DIST_NAME": "ghc-x86_64-linux-fedora42-release",
"BUILD_FLAVOUR": "release",
"CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
"INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
- "LLC": "/bin/false",
- "OPT": "/bin/false",
"RUNTEST_ARGS": "",
- "TEST_ENV": "x86_64-linux-fedora33-release"
+ "TEST_ENV": "x86_64-linux-fedora42-release"
}
},
- "x86_64-linux-fedora33-release-hackage": {
+ "x86_64-linux-fedora42-release-hackage": {
"after_script": [
".gitlab/ci.sh save_cache",
".gitlab/ci.sh save_test_output",
@@ -7183,7 +7105,7 @@
"artifacts": {
"expire_in": "2 weeks",
"paths": [
- "ghc-x86_64-linux-fedora33-release.tar.xz",
+ "ghc-x86_64-linux-fedora42-release.tar.xz",
"junit.xml",
"unexpected-test-output.tar.gz"
],
@@ -7193,14 +7115,14 @@
"when": "always"
},
"cache": {
- "key": "x86_64-linux-fedora33-$CACHE_REV",
+ "key": "x86_64-linux-fedora42-$CACHE_REV",
"paths": [
"cabal-cache",
"toolchain"
]
},
"dependencies": [],
- "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora33:$DOCKER_REV",
+ "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora42:$DOCKER_REV",
"needs": [
{
"artifacts": false,
@@ -7209,7 +7131,7 @@
],
"rules": [
{
- "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-fedora33-release(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+ "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-fedora42-release(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
"when": "on_success"
}
],
@@ -7226,18 +7148,16 @@
],
"variables": {
"BIGNUM_BACKEND": "gmp",
- "BIN_DIST_NAME": "ghc-x86_64-linux-fedora33-release",
+ "BIN_DIST_NAME": "ghc-x86_64-linux-fedora42-release",
"BUILD_FLAVOUR": "release",
"CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
"HADRIAN_ARGS": "--haddock-for-hackage",
"INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
- "LLC": "/bin/false",
- "OPT": "/bin/false",
"RUNTEST_ARGS": "",
- "TEST_ENV": "x86_64-linux-fedora33-release"
+ "TEST_ENV": "x86_64-linux-fedora42-release"
}
},
- "x86_64-linux-fedora33-validate+debug_info": {
+ "x86_64-linux-fedora42-validate": {
"after_script": [
".gitlab/ci.sh save_cache",
".gitlab/ci.sh save_test_output",
@@ -7248,7 +7168,7 @@
"artifacts": {
"expire_in": "2 weeks",
"paths": [
- "ghc-x86_64-linux-fedora33-validate+debug_info.tar.xz",
+ "ghc-x86_64-linux-fedora42-validate.tar.xz",
"junit.xml",
"unexpected-test-output.tar.gz"
],
@@ -7258,14 +7178,14 @@
"when": "always"
},
"cache": {
- "key": "x86_64-linux-fedora33-$CACHE_REV",
+ "key": "x86_64-linux-fedora42-$CACHE_REV",
"paths": [
"cabal-cache",
"toolchain"
]
},
"dependencies": [],
- "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora33:$DOCKER_REV",
+ "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora42:$DOCKER_REV",
"needs": [
{
"artifacts": false,
@@ -7274,7 +7194,7 @@
],
"rules": [
{
- "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-fedora33-validate\\+debug_info(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+ "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-fedora42-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
"when": "on_success"
}
],
@@ -7291,17 +7211,15 @@
],
"variables": {
"BIGNUM_BACKEND": "gmp",
- "BIN_DIST_NAME": "ghc-x86_64-linux-fedora33-validate+debug_info",
- "BUILD_FLAVOUR": "validate+debug_info",
+ "BIN_DIST_NAME": "ghc-x86_64-linux-fedora42-validate",
+ "BUILD_FLAVOUR": "validate",
"CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
"INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
- "LLC": "/bin/false",
- "OPT": "/bin/false",
"RUNTEST_ARGS": "",
- "TEST_ENV": "x86_64-linux-fedora33-validate+debug_info"
+ "TEST_ENV": "x86_64-linux-fedora42-validate"
}
},
- "x86_64-linux-fedora38-validate": {
+ "x86_64-linux-fedora42-validate+debug_info": {
"after_script": [
".gitlab/ci.sh save_cache",
".gitlab/ci.sh save_test_output",
@@ -7312,7 +7230,7 @@
"artifacts": {
"expire_in": "2 weeks",
"paths": [
- "ghc-x86_64-linux-fedora38-validate.tar.xz",
+ "ghc-x86_64-linux-fedora42-validate+debug_info.tar.xz",
"junit.xml",
"unexpected-test-output.tar.gz"
],
@@ -7322,14 +7240,14 @@
"when": "always"
},
"cache": {
- "key": "x86_64-linux-fedora38-$CACHE_REV",
+ "key": "x86_64-linux-fedora42-$CACHE_REV",
"paths": [
"cabal-cache",
"toolchain"
]
},
"dependencies": [],
- "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora38:$DOCKER_REV",
+ "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora42:$DOCKER_REV",
"needs": [
{
"artifacts": false,
@@ -7338,7 +7256,7 @@
],
"rules": [
{
- "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-fedora38-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+ "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-fedora42-validate\\+debug_info(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
"when": "on_success"
}
],
@@ -7355,12 +7273,12 @@
],
"variables": {
"BIGNUM_BACKEND": "gmp",
- "BIN_DIST_NAME": "ghc-x86_64-linux-fedora38-validate",
- "BUILD_FLAVOUR": "validate",
+ "BIN_DIST_NAME": "ghc-x86_64-linux-fedora42-validate+debug_info",
+ "BUILD_FLAVOUR": "validate+debug_info",
"CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
"INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
"RUNTEST_ARGS": "",
- "TEST_ENV": "x86_64-linux-fedora38-validate"
+ "TEST_ENV": "x86_64-linux-fedora42-validate+debug_info"
}
},
"x86_64-linux-rocky8-validate": {
=====================================
.gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py
=====================================
@@ -23,10 +23,8 @@ def job_triple(job_name):
'release-x86_64-linux-ubuntu22_04-release': 'x86_64-ubuntu22_04-linux',
'release-x86_64-linux-ubuntu20_04-release': 'x86_64-ubuntu20_04-linux',
'release-x86_64-linux-ubuntu18_04-release': 'x86_64-ubuntu18_04-linux',
- 'release-x86_64-linux-fedora38-release': 'x86_64-fedora38-linux',
- 'release-x86_64-linux-fedora33-release+debug_info': 'x86_64-fedora33-linux-dwarf',
- 'release-x86_64-linux-fedora33-release': 'x86_64-fedora33-linux',
- 'release-x86_64-linux-fedora27-release': 'x86_64-fedora27-linux',
+ 'release-x86_64-linux-fedora42-release': 'x86_64-fedora42-linux',
+ 'release-x86_64-linux-fedora42-release+debug_info': 'x86_64-fedora42-linux-dwarf',
'release-x86_64-linux-deb12-release': 'x86_64-deb12-linux',
'release-x86_64-linux-deb11-release': 'x86_64-deb11-linux',
'release-x86_64-linux-deb10-release+debug_info': 'x86_64-deb10-linux-dwarf',
=====================================
.gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
=====================================
@@ -200,7 +200,7 @@ def mk_new_yaml(release_mode, version, date, pipeline_type, job_map):
ubuntu2204 = mk(ubuntu("22_04"))
ubuntu2404 = mk(ubuntu("24_04"))
rocky8 = mk(rocky("8"))
- fedora33 = mk(fedora(33))
+ fedora42 = mk(fedora(42))
darwin_x86 = mk(darwin("x86_64"))
darwin_arm64 = mk(darwin("aarch64"))
windows = mk(windowsArtifact)
@@ -239,11 +239,9 @@ def mk_new_yaml(release_mode, version, date, pipeline_type, job_map):
, "unknown_versioning": ubuntu2004 }
, "Linux_CentOS" : { "( >= 8 && < 9 )" : rocky8
, "unknown_versioning" : rocky8 }
- , "Linux_Fedora" : { ">= 33": fedora33
+ , "Linux_Fedora" : { ">= 42": fedora42
, "unknown_versioning": rocky8 }
- , "Linux_RedHat" : { "< 9": rocky8
- , ">= 9": fedora33
- , "unknown_versioning": fedora33 }
+ , "Linux_RedHat" : { "unknown_versioning": rocky8 }
, "Linux_UnknownLinux" : { "unknown_versioning": rocky8 }
, "Darwin" : { "unknown_versioning" : darwin_x86 }
, "Windows" : { "unknown_versioning" : windows }
=====================================
compiler/GHC/HsToCore/Monad.hs
=====================================
@@ -58,6 +58,7 @@ module GHC.HsToCore.Monad (
import GHC.Prelude
import GHC.Driver.Env
+import GHC.Driver.Env.KnotVars
import GHC.Driver.DynFlags
import GHC.Driver.Ppr
import GHC.Driver.Config.Diagnostic
@@ -117,7 +118,7 @@ import GHC.Utils.Panic
import qualified GHC.Data.Strict as Strict
import Data.IORef
-import GHC.Driver.Env.KnotVars
+
import GHC.IO.Unsafe (unsafeInterleaveIO)
{-
=====================================
compiler/GHC/Tc/Module.hs
=====================================
@@ -26,6 +26,7 @@ module GHC.Tc.Module (
runTcInteractive, -- Used by GHC API clients (#8878)
withTcPlugins, -- Used by GHC API clients (#20499)
withHoleFitPlugins, -- Used by GHC API clients (#20499)
+ withDefaultingPlugins,
tcRnLookupName,
tcRnGetInfo,
tcRnModule, tcRnModuleTcRnM,
@@ -53,7 +54,6 @@ import GHC.Driver.DynFlags
import GHC.Driver.Config.Diagnostic
import GHC.IO.Unsafe ( unsafeInterleaveIO )
-import GHC.Tc.Errors.Hole.Plugin ( HoleFitPluginR (..) )
import GHC.Tc.Errors.Types
import {-# SOURCE #-} GHC.Tc.Gen.Splice ( finishTH, runRemoteModFinalizers )
import GHC.Tc.Gen.HsType
@@ -141,7 +141,6 @@ import GHC.Types.Id as Id
import GHC.Types.Id.Info( IdDetails(..) )
import GHC.Types.Var.Env
import GHC.Types.TypeEnv
-import GHC.Types.Unique.FM
import GHC.Types.Name
import GHC.Types.Name.Env
import GHC.Types.Name.Set
@@ -212,10 +211,6 @@ tcRnModule hsc_env mod_sum save_rn_syntax
(text "Renamer/typechecker"<+>brackets (ppr this_mod))
(const ()) $
initTc hsc_env hsc_src save_rn_syntax this_mod real_loc $
- withTcPlugins hsc_env $
- withDefaultingPlugins hsc_env $
- withHoleFitPlugins hsc_env $
-
tcRnModuleTcRnM hsc_env mod_sum parsedModule this_mod
| otherwise
@@ -3182,72 +3177,11 @@ hasTopUserName x
{-
********************************************************************************
-Type Checker Plugins
+ Running plugins
********************************************************************************
-}
-withTcPlugins :: HscEnv -> TcM a -> TcM a
-withTcPlugins hsc_env m =
- case catMaybes $ mapPlugins (hsc_plugins hsc_env) tcPlugin of
- [] -> m -- Common fast case
- plugins -> do
- (solvers, rewriters, stops) <-
- unzip3 `fmap` mapM start_plugin plugins
- let
- rewritersUniqFM :: UniqFM TyCon [TcPluginRewriter]
- !rewritersUniqFM = sequenceUFMList rewriters
- -- The following ensures that tcPluginStop is called even if a type
- -- error occurs during compilation (Fix of #10078)
- eitherRes <- tryM $
- updGblEnv (\e -> e { tcg_tc_plugin_solvers = solvers
- , tcg_tc_plugin_rewriters = rewritersUniqFM }) m
- mapM_ runTcPluginM stops
- case eitherRes of
- Left _ -> failM
- Right res -> return res
- where
- start_plugin (TcPlugin start solve rewrite stop) =
- do s <- runTcPluginM start
- return (solve s, rewrite s, stop s)
-
-withDefaultingPlugins :: HscEnv -> TcM a -> TcM a
-withDefaultingPlugins hsc_env m =
- do case catMaybes $ mapPlugins (hsc_plugins hsc_env) defaultingPlugin of
- [] -> m -- Common fast case
- plugins -> do (plugins,stops) <- mapAndUnzipM start_plugin plugins
- -- This ensures that dePluginStop is called even if a type
- -- error occurs during compilation
- eitherRes <- tryM $ do
- updGblEnv (\e -> e { tcg_defaulting_plugins = plugins }) m
- mapM_ runTcPluginM stops
- case eitherRes of
- Left _ -> failM
- Right res -> return res
- where
- start_plugin (DefaultingPlugin start fill stop) =
- do s <- runTcPluginM start
- return (fill s, stop s)
-
-withHoleFitPlugins :: HscEnv -> TcM a -> TcM a
-withHoleFitPlugins hsc_env m =
- case catMaybes $ mapPlugins (hsc_plugins hsc_env) holeFitPlugin of
- [] -> m -- Common fast case
- plugins -> do (plugins,stops) <- mapAndUnzipM start_plugin plugins
- -- This ensures that hfPluginStop is called even if a type
- -- error occurs during compilation.
- eitherRes <- tryM $
- updGblEnv (\e -> e { tcg_hf_plugins = plugins }) m
- sequence_ stops
- case eitherRes of
- Left _ -> failM
- Right res -> return res
- where
- start_plugin (HoleFitPluginR init plugin stop) =
- do ref <- init
- return (plugin ref, stop ref)
-
-
runRenamerPlugin :: TcGblEnv
-> HsGroup GhcRn
-> TcM (TcGblEnv, HsGroup GhcRn)
=====================================
compiler/GHC/Tc/Utils/Monad.hs
=====================================
@@ -31,6 +31,9 @@ module GHC.Tc.Utils.Monad(
updateEps, updateEps_,
getHpt, getEpsAndHug,
+ -- * Initialising TcM plugins
+ withTcPlugins, withDefaultingPlugins, withHoleFitPlugins,
+
-- * Arrow scopes
newArrowScope, escapeArrowScope,
@@ -163,6 +166,7 @@ import GHC.Builtin.Names
import GHC.Builtin.Types( zonkAnyTyCon )
import GHC.Tc.Errors.Types
+import GHC.Tc.Errors.Hole.Plugin ( HoleFitPluginR (..) )
import GHC.Tc.Types -- Re-export all
import GHC.Tc.Types.Constraint
import GHC.Tc.Types.CtLoc
@@ -183,13 +187,17 @@ import GHC.Unit.Module.Warnings
import GHC.Unit.Home.PackageTable
import GHC.Core.UsageEnv
+
+import GHC.Core.Coercion ( isReflCo )
import GHC.Core.Multiplicity
import GHC.Core.InstEnv
import GHC.Core.FamInstEnv
import GHC.Core.Type( mkNumLitTy )
+import GHC.Core.TyCon ( TyCon )
import GHC.Driver.Env
import GHC.Driver.Env.KnotVars
+import GHC.Driver.Plugins ( Plugin(..), mapPlugins )
import GHC.Driver.Session
import GHC.Driver.Config.Diagnostic
@@ -226,7 +234,7 @@ import GHC.Types.SrcLoc
import GHC.Types.Name.Env
import GHC.Types.Name.Set
import GHC.Types.Name.Ppr
-import GHC.Types.Unique.FM ( emptyUFM )
+import GHC.Types.Unique.FM ( UniqFM, emptyUFM, sequenceUFMList )
import GHC.Types.Unique.DFM
import GHC.Types.Unique.Supply
import GHC.Types.Annotations
@@ -240,8 +248,6 @@ import Data.IORef
import Control.Monad
import qualified Data.Map as Map
-import GHC.Core.Coercion (isReflCo)
-
{-
************************************************************************
@@ -263,129 +269,139 @@ initTc :: HscEnv
-- (error messages should have been printed already)
initTc hsc_env hsc_src keep_rn_syntax mod loc do_this
- = do { keep_var <- newIORef emptyNameSet ;
- used_gre_var <- newIORef [] ;
- th_var <- newIORef False ;
- infer_var <- newIORef True ;
- infer_reasons_var <- newIORef emptyMessages ;
- dfun_n_var <- newIORef emptyOccSet ;
- zany_n_var <- newIORef 0 ;
- let { type_env_var = hsc_type_env_vars hsc_env };
-
- dependent_files_var <- newIORef [] ;
- dependent_dirs_var <- newIORef [] ;
- static_wc_var <- newIORef emptyWC ;
- cc_st_var <- newIORef newCostCentreState ;
- th_topdecls_var <- newIORef [] ;
- th_foreign_files_var <- newIORef [] ;
- th_topnames_var <- newIORef emptyNameSet ;
- th_modfinalizers_var <- newIORef [] ;
- th_coreplugins_var <- newIORef [] ;
- th_state_var <- newIORef Map.empty ;
- th_remote_state_var <- newIORef Nothing ;
- th_docs_var <- newIORef Map.empty ;
- th_needed_deps_var <- newIORef ([], emptyUDFM) ;
- next_wrapper_num <- newIORef emptyModuleEnv ;
- let {
- -- bangs to avoid leaking the env (#19356)
- !dflags = hsc_dflags hsc_env ;
- !mhome_unit = hsc_home_unit_maybe hsc_env;
- !logger = hsc_logger hsc_env ;
-
- maybe_rn_syntax :: forall a. a -> Maybe a ;
- maybe_rn_syntax empty_val
- | logHasDumpFlag logger Opt_D_dump_rn_ast = Just empty_val
-
- | gopt Opt_WriteHie dflags = Just empty_val
-
- -- We want to serialize the documentation in the .hi-files,
- -- and need to extract it from the renamed syntax first.
- -- See 'GHC.HsToCore.Docs.extractDocs'.
- | gopt Opt_Haddock dflags = Just empty_val
-
- | keep_rn_syntax = Just empty_val
- | otherwise = Nothing ;
-
- gbl_env = TcGblEnv {
- tcg_th_topdecls = th_topdecls_var,
- tcg_th_foreign_files = th_foreign_files_var,
- tcg_th_topnames = th_topnames_var,
- tcg_th_modfinalizers = th_modfinalizers_var,
- tcg_th_coreplugins = th_coreplugins_var,
- tcg_th_state = th_state_var,
- tcg_th_remote_state = th_remote_state_var,
- tcg_th_docs = th_docs_var,
-
- tcg_mod = mod,
- tcg_semantic_mod = homeModuleInstantiation mhome_unit mod,
- tcg_src = hsc_src,
- tcg_rdr_env = emptyGlobalRdrEnv,
- tcg_fix_env = emptyNameEnv,
- tcg_default = emptyDefaultEnv,
- tcg_default_exports = emptyDefaultEnv,
- tcg_type_env = emptyNameEnv,
- tcg_type_env_var = type_env_var,
- tcg_inst_env = emptyInstEnv,
- tcg_fam_inst_env = emptyFamInstEnv,
- tcg_ann_env = emptyAnnEnv,
- tcg_complete_match_env = [],
- tcg_th_used = th_var,
- tcg_th_needed_deps = th_needed_deps_var,
- tcg_exports = [],
- tcg_imports = emptyImportAvails,
- tcg_import_decls = [],
- tcg_used_gres = used_gre_var,
- tcg_dus = emptyDUs,
-
- tcg_rn_imports = [],
- tcg_rn_exports =
- if hsc_src == HsigFile
- -- Always retain renamed syntax, so that we can give
- -- better errors. (TODO: how?)
- then Just []
- else maybe_rn_syntax [],
- tcg_rn_decls = maybe_rn_syntax emptyRnGroup,
- tcg_tr_module = Nothing,
- tcg_binds = emptyLHsBinds,
- tcg_imp_specs = [],
- tcg_sigs = emptyNameSet,
- tcg_ksigs = emptyNameSet,
- tcg_ev_binds = emptyBag,
- tcg_warns = emptyWarn,
- tcg_anns = [],
- tcg_tcs = [],
- tcg_insts = [],
- tcg_fam_insts = [],
- tcg_rules = [],
- tcg_fords = [],
- tcg_patsyns = [],
- tcg_merged = [],
- tcg_dfun_n = dfun_n_var,
- tcg_zany_n = zany_n_var,
- tcg_keep = keep_var,
- tcg_hdr_info = (Nothing,Nothing),
- tcg_main = Nothing,
- tcg_self_boot = NoSelfBoot,
- tcg_safe_infer = infer_var,
- tcg_safe_infer_reasons = infer_reasons_var,
- tcg_dependent_files = dependent_files_var,
- tcg_dependent_dirs = dependent_dirs_var,
- tcg_tc_plugin_solvers = [],
- tcg_tc_plugin_rewriters = emptyUFM,
- tcg_defaulting_plugins = [],
- tcg_hf_plugins = [],
- tcg_top_loc = loc,
- tcg_static_wc = static_wc_var,
- tcg_complete_matches = [],
- tcg_cc_st = cc_st_var,
- tcg_next_wrapper_num = next_wrapper_num
- } ;
- } ;
+ = do { gbl_env <- initTcGblEnv hsc_env hsc_src keep_rn_syntax mod loc
-- OK, here's the business end!
- initTcWithGbl hsc_env gbl_env loc do_this
+ ; initTcWithGbl hsc_env gbl_env loc $
+
+ -- Make sure to initialise all TcM plugins from the ambient HscEnv.
+ --
+ -- This ensures that all callers of 'initTc' enable plugins (#26395).
+ withTcPlugins hsc_env $
+ withDefaultingPlugins hsc_env $
+ withHoleFitPlugins hsc_env $
+
+ do_this
}
+-- | Create an empty 'TcGblEnv'.
+initTcGblEnv :: HscEnv -> HscSource -> Bool -> Module -> RealSrcSpan -> IO TcGblEnv
+initTcGblEnv hsc_env hsc_src keep_rn_syntax mod loc =
+ do { keep_var <- newIORef emptyNameSet
+ ; used_gre_var <- newIORef []
+ ; th_var <- newIORef False
+ ; infer_var <- newIORef True
+ ; infer_reasons_var <- newIORef emptyMessages
+ ; dfun_n_var <- newIORef emptyOccSet
+ ; zany_n_var <- newIORef 0
+ ; dependent_files_var <- newIORef []
+ ; dependent_dirs_var <- newIORef []
+ ; static_wc_var <- newIORef emptyWC
+ ; cc_st_var <- newIORef newCostCentreState
+ ; th_topdecls_var <- newIORef []
+ ; th_foreign_files_var <- newIORef []
+ ; th_topnames_var <- newIORef emptyNameSet
+ ; th_modfinalizers_var <- newIORef []
+ ; th_coreplugins_var <- newIORef []
+ ; th_state_var <- newIORef Map.empty
+ ; th_remote_state_var <- newIORef Nothing
+ ; th_docs_var <- newIORef Map.empty
+ ; th_needed_deps_var <- newIORef ([], emptyUDFM)
+ ; next_wrapper_num <- newIORef emptyModuleEnv
+ ; let
+ -- bangs to avoid leaking the env (#19356)
+ !dflags = hsc_dflags hsc_env
+ !mhome_unit = hsc_home_unit_maybe hsc_env
+ !logger = hsc_logger hsc_env
+
+ maybe_rn_syntax :: forall a. a -> Maybe a ;
+ maybe_rn_syntax empty_val
+ | logHasDumpFlag logger Opt_D_dump_rn_ast = Just empty_val
+
+ | gopt Opt_WriteHie dflags = Just empty_val
+
+ -- We want to serialize the documentation in the .hi-files,
+ -- and need to extract it from the renamed syntax first.
+ -- See 'GHC.HsToCore.Docs.extractDocs'.
+ | gopt Opt_Haddock dflags = Just empty_val
+
+ | keep_rn_syntax = Just empty_val
+ | otherwise = Nothing ;
+
+ ; return $ TcGblEnv
+ { tcg_th_topdecls = th_topdecls_var
+ , tcg_th_foreign_files = th_foreign_files_var
+ , tcg_th_topnames = th_topnames_var
+ , tcg_th_modfinalizers = th_modfinalizers_var
+ , tcg_th_coreplugins = th_coreplugins_var
+ , tcg_th_state = th_state_var
+ , tcg_th_remote_state = th_remote_state_var
+ , tcg_th_docs = th_docs_var
+
+ , tcg_mod = mod
+ , tcg_semantic_mod = homeModuleInstantiation mhome_unit mod
+ , tcg_src = hsc_src
+ , tcg_rdr_env = emptyGlobalRdrEnv
+ , tcg_fix_env = emptyNameEnv
+ , tcg_default = emptyDefaultEnv
+ , tcg_default_exports = emptyDefaultEnv
+ , tcg_type_env = emptyNameEnv
+ , tcg_type_env_var = hsc_type_env_vars hsc_env
+ , tcg_inst_env = emptyInstEnv
+ , tcg_fam_inst_env = emptyFamInstEnv
+ , tcg_ann_env = emptyAnnEnv
+ , tcg_complete_match_env = []
+ , tcg_th_used = th_var
+ , tcg_th_needed_deps = th_needed_deps_var
+ , tcg_exports = []
+ , tcg_imports = emptyImportAvails
+ , tcg_import_decls = []
+ , tcg_used_gres = used_gre_var
+ , tcg_dus = emptyDUs
+
+ , tcg_rn_imports = []
+ , tcg_rn_exports = if hsc_src == HsigFile
+ -- Always retain renamed syntax, so that we can give
+ -- better errors. (TODO: how?)
+ then Just []
+ else maybe_rn_syntax []
+ , tcg_rn_decls = maybe_rn_syntax emptyRnGroup
+ , tcg_tr_module = Nothing
+ , tcg_binds = emptyLHsBinds
+ , tcg_imp_specs = []
+ , tcg_sigs = emptyNameSet
+ , tcg_ksigs = emptyNameSet
+ , tcg_ev_binds = emptyBag
+ , tcg_warns = emptyWarn
+ , tcg_anns = []
+ , tcg_tcs = []
+ , tcg_insts = []
+ , tcg_fam_insts = []
+ , tcg_rules = []
+ , tcg_fords = []
+ , tcg_patsyns = []
+ , tcg_merged = []
+ , tcg_dfun_n = dfun_n_var
+ , tcg_zany_n = zany_n_var
+ , tcg_keep = keep_var
+ , tcg_hdr_info = (Nothing,Nothing)
+ , tcg_main = Nothing
+ , tcg_self_boot = NoSelfBoot
+ , tcg_safe_infer = infer_var
+ , tcg_safe_infer_reasons = infer_reasons_var
+ , tcg_dependent_files = dependent_files_var
+ , tcg_dependent_dirs = dependent_dirs_var
+ , tcg_tc_plugin_solvers = []
+ , tcg_tc_plugin_rewriters = emptyUFM
+ , tcg_defaulting_plugins = []
+ , tcg_hf_plugins = []
+ , tcg_top_loc = loc
+ , tcg_static_wc = static_wc_var
+ , tcg_complete_matches = []
+ , tcg_cc_st = cc_st_var
+ , tcg_next_wrapper_num = next_wrapper_num
+ } }
+
-- | Run a 'TcM' action in the context of an existing 'GblEnv'.
initTcWithGbl :: HscEnv
-> TcGblEnv
@@ -686,6 +702,83 @@ withIfaceErr ctx do_this = do
liftIO $ throwGhcExceptionIO (ProgramError (renderWithContext ctx msg))
Succeeded result -> return result
+{-
+************************************************************************
+* *
+ Initialising plugins for TcM
+* *
+************************************************************************
+-}
+
+-- | Initialise typechecker plugins, run the inner action, then stop
+-- the typechecker plugins.
+withTcPlugins :: HscEnv -> TcM a -> TcM a
+withTcPlugins hsc_env m =
+ case catMaybes $ mapPlugins (hsc_plugins hsc_env) tcPlugin of
+ [] -> m -- Common fast case
+ plugins -> do
+ (solvers, rewriters, stops) <-
+ unzip3 `fmap` mapM start_plugin plugins
+ let
+ rewritersUniqFM :: UniqFM TyCon [TcPluginRewriter]
+ !rewritersUniqFM = sequenceUFMList rewriters
+ -- The following ensures that tcPluginStop is called even if a type
+ -- error occurs during compilation (Fix of #10078)
+ eitherRes <- tryM $
+ updGblEnv (\e -> e { tcg_tc_plugin_solvers = solvers
+ , tcg_tc_plugin_rewriters = rewritersUniqFM })
+ m
+ mapM_ runTcPluginM stops
+ case eitherRes of
+ Left _ -> failM
+ Right res -> return res
+ where
+ start_plugin (TcPlugin start solve rewrite stop) =
+ do s <- runTcPluginM start
+ return (solve s, rewrite s, stop s)
+
+-- | Initialise defaulting plugins, run the inner action, then stop
+-- the defaulting plugins.
+withDefaultingPlugins :: HscEnv -> TcM a -> TcM a
+withDefaultingPlugins hsc_env m =
+ do case catMaybes $ mapPlugins (hsc_plugins hsc_env) defaultingPlugin of
+ [] -> m -- Common fast case
+ plugins -> do (plugins,stops) <- mapAndUnzipM start_plugin plugins
+ -- This ensures that dePluginStop is called even if a type
+ -- error occurs during compilation
+ eitherRes <- tryM $ do
+ updGblEnv (\e -> e { tcg_defaulting_plugins = plugins })
+ m
+ mapM_ runTcPluginM stops
+ case eitherRes of
+ Left _ -> failM
+ Right res -> return res
+ where
+ start_plugin (DefaultingPlugin start fill stop) =
+ do s <- runTcPluginM start
+ return (fill s, stop s)
+
+-- | Initialise hole fit plugins, run the inner action, then stop
+-- the hole fit plugins.
+withHoleFitPlugins :: HscEnv -> TcM a -> TcM a
+withHoleFitPlugins hsc_env m =
+ case catMaybes $ mapPlugins (hsc_plugins hsc_env) holeFitPlugin of
+ [] -> m -- Common fast case
+ plugins -> do (plugins,stops) <- mapAndUnzipM start_plugin plugins
+ -- This ensures that hfPluginStop is called even if a type
+ -- error occurs during compilation.
+ eitherRes <- tryM $
+ updGblEnv (\e -> e { tcg_hf_plugins = plugins })
+ m
+ sequence_ stops
+ case eitherRes of
+ Left _ -> failM
+ Right res -> return res
+ where
+ start_plugin (HoleFitPluginR init plugin stop) =
+ do ref <- init
+ return (plugin ref, stop ref)
+
{-
************************************************************************
* *
=====================================
testsuite/tests/tcplugins/T26395.hs
=====================================
@@ -0,0 +1,51 @@
+
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE GADTs #-}
+{-# LANGUAGE StandaloneKindSignatures #-}
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE TypeOperators #-}
+{-# LANGUAGE UnliftedDatatypes #-}
+
+{-# OPTIONS_GHC -fplugin=T26395_Plugin #-}
+
+{-# OPTIONS_GHC -Wincomplete-patterns #-}
+{-# OPTIONS_GHC -Winaccessible-code #-}
+{-# OPTIONS_GHC -Woverlapping-patterns #-}
+
+module T26395 where
+
+import Data.Kind
+import GHC.TypeNats
+import GHC.Exts ( UnliftedType )
+
+-- This test verifies that typechecker plugins are enabled
+-- when we run the solver for pattern-match checking.
+
+type Peano :: Nat -> UnliftedType
+data Peano n where
+ Z :: Peano 0
+ S :: Peano n -> Peano (1 + n)
+
+test1 :: Peano n -> Peano n -> Int
+test1 Z Z = 0
+test1 (S n) (S m) = 1 + test1 n m
+
+{-
+The following test doesn't work properly due to #26401:
+the pattern-match checker reports a missing equation
+
+ Z (S _) _
+
+but there is no invocation of the solver of the form
+
+ [G] n ~ 0
+ [G] m ~ 1 + m1
+ [G] (n-m) ~ m2
+
+for which we could report the Givens as contradictory.
+
+test2 :: Peano n -> Peano m -> Peano (n - m) -> Int
+test2 Z Z Z = 0
+test2 (S _) (S _) _ = 1
+test2 (S _) Z (S _) = 2
+-}
=====================================
testsuite/tests/tcplugins/T26395.stderr
=====================================
@@ -0,0 +1,2 @@
+[1 of 2] Compiling T26395_Plugin ( T26395_Plugin.hs, T26395_Plugin.o )
+[2 of 2] Compiling T26395 ( T26395.hs, T26395.o )
=====================================
testsuite/tests/tcplugins/T26395_Plugin.hs
=====================================
@@ -0,0 +1,208 @@
+{-# LANGUAGE RecordWildCards #-}
+{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE MultiWayIf #-}
+{-# LANGUAGE BlockArguments #-}
+{-# LANGUAGE ViewPatterns #-}
+
+{-# OPTIONS_GHC -Wall -Wno-orphans #-}
+
+module T26395_Plugin where
+
+-- base
+import Prelude hiding ( (<>) )
+import qualified Data.Semigroup as S
+import Data.List ( partition )
+import Data.Maybe
+import GHC.TypeNats
+
+-- ghc
+import GHC.Builtin.Types.Literals
+import GHC.Core.Predicate
+import GHC.Core.TyCo.Rep
+import GHC.Plugins
+import GHC.Tc.Plugin
+import GHC.Tc.Types
+import GHC.Tc.Types.Constraint
+import GHC.Tc.Types.Evidence
+import GHC.Tc.Utils.TcType
+import GHC.Types.Unique.Map
+
+--------------------------------------------------------------------------------
+
+plugin :: Plugin
+plugin =
+ defaultPlugin
+ { pluginRecompile = purePlugin
+ , tcPlugin = \ _-> Just $
+ TcPlugin
+ { tcPluginInit = pure ()
+ , tcPluginSolve = \ _ -> solve
+ , tcPluginRewrite = \ _ -> emptyUFM
+ , tcPluginStop = \ _ -> pure ()
+ }
+ }
+
+solve :: EvBindsVar -> [Ct] -> [Ct] -> TcPluginM TcPluginSolveResult
+solve _ givens wanteds
+ -- This plugin only reports inconsistencies among Given constraints.
+ | not $ null wanteds
+ = pure $ TcPluginOk [] []
+ | otherwise
+ = do { let givenLinearExprs = mapMaybe linearExprCt_maybe givens
+ sols = solutions givenLinearExprs
+
+ ; tcPluginTrace "solveLinearExprs" $
+ vcat [ text "givens:" <+> ppr givens
+ , text "linExprs:" <+> ppr givenLinearExprs
+ , text "sols:" <+> ppr (take 1 sols)
+ ]
+ ; return $
+ if null sols
+ then TcPluginContradiction givens
+ else TcPluginOk [] []
+ }
+
+data LinearExpr =
+ LinearExpr
+ { constant :: Integer
+ , coeffs :: UniqMap TyVar Integer
+ }
+instance Semigroup LinearExpr where
+ LinearExpr c xs <> LinearExpr d ys =
+ LinearExpr ( c + d ) ( plusMaybeUniqMap_C comb xs ys )
+ where
+ comb a1 a2 =
+ let a = a1 + a2
+ in if a == 0
+ then Nothing
+ else Just a
+
+instance Monoid LinearExpr where
+ mempty = LinearExpr 0 emptyUniqMap
+
+mapLinearExpr :: (Integer -> Integer) -> LinearExpr -> LinearExpr
+mapLinearExpr f (LinearExpr c xs) = LinearExpr (f c) (mapUniqMap f xs)
+
+minusLinearExpr :: LinearExpr -> LinearExpr -> LinearExpr
+minusLinearExpr a b = a S.<> mapLinearExpr negate b
+
+instance Outputable LinearExpr where
+ ppr ( LinearExpr c xs ) =
+ hcat $ punctuate ( text " + " ) $
+ ( ppr c : map ppr_var ( nonDetUniqMapToList xs ) )
+ where
+ ppr_var ( tv, i )
+ | i == 1
+ = ppr tv
+ | i < 0
+ = parens ( text "-" <> ppr (abs i) ) <> text "*" <> ppr tv
+ | otherwise
+ = ppr i <> text "*" <> ppr tv
+
+maxCoeff :: LinearExpr -> Double
+maxCoeff ( LinearExpr c xs ) =
+ maximum ( map fromInteger ( c : nonDetEltsUniqMap xs ) )
+
+
+linearExprCt_maybe :: Ct -> Maybe LinearExpr
+linearExprCt_maybe ct =
+ case classifyPredType (ctPred ct) of
+ EqPred NomEq lhs rhs
+ | all isNaturalTy [ typeKind lhs, typeKind rhs ]
+ , Just e1 <- linearExprTy_maybe lhs
+ , Just e2 <- linearExprTy_maybe rhs
+ -> Just $ e1 `minusLinearExpr` e2
+ _ -> Nothing
+
+isNat :: Type -> Maybe Integer
+isNat ty
+ | Just (NumTyLit n) <- isLitTy ty
+ = Just n
+ | otherwise
+ = Nothing
+
+linearExprTy_maybe :: Type -> Maybe LinearExpr
+linearExprTy_maybe ty
+ | Just n <- isNat ty
+ = Just $ LinearExpr n emptyUniqMap
+ | Just (tc, args) <- splitTyConApp_maybe ty
+ = if | tc == typeNatAddTyCon
+ , [x, y] <- args
+ , Just e1 <- linearExprTy_maybe x
+ , Just e2 <- linearExprTy_maybe y
+ -> Just $ e1 S.<> e2
+ | tc == typeNatSubTyCon
+ , [x,y] <- args
+ , Just e1 <- linearExprTy_maybe x
+ , Just e2 <- linearExprTy_maybe y
+ -> Just $ e1 `minusLinearExpr` e2
+ | tc == typeNatMulTyCon
+ , [x, y] <- args
+ ->
+ if | Just ( LinearExpr n xs ) <- linearExprTy_maybe x
+ , isNullUniqMap xs
+ , Just e <- linearExprTy_maybe y
+ -> Just $
+ if n == 0
+ then mempty
+ else mapLinearExpr (n *) e
+ | Just ( LinearExpr n ys ) <- linearExprTy_maybe y
+ , isNullUniqMap ys
+ , Just e <- linearExprTy_maybe x
+ -> Just $
+ if n == 0
+ then mempty
+ else mapLinearExpr (fromIntegral n *) e
+ | otherwise
+ -> Nothing
+ | otherwise
+ -> Nothing
+ | Just tv <- getTyVar_maybe ty
+ = Just $ LinearExpr 0 ( unitUniqMap tv 1 )
+ | otherwise
+ = Nothing
+
+-- Brute force algorithm to check whether a system of Diophantine
+-- linear equations is solvable in natural numbers.
+solutions :: [ LinearExpr ] -> [ UniqMap TyVar Natural ]
+solutions eqs =
+ let
+ (constEqs, realEqs) = partition (isNullUniqMap . coeffs) eqs
+ d = length realEqs
+ fvs = nonDetKeysUniqMap $ plusUniqMapList ( map coeffs realEqs )
+ in
+ if | any ( ( /= 0 ) . evalLinearExpr emptyUniqMap ) constEqs
+ -> []
+ | d == 0
+ -> [ emptyUniqMap ]
+ | otherwise
+ ->
+ let
+ m = maximum $ map maxCoeff realEqs
+ hadamardBound = sqrt ( fromIntegral $ d ^ d ) * m ^ d
+ tests = mkAssignments ( floor hadamardBound ) fvs
+ in
+ filter ( \ test -> isSolution test realEqs ) tests
+
+
+mkAssignments :: Natural -> [ TyVar ] -> [ UniqMap TyVar Natural ]
+mkAssignments _ [] = [ emptyUniqMap ]
+mkAssignments b (v : vs) =
+ [ addToUniqMap rest v n
+ | n <- [ 0 .. b ]
+ , rest <- mkAssignments b vs
+ ]
+
+isSolution :: UniqMap TyVar Natural -> [ LinearExpr ] -> Bool
+isSolution assig =
+ all ( \ expr -> evalLinearExpr assig expr == 0 )
+
+evalLinearExpr :: UniqMap TyVar Natural -> LinearExpr -> Integer
+evalLinearExpr vals ( LinearExpr c xs ) = nonDetFoldUniqMap aux c xs
+ where
+ aux ( tv, coeff ) !acc = acc + coeff * val
+ where
+ val :: Integer
+ val = case lookupUniqMap vals tv of
+ Nothing -> pprPanic "evalLinearExpr: missing tv" (ppr tv)
+ Just v -> fromIntegral v
=====================================
testsuite/tests/tcplugins/all.T
=====================================
@@ -110,6 +110,19 @@ test('TcPlugin_CtId'
, '-dynamic -package ghc' if have_dynamic() else '-package ghc' ]
)
+# Checks that we run type-checker plugins for pattern-match warnings.
+test('T26395'
+ , [ extra_files(
+ [ 'T26395_Plugin.hs'
+ , 'T26395.hs'
+ ])
+ , req_th
+ ]
+ , multimod_compile
+ , [ 'T26395.hs'
+ , '-dynamic -package ghc' if have_dynamic() else '-package ghc' ]
+ )
+
test('T11462', [js_broken(22261), req_th, req_plugins], multi_compile,
[None, [('T11462_Plugin.hs', '-package ghc'), ('T11462.hs', '')],
'-dynamic' if have_dynamic() else ''])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8919e7f9943cb47db47c4a42a60e6a…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8919e7f9943cb47db47c4a42a60e6a…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/T26330] Improve pretty printer for HsExpr
by Simon Peyton Jones (@simonpj) 18 Sep '25
by Simon Peyton Jones (@simonpj) 18 Sep '25
18 Sep '25
Simon Peyton Jones pushed to branch wip/T26330 at Glasgow Haskell Compiler / GHC
Commits:
4a03551b by Simon Peyton Jones at 2025-09-18T10:51:41+01:00
Improve pretty printer for HsExpr
Given a very deeply-nested application, it just kept printing
deeper and deeper. This small change makes it cut off.
Test is in #26330, but we also get a dramatic decrease in compile
time for perf/compiler/InstanceMatching:
InstanceMatching 4,086,884,584 1,181,767,232 -71.1% GOOD
Why? Because before we got a GIGANTIC error message that took
ages to pretty-print; now we get this much more civilised message
(I have removed some whitespace.)
Match.hs:1007:1: error:
• No instance for ‘Show (F001 a)’ arising from a use of ‘showsPrec’
• In the second argument of ‘showString’, namely
‘(showsPrec
11 b1
(GHC.Internal.Show.showSpace
(showsPrec
11 b2
(GHC.Internal.Show.showSpace
(showsPrec
11 b3
(GHC.Internal.Show.showSpace
(showsPrec
11 b4
(GHC.Internal.Show.showSpace
(showsPrec
11 b5
(GHC.Internal.Show.showSpace
(showsPrec
11 b6
(GHC.Internal.Show.showSpace (showsPrec ...)))))))))))))’
-----------------------
The main payload is
* At the start of `pprExpr`
* In the defn of `pprApp`
A little bit of refactoring:
* It turned out that we were setting the default cut-off depth to a
fixed value in two places, so changing one didn't change the other.
See defaultSDocDepth and defaultSDocCols
* I refactored `pprDeeperList` a bit so I could understand it better.
Because the depth calculation has changed, there are lots of small
error message wibbles.
Metric Decrease:
InstanceMatching
- - - - -
38 changed files:
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Runtime/Heap/Inspect.hs
- compiler/GHC/Utils/Outputable.hs
- testsuite/tests/arrows/gadt/T17423.stderr
- testsuite/tests/indexed-types/should_compile/PushedInAsGivens.stderr
- testsuite/tests/indexed-types/should_fail/T26176.stderr
- testsuite/tests/indexed-types/should_fail/T2693.stderr
- testsuite/tests/indexed-types/should_fail/T4093b.stderr
- testsuite/tests/indexed-types/should_fail/T8518.stderr
- testsuite/tests/indexed-types/should_fail/T9662.stderr
- testsuite/tests/linear/should_fail/Linear17.stderr
- testsuite/tests/linear/should_fail/LinearLet7.stderr
- testsuite/tests/parser/should_fail/RecordDotSyntaxFail10.stderr
- testsuite/tests/parser/should_fail/RecordDotSyntaxFail11.stderr
- testsuite/tests/parser/should_fail/RecordDotSyntaxFail13.stderr
- testsuite/tests/parser/should_fail/RecordDotSyntaxFail8.stderr
- testsuite/tests/partial-sigs/should_compile/T21719.stderr
- testsuite/tests/polykinds/T13393.stderr
- testsuite/tests/rep-poly/T12709.stderr
- testsuite/tests/simplCore/should_compile/simpl017.stderr
- testsuite/tests/th/T10945.stderr
- testsuite/tests/th/TH_StaticPointers02.stderr
- testsuite/tests/typecheck/should_compile/T11339.stderr
- testsuite/tests/typecheck/should_fail/DoExpansion3.stderr
- testsuite/tests/typecheck/should_fail/T12177.stderr
- testsuite/tests/typecheck/should_fail/T22707.stderr
- testsuite/tests/typecheck/should_fail/T24064.stderr
- + testsuite/tests/typecheck/should_fail/T26330.hs
- + testsuite/tests/typecheck/should_fail/T26330.stderr
- testsuite/tests/typecheck/should_fail/T8603.stderr
- testsuite/tests/typecheck/should_fail/all.T
- testsuite/tests/typecheck/should_fail/tcfail128.stderr
- testsuite/tests/typecheck/should_fail/tcfail153.stderr
- testsuite/tests/typecheck/should_fail/tcfail168.stderr
- testsuite/tests/typecheck/should_fail/tcfail177.stderr
- testsuite/tests/typecheck/should_fail/tcfail185.stderr
- testsuite/tests/typecheck/should_run/Typeable1.stderr
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4a03551be9697c5cce416560c2e6060…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4a03551be9697c5cce416560c2e6060…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 5 commits: compiler/ghci: replace the LoadDLL message with LoadDLLs
by Marge Bot (@marge-bot) 18 Sep '25
by Marge Bot (@marge-bot) 18 Sep '25
18 Sep '25
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
e23c99b9 by Cheng Shao at 2025-09-18T00:17:24-04:00
compiler/ghci: replace the LoadDLL message with LoadDLLs
As a part of #25407, this commit changes the LoadDLL message to
LoadDLLs, which takes a list of DLL paths to load and returns the list
of remote pointer handles. The wasm dyld is refactored to take
advantage of LoadDLLs and harvest background parallelism. On other
platforms, LoadDLLs is based on a fallback codepath that does
sequential loading.
The driver is not actually emitting singular LoadDLLs message with
multiple DLLs yet, this is left in subsequent commits.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
cfb6bba1 by Cheng Shao at 2025-09-18T00:17:24-04:00
driver: separate downsweep/upsweep phase in loadPackages'
This commit refactors GHC.Linker.Loader.loadPackages' to be separated
into downsweep/upsweep phases:
- The downsweep phase performs dependency analysis and generates a
list of topologically sorted packages to load
- The upsweep phase sequentially loads these packages by calling
loadPackage
This is a necessary refactoring to make it possible to make loading of
DLLs concurrent.
- - - - -
b3464604 by Cheng Shao at 2025-09-18T00:17:24-04:00
driver: emit single LoadDLLs message to load multiple DLLs
This commit refactors the driver so that it emits a single LoadDLLs
message to load multiple DLLs in GHC.Linker.Loader.loadPackages'.
Closes #25407.
-------------------------
Metric Increase:
TcPlugin_RewritePerf
-------------------------
- - - - -
36ca8b5e by sheaf at 2025-09-18T00:17:39-04:00
Enable TcM plugins in initTc
This commit ensures that we run typechecker plugins and defaulting
plugins whenever we call initTc.
In particular, this ensures that the pattern-match checker, which calls
'initTcDsForSolver' which calls 'initTc', runs with typechecker plugins
enabled. This matters for situations like:
merge :: Vec n a -> Vec n a -> Vec (2 * n) a
merge Nil Nil = Nil
merge (a <: as) (b <: bs) = a :< (b <: merge as bs)
in which we need the typechecker plugin to run in order to tell us that
the Givens would be inconsistent in the additional equation
merge (_ <: _) Nil
and thus that the equation is not needed.
Fixes #26395
- - - - -
8919e7f9 by Cheng Shao at 2025-09-18T00:17:40-04:00
rel-eng: update fedora image to 42
This patch is a part of #25876 and updates fedora image to 42.
- - - - -
22 changed files:
- .gitlab-ci.yml
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- compiler/GHC/Driver/Plugins.hs
- compiler/GHC/HsToCore/Monad.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Linker/MacOS.hs
- compiler/GHC/Linker/Types.hs
- compiler/GHC/Runtime/Interpreter.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Tc/Utils/Monad.hs
- libraries/ghci/GHCi/Message.hs
- libraries/ghci/GHCi/ObjLink.hs
- libraries/ghci/GHCi/Run.hs
- testsuite/tests/rts/linker/T2615.hs
- + testsuite/tests/tcplugins/T26395.hs
- + testsuite/tests/tcplugins/T26395.stderr
- + testsuite/tests/tcplugins/T26395_Plugin.hs
- testsuite/tests/tcplugins/all.T
- utils/jsffi/dyld.mjs
Changes:
=====================================
.gitlab-ci.yml
=====================================
@@ -2,7 +2,7 @@ variables:
GIT_SSL_NO_VERIFY: "1"
# Commit of ghc/ci-images repository from which to pull Docker images
- DOCKER_REV: be4ac2cd18f38e63b263e2a27c76a7c279385796
+ DOCKER_REV: a97d5c67d803c6b3811c6cccdf33dc8e9d7eafe3
# Sequential version number of all cached things.
# Bump to invalidate GitLab CI cache.
@@ -433,14 +433,14 @@ hadrian-ghc-in-ghci:
hadrian-multi:
stage: testing
needs:
- - job: x86_64-linux-fedora33-release
+ - job: x86_64-linux-fedora42-release
optional: true
- - job: nightly-x86_64-linux-fedora33-release
+ - job: nightly-x86_64-linux-fedora42-release
optional: true
- - job: release-x86_64-linux-fedora33-release
+ - job: release-x86_64-linux-fedora42-release
optional: true
dependencies: null
- image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora33:$DOCKER_REV"
+ image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora42:$DOCKER_REV"
before_script:
# workaround for docker permissions
- sudo chown ghc:ghc -R .
@@ -460,7 +460,7 @@ hadrian-multi:
- ls
- |
mkdir tmp
- tar -xf ghc-x86_64-linux-fedora33-release.tar.xz -C tmp
+ tar -xf ghc-x86_64-linux-fedora42-release.tar.xz -C tmp
pushd tmp/ghc-*/
./configure --prefix=$root
make install
@@ -522,17 +522,17 @@ test-cabal-reinstall-x86_64-linux-deb10:
abi-test-nightly:
stage: full-build
needs:
- - job: nightly-x86_64-linux-fedora33-release-hackage
- - job: nightly-x86_64-linux-fedora33-release
+ - job: nightly-x86_64-linux-fedora42-release-hackage
+ - job: nightly-x86_64-linux-fedora42-release
tags:
- x86_64-linux
- image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora33:$DOCKER_REV"
+ image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora42:$DOCKER_REV"
dependencies: null
before_script:
- mkdir -p normal
- mkdir -p hackage
- - tar -xf ghc-x86_64-linux-fedora33-release.tar.xz -C normal/
- - tar -xf ghc-x86_64-linux-fedora33-release-hackage_docs.tar.xz -C hackage/
+ - tar -xf ghc-x86_64-linux-fedora42-release.tar.xz -C normal/
+ - tar -xf ghc-x86_64-linux-fedora42-release-hackage_docs.tar.xz -C hackage/
script:
- .gitlab/ci.sh compare_interfaces_of "normal/ghc-*" "hackage/ghc-*"
artifacts:
@@ -609,9 +609,9 @@ doc-tarball:
hackage-doc-tarball:
stage: packaging
needs:
- - job: nightly-x86_64-linux-fedora33-release-hackage
+ - job: nightly-x86_64-linux-fedora42-release-hackage
optional: true
- - job: release-x86_64-linux-fedora33-release-hackage
+ - job: release-x86_64-linux-fedora42-release-hackage
optional: true
- job: source-tarball
tags:
@@ -628,7 +628,7 @@ hackage-doc-tarball:
- hackage_docs
before_script:
- tar -xf ghc-*[0-9]-src.tar.xz
- - tar -xf ghc-x86_64-linux-fedora33-release.tar.xz -C ghc*/
+ - tar -xf ghc-x86_64-linux-fedora42-release.tar.xz -C ghc*/
script:
- cd ghc*/
- mv .gitlab/rel_eng/upload_ghc_libs.py .
@@ -754,7 +754,7 @@ test-bootstrap:
# Triggering jobs in the ghc/head.hackage project requires that we have a job
# token for that repository. Furthermore the head.hackage CI job must have
# access to an unprivileged access token with the ability to query the ghc/ghc
-# project such that it can find the job ID of the fedora33 job for the current
+# project such that it can find the job ID of the fedora42 job for the current
# pipeline.
#
# hackage-lint: Can be triggered on any MR, normal validate pipeline or nightly build.
@@ -841,7 +841,7 @@ nightly-hackage-lint:
nightly-hackage-perf:
needs:
- - job: nightly-x86_64-linux-fedora33-release
+ - job: nightly-x86_64-linux-fedora42-release
optional: true
artifacts: false
- job: nightly-aarch64-linux-deb12-validate
@@ -860,7 +860,7 @@ nightly-hackage-perf:
release-hackage-lint:
needs:
- - job: release-x86_64-linux-fedora33-release
+ - job: release-x86_64-linux-fedora42-release
optional: true
artifacts: false
- job: release-aarch64-linux-deb12-release+no_split_sections
@@ -946,13 +946,13 @@ perf-nofib:
allow_failure: true
stage: testing
needs:
- - job: x86_64-linux-fedora33-release
+ - job: x86_64-linux-fedora42-release
optional: true
- - job: nightly-x86_64-linux-fedora33-release
+ - job: nightly-x86_64-linux-fedora42-release
optional: true
- - job: release-x86_64-linux-fedora33-release
+ - job: release-x86_64-linux-fedora42-release
optional: true
- image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora33:$DOCKER_REV"
+ image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora42:$DOCKER_REV"
rules:
- when: never
- *full-ci
@@ -965,7 +965,7 @@ perf-nofib:
- root=$(pwd)/ghc
- |
mkdir tmp
- tar -xf ../ghc-x86_64-linux-fedora33-release.tar.xz -C tmp
+ tar -xf ../ghc-x86_64-linux-fedora42-release.tar.xz -C tmp
pushd tmp/ghc-*/
./configure --prefix=$root
make install
@@ -989,21 +989,21 @@ perf-nofib:
perf:
stage: testing
needs:
- - job: x86_64-linux-fedora33-release
+ - job: x86_64-linux-fedora42-release
optional: true
- - job: nightly-x86_64-linux-fedora33-release
+ - job: nightly-x86_64-linux-fedora42-release
optional: true
- - job: release-x86_64-linux-fedora33-release
+ - job: release-x86_64-linux-fedora42-release
optional: true
dependencies: null
- image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora33:$DOCKER_REV"
+ image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora42:$DOCKER_REV"
tags:
- x86_64-linux-perf
script:
- root=$(pwd)/ghc
- |
mkdir tmp
- tar -xf ghc-x86_64-linux-fedora33-release.tar.xz -C tmp
+ tar -xf ghc-x86_64-linux-fedora42-release.tar.xz -C tmp
pushd tmp/ghc-*/
./configure --prefix=$root
make install
@@ -1027,14 +1027,14 @@ perf:
abi-test:
stage: testing
needs:
- - job: x86_64-linux-fedora33-release
+ - job: x86_64-linux-fedora42-release
optional: true
- - job: nightly-x86_64-linux-fedora33-release
+ - job: nightly-x86_64-linux-fedora42-release
optional: true
- - job: release-x86_64-linux-fedora33-release
+ - job: release-x86_64-linux-fedora42-release
optional: true
dependencies: null
- image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora33:$DOCKER_REV"
+ image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora42:$DOCKER_REV"
rules:
- if: $CI_MERGE_REQUEST_ID
- if: '$CI_COMMIT_BRANCH == "master"'
@@ -1045,7 +1045,7 @@ abi-test:
- root=$(pwd)/ghc
- |
mkdir tmp
- tar -xf ghc-x86_64-linux-fedora33-release.tar.xz -C tmp
+ tar -xf ghc-x86_64-linux-fedora42-release.tar.xz -C tmp
pushd tmp/ghc-*/
./configure --prefix=$root
make install
@@ -1200,7 +1200,7 @@ ghcup-metadata-nightly:
extends: .ghcup-metadata
# Explicit needs for validate pipeline because we only need certain bindists
needs:
- - job: nightly-x86_64-linux-fedora33-release
+ - job: nightly-x86_64-linux-fedora42-release
artifacts: false
- job: nightly-x86_64-linux-ubuntu24_04-validate
artifacts: false
@@ -1251,7 +1251,7 @@ ghcup-metadata-nightly:
# Update the ghcup metadata with information about this nightly pipeline
ghcup-metadata-nightly-push:
stage: deploy
- image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora33:$DOCKER_REV"
+ image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora42:$DOCKER_REV"
dependencies: null
tags:
- x86_64-linux
=====================================
.gitlab/generate-ci/gen_ci.hs
=====================================
@@ -82,7 +82,7 @@ The generated names for the jobs is important as there are a few downstream cons
of the jobs artifacts. Therefore some care should be taken if changing the generated
names of jobs to update these other places.
-1. Fedora33 jobs are required by head.hackage
+1. fedora42 jobs are required by head.hackage
2. The fetch-gitlab release utility pulls release artifacts from the
3. The ghc-head-from script downloads release artifacts based on a pipeline change.
4. Some subsequent CI jobs have explicit dependencies (for example docs-tarball, perf, perf-nofib)
@@ -118,8 +118,7 @@ data LinuxDistro
| Debian11Js
| Debian10
| Debian9
- | Fedora33
- | Fedora38
+ | Fedora42
| Ubuntu2404LoongArch64
| Ubuntu2404
| Ubuntu2204
@@ -319,8 +318,7 @@ distroName Debian12Riscv = "deb12-riscv"
distroName Debian12Wine = "deb12-wine"
distroName Debian10 = "deb10"
distroName Debian9 = "deb9"
-distroName Fedora33 = "fedora33"
-distroName Fedora38 = "fedora38"
+distroName Fedora42 = "fedora42"
distroName Ubuntu2404LoongArch64 = "ubuntu24_04-loongarch"
distroName Ubuntu1804 = "ubuntu18_04"
distroName Ubuntu2004 = "ubuntu20_04"
@@ -501,14 +499,6 @@ alpineVariables arch = mconcat $
distroVariables :: Arch -> LinuxDistro -> Variables
distroVariables arch Alpine312 = alpineVariables arch
distroVariables arch Alpine322 = alpineVariables arch
-distroVariables _ Fedora33 = mconcat
- -- LLC/OPT do not work for some reason in our fedora images
- -- These tests fail with this error: T11649 T5681 T7571 T8131b
- -- +/opt/llvm/bin/opt: /lib64/libtinfo.so.5: no version information available (required by /opt/llvm/bin/opt)
- -- +/opt/llvm/bin/llc: /lib64/libtinfo.so.5: no version information available (required by /opt/llvm/bin/llc)
- [ "LLC" =: "/bin/false"
- , "OPT" =: "/bin/false"
- ]
distroVariables _ _ = mempty
-----------------------------------------------------------------------------
@@ -1207,13 +1197,13 @@ rhel_x86 =
fedora_x86 :: [JobGroup Job]
fedora_x86 =
- [ -- Fedora33 job is always built with perf so there's one job in the normal
+ [ -- Fedora42 job is always built with perf so there's one job in the normal
-- validate pipeline which is built with perf.
- fastCI (standardBuildsWithConfig Amd64 (Linux Fedora33) releaseConfig)
+ fastCI (standardBuildsWithConfig Amd64 (Linux Fedora42) releaseConfig)
-- This job is only for generating head.hackage docs
- , hackage_doc_job (disableValidate (standardBuildsWithConfig Amd64 (Linux Fedora33) releaseConfig))
- , disableValidate (standardBuildsWithConfig Amd64 (Linux Fedora33) dwarf)
- , disableValidate (standardBuilds Amd64 (Linux Fedora38))
+ , hackage_doc_job (disableValidate (standardBuildsWithConfig Amd64 (Linux Fedora42) releaseConfig))
+ , disableValidate (standardBuildsWithConfig Amd64 (Linux Fedora42) dwarf)
+ , disableValidate (standardBuilds Amd64 (Linux Fedora42))
]
where
hackage_doc_job = rename (<> "-hackage") . modifyJobs (addVariable "HADRIAN_ARGS" "--haddock-for-hackage")
@@ -1375,7 +1365,7 @@ platform_mapping = Map.map go combined_result
, "x86_64-linux-deb11-validate"
, "x86_64-linux-deb12-validate"
, "x86_64-linux-deb10-validate+debug_info"
- , "x86_64-linux-fedora33-release"
+ , "x86_64-linux-fedora42-release"
, "x86_64-linux-deb11-cross_aarch64-linux-gnu-validate"
, "x86_64-windows-validate"
, "aarch64-linux-deb12-validate"
@@ -1390,13 +1380,13 @@ platform_mapping = Map.map go combined_result
, "nightly-aarch64-linux-deb12-wine-int_native-cross_aarch64-unknown-mingw32-validate"
, "nightly-x86_64-linux-alpine3_12-validate+fully_static"
, "nightly-x86_64-linux-deb10-validate"
- , "nightly-x86_64-linux-fedora33-release"
+ , "nightly-x86_64-linux-fedora42-release"
, "nightly-x86_64-windows-validate"
, "release-x86_64-linux-alpine3_12-release+fully_static+no_split_sections"
, "release-x86_64-linux-deb10-release"
, "release-x86_64-linux-deb11-release"
, "release-x86_64-linux-deb12-release"
- , "release-x86_64-linux-fedora33-release"
+ , "release-x86_64-linux-fedora42-release"
, "release-x86_64-windows-release"
]
=====================================
.gitlab/jobs.yaml
=====================================
@@ -2942,7 +2942,7 @@
"XZ_OPT": "-9"
}
},
- "nightly-x86_64-linux-fedora33-release": {
+ "nightly-x86_64-linux-fedora42-release": {
"after_script": [
".gitlab/ci.sh save_cache",
".gitlab/ci.sh save_test_output",
@@ -2953,7 +2953,7 @@
"artifacts": {
"expire_in": "8 weeks",
"paths": [
- "ghc-x86_64-linux-fedora33-release.tar.xz",
+ "ghc-x86_64-linux-fedora42-release.tar.xz",
"junit.xml",
"unexpected-test-output.tar.gz"
],
@@ -2963,14 +2963,14 @@
"when": "always"
},
"cache": {
- "key": "x86_64-linux-fedora33-$CACHE_REV",
+ "key": "x86_64-linux-fedora42-$CACHE_REV",
"paths": [
"cabal-cache",
"toolchain"
]
},
"dependencies": [],
- "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora33:$DOCKER_REV",
+ "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora42:$DOCKER_REV",
"needs": [
{
"artifacts": false,
@@ -2996,18 +2996,16 @@
],
"variables": {
"BIGNUM_BACKEND": "gmp",
- "BIN_DIST_NAME": "ghc-x86_64-linux-fedora33-release",
+ "BIN_DIST_NAME": "ghc-x86_64-linux-fedora42-release",
"BUILD_FLAVOUR": "release",
"CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
"INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
- "LLC": "/bin/false",
- "OPT": "/bin/false",
"RUNTEST_ARGS": "",
- "TEST_ENV": "x86_64-linux-fedora33-release",
+ "TEST_ENV": "x86_64-linux-fedora42-release",
"XZ_OPT": "-9"
}
},
- "nightly-x86_64-linux-fedora33-release-hackage": {
+ "nightly-x86_64-linux-fedora42-release-hackage": {
"after_script": [
".gitlab/ci.sh save_cache",
".gitlab/ci.sh save_test_output",
@@ -3018,7 +3016,7 @@
"artifacts": {
"expire_in": "8 weeks",
"paths": [
- "ghc-x86_64-linux-fedora33-release.tar.xz",
+ "ghc-x86_64-linux-fedora42-release.tar.xz",
"junit.xml",
"unexpected-test-output.tar.gz"
],
@@ -3028,14 +3026,14 @@
"when": "always"
},
"cache": {
- "key": "x86_64-linux-fedora33-$CACHE_REV",
+ "key": "x86_64-linux-fedora42-$CACHE_REV",
"paths": [
"cabal-cache",
"toolchain"
]
},
"dependencies": [],
- "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora33:$DOCKER_REV",
+ "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora42:$DOCKER_REV",
"needs": [
{
"artifacts": false,
@@ -3061,19 +3059,17 @@
],
"variables": {
"BIGNUM_BACKEND": "gmp",
- "BIN_DIST_NAME": "ghc-x86_64-linux-fedora33-release",
+ "BIN_DIST_NAME": "ghc-x86_64-linux-fedora42-release",
"BUILD_FLAVOUR": "release",
"CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
"HADRIAN_ARGS": "--haddock-for-hackage",
"INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
- "LLC": "/bin/false",
- "OPT": "/bin/false",
"RUNTEST_ARGS": "",
- "TEST_ENV": "x86_64-linux-fedora33-release",
+ "TEST_ENV": "x86_64-linux-fedora42-release",
"XZ_OPT": "-9"
}
},
- "nightly-x86_64-linux-fedora33-validate+debug_info": {
+ "nightly-x86_64-linux-fedora42-validate": {
"after_script": [
".gitlab/ci.sh save_cache",
".gitlab/ci.sh save_test_output",
@@ -3084,7 +3080,7 @@
"artifacts": {
"expire_in": "8 weeks",
"paths": [
- "ghc-x86_64-linux-fedora33-validate+debug_info.tar.xz",
+ "ghc-x86_64-linux-fedora42-validate.tar.xz",
"junit.xml",
"unexpected-test-output.tar.gz"
],
@@ -3094,14 +3090,14 @@
"when": "always"
},
"cache": {
- "key": "x86_64-linux-fedora33-$CACHE_REV",
+ "key": "x86_64-linux-fedora42-$CACHE_REV",
"paths": [
"cabal-cache",
"toolchain"
]
},
"dependencies": [],
- "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora33:$DOCKER_REV",
+ "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora42:$DOCKER_REV",
"needs": [
{
"artifacts": false,
@@ -3127,18 +3123,16 @@
],
"variables": {
"BIGNUM_BACKEND": "gmp",
- "BIN_DIST_NAME": "ghc-x86_64-linux-fedora33-validate+debug_info",
- "BUILD_FLAVOUR": "validate+debug_info",
+ "BIN_DIST_NAME": "ghc-x86_64-linux-fedora42-validate",
+ "BUILD_FLAVOUR": "validate",
"CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
"INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
- "LLC": "/bin/false",
- "OPT": "/bin/false",
"RUNTEST_ARGS": "",
- "TEST_ENV": "x86_64-linux-fedora33-validate+debug_info",
+ "TEST_ENV": "x86_64-linux-fedora42-validate",
"XZ_OPT": "-9"
}
},
- "nightly-x86_64-linux-fedora38-validate": {
+ "nightly-x86_64-linux-fedora42-validate+debug_info": {
"after_script": [
".gitlab/ci.sh save_cache",
".gitlab/ci.sh save_test_output",
@@ -3149,7 +3143,7 @@
"artifacts": {
"expire_in": "8 weeks",
"paths": [
- "ghc-x86_64-linux-fedora38-validate.tar.xz",
+ "ghc-x86_64-linux-fedora42-validate+debug_info.tar.xz",
"junit.xml",
"unexpected-test-output.tar.gz"
],
@@ -3159,14 +3153,14 @@
"when": "always"
},
"cache": {
- "key": "x86_64-linux-fedora38-$CACHE_REV",
+ "key": "x86_64-linux-fedora42-$CACHE_REV",
"paths": [
"cabal-cache",
"toolchain"
]
},
"dependencies": [],
- "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora38:$DOCKER_REV",
+ "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora42:$DOCKER_REV",
"needs": [
{
"artifacts": false,
@@ -3192,12 +3186,12 @@
],
"variables": {
"BIGNUM_BACKEND": "gmp",
- "BIN_DIST_NAME": "ghc-x86_64-linux-fedora38-validate",
- "BUILD_FLAVOUR": "validate",
+ "BIN_DIST_NAME": "ghc-x86_64-linux-fedora42-validate+debug_info",
+ "BUILD_FLAVOUR": "validate+debug_info",
"CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
"INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
"RUNTEST_ARGS": "",
- "TEST_ENV": "x86_64-linux-fedora38-validate",
+ "TEST_ENV": "x86_64-linux-fedora42-validate+debug_info",
"XZ_OPT": "-9"
}
},
@@ -4814,7 +4808,7 @@
"XZ_OPT": "-9"
}
},
- "release-x86_64-linux-fedora33-release": {
+ "release-x86_64-linux-fedora42-release": {
"after_script": [
".gitlab/ci.sh save_cache",
".gitlab/ci.sh save_test_output",
@@ -4825,7 +4819,7 @@
"artifacts": {
"expire_in": "1 year",
"paths": [
- "ghc-x86_64-linux-fedora33-release.tar.xz",
+ "ghc-x86_64-linux-fedora42-release.tar.xz",
"junit.xml",
"unexpected-test-output.tar.gz"
],
@@ -4835,14 +4829,14 @@
"when": "always"
},
"cache": {
- "key": "x86_64-linux-fedora33-$CACHE_REV",
+ "key": "x86_64-linux-fedora42-$CACHE_REV",
"paths": [
"cabal-cache",
"toolchain"
]
},
"dependencies": [],
- "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora33:$DOCKER_REV",
+ "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora42:$DOCKER_REV",
"needs": [
{
"artifacts": false,
@@ -4868,19 +4862,17 @@
],
"variables": {
"BIGNUM_BACKEND": "gmp",
- "BIN_DIST_NAME": "ghc-x86_64-linux-fedora33-release",
+ "BIN_DIST_NAME": "ghc-x86_64-linux-fedora42-release",
"BUILD_FLAVOUR": "release",
"CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
"IGNORE_PERF_FAILURES": "all",
"INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
- "LLC": "/bin/false",
- "OPT": "/bin/false",
"RUNTEST_ARGS": "",
- "TEST_ENV": "x86_64-linux-fedora33-release",
+ "TEST_ENV": "x86_64-linux-fedora42-release",
"XZ_OPT": "-9"
}
},
- "release-x86_64-linux-fedora33-release+debug_info": {
+ "release-x86_64-linux-fedora42-release+debug_info": {
"after_script": [
".gitlab/ci.sh save_cache",
".gitlab/ci.sh save_test_output",
@@ -4891,7 +4883,7 @@
"artifacts": {
"expire_in": "1 year",
"paths": [
- "ghc-x86_64-linux-fedora33-release+debug_info.tar.xz",
+ "ghc-x86_64-linux-fedora42-release+debug_info.tar.xz",
"junit.xml",
"unexpected-test-output.tar.gz"
],
@@ -4901,14 +4893,14 @@
"when": "always"
},
"cache": {
- "key": "x86_64-linux-fedora33-$CACHE_REV",
+ "key": "x86_64-linux-fedora42-$CACHE_REV",
"paths": [
"cabal-cache",
"toolchain"
]
},
"dependencies": [],
- "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora33:$DOCKER_REV",
+ "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora42:$DOCKER_REV",
"needs": [
{
"artifacts": false,
@@ -4934,19 +4926,17 @@
],
"variables": {
"BIGNUM_BACKEND": "gmp",
- "BIN_DIST_NAME": "ghc-x86_64-linux-fedora33-release+debug_info",
+ "BIN_DIST_NAME": "ghc-x86_64-linux-fedora42-release+debug_info",
"BUILD_FLAVOUR": "release+debug_info",
"CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
"IGNORE_PERF_FAILURES": "all",
"INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
- "LLC": "/bin/false",
- "OPT": "/bin/false",
"RUNTEST_ARGS": "",
- "TEST_ENV": "x86_64-linux-fedora33-release+debug_info",
+ "TEST_ENV": "x86_64-linux-fedora42-release+debug_info",
"XZ_OPT": "-9"
}
},
- "release-x86_64-linux-fedora33-release-hackage": {
+ "release-x86_64-linux-fedora42-release-hackage": {
"after_script": [
".gitlab/ci.sh save_cache",
".gitlab/ci.sh save_test_output",
@@ -4957,7 +4947,7 @@
"artifacts": {
"expire_in": "1 year",
"paths": [
- "ghc-x86_64-linux-fedora33-release.tar.xz",
+ "ghc-x86_64-linux-fedora42-release.tar.xz",
"junit.xml",
"unexpected-test-output.tar.gz"
],
@@ -4967,14 +4957,14 @@
"when": "always"
},
"cache": {
- "key": "x86_64-linux-fedora33-$CACHE_REV",
+ "key": "x86_64-linux-fedora42-$CACHE_REV",
"paths": [
"cabal-cache",
"toolchain"
]
},
"dependencies": [],
- "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora33:$DOCKER_REV",
+ "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora42:$DOCKER_REV",
"needs": [
{
"artifacts": false,
@@ -5000,80 +4990,14 @@
],
"variables": {
"BIGNUM_BACKEND": "gmp",
- "BIN_DIST_NAME": "ghc-x86_64-linux-fedora33-release",
+ "BIN_DIST_NAME": "ghc-x86_64-linux-fedora42-release",
"BUILD_FLAVOUR": "release",
"CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
"HADRIAN_ARGS": "--haddock-for-hackage",
"IGNORE_PERF_FAILURES": "all",
"INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
- "LLC": "/bin/false",
- "OPT": "/bin/false",
- "RUNTEST_ARGS": "",
- "TEST_ENV": "x86_64-linux-fedora33-release",
- "XZ_OPT": "-9"
- }
- },
- "release-x86_64-linux-fedora38-release": {
- "after_script": [
- ".gitlab/ci.sh save_cache",
- ".gitlab/ci.sh save_test_output",
- ".gitlab/ci.sh clean",
- "cat ci_timings.txt"
- ],
- "allow_failure": false,
- "artifacts": {
- "expire_in": "1 year",
- "paths": [
- "ghc-x86_64-linux-fedora38-release.tar.xz",
- "junit.xml",
- "unexpected-test-output.tar.gz"
- ],
- "reports": {
- "junit": "junit.xml"
- },
- "when": "always"
- },
- "cache": {
- "key": "x86_64-linux-fedora38-$CACHE_REV",
- "paths": [
- "cabal-cache",
- "toolchain"
- ]
- },
- "dependencies": [],
- "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora38:$DOCKER_REV",
- "needs": [
- {
- "artifacts": false,
- "job": "hadrian-ghc-in-ghci"
- }
- ],
- "rules": [
- {
- "if": "(\"true\" == \"true\") && ($RELEASE_JOB == \"yes\") && ($NIGHTLY == null)",
- "when": "on_success"
- }
- ],
- "script": [
- "sudo chown ghc:ghc -R .",
- ".gitlab/ci.sh setup",
- ".gitlab/ci.sh configure",
- ".gitlab/ci.sh build_hadrian",
- ".gitlab/ci.sh test_hadrian"
- ],
- "stage": "full-build",
- "tags": [
- "x86_64-linux"
- ],
- "variables": {
- "BIGNUM_BACKEND": "gmp",
- "BIN_DIST_NAME": "ghc-x86_64-linux-fedora38-release",
- "BUILD_FLAVOUR": "release",
- "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
- "IGNORE_PERF_FAILURES": "all",
- "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
"RUNTEST_ARGS": "",
- "TEST_ENV": "x86_64-linux-fedora38-release",
+ "TEST_ENV": "x86_64-linux-fedora42-release",
"XZ_OPT": "-9"
}
},
@@ -7108,7 +7032,7 @@
"TEST_ENV": "x86_64-linux-deb9-validate"
}
},
- "x86_64-linux-fedora33-release": {
+ "x86_64-linux-fedora42-release": {
"after_script": [
".gitlab/ci.sh save_cache",
".gitlab/ci.sh save_test_output",
@@ -7119,7 +7043,7 @@
"artifacts": {
"expire_in": "2 weeks",
"paths": [
- "ghc-x86_64-linux-fedora33-release.tar.xz",
+ "ghc-x86_64-linux-fedora42-release.tar.xz",
"junit.xml",
"unexpected-test-output.tar.gz"
],
@@ -7129,14 +7053,14 @@
"when": "always"
},
"cache": {
- "key": "x86_64-linux-fedora33-$CACHE_REV",
+ "key": "x86_64-linux-fedora42-$CACHE_REV",
"paths": [
"cabal-cache",
"toolchain"
]
},
"dependencies": [],
- "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora33:$DOCKER_REV",
+ "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora42:$DOCKER_REV",
"needs": [
{
"artifacts": false,
@@ -7145,7 +7069,7 @@
],
"rules": [
{
- "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-fedora33-release(\\s|$).*/)) || (($ONLY_JOBS == null) && ((\"true\" == \"true\")))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+ "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-fedora42-release(\\s|$).*/)) || (($ONLY_JOBS == null) && ((\"true\" == \"true\")))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
"when": "on_success"
}
],
@@ -7162,17 +7086,15 @@
],
"variables": {
"BIGNUM_BACKEND": "gmp",
- "BIN_DIST_NAME": "ghc-x86_64-linux-fedora33-release",
+ "BIN_DIST_NAME": "ghc-x86_64-linux-fedora42-release",
"BUILD_FLAVOUR": "release",
"CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
"INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
- "LLC": "/bin/false",
- "OPT": "/bin/false",
"RUNTEST_ARGS": "",
- "TEST_ENV": "x86_64-linux-fedora33-release"
+ "TEST_ENV": "x86_64-linux-fedora42-release"
}
},
- "x86_64-linux-fedora33-release-hackage": {
+ "x86_64-linux-fedora42-release-hackage": {
"after_script": [
".gitlab/ci.sh save_cache",
".gitlab/ci.sh save_test_output",
@@ -7183,7 +7105,7 @@
"artifacts": {
"expire_in": "2 weeks",
"paths": [
- "ghc-x86_64-linux-fedora33-release.tar.xz",
+ "ghc-x86_64-linux-fedora42-release.tar.xz",
"junit.xml",
"unexpected-test-output.tar.gz"
],
@@ -7193,14 +7115,14 @@
"when": "always"
},
"cache": {
- "key": "x86_64-linux-fedora33-$CACHE_REV",
+ "key": "x86_64-linux-fedora42-$CACHE_REV",
"paths": [
"cabal-cache",
"toolchain"
]
},
"dependencies": [],
- "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora33:$DOCKER_REV",
+ "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora42:$DOCKER_REV",
"needs": [
{
"artifacts": false,
@@ -7209,7 +7131,7 @@
],
"rules": [
{
- "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-fedora33-release(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+ "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-fedora42-release(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
"when": "on_success"
}
],
@@ -7226,18 +7148,16 @@
],
"variables": {
"BIGNUM_BACKEND": "gmp",
- "BIN_DIST_NAME": "ghc-x86_64-linux-fedora33-release",
+ "BIN_DIST_NAME": "ghc-x86_64-linux-fedora42-release",
"BUILD_FLAVOUR": "release",
"CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
"HADRIAN_ARGS": "--haddock-for-hackage",
"INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
- "LLC": "/bin/false",
- "OPT": "/bin/false",
"RUNTEST_ARGS": "",
- "TEST_ENV": "x86_64-linux-fedora33-release"
+ "TEST_ENV": "x86_64-linux-fedora42-release"
}
},
- "x86_64-linux-fedora33-validate+debug_info": {
+ "x86_64-linux-fedora42-validate": {
"after_script": [
".gitlab/ci.sh save_cache",
".gitlab/ci.sh save_test_output",
@@ -7248,7 +7168,7 @@
"artifacts": {
"expire_in": "2 weeks",
"paths": [
- "ghc-x86_64-linux-fedora33-validate+debug_info.tar.xz",
+ "ghc-x86_64-linux-fedora42-validate.tar.xz",
"junit.xml",
"unexpected-test-output.tar.gz"
],
@@ -7258,14 +7178,14 @@
"when": "always"
},
"cache": {
- "key": "x86_64-linux-fedora33-$CACHE_REV",
+ "key": "x86_64-linux-fedora42-$CACHE_REV",
"paths": [
"cabal-cache",
"toolchain"
]
},
"dependencies": [],
- "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora33:$DOCKER_REV",
+ "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora42:$DOCKER_REV",
"needs": [
{
"artifacts": false,
@@ -7274,7 +7194,7 @@
],
"rules": [
{
- "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-fedora33-validate\\+debug_info(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+ "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-fedora42-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
"when": "on_success"
}
],
@@ -7291,17 +7211,15 @@
],
"variables": {
"BIGNUM_BACKEND": "gmp",
- "BIN_DIST_NAME": "ghc-x86_64-linux-fedora33-validate+debug_info",
- "BUILD_FLAVOUR": "validate+debug_info",
+ "BIN_DIST_NAME": "ghc-x86_64-linux-fedora42-validate",
+ "BUILD_FLAVOUR": "validate",
"CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
"INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
- "LLC": "/bin/false",
- "OPT": "/bin/false",
"RUNTEST_ARGS": "",
- "TEST_ENV": "x86_64-linux-fedora33-validate+debug_info"
+ "TEST_ENV": "x86_64-linux-fedora42-validate"
}
},
- "x86_64-linux-fedora38-validate": {
+ "x86_64-linux-fedora42-validate+debug_info": {
"after_script": [
".gitlab/ci.sh save_cache",
".gitlab/ci.sh save_test_output",
@@ -7312,7 +7230,7 @@
"artifacts": {
"expire_in": "2 weeks",
"paths": [
- "ghc-x86_64-linux-fedora38-validate.tar.xz",
+ "ghc-x86_64-linux-fedora42-validate+debug_info.tar.xz",
"junit.xml",
"unexpected-test-output.tar.gz"
],
@@ -7322,14 +7240,14 @@
"when": "always"
},
"cache": {
- "key": "x86_64-linux-fedora38-$CACHE_REV",
+ "key": "x86_64-linux-fedora42-$CACHE_REV",
"paths": [
"cabal-cache",
"toolchain"
]
},
"dependencies": [],
- "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora38:$DOCKER_REV",
+ "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora42:$DOCKER_REV",
"needs": [
{
"artifacts": false,
@@ -7338,7 +7256,7 @@
],
"rules": [
{
- "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-fedora38-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+ "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-fedora42-validate\\+debug_info(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
"when": "on_success"
}
],
@@ -7355,12 +7273,12 @@
],
"variables": {
"BIGNUM_BACKEND": "gmp",
- "BIN_DIST_NAME": "ghc-x86_64-linux-fedora38-validate",
- "BUILD_FLAVOUR": "validate",
+ "BIN_DIST_NAME": "ghc-x86_64-linux-fedora42-validate+debug_info",
+ "BUILD_FLAVOUR": "validate+debug_info",
"CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
"INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
"RUNTEST_ARGS": "",
- "TEST_ENV": "x86_64-linux-fedora38-validate"
+ "TEST_ENV": "x86_64-linux-fedora42-validate+debug_info"
}
},
"x86_64-linux-rocky8-validate": {
=====================================
.gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py
=====================================
@@ -23,10 +23,8 @@ def job_triple(job_name):
'release-x86_64-linux-ubuntu22_04-release': 'x86_64-ubuntu22_04-linux',
'release-x86_64-linux-ubuntu20_04-release': 'x86_64-ubuntu20_04-linux',
'release-x86_64-linux-ubuntu18_04-release': 'x86_64-ubuntu18_04-linux',
- 'release-x86_64-linux-fedora38-release': 'x86_64-fedora38-linux',
- 'release-x86_64-linux-fedora33-release+debug_info': 'x86_64-fedora33-linux-dwarf',
- 'release-x86_64-linux-fedora33-release': 'x86_64-fedora33-linux',
- 'release-x86_64-linux-fedora27-release': 'x86_64-fedora27-linux',
+ 'release-x86_64-linux-fedora42-release': 'x86_64-fedora42-linux',
+ 'release-x86_64-linux-fedora42-release+debug_info': 'x86_64-fedora42-linux-dwarf',
'release-x86_64-linux-deb12-release': 'x86_64-deb12-linux',
'release-x86_64-linux-deb11-release': 'x86_64-deb11-linux',
'release-x86_64-linux-deb10-release+debug_info': 'x86_64-deb10-linux-dwarf',
=====================================
.gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
=====================================
@@ -200,7 +200,7 @@ def mk_new_yaml(release_mode, version, date, pipeline_type, job_map):
ubuntu2204 = mk(ubuntu("22_04"))
ubuntu2404 = mk(ubuntu("24_04"))
rocky8 = mk(rocky("8"))
- fedora33 = mk(fedora(33))
+ fedora42 = mk(fedora(42))
darwin_x86 = mk(darwin("x86_64"))
darwin_arm64 = mk(darwin("aarch64"))
windows = mk(windowsArtifact)
@@ -239,11 +239,9 @@ def mk_new_yaml(release_mode, version, date, pipeline_type, job_map):
, "unknown_versioning": ubuntu2004 }
, "Linux_CentOS" : { "( >= 8 && < 9 )" : rocky8
, "unknown_versioning" : rocky8 }
- , "Linux_Fedora" : { ">= 33": fedora33
+ , "Linux_Fedora" : { ">= 42": fedora42
, "unknown_versioning": rocky8 }
- , "Linux_RedHat" : { "< 9": rocky8
- , ">= 9": fedora33
- , "unknown_versioning": fedora33 }
+ , "Linux_RedHat" : { "unknown_versioning": rocky8 }
, "Linux_UnknownLinux" : { "unknown_versioning": rocky8 }
, "Darwin" : { "unknown_versioning" : darwin_x86 }
, "Windows" : { "unknown_versioning" : windows }
=====================================
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/HsToCore/Monad.hs
=====================================
@@ -58,6 +58,7 @@ module GHC.HsToCore.Monad (
import GHC.Prelude
import GHC.Driver.Env
+import GHC.Driver.Env.KnotVars
import GHC.Driver.DynFlags
import GHC.Driver.Ppr
import GHC.Driver.Config.Diagnostic
@@ -117,7 +118,7 @@ import GHC.Utils.Panic
import qualified GHC.Data.Strict as Strict
import Data.IORef
-import GHC.Driver.Env.KnotVars
+
import GHC.IO.Unsafe (unsafeInterleaveIO)
{-
=====================================
compiler/GHC/Linker/Loader.hs
=====================================
@@ -1,6 +1,7 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE ViewPatterns #-}
--
-- (c) The University of Glasgow 2002-2006
@@ -104,6 +105,7 @@ import Data.Array
import Data.ByteString (ByteString)
import qualified Data.Set as Set
import Data.Char (isSpace)
+import Data.Foldable (for_)
import qualified Data.Foldable as Foldable
import Data.IORef
import Data.List (intercalate, isPrefixOf, nub, partition)
@@ -535,7 +537,7 @@ preloadLib interp hsc_env lib_paths framework_paths pls lib_spec = do
return pls
DLL dll_unadorned -> do
- maybe_errstr <- loadDLL interp (platformSOName platform dll_unadorned)
+ maybe_errstr <- loadDLLs interp [platformSOName platform dll_unadorned]
case maybe_errstr of
Right _ -> maybePutStrLn logger "done"
Left mm | platformOS platform /= OSDarwin ->
@@ -545,14 +547,14 @@ preloadLib interp hsc_env lib_paths framework_paths pls lib_spec = do
-- since (apparently) some things install that way - see
-- ticket #8770.
let libfile = ("lib" ++ dll_unadorned) <.> "so"
- err2 <- loadDLL interp libfile
+ err2 <- loadDLLs interp [libfile]
case err2 of
Right _ -> maybePutStrLn logger "done"
Left _ -> preloadFailed mm lib_paths lib_spec
return pls
DLLPath dll_path -> do
- do maybe_errstr <- loadDLL interp dll_path
+ do maybe_errstr <- loadDLLs interp [dll_path]
case maybe_errstr of
Right _ -> maybePutStrLn logger "done"
Left mm -> preloadFailed mm lib_paths lib_spec
@@ -892,7 +894,7 @@ dynLoadObjs interp hsc_env pls@LoaderState{..} objs = do
-- if we got this far, extend the lifetime of the library file
changeTempFilesLifetime tmpfs TFL_GhcSession [soFile]
- m <- loadDLL interp soFile
+ m <- loadDLLs interp [soFile]
case m of
Right _ -> return $! pls { temp_sos = (libPath, libName) : temp_sos }
Left err -> linkFail msg (text err)
@@ -1129,51 +1131,91 @@ loadPackages interp hsc_env new_pkgs = do
loadPackages' :: Interp -> HscEnv -> [UnitId] -> LoaderState -> IO LoaderState
loadPackages' interp hsc_env new_pks pls = do
- pkgs' <- link (pkgs_loaded pls) new_pks
- return $! pls { pkgs_loaded = pkgs'
- }
+ (reverse -> pkgs_info_list, pkgs_almost_loaded) <-
+ downsweep
+ ([], pkgs_loaded pls)
+ new_pks
+ loaded_pkgs_info_list <- loadPackage interp hsc_env pkgs_info_list
+ evaluate $
+ pls
+ { pkgs_loaded =
+ foldl'
+ ( \pkgs (new_pkg_info, (hs_cls, extra_cls, loaded_dlls)) ->
+ adjustUDFM
+ ( \old_pkg_info ->
+ old_pkg_info
+ { loaded_pkg_hs_objs = hs_cls,
+ loaded_pkg_non_hs_objs = extra_cls,
+ loaded_pkg_hs_dlls = loaded_dlls
+ }
+ )
+ pkgs
+ (Packages.unitId new_pkg_info)
+ )
+ pkgs_almost_loaded
+ (zip pkgs_info_list loaded_pkgs_info_list)
+ }
where
- link :: PkgsLoaded -> [UnitId] -> IO PkgsLoaded
- link pkgs new_pkgs =
- foldM link_one pkgs new_pkgs
-
- link_one pkgs new_pkg
- | new_pkg `elemUDFM` pkgs -- Already linked
- = return pkgs
-
- | Just pkg_cfg <- lookupUnitId (hsc_units hsc_env) new_pkg
- = do { let deps = unitDepends pkg_cfg
- -- Link dependents first
- ; pkgs' <- link pkgs deps
- -- Now link the package itself
- ; (hs_cls, extra_cls, loaded_dlls) <- loadPackage interp hsc_env pkg_cfg
- ; let trans_deps = unionManyUniqDSets [ addOneToUniqDSet (loaded_pkg_trans_deps loaded_pkg_info) dep_pkg
- | dep_pkg <- deps
- , Just loaded_pkg_info <- pure (lookupUDFM pkgs' dep_pkg)
- ]
- ; return (addToUDFM pkgs' new_pkg (LoadedPkgInfo new_pkg hs_cls extra_cls loaded_dlls trans_deps)) }
-
- | otherwise
- = throwGhcExceptionIO (CmdLineError ("unknown package: " ++ unpackFS (unitIdFS new_pkg)))
-
-
-loadPackage :: Interp -> HscEnv -> UnitInfo -> IO ([LibrarySpec], [LibrarySpec], [RemotePtr LoadedDLL])
-loadPackage interp hsc_env pkg
+ -- The downsweep process takes an initial 'PkgsLoaded' and uses it
+ -- to memoize new packages to load when recursively downsweeping
+ -- the dependencies. The returned 'PkgsLoaded' is popularized with
+ -- placeholder 'LoadedPkgInfo' for new packages yet to be loaded,
+ -- which need to be modified later to fill in the missing fields.
+ --
+ -- The [UnitInfo] list is an accumulated *reverse* topologically
+ -- sorted list of new packages to load: 'downsweep_one' appends a
+ -- package to its head after that package's transitive
+ -- dependencies go into that list. There are no duplicate items in
+ -- this list due to memoization.
+ downsweep ::
+ ([UnitInfo], PkgsLoaded) -> [UnitId] -> IO ([UnitInfo], PkgsLoaded)
+ downsweep = foldlM downsweep_one
+
+ downsweep_one ::
+ ([UnitInfo], PkgsLoaded) -> UnitId -> IO ([UnitInfo], PkgsLoaded)
+ downsweep_one (pkgs_info_list, pkgs) new_pkg
+ | new_pkg `elemUDFM` pkgs = pure (pkgs_info_list, pkgs)
+ | Just new_pkg_info <- lookupUnitId (hsc_units hsc_env) new_pkg = do
+ let new_pkg_deps = unitDepends new_pkg_info
+ (pkgs_info_list', pkgs') <- downsweep (pkgs_info_list, pkgs) new_pkg_deps
+ let new_pkg_trans_deps =
+ unionManyUniqDSets
+ [ addOneToUniqDSet (loaded_pkg_trans_deps loaded_pkg_info) dep_pkg
+ | dep_pkg <- new_pkg_deps,
+ loaded_pkg_info <- maybeToList $ pkgs' `lookupUDFM` dep_pkg
+ ]
+ pure
+ ( new_pkg_info : pkgs_info_list',
+ addToUDFM pkgs' new_pkg $
+ LoadedPkgInfo
+ { loaded_pkg_uid = new_pkg,
+ loaded_pkg_hs_objs = [],
+ loaded_pkg_non_hs_objs = [],
+ loaded_pkg_hs_dlls = [],
+ loaded_pkg_trans_deps = new_pkg_trans_deps
+ }
+ )
+ | otherwise =
+ throwGhcExceptionIO
+ (CmdLineError ("unknown package: " ++ unpackFS (unitIdFS new_pkg)))
+
+loadPackage :: Interp -> HscEnv -> [UnitInfo] -> IO [([LibrarySpec], [LibrarySpec], [RemotePtr LoadedDLL])]
+loadPackage interp hsc_env pkgs
= do
let dflags = hsc_dflags hsc_env
let logger = hsc_logger hsc_env
platform = targetPlatform dflags
is_dyn = interpreterDynamic interp
- dirs | is_dyn = map ST.unpack $ Packages.unitLibraryDynDirs pkg
- | otherwise = map ST.unpack $ Packages.unitLibraryDirs pkg
+ dirs | is_dyn = [map ST.unpack $ Packages.unitLibraryDynDirs pkg | pkg <- pkgs]
+ | otherwise = [map ST.unpack $ Packages.unitLibraryDirs pkg | pkg <- pkgs]
- let hs_libs = map ST.unpack $ Packages.unitLibraries pkg
+ let hs_libs = [map ST.unpack $ Packages.unitLibraries pkg | pkg <- pkgs]
-- The FFI GHCi import lib isn't needed as
-- GHC.Linker.Loader + rts/Linker.c link the
-- interpreted references to FFI to the compiled FFI.
-- We therefore filter it out so that we don't get
-- duplicate symbol errors.
- hs_libs' = filter ("HSffi" /=) hs_libs
+ hs_libs' = filter ("HSffi" /=) <$> hs_libs
-- Because of slight differences between the GHC dynamic linker and
-- the native system linker some packages have to link with a
@@ -1182,51 +1224,60 @@ loadPackage interp hsc_env pkg
-- libs do not exactly match the .so/.dll equivalents. So if the
-- package file provides an "extra-ghci-libraries" field then we use
-- that instead of the "extra-libraries" field.
- extdeplibs = map ST.unpack (if null (Packages.unitExtDepLibsGhc pkg)
+ extdeplibs = [map ST.unpack (if null (Packages.unitExtDepLibsGhc pkg)
then Packages.unitExtDepLibsSys pkg
- else Packages.unitExtDepLibsGhc pkg)
- linkerlibs = [ lib | '-':'l':lib <- (map ST.unpack $ Packages.unitLinkerOptions pkg) ]
- extra_libs = extdeplibs ++ linkerlibs
+ else Packages.unitExtDepLibsGhc pkg) | pkg <- pkgs]
+ linkerlibs = [[ lib | '-':'l':lib <- (map ST.unpack $ Packages.unitLinkerOptions pkg) ] | pkg <- pkgs]
+ extra_libs = zipWith (++) extdeplibs linkerlibs
-- See Note [Fork/Exec Windows]
gcc_paths <- getGCCPaths logger dflags (platformOS platform)
- dirs_env <- addEnvPaths "LIBRARY_PATH" dirs
+ dirs_env <- traverse (addEnvPaths "LIBRARY_PATH") dirs
hs_classifieds
- <- mapM (locateLib interp hsc_env True dirs_env gcc_paths) hs_libs'
+ <- sequenceA [mapM (locateLib interp hsc_env True dirs_env_ gcc_paths) hs_libs'_ | (dirs_env_, hs_libs'_) <- zip dirs_env hs_libs' ]
extra_classifieds
- <- mapM (locateLib interp hsc_env False dirs_env gcc_paths) extra_libs
- let classifieds = hs_classifieds ++ extra_classifieds
+ <- sequenceA [mapM (locateLib interp hsc_env False dirs_env_ gcc_paths) extra_libs_ | (dirs_env_, extra_libs_) <- zip dirs_env extra_libs]
+ let classifieds = zipWith (++) hs_classifieds extra_classifieds
-- Complication: all the .so's must be loaded before any of the .o's.
- let known_hs_dlls = [ dll | DLLPath dll <- hs_classifieds ]
- known_extra_dlls = [ dll | DLLPath dll <- extra_classifieds ]
- known_dlls = known_hs_dlls ++ known_extra_dlls
+ let known_hs_dlls = [[ dll | DLLPath dll <- hs_classifieds_ ] | hs_classifieds_ <- hs_classifieds]
+ known_extra_dlls = [ dll | extra_classifieds_ <- extra_classifieds, DLLPath dll <- extra_classifieds_ ]
+ known_dlls = concat known_hs_dlls ++ known_extra_dlls
#if defined(CAN_LOAD_DLL)
- dlls = [ dll | DLL dll <- classifieds ]
+ dlls = [ dll | classifieds_ <- classifieds, DLL dll <- classifieds_ ]
#endif
- objs = [ obj | Objects objs <- classifieds
- , obj <- objs ]
- archs = [ arch | Archive arch <- classifieds ]
+ objs = [ obj | classifieds_ <- classifieds, Objects objs <- classifieds_
+ , obj <- objs]
+ archs = [ arch | classifieds_ <- classifieds, Archive arch <- classifieds_ ]
-- Add directories to library search paths
let dll_paths = map takeDirectory known_dlls
- all_paths = nub $ map normalise $ dll_paths ++ dirs
+ all_paths = nub $ map normalise $ dll_paths ++ concat dirs
all_paths_env <- addEnvPaths "LD_LIBRARY_PATH" all_paths
pathCache <- mapM (addLibrarySearchPath interp) all_paths_env
maybePutSDoc logger
- (text "Loading unit " <> pprUnitInfoForUser pkg <> text " ... ")
+ (text "Loading units " <> vcat (map pprUnitInfoForUser pkgs) <> text " ... ")
#if defined(CAN_LOAD_DLL)
- loadFrameworks interp platform pkg
+ for_ pkgs $ loadFrameworks interp platform
-- See Note [Crash early load_dyn and locateLib]
-- Crash early if can't load any of `known_dlls`
- mapM_ (load_dyn interp hsc_env True) known_extra_dlls
- loaded_dlls <- mapMaybeM (load_dyn interp hsc_env True) known_hs_dlls
+ _ <- load_dyn interp hsc_env True known_extra_dlls
+
+ -- We pass [[FilePath]] of dlls to load and flattens the list
+ -- before doing a LoadDLLs. The returned list of RemotePtrs
+ -- would need to be regrouped to the same shape of the input
+ -- [[FilePath]], each group's [RemotePtr LoadedDLL]
+ -- corresponds to the DLL handles of a Haskell unit.
+ let regroup :: [[a]] -> [b] -> [[b]]
+ regroup [] _ = []
+ regroup (l:ls) xs = xs0: regroup ls xs1 where (xs0, xs1) = splitAt (length l) xs
+ loaded_dlls <- regroup known_hs_dlls <$> load_dyn interp hsc_env True (concat known_hs_dlls)
-- For remaining `dlls` crash early only when there is surely
-- no package's DLL around ... (not is_dyn)
- mapM_ (load_dyn interp hsc_env (not is_dyn) . platformSOName platform) dlls
+ _ <- load_dyn interp hsc_env (not is_dyn) $ map (platformSOName platform) dlls
#else
let loaded_dlls = []
#endif
@@ -1248,9 +1299,9 @@ loadPackage interp hsc_env pkg
if succeeded ok
then do
maybePutStrLn logger "done."
- return (hs_classifieds, extra_classifieds, loaded_dlls)
- else let errmsg = text "unable to load unit `"
- <> pprUnitInfoForUser pkg <> text "'"
+ pure $ zip3 hs_classifieds extra_classifieds loaded_dlls
+ else let errmsg = text "unable to load units `"
+ <> vcat (map pprUnitInfoForUser pkgs) <> text "'"
in throwGhcExceptionIO (InstallationError (showSDoc dflags errmsg))
{-
@@ -1300,12 +1351,12 @@ restriction very easily.
-- we have already searched the filesystem; the strings passed to load_dyn
-- can be passed directly to loadDLL. They are either fully-qualified
-- ("/usr/lib/libfoo.so"), or unqualified ("libfoo.so"). In the latter case,
--- loadDLL is going to search the system paths to find the library.
-load_dyn :: Interp -> HscEnv -> Bool -> FilePath -> IO (Maybe (RemotePtr LoadedDLL))
-load_dyn interp hsc_env crash_early dll = do
- r <- loadDLL interp dll
+-- loadDLLs is going to search the system paths to find the library.
+load_dyn :: Interp -> HscEnv -> Bool -> [FilePath] -> IO [RemotePtr LoadedDLL]
+load_dyn interp hsc_env crash_early dlls = do
+ r <- loadDLLs interp dlls
case r of
- Right loaded_dll -> pure (Just loaded_dll)
+ Right loaded_dlls -> pure loaded_dlls
Left err ->
if crash_early
then cmdLineErrorIO err
@@ -1314,7 +1365,7 @@ load_dyn interp hsc_env crash_early dll = do
$ reportDiagnostic logger
neverQualify diag_opts
noSrcSpan (WarningWithFlag Opt_WarnMissedExtraSharedLib) $ withPprStyle defaultUserStyle (note err)
- pure Nothing
+ pure []
where
diag_opts = initDiagOpts (hsc_dflags hsc_env)
logger = hsc_logger hsc_env
@@ -1370,7 +1421,7 @@ locateLib interp hsc_env is_hs lib_dirs gcc_dirs lib0
-- then look in library-dirs and inplace GCC for a static library (libfoo.a)
-- then try "gcc --print-file-name" to search gcc's search path
-- for a dynamic library (#5289)
- -- otherwise, assume loadDLL can find it
+ -- otherwise, assume loadDLLs can find it
--
-- The logic is a bit complicated, but the rationale behind it is that
-- loading a shared library for us is O(1) while loading an archive is
=====================================
compiler/GHC/Linker/MacOS.hs
=====================================
@@ -162,7 +162,7 @@ loadFramework interp extraPaths rootname
-- sorry for the hardcoded paths, I hope they won't change anytime soon:
defaultFrameworkPaths = ["/Library/Frameworks", "/System/Library/Frameworks"]
- -- Try to call loadDLL for each candidate path.
+ -- Try to call loadDLLs for each candidate path.
--
-- See Note [macOS Big Sur dynamic libraries]
findLoadDLL [] errs =
@@ -170,7 +170,7 @@ loadFramework interp extraPaths rootname
-- has no built-in paths for frameworks: give up
return $ Just errs
findLoadDLL (p:ps) errs =
- do { dll <- loadDLL interp (p </> fwk_file)
+ do { dll <- loadDLLs interp [p </> fwk_file]
; case dll of
Right _ -> return Nothing
Left err -> findLoadDLL ps ((p ++ ": " ++ err):errs)
=====================================
compiler/GHC/Linker/Types.hs
=====================================
@@ -494,7 +494,7 @@ data LibrarySpec
| DLL String -- "Unadorned" name of a .DLL/.so
-- e.g. On unix "qt" denotes "libqt.so"
-- On Windows "burble" denotes "burble.DLL" or "libburble.dll"
- -- loadDLL is platform-specific and adds the lib/.so/.DLL
+ -- loadDLLs is platform-specific and adds the lib/.so/.DLL
-- suffixes platform-dependently
| DLLPath FilePath -- Absolute or relative pathname to a dynamic library
=====================================
compiler/GHC/Runtime/Interpreter.hs
=====================================
@@ -38,7 +38,7 @@ module GHC.Runtime.Interpreter
, lookupSymbol
, lookupSymbolInDLL
, lookupClosure
- , loadDLL
+ , loadDLLs
, loadArchive
, loadObj
, unloadObj
@@ -559,13 +559,13 @@ withSymbolCache interp str determine_addr = do
purgeLookupSymbolCache :: Interp -> IO ()
purgeLookupSymbolCache interp = purgeInterpSymbolCache (interpSymbolCache interp)
--- | loadDLL loads a dynamic library using the OS's native linker
+-- | 'loadDLLs' loads dynamic libraries using the OS's native linker
-- (i.e. dlopen() on Unix, LoadLibrary() on Windows). It takes either
--- an absolute pathname to the file, or a relative filename
--- (e.g. "libfoo.so" or "foo.dll"). In the latter case, loadDLL
--- searches the standard locations for the appropriate library.
-loadDLL :: Interp -> String -> IO (Either String (RemotePtr LoadedDLL))
-loadDLL interp str = interpCmd interp (LoadDLL str)
+-- absolute pathnames to the files, or relative filenames
+-- (e.g. "libfoo.so" or "foo.dll"). In the latter case, 'loadDLLs'
+-- searches the standard locations for the appropriate libraries.
+loadDLLs :: Interp -> [String] -> IO (Either String [RemotePtr LoadedDLL])
+loadDLLs interp strs = interpCmd interp (LoadDLLs strs)
loadArchive :: Interp -> String -> IO ()
loadArchive interp path = do
@@ -761,4 +761,3 @@ readIModModBreaks hug mod = imodBreaks_modBreaks . expectJust <$> readIModBreaks
fromEvalResult :: EvalResult a -> IO a
fromEvalResult (EvalException e) = throwIO (fromSerializableException e)
fromEvalResult (EvalSuccess a) = return a
-
=====================================
compiler/GHC/Tc/Module.hs
=====================================
@@ -26,6 +26,7 @@ module GHC.Tc.Module (
runTcInteractive, -- Used by GHC API clients (#8878)
withTcPlugins, -- Used by GHC API clients (#20499)
withHoleFitPlugins, -- Used by GHC API clients (#20499)
+ withDefaultingPlugins,
tcRnLookupName,
tcRnGetInfo,
tcRnModule, tcRnModuleTcRnM,
@@ -53,7 +54,6 @@ import GHC.Driver.DynFlags
import GHC.Driver.Config.Diagnostic
import GHC.IO.Unsafe ( unsafeInterleaveIO )
-import GHC.Tc.Errors.Hole.Plugin ( HoleFitPluginR (..) )
import GHC.Tc.Errors.Types
import {-# SOURCE #-} GHC.Tc.Gen.Splice ( finishTH, runRemoteModFinalizers )
import GHC.Tc.Gen.HsType
@@ -141,7 +141,6 @@ import GHC.Types.Id as Id
import GHC.Types.Id.Info( IdDetails(..) )
import GHC.Types.Var.Env
import GHC.Types.TypeEnv
-import GHC.Types.Unique.FM
import GHC.Types.Name
import GHC.Types.Name.Env
import GHC.Types.Name.Set
@@ -212,10 +211,6 @@ tcRnModule hsc_env mod_sum save_rn_syntax
(text "Renamer/typechecker"<+>brackets (ppr this_mod))
(const ()) $
initTc hsc_env hsc_src save_rn_syntax this_mod real_loc $
- withTcPlugins hsc_env $
- withDefaultingPlugins hsc_env $
- withHoleFitPlugins hsc_env $
-
tcRnModuleTcRnM hsc_env mod_sum parsedModule this_mod
| otherwise
@@ -3182,72 +3177,11 @@ hasTopUserName x
{-
********************************************************************************
-Type Checker Plugins
+ Running plugins
********************************************************************************
-}
-withTcPlugins :: HscEnv -> TcM a -> TcM a
-withTcPlugins hsc_env m =
- case catMaybes $ mapPlugins (hsc_plugins hsc_env) tcPlugin of
- [] -> m -- Common fast case
- plugins -> do
- (solvers, rewriters, stops) <-
- unzip3 `fmap` mapM start_plugin plugins
- let
- rewritersUniqFM :: UniqFM TyCon [TcPluginRewriter]
- !rewritersUniqFM = sequenceUFMList rewriters
- -- The following ensures that tcPluginStop is called even if a type
- -- error occurs during compilation (Fix of #10078)
- eitherRes <- tryM $
- updGblEnv (\e -> e { tcg_tc_plugin_solvers = solvers
- , tcg_tc_plugin_rewriters = rewritersUniqFM }) m
- mapM_ runTcPluginM stops
- case eitherRes of
- Left _ -> failM
- Right res -> return res
- where
- start_plugin (TcPlugin start solve rewrite stop) =
- do s <- runTcPluginM start
- return (solve s, rewrite s, stop s)
-
-withDefaultingPlugins :: HscEnv -> TcM a -> TcM a
-withDefaultingPlugins hsc_env m =
- do case catMaybes $ mapPlugins (hsc_plugins hsc_env) defaultingPlugin of
- [] -> m -- Common fast case
- plugins -> do (plugins,stops) <- mapAndUnzipM start_plugin plugins
- -- This ensures that dePluginStop is called even if a type
- -- error occurs during compilation
- eitherRes <- tryM $ do
- updGblEnv (\e -> e { tcg_defaulting_plugins = plugins }) m
- mapM_ runTcPluginM stops
- case eitherRes of
- Left _ -> failM
- Right res -> return res
- where
- start_plugin (DefaultingPlugin start fill stop) =
- do s <- runTcPluginM start
- return (fill s, stop s)
-
-withHoleFitPlugins :: HscEnv -> TcM a -> TcM a
-withHoleFitPlugins hsc_env m =
- case catMaybes $ mapPlugins (hsc_plugins hsc_env) holeFitPlugin of
- [] -> m -- Common fast case
- plugins -> do (plugins,stops) <- mapAndUnzipM start_plugin plugins
- -- This ensures that hfPluginStop is called even if a type
- -- error occurs during compilation.
- eitherRes <- tryM $
- updGblEnv (\e -> e { tcg_hf_plugins = plugins }) m
- sequence_ stops
- case eitherRes of
- Left _ -> failM
- Right res -> return res
- where
- start_plugin (HoleFitPluginR init plugin stop) =
- do ref <- init
- return (plugin ref, stop ref)
-
-
runRenamerPlugin :: TcGblEnv
-> HsGroup GhcRn
-> TcM (TcGblEnv, HsGroup GhcRn)
=====================================
compiler/GHC/Tc/Utils/Monad.hs
=====================================
@@ -31,6 +31,9 @@ module GHC.Tc.Utils.Monad(
updateEps, updateEps_,
getHpt, getEpsAndHug,
+ -- * Initialising TcM plugins
+ withTcPlugins, withDefaultingPlugins, withHoleFitPlugins,
+
-- * Arrow scopes
newArrowScope, escapeArrowScope,
@@ -163,6 +166,7 @@ import GHC.Builtin.Names
import GHC.Builtin.Types( zonkAnyTyCon )
import GHC.Tc.Errors.Types
+import GHC.Tc.Errors.Hole.Plugin ( HoleFitPluginR (..) )
import GHC.Tc.Types -- Re-export all
import GHC.Tc.Types.Constraint
import GHC.Tc.Types.CtLoc
@@ -183,13 +187,17 @@ import GHC.Unit.Module.Warnings
import GHC.Unit.Home.PackageTable
import GHC.Core.UsageEnv
+
+import GHC.Core.Coercion ( isReflCo )
import GHC.Core.Multiplicity
import GHC.Core.InstEnv
import GHC.Core.FamInstEnv
import GHC.Core.Type( mkNumLitTy )
+import GHC.Core.TyCon ( TyCon )
import GHC.Driver.Env
import GHC.Driver.Env.KnotVars
+import GHC.Driver.Plugins ( Plugin(..), mapPlugins )
import GHC.Driver.Session
import GHC.Driver.Config.Diagnostic
@@ -226,7 +234,7 @@ import GHC.Types.SrcLoc
import GHC.Types.Name.Env
import GHC.Types.Name.Set
import GHC.Types.Name.Ppr
-import GHC.Types.Unique.FM ( emptyUFM )
+import GHC.Types.Unique.FM ( UniqFM, emptyUFM, sequenceUFMList )
import GHC.Types.Unique.DFM
import GHC.Types.Unique.Supply
import GHC.Types.Annotations
@@ -240,8 +248,6 @@ import Data.IORef
import Control.Monad
import qualified Data.Map as Map
-import GHC.Core.Coercion (isReflCo)
-
{-
************************************************************************
@@ -263,129 +269,139 @@ initTc :: HscEnv
-- (error messages should have been printed already)
initTc hsc_env hsc_src keep_rn_syntax mod loc do_this
- = do { keep_var <- newIORef emptyNameSet ;
- used_gre_var <- newIORef [] ;
- th_var <- newIORef False ;
- infer_var <- newIORef True ;
- infer_reasons_var <- newIORef emptyMessages ;
- dfun_n_var <- newIORef emptyOccSet ;
- zany_n_var <- newIORef 0 ;
- let { type_env_var = hsc_type_env_vars hsc_env };
-
- dependent_files_var <- newIORef [] ;
- dependent_dirs_var <- newIORef [] ;
- static_wc_var <- newIORef emptyWC ;
- cc_st_var <- newIORef newCostCentreState ;
- th_topdecls_var <- newIORef [] ;
- th_foreign_files_var <- newIORef [] ;
- th_topnames_var <- newIORef emptyNameSet ;
- th_modfinalizers_var <- newIORef [] ;
- th_coreplugins_var <- newIORef [] ;
- th_state_var <- newIORef Map.empty ;
- th_remote_state_var <- newIORef Nothing ;
- th_docs_var <- newIORef Map.empty ;
- th_needed_deps_var <- newIORef ([], emptyUDFM) ;
- next_wrapper_num <- newIORef emptyModuleEnv ;
- let {
- -- bangs to avoid leaking the env (#19356)
- !dflags = hsc_dflags hsc_env ;
- !mhome_unit = hsc_home_unit_maybe hsc_env;
- !logger = hsc_logger hsc_env ;
-
- maybe_rn_syntax :: forall a. a -> Maybe a ;
- maybe_rn_syntax empty_val
- | logHasDumpFlag logger Opt_D_dump_rn_ast = Just empty_val
-
- | gopt Opt_WriteHie dflags = Just empty_val
-
- -- We want to serialize the documentation in the .hi-files,
- -- and need to extract it from the renamed syntax first.
- -- See 'GHC.HsToCore.Docs.extractDocs'.
- | gopt Opt_Haddock dflags = Just empty_val
-
- | keep_rn_syntax = Just empty_val
- | otherwise = Nothing ;
-
- gbl_env = TcGblEnv {
- tcg_th_topdecls = th_topdecls_var,
- tcg_th_foreign_files = th_foreign_files_var,
- tcg_th_topnames = th_topnames_var,
- tcg_th_modfinalizers = th_modfinalizers_var,
- tcg_th_coreplugins = th_coreplugins_var,
- tcg_th_state = th_state_var,
- tcg_th_remote_state = th_remote_state_var,
- tcg_th_docs = th_docs_var,
-
- tcg_mod = mod,
- tcg_semantic_mod = homeModuleInstantiation mhome_unit mod,
- tcg_src = hsc_src,
- tcg_rdr_env = emptyGlobalRdrEnv,
- tcg_fix_env = emptyNameEnv,
- tcg_default = emptyDefaultEnv,
- tcg_default_exports = emptyDefaultEnv,
- tcg_type_env = emptyNameEnv,
- tcg_type_env_var = type_env_var,
- tcg_inst_env = emptyInstEnv,
- tcg_fam_inst_env = emptyFamInstEnv,
- tcg_ann_env = emptyAnnEnv,
- tcg_complete_match_env = [],
- tcg_th_used = th_var,
- tcg_th_needed_deps = th_needed_deps_var,
- tcg_exports = [],
- tcg_imports = emptyImportAvails,
- tcg_import_decls = [],
- tcg_used_gres = used_gre_var,
- tcg_dus = emptyDUs,
-
- tcg_rn_imports = [],
- tcg_rn_exports =
- if hsc_src == HsigFile
- -- Always retain renamed syntax, so that we can give
- -- better errors. (TODO: how?)
- then Just []
- else maybe_rn_syntax [],
- tcg_rn_decls = maybe_rn_syntax emptyRnGroup,
- tcg_tr_module = Nothing,
- tcg_binds = emptyLHsBinds,
- tcg_imp_specs = [],
- tcg_sigs = emptyNameSet,
- tcg_ksigs = emptyNameSet,
- tcg_ev_binds = emptyBag,
- tcg_warns = emptyWarn,
- tcg_anns = [],
- tcg_tcs = [],
- tcg_insts = [],
- tcg_fam_insts = [],
- tcg_rules = [],
- tcg_fords = [],
- tcg_patsyns = [],
- tcg_merged = [],
- tcg_dfun_n = dfun_n_var,
- tcg_zany_n = zany_n_var,
- tcg_keep = keep_var,
- tcg_hdr_info = (Nothing,Nothing),
- tcg_main = Nothing,
- tcg_self_boot = NoSelfBoot,
- tcg_safe_infer = infer_var,
- tcg_safe_infer_reasons = infer_reasons_var,
- tcg_dependent_files = dependent_files_var,
- tcg_dependent_dirs = dependent_dirs_var,
- tcg_tc_plugin_solvers = [],
- tcg_tc_plugin_rewriters = emptyUFM,
- tcg_defaulting_plugins = [],
- tcg_hf_plugins = [],
- tcg_top_loc = loc,
- tcg_static_wc = static_wc_var,
- tcg_complete_matches = [],
- tcg_cc_st = cc_st_var,
- tcg_next_wrapper_num = next_wrapper_num
- } ;
- } ;
+ = do { gbl_env <- initTcGblEnv hsc_env hsc_src keep_rn_syntax mod loc
-- OK, here's the business end!
- initTcWithGbl hsc_env gbl_env loc do_this
+ ; initTcWithGbl hsc_env gbl_env loc $
+
+ -- Make sure to initialise all TcM plugins from the ambient HscEnv.
+ --
+ -- This ensures that all callers of 'initTc' enable plugins (#26395).
+ withTcPlugins hsc_env $
+ withDefaultingPlugins hsc_env $
+ withHoleFitPlugins hsc_env $
+
+ do_this
}
+-- | Create an empty 'TcGblEnv'.
+initTcGblEnv :: HscEnv -> HscSource -> Bool -> Module -> RealSrcSpan -> IO TcGblEnv
+initTcGblEnv hsc_env hsc_src keep_rn_syntax mod loc =
+ do { keep_var <- newIORef emptyNameSet
+ ; used_gre_var <- newIORef []
+ ; th_var <- newIORef False
+ ; infer_var <- newIORef True
+ ; infer_reasons_var <- newIORef emptyMessages
+ ; dfun_n_var <- newIORef emptyOccSet
+ ; zany_n_var <- newIORef 0
+ ; dependent_files_var <- newIORef []
+ ; dependent_dirs_var <- newIORef []
+ ; static_wc_var <- newIORef emptyWC
+ ; cc_st_var <- newIORef newCostCentreState
+ ; th_topdecls_var <- newIORef []
+ ; th_foreign_files_var <- newIORef []
+ ; th_topnames_var <- newIORef emptyNameSet
+ ; th_modfinalizers_var <- newIORef []
+ ; th_coreplugins_var <- newIORef []
+ ; th_state_var <- newIORef Map.empty
+ ; th_remote_state_var <- newIORef Nothing
+ ; th_docs_var <- newIORef Map.empty
+ ; th_needed_deps_var <- newIORef ([], emptyUDFM)
+ ; next_wrapper_num <- newIORef emptyModuleEnv
+ ; let
+ -- bangs to avoid leaking the env (#19356)
+ !dflags = hsc_dflags hsc_env
+ !mhome_unit = hsc_home_unit_maybe hsc_env
+ !logger = hsc_logger hsc_env
+
+ maybe_rn_syntax :: forall a. a -> Maybe a ;
+ maybe_rn_syntax empty_val
+ | logHasDumpFlag logger Opt_D_dump_rn_ast = Just empty_val
+
+ | gopt Opt_WriteHie dflags = Just empty_val
+
+ -- We want to serialize the documentation in the .hi-files,
+ -- and need to extract it from the renamed syntax first.
+ -- See 'GHC.HsToCore.Docs.extractDocs'.
+ | gopt Opt_Haddock dflags = Just empty_val
+
+ | keep_rn_syntax = Just empty_val
+ | otherwise = Nothing ;
+
+ ; return $ TcGblEnv
+ { tcg_th_topdecls = th_topdecls_var
+ , tcg_th_foreign_files = th_foreign_files_var
+ , tcg_th_topnames = th_topnames_var
+ , tcg_th_modfinalizers = th_modfinalizers_var
+ , tcg_th_coreplugins = th_coreplugins_var
+ , tcg_th_state = th_state_var
+ , tcg_th_remote_state = th_remote_state_var
+ , tcg_th_docs = th_docs_var
+
+ , tcg_mod = mod
+ , tcg_semantic_mod = homeModuleInstantiation mhome_unit mod
+ , tcg_src = hsc_src
+ , tcg_rdr_env = emptyGlobalRdrEnv
+ , tcg_fix_env = emptyNameEnv
+ , tcg_default = emptyDefaultEnv
+ , tcg_default_exports = emptyDefaultEnv
+ , tcg_type_env = emptyNameEnv
+ , tcg_type_env_var = hsc_type_env_vars hsc_env
+ , tcg_inst_env = emptyInstEnv
+ , tcg_fam_inst_env = emptyFamInstEnv
+ , tcg_ann_env = emptyAnnEnv
+ , tcg_complete_match_env = []
+ , tcg_th_used = th_var
+ , tcg_th_needed_deps = th_needed_deps_var
+ , tcg_exports = []
+ , tcg_imports = emptyImportAvails
+ , tcg_import_decls = []
+ , tcg_used_gres = used_gre_var
+ , tcg_dus = emptyDUs
+
+ , tcg_rn_imports = []
+ , tcg_rn_exports = if hsc_src == HsigFile
+ -- Always retain renamed syntax, so that we can give
+ -- better errors. (TODO: how?)
+ then Just []
+ else maybe_rn_syntax []
+ , tcg_rn_decls = maybe_rn_syntax emptyRnGroup
+ , tcg_tr_module = Nothing
+ , tcg_binds = emptyLHsBinds
+ , tcg_imp_specs = []
+ , tcg_sigs = emptyNameSet
+ , tcg_ksigs = emptyNameSet
+ , tcg_ev_binds = emptyBag
+ , tcg_warns = emptyWarn
+ , tcg_anns = []
+ , tcg_tcs = []
+ , tcg_insts = []
+ , tcg_fam_insts = []
+ , tcg_rules = []
+ , tcg_fords = []
+ , tcg_patsyns = []
+ , tcg_merged = []
+ , tcg_dfun_n = dfun_n_var
+ , tcg_zany_n = zany_n_var
+ , tcg_keep = keep_var
+ , tcg_hdr_info = (Nothing,Nothing)
+ , tcg_main = Nothing
+ , tcg_self_boot = NoSelfBoot
+ , tcg_safe_infer = infer_var
+ , tcg_safe_infer_reasons = infer_reasons_var
+ , tcg_dependent_files = dependent_files_var
+ , tcg_dependent_dirs = dependent_dirs_var
+ , tcg_tc_plugin_solvers = []
+ , tcg_tc_plugin_rewriters = emptyUFM
+ , tcg_defaulting_plugins = []
+ , tcg_hf_plugins = []
+ , tcg_top_loc = loc
+ , tcg_static_wc = static_wc_var
+ , tcg_complete_matches = []
+ , tcg_cc_st = cc_st_var
+ , tcg_next_wrapper_num = next_wrapper_num
+ } }
+
-- | Run a 'TcM' action in the context of an existing 'GblEnv'.
initTcWithGbl :: HscEnv
-> TcGblEnv
@@ -686,6 +702,83 @@ withIfaceErr ctx do_this = do
liftIO $ throwGhcExceptionIO (ProgramError (renderWithContext ctx msg))
Succeeded result -> return result
+{-
+************************************************************************
+* *
+ Initialising plugins for TcM
+* *
+************************************************************************
+-}
+
+-- | Initialise typechecker plugins, run the inner action, then stop
+-- the typechecker plugins.
+withTcPlugins :: HscEnv -> TcM a -> TcM a
+withTcPlugins hsc_env m =
+ case catMaybes $ mapPlugins (hsc_plugins hsc_env) tcPlugin of
+ [] -> m -- Common fast case
+ plugins -> do
+ (solvers, rewriters, stops) <-
+ unzip3 `fmap` mapM start_plugin plugins
+ let
+ rewritersUniqFM :: UniqFM TyCon [TcPluginRewriter]
+ !rewritersUniqFM = sequenceUFMList rewriters
+ -- The following ensures that tcPluginStop is called even if a type
+ -- error occurs during compilation (Fix of #10078)
+ eitherRes <- tryM $
+ updGblEnv (\e -> e { tcg_tc_plugin_solvers = solvers
+ , tcg_tc_plugin_rewriters = rewritersUniqFM })
+ m
+ mapM_ runTcPluginM stops
+ case eitherRes of
+ Left _ -> failM
+ Right res -> return res
+ where
+ start_plugin (TcPlugin start solve rewrite stop) =
+ do s <- runTcPluginM start
+ return (solve s, rewrite s, stop s)
+
+-- | Initialise defaulting plugins, run the inner action, then stop
+-- the defaulting plugins.
+withDefaultingPlugins :: HscEnv -> TcM a -> TcM a
+withDefaultingPlugins hsc_env m =
+ do case catMaybes $ mapPlugins (hsc_plugins hsc_env) defaultingPlugin of
+ [] -> m -- Common fast case
+ plugins -> do (plugins,stops) <- mapAndUnzipM start_plugin plugins
+ -- This ensures that dePluginStop is called even if a type
+ -- error occurs during compilation
+ eitherRes <- tryM $ do
+ updGblEnv (\e -> e { tcg_defaulting_plugins = plugins })
+ m
+ mapM_ runTcPluginM stops
+ case eitherRes of
+ Left _ -> failM
+ Right res -> return res
+ where
+ start_plugin (DefaultingPlugin start fill stop) =
+ do s <- runTcPluginM start
+ return (fill s, stop s)
+
+-- | Initialise hole fit plugins, run the inner action, then stop
+-- the hole fit plugins.
+withHoleFitPlugins :: HscEnv -> TcM a -> TcM a
+withHoleFitPlugins hsc_env m =
+ case catMaybes $ mapPlugins (hsc_plugins hsc_env) holeFitPlugin of
+ [] -> m -- Common fast case
+ plugins -> do (plugins,stops) <- mapAndUnzipM start_plugin plugins
+ -- This ensures that hfPluginStop is called even if a type
+ -- error occurs during compilation.
+ eitherRes <- tryM $
+ updGblEnv (\e -> e { tcg_hf_plugins = plugins })
+ m
+ sequence_ stops
+ case eitherRes of
+ Left _ -> failM
+ Right res -> return res
+ where
+ start_plugin (HoleFitPluginR init plugin stop) =
+ do ref <- init
+ return (plugin ref, stop ref)
+
{-
************************************************************************
* *
=====================================
libraries/ghci/GHCi/Message.hs
=====================================
@@ -89,7 +89,7 @@ data Message a where
LookupSymbol :: String -> Message (Maybe (RemotePtr ()))
LookupSymbolInDLL :: RemotePtr LoadedDLL -> String -> Message (Maybe (RemotePtr ()))
LookupClosure :: String -> Message (Maybe HValueRef)
- LoadDLL :: String -> Message (Either String (RemotePtr LoadedDLL))
+ LoadDLLs :: [String] -> Message (Either String [RemotePtr LoadedDLL])
LoadArchive :: String -> Message () -- error?
LoadObj :: String -> Message () -- error?
UnloadObj :: String -> Message () -- error?
@@ -448,7 +448,7 @@ data BreakModule
-- that type isn't available here.
data BreakUnitId
--- | A dummy type that tags pointers returned by 'LoadDLL'.
+-- | A dummy type that tags pointers returned by 'LoadDLLs'.
data LoadedDLL
-- SomeException can't be serialized because it contains dynamic
@@ -564,7 +564,7 @@ getMessage = do
1 -> Msg <$> return InitLinker
2 -> Msg <$> LookupSymbol <$> get
3 -> Msg <$> LookupClosure <$> get
- 4 -> Msg <$> LoadDLL <$> get
+ 4 -> Msg <$> LoadDLLs <$> get
5 -> Msg <$> LoadArchive <$> get
6 -> Msg <$> LoadObj <$> get
7 -> Msg <$> UnloadObj <$> get
@@ -610,7 +610,7 @@ putMessage m = case m of
InitLinker -> putWord8 1
LookupSymbol str -> putWord8 2 >> put str
LookupClosure str -> putWord8 3 >> put str
- LoadDLL str -> putWord8 4 >> put str
+ LoadDLLs strs -> putWord8 4 >> put strs
LoadArchive str -> putWord8 5 >> put str
LoadObj str -> putWord8 6 >> put str
UnloadObj str -> putWord8 7 >> put str
=====================================
libraries/ghci/GHCi/ObjLink.hs
=====================================
@@ -12,7 +12,7 @@
-- dynamic linker.
module GHCi.ObjLink
( initObjLinker, ShouldRetainCAFs(..)
- , loadDLL
+ , loadDLLs
, loadArchive
, loadObj
, unloadObj
@@ -31,6 +31,7 @@ import GHCi.RemoteTypes
import GHCi.Message (LoadedDLL)
import Control.Exception (throwIO, ErrorCall(..))
import Control.Monad ( when )
+import Data.Foldable
import Foreign.C
import Foreign.Marshal.Alloc ( alloca, free )
import Foreign ( nullPtr, peek )
@@ -43,6 +44,10 @@ import Control.Exception (catch, evaluate)
import GHC.Wasm.Prim
#endif
+#if defined(wasm32_HOST_ARCH)
+import Data.List (intercalate)
+#endif
+
-- ---------------------------------------------------------------------------
-- RTS Linker Interface
-- ---------------------------------------------------------------------------
@@ -67,20 +72,25 @@ data ShouldRetainCAFs
initObjLinker :: ShouldRetainCAFs -> IO ()
initObjLinker _ = pure ()
-loadDLL :: String -> IO (Either String (Ptr LoadedDLL))
-loadDLL f =
+-- Batch load multiple DLLs at once via dyld to enable a single
+-- dependency resolution and more parallel compilation. We pass a
+-- NUL-delimited JSString to avoid array marshalling on wasm.
+loadDLLs :: [String] -> IO (Either String [Ptr LoadedDLL])
+loadDLLs fs =
m `catch` \(err :: JSException) ->
- pure $ Left $ "loadDLL failed for " <> f <> ": " <> show err
+ pure $ Left $ "loadDLLs failed: " <> show err
where
+ packed :: JSString
+ packed = toJSString (intercalate ['\0'] fs)
m = do
- evaluate =<< js_loadDLL (toJSString f)
- pure $ Right nullPtr
+ evaluate =<< js_loadDLLs packed
+ pure $ Right (replicate (length fs) nullPtr)
-- See Note [Variable passing in JSFFI] for where
-- __ghc_wasm_jsffi_dyld comes from
-foreign import javascript safe "__ghc_wasm_jsffi_dyld.loadDLL($1)"
- js_loadDLL :: JSString -> IO ()
+foreign import javascript safe "__ghc_wasm_jsffi_dyld.loadDLLs($1)"
+ js_loadDLLs :: JSString -> IO ()
loadArchive :: String -> IO ()
loadArchive f = throwIO $ ErrorCall $ "loadArchive: unsupported on wasm for " <> f
@@ -241,6 +251,16 @@ resolveObjs = do
r <- c_resolveObjs
return (r /= 0)
+loadDLLs :: [String] -> IO (Either String [Ptr LoadedDLL])
+loadDLLs = foldrM load_one $ Right []
+ where
+ load_one _ err@(Left _) = pure err
+ load_one p (Right dlls) = do
+ r <- loadDLL p
+ pure $ case r of
+ Left err -> Left err
+ Right dll -> Right $ dll : dlls
+
-- ---------------------------------------------------------------------------
-- Foreign declarations to RTS entry points which does the real work;
-- ---------------------------------------------------------------------------
=====================================
libraries/ghci/GHCi/Run.hs
=====================================
@@ -57,7 +57,7 @@ run m = case m of
#if defined(javascript_HOST_ARCH)
LoadObj p -> withCString p loadJS
InitLinker -> notSupportedJS m
- LoadDLL {} -> notSupportedJS m
+ LoadDLLs {} -> notSupportedJS m
LoadArchive {} -> notSupportedJS m
UnloadObj {} -> notSupportedJS m
AddLibrarySearchPath {} -> notSupportedJS m
@@ -69,7 +69,7 @@ run m = case m of
LookupClosure str -> lookupJSClosure str
#else
InitLinker -> initObjLinker RetainCAFs
- LoadDLL str -> fmap toRemotePtr <$> loadDLL str
+ LoadDLLs strs -> fmap (map toRemotePtr) <$> loadDLLs strs
LoadArchive str -> loadArchive str
LoadObj str -> loadObj str
UnloadObj str -> unloadObj str
=====================================
testsuite/tests/rts/linker/T2615.hs
=====================================
@@ -4,7 +4,7 @@ library_name = "libfoo_script_T2615.so" -- this is really a linker script
main = do
initObjLinker RetainCAFs
- result <- loadDLL library_name
+ result <- loadDLLs [library_name]
case result of
Right _ -> putStrLn (library_name ++ " loaded successfully")
Left x -> putStrLn ("error: " ++ x)
=====================================
testsuite/tests/tcplugins/T26395.hs
=====================================
@@ -0,0 +1,51 @@
+
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE GADTs #-}
+{-# LANGUAGE StandaloneKindSignatures #-}
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE TypeOperators #-}
+{-# LANGUAGE UnliftedDatatypes #-}
+
+{-# OPTIONS_GHC -fplugin=T26395_Plugin #-}
+
+{-# OPTIONS_GHC -Wincomplete-patterns #-}
+{-# OPTIONS_GHC -Winaccessible-code #-}
+{-# OPTIONS_GHC -Woverlapping-patterns #-}
+
+module T26395 where
+
+import Data.Kind
+import GHC.TypeNats
+import GHC.Exts ( UnliftedType )
+
+-- This test verifies that typechecker plugins are enabled
+-- when we run the solver for pattern-match checking.
+
+type Peano :: Nat -> UnliftedType
+data Peano n where
+ Z :: Peano 0
+ S :: Peano n -> Peano (1 + n)
+
+test1 :: Peano n -> Peano n -> Int
+test1 Z Z = 0
+test1 (S n) (S m) = 1 + test1 n m
+
+{-
+The following test doesn't work properly due to #26401:
+the pattern-match checker reports a missing equation
+
+ Z (S _) _
+
+but there is no invocation of the solver of the form
+
+ [G] n ~ 0
+ [G] m ~ 1 + m1
+ [G] (n-m) ~ m2
+
+for which we could report the Givens as contradictory.
+
+test2 :: Peano n -> Peano m -> Peano (n - m) -> Int
+test2 Z Z Z = 0
+test2 (S _) (S _) _ = 1
+test2 (S _) Z (S _) = 2
+-}
=====================================
testsuite/tests/tcplugins/T26395.stderr
=====================================
@@ -0,0 +1,2 @@
+[1 of 2] Compiling T26395_Plugin ( T26395_Plugin.hs, T26395_Plugin.o )
+[2 of 2] Compiling T26395 ( T26395.hs, T26395.o )
=====================================
testsuite/tests/tcplugins/T26395_Plugin.hs
=====================================
@@ -0,0 +1,208 @@
+{-# LANGUAGE RecordWildCards #-}
+{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE MultiWayIf #-}
+{-# LANGUAGE BlockArguments #-}
+{-# LANGUAGE ViewPatterns #-}
+
+{-# OPTIONS_GHC -Wall -Wno-orphans #-}
+
+module T26395_Plugin where
+
+-- base
+import Prelude hiding ( (<>) )
+import qualified Data.Semigroup as S
+import Data.List ( partition )
+import Data.Maybe
+import GHC.TypeNats
+
+-- ghc
+import GHC.Builtin.Types.Literals
+import GHC.Core.Predicate
+import GHC.Core.TyCo.Rep
+import GHC.Plugins
+import GHC.Tc.Plugin
+import GHC.Tc.Types
+import GHC.Tc.Types.Constraint
+import GHC.Tc.Types.Evidence
+import GHC.Tc.Utils.TcType
+import GHC.Types.Unique.Map
+
+--------------------------------------------------------------------------------
+
+plugin :: Plugin
+plugin =
+ defaultPlugin
+ { pluginRecompile = purePlugin
+ , tcPlugin = \ _-> Just $
+ TcPlugin
+ { tcPluginInit = pure ()
+ , tcPluginSolve = \ _ -> solve
+ , tcPluginRewrite = \ _ -> emptyUFM
+ , tcPluginStop = \ _ -> pure ()
+ }
+ }
+
+solve :: EvBindsVar -> [Ct] -> [Ct] -> TcPluginM TcPluginSolveResult
+solve _ givens wanteds
+ -- This plugin only reports inconsistencies among Given constraints.
+ | not $ null wanteds
+ = pure $ TcPluginOk [] []
+ | otherwise
+ = do { let givenLinearExprs = mapMaybe linearExprCt_maybe givens
+ sols = solutions givenLinearExprs
+
+ ; tcPluginTrace "solveLinearExprs" $
+ vcat [ text "givens:" <+> ppr givens
+ , text "linExprs:" <+> ppr givenLinearExprs
+ , text "sols:" <+> ppr (take 1 sols)
+ ]
+ ; return $
+ if null sols
+ then TcPluginContradiction givens
+ else TcPluginOk [] []
+ }
+
+data LinearExpr =
+ LinearExpr
+ { constant :: Integer
+ , coeffs :: UniqMap TyVar Integer
+ }
+instance Semigroup LinearExpr where
+ LinearExpr c xs <> LinearExpr d ys =
+ LinearExpr ( c + d ) ( plusMaybeUniqMap_C comb xs ys )
+ where
+ comb a1 a2 =
+ let a = a1 + a2
+ in if a == 0
+ then Nothing
+ else Just a
+
+instance Monoid LinearExpr where
+ mempty = LinearExpr 0 emptyUniqMap
+
+mapLinearExpr :: (Integer -> Integer) -> LinearExpr -> LinearExpr
+mapLinearExpr f (LinearExpr c xs) = LinearExpr (f c) (mapUniqMap f xs)
+
+minusLinearExpr :: LinearExpr -> LinearExpr -> LinearExpr
+minusLinearExpr a b = a S.<> mapLinearExpr negate b
+
+instance Outputable LinearExpr where
+ ppr ( LinearExpr c xs ) =
+ hcat $ punctuate ( text " + " ) $
+ ( ppr c : map ppr_var ( nonDetUniqMapToList xs ) )
+ where
+ ppr_var ( tv, i )
+ | i == 1
+ = ppr tv
+ | i < 0
+ = parens ( text "-" <> ppr (abs i) ) <> text "*" <> ppr tv
+ | otherwise
+ = ppr i <> text "*" <> ppr tv
+
+maxCoeff :: LinearExpr -> Double
+maxCoeff ( LinearExpr c xs ) =
+ maximum ( map fromInteger ( c : nonDetEltsUniqMap xs ) )
+
+
+linearExprCt_maybe :: Ct -> Maybe LinearExpr
+linearExprCt_maybe ct =
+ case classifyPredType (ctPred ct) of
+ EqPred NomEq lhs rhs
+ | all isNaturalTy [ typeKind lhs, typeKind rhs ]
+ , Just e1 <- linearExprTy_maybe lhs
+ , Just e2 <- linearExprTy_maybe rhs
+ -> Just $ e1 `minusLinearExpr` e2
+ _ -> Nothing
+
+isNat :: Type -> Maybe Integer
+isNat ty
+ | Just (NumTyLit n) <- isLitTy ty
+ = Just n
+ | otherwise
+ = Nothing
+
+linearExprTy_maybe :: Type -> Maybe LinearExpr
+linearExprTy_maybe ty
+ | Just n <- isNat ty
+ = Just $ LinearExpr n emptyUniqMap
+ | Just (tc, args) <- splitTyConApp_maybe ty
+ = if | tc == typeNatAddTyCon
+ , [x, y] <- args
+ , Just e1 <- linearExprTy_maybe x
+ , Just e2 <- linearExprTy_maybe y
+ -> Just $ e1 S.<> e2
+ | tc == typeNatSubTyCon
+ , [x,y] <- args
+ , Just e1 <- linearExprTy_maybe x
+ , Just e2 <- linearExprTy_maybe y
+ -> Just $ e1 `minusLinearExpr` e2
+ | tc == typeNatMulTyCon
+ , [x, y] <- args
+ ->
+ if | Just ( LinearExpr n xs ) <- linearExprTy_maybe x
+ , isNullUniqMap xs
+ , Just e <- linearExprTy_maybe y
+ -> Just $
+ if n == 0
+ then mempty
+ else mapLinearExpr (n *) e
+ | Just ( LinearExpr n ys ) <- linearExprTy_maybe y
+ , isNullUniqMap ys
+ , Just e <- linearExprTy_maybe x
+ -> Just $
+ if n == 0
+ then mempty
+ else mapLinearExpr (fromIntegral n *) e
+ | otherwise
+ -> Nothing
+ | otherwise
+ -> Nothing
+ | Just tv <- getTyVar_maybe ty
+ = Just $ LinearExpr 0 ( unitUniqMap tv 1 )
+ | otherwise
+ = Nothing
+
+-- Brute force algorithm to check whether a system of Diophantine
+-- linear equations is solvable in natural numbers.
+solutions :: [ LinearExpr ] -> [ UniqMap TyVar Natural ]
+solutions eqs =
+ let
+ (constEqs, realEqs) = partition (isNullUniqMap . coeffs) eqs
+ d = length realEqs
+ fvs = nonDetKeysUniqMap $ plusUniqMapList ( map coeffs realEqs )
+ in
+ if | any ( ( /= 0 ) . evalLinearExpr emptyUniqMap ) constEqs
+ -> []
+ | d == 0
+ -> [ emptyUniqMap ]
+ | otherwise
+ ->
+ let
+ m = maximum $ map maxCoeff realEqs
+ hadamardBound = sqrt ( fromIntegral $ d ^ d ) * m ^ d
+ tests = mkAssignments ( floor hadamardBound ) fvs
+ in
+ filter ( \ test -> isSolution test realEqs ) tests
+
+
+mkAssignments :: Natural -> [ TyVar ] -> [ UniqMap TyVar Natural ]
+mkAssignments _ [] = [ emptyUniqMap ]
+mkAssignments b (v : vs) =
+ [ addToUniqMap rest v n
+ | n <- [ 0 .. b ]
+ , rest <- mkAssignments b vs
+ ]
+
+isSolution :: UniqMap TyVar Natural -> [ LinearExpr ] -> Bool
+isSolution assig =
+ all ( \ expr -> evalLinearExpr assig expr == 0 )
+
+evalLinearExpr :: UniqMap TyVar Natural -> LinearExpr -> Integer
+evalLinearExpr vals ( LinearExpr c xs ) = nonDetFoldUniqMap aux c xs
+ where
+ aux ( tv, coeff ) !acc = acc + coeff * val
+ where
+ val :: Integer
+ val = case lookupUniqMap vals tv of
+ Nothing -> pprPanic "evalLinearExpr: missing tv" (ppr tv)
+ Just v -> fromIntegral v
=====================================
testsuite/tests/tcplugins/all.T
=====================================
@@ -110,6 +110,19 @@ test('TcPlugin_CtId'
, '-dynamic -package ghc' if have_dynamic() else '-package ghc' ]
)
+# Checks that we run type-checker plugins for pattern-match warnings.
+test('T26395'
+ , [ extra_files(
+ [ 'T26395_Plugin.hs'
+ , 'T26395.hs'
+ ])
+ , req_th
+ ]
+ , multimod_compile
+ , [ 'T26395.hs'
+ , '-dynamic -package ghc' if have_dynamic() else '-package ghc' ]
+ )
+
test('T11462', [js_broken(22261), req_th, req_plugins], multi_compile,
[None, [('T11462_Plugin.hs', '-package ghc'), ('T11462.hs', '')],
'-dynamic' if have_dynamic() else ''])
=====================================
utils/jsffi/dyld.mjs
=====================================
@@ -9,7 +9,7 @@
// iserv (GHCi.Server.defaultServer). This part only runs in
// nodejs.
// 2. Dynamic linker: provide RTS linker interfaces like
-// loadDLL/lookupSymbol etc which are imported by wasm iserv. This
+// loadDLLs/lookupSymbol etc which are imported by wasm iserv. This
// part can run in browsers as well.
//
// When GHC starts external interpreter for the wasm target, it starts
@@ -50,7 +50,7 @@
//
// *** What works right now and what doesn't work yet?
//
-// loadDLL & bytecode interpreter work. Template Haskell & ghci work.
+// loadDLLs & bytecode interpreter work. Template Haskell & ghci work.
// Profiled dynamic code works. Compiled code and bytecode can all be
// loaded, though the side effects are constrained to what's supported
// by wasi preview1: we map the full host filesystem into wasm cause
@@ -777,17 +777,17 @@ class DyLD {
return this.#rpc.findSystemLibrary(f);
}
- // When we do loadDLL, we first perform "downsweep" which return a
+ // When we do loadDLLs, we first perform "downsweep" which return a
// toposorted array of dependencies up to itself, then sequentially
// load the downsweep result.
//
// The rationale of a separate downsweep phase, instead of a simple
- // recursive loadDLL function is: V8 delegates async
+ // recursive loadDLLs function is: V8 delegates async
// WebAssembly.compile to a background worker thread pool. To
// maintain consistent internal linker state, we *must* load each so
// file sequentially, but it's okay to kick off compilation asap,
// store the Promise in downsweep result and await for the actual
- // WebAssembly.Module in loadDLL logic. This way we can harness some
+ // WebAssembly.Module in loadDLLs logic. This way we can harness some
// background parallelism.
async #downsweep(p) {
const toks = p.split("/");
@@ -828,8 +828,26 @@ class DyLD {
return acc;
}
- // The real stuff
- async loadDLL(p) {
+ // Batch load multiple DLLs in one go.
+ // Accepts a NUL-delimited string of paths to avoid array marshalling.
+ // Each path can be absolute or a soname; dependency resolution is
+ // performed across the full set to enable maximal parallel compile
+ // while maintaining sequential instantiation order.
+ async loadDLLs(packed) {
+ // Normalize input to an array of strings. When called from Haskell
+ // we pass a single JSString containing NUL-separated paths.
+ const paths = (typeof packed === "string"
+ ? (packed.length === 0 ? [] : packed.split("\0"))
+ : [packed] // tolerate an accidental single path object
+ ).filter((s) => s.length > 0).reverse();
+
+ // Compute a single downsweep plan for the whole batch.
+ // Note: #downsweep mutates #loadedSos to break cycles and dedup.
+ const plan = [];
+ for (const p of paths) {
+ plan.push(...(await this.#downsweep(p)));
+ }
+
for (const {
memSize,
memP2Align,
@@ -837,7 +855,7 @@ class DyLD {
tableP2Align,
modp,
soname,
- } of await this.#downsweep(p)) {
+ } of plan) {
const import_obj = {
wasi_snapshot_preview1: this.#wasi.wasiImport,
env: {
@@ -1128,7 +1146,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/be9f9fb259cbfc8f6e7db3c909f51b…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/be9f9fb259cbfc8f6e7db3c909f51b…
You're receiving this email because of your account on gitlab.haskell.org.
1
0