Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
a8a94aad by Cheng Shao at 2026-01-05T16:24:04-05:00
hadrian: drops unused PE linker script for windows
This patch drops unused PE linker script for windows in the
`MergeObjects` builder of hadrian. The linker script is used for
merging object files into a single `HS*.o` object file and undoing the
effect of split sections, when building the "ghci library" object
file. However, we don't build the ghci library on windows, and this
code path is actually unreachable.
- - - - -
53038ea9 by Cheng Shao at 2026-01-05T16:24:04-05:00
hadrian: drop unused logic for building ghci libraries
This patch drops the unused logic for building ghci libraries in
hadrian:
- The term "ghci library" refers to an optional object file per
library `HS*.o`, which is merged from multiple object files in that
library using the `MergeObjects` builder in hadrian.
- The original rationale of having a ghci library object, in addition
to normal archives, was to speedup ghci loading, since the combined
object is linked with a linker script to undo the effects of
`-fsplit-sections` to reduce section count and make it easier for
the RTS linker to handle.
- However, most GHC builds enable `dynamicGhcPrograms` by default, in
such cases the ghci library would already not be built.
- `dynamicGhcPrograms` is disabled on Windows, but still we don't
build the ghci library due to lack of functioning merge objects
command.
- The only case that we actually build ghci library objects, are
alpine fully static bindists. However, for other reasons, split
sections is already disabled for fully static builds anyway!
- There will not be any regression if the ghci library objects are
absent from a GHC global libdir when `dynamicGhcPrograms` is
disabled. The RTS linker can already load the archives without any
issue.
Hence the removal. We now forcibly disable ghci libraries for all
Cabal components, and rip out all logic related to `MergeObjects` and
ghci libraries in hadrian. This also nicely cleans up some old todos
and fixmes that are no longer relevant.
Note that MergeObjects in hadrian is not the same thing as merge
objects in the GHC driver. The latter is not affected by this patch.
-------------------------
Metric Decrease:
libdir
-------------------------
Co-authored-by: Codex
- - - - -
17 changed files:
- − driver/utils/merge_sections.ld
- − driver/utils/merge_sections_pe.ld
- hadrian/hadrian.cabal
- hadrian/src/Builder.hs
- hadrian/src/Context.hs
- hadrian/src/Hadrian/Haskell/Cabal/Parse.hs
- hadrian/src/Hadrian/Haskell/Cabal/Type.hs
- hadrian/src/Hadrian/Haskell/Hash.hs
- hadrian/src/Oracles/Flag.hs
- hadrian/src/Rules.hs
- hadrian/src/Rules/Library.hs
- hadrian/src/Rules/Register.hs
- hadrian/src/Settings/Builders/Cabal.hs
- − hadrian/src/Settings/Builders/MergeObjects.hs
- hadrian/src/Settings/Builders/SplitSections.hs
- hadrian/src/Settings/Default.hs
- hadrian/src/Settings/Packages.hs
Changes:
=====================================
driver/utils/merge_sections.ld deleted
=====================================
@@ -1,26 +0,0 @@
-/* Linker script to undo -split-sections and merge all sections together when
- * linking relocatable object files for GHCi.
- * ld -r normally retains the individual sections, which is what you would want
- * if the intention is to eventually link into a binary with --gc-sections, but
- * it doesn't have a flag for directly doing what we want. */
-SECTIONS
-{
- .text : {
- *(.text*)
- }
- .rodata.cst16 : {
- *(.rodata.cst16*)
- }
- .rodata : {
- *(.rodata*)
- }
- .data.rel.ro : {
- *(.data.rel.ro*)
- }
- .data : {
- *(.data*)
- }
- .bss : {
- *(.bss*)
- }
-}
=====================================
driver/utils/merge_sections_pe.ld deleted
=====================================
@@ -1,26 +0,0 @@
-/* Linker script to undo -split-sections and merge all sections together when
- * linking relocatable object files for GHCi.
- * ld -r normally retains the individual sections, which is what you would want
- * if the intention is to eventually link into a binary with --gc-sections, but
- * it doesn't have a flag for directly doing what we want. */
-SECTIONS
-{
- .text : {
- *(.text$*)
- }
- .rdata : {
- *(.rdata$*)
- }
- .data : {
- *(.data$*)
- }
- .pdata : {
- *(.pdata$*)
- }
- .xdata : {
- *(.xdata$*)
- }
- .bss : {
- *(.bss$*)
- }
-}
=====================================
hadrian/hadrian.cabal
=====================================
@@ -115,7 +115,6 @@ executable hadrian
, Settings.Builders.Ar
, Settings.Builders.Ld
, Settings.Builders.Make
- , Settings.Builders.MergeObjects
, Settings.Builders.SplitSections
, Settings.Builders.RunTest
, Settings.Builders.Win32Tarballs
=====================================
hadrian/src/Builder.hs
=====================================
@@ -178,7 +178,6 @@ data Builder = Alex
| Ld Stage --- ^ linker
| Make FilePath
| Makeinfo
- | MergeObjects Stage -- ^ linker to be used to merge object files.
| Nm
| Objdump
| Python
@@ -453,15 +452,6 @@ systemBuilderPath builder = case builder of
HsCpp -> fromTargetTC "hs-cpp" (Toolchain.hsCppProgram . tgtHsCPreprocessor)
JsCpp -> fromTargetTC "js-cpp" (maybeProg Toolchain.jsCppProgram . tgtJsCPreprocessor)
Ld _ -> fromTargetTC "ld" (Toolchain.ccLinkProgram . tgtCCompilerLink)
- -- MergeObjects Stage0 is a special case in case of
- -- cross-compiling. We're building stage1, e.g. code which will be
- -- executed on the host and hence we need to use host's merge
- -- objects tool and not the target merge object tool.
- -- Note, merge object tool is usually platform linker with some
- -- parameters. E.g. building a cross-compiler on and for x86_64
- -- which will target ppc64 means that MergeObjects Stage0 will use
- -- x86_64 linker and MergeObject _ will use ppc64 linker.
- MergeObjects st -> fromStageTC st "merge-objects" (maybeProg Toolchain.mergeObjsProgram . tgtMergeObjs)
Make _ -> fromKey "make"
Makeinfo -> fromKey "makeinfo"
Nm -> fromTargetTC "nm" (Toolchain.nmProgram . tgtNm)
=====================================
hadrian/src/Context.hs
=====================================
@@ -8,7 +8,7 @@ module Context (
-- * Paths
contextDir, buildPath, buildDir, pkgInplaceConfig, pkgSetupConfigFile, pkgSetupConfigDir,
pkgHaddockFile, pkgRegisteredLibraryFile, pkgRegisteredLibraryFileName,
- pkgLibraryFile, pkgGhciLibraryFile,
+ pkgLibraryFile,
pkgConfFile, pkgStampFile, resourcePath, objectPath, contextPath, getContextPath, libPath, distDir,
distDynDir,
haddockStatsFilesDir, ensureConfigured, autogenPath, rtsContext, rtsBuildPath, libffiBuildPath
@@ -155,13 +155,6 @@ pkgLibraryFile context@Context {..} = do
extension <- libsuf stage way
pkgFile context "libHS" extension
--- | Path to the GHCi library file of a given 'Context', e.g.:
--- @_build/stage1/libraries/array/build/HSarray-0.5.1.0.o@.
-pkgGhciLibraryFile :: Context -> Action FilePath
-pkgGhciLibraryFile context@Context {..} = do
- let extension = "" <.> osuf way
- pkgFile context "HS" extension
-
-- | Path to the configuration file of a given 'Context'.
pkgConfFile :: Context -> Action FilePath
pkgConfFile Context {..} = do
=====================================
hadrian/src/Hadrian/Haskell/Cabal/Parse.hs
=====================================
@@ -334,7 +334,6 @@ resolveContextData context@Context {..} = do
, depIncludeDirs = forDeps Installed.includeDirs
, depCcOpts = forDeps Installed.ccOptions
, depLdOpts = forDeps Installed.ldOptions
- , buildGhciLib = C.withGHCiLib lbi'
, frameworks = map C.getSymbolicPath (C.frameworks buildInfo)
, packageDescription = pd'
, contextLibdir = libdir install_dirs
=====================================
hadrian/src/Hadrian/Haskell/Cabal/Type.hs
=====================================
@@ -67,7 +67,6 @@ data ContextData = ContextData
, depIncludeDirs :: [String]
, depCcOpts :: [String]
, depLdOpts :: [String]
- , buildGhciLib :: Bool
, frameworks :: [String]
, packageDescription :: PackageDescription
=====================================
hadrian/src/Hadrian/Haskell/Hash.hs
=====================================
@@ -82,7 +82,6 @@ data PackageHashConfigInputs = PackageHashConfigInputs {
pkgHashVanillaLib :: Bool,
pkgHashSharedLib :: Bool,
pkgHashDynExe :: Bool,
- pkgHashGHCiLib :: Bool,
pkgHashProfLib :: Bool,
pkgHashProfExe :: Bool,
pkgHashSplitObjs :: Bool,
@@ -139,7 +138,6 @@ pkgHashOracle = void $ addOracleCache $ \(PkgHashKey (stag, pkg)) -> do
pkgHashVanillaLib = vanilla `Set.member` libWays
pkgHashSharedLib = dynamic `Set.member` libWays
pkgHashDynExe = dyn_ghc
- pkgHashGHCiLib = False
pkgHashProfLib = profiling `Set.member` libWays
pkgHashProfExe = pkg == ghc && ghcProfiled flav stag
pkgHashSplitObjs = False -- Deprecated
@@ -239,7 +237,6 @@ renderPackageHashInputs PackageHashInputs{
, opt "vanilla-lib" True show pkgHashVanillaLib
, opt "shared-lib" False show pkgHashSharedLib
, opt "dynamic-exe" False show pkgHashDynExe
- , opt "ghci-lib" False show pkgHashGHCiLib
, opt "prof-lib" False show pkgHashProfLib
, opt "prof-exe" False show pkgHashProfExe
, opt "split-objs" False show pkgHashSplitObjs
=====================================
hadrian/src/Oracles/Flag.hs
=====================================
@@ -3,7 +3,6 @@
module Oracles.Flag (
Flag (..), flag, getFlag,
platformSupportsSharedLibs,
- platformSupportsGhciObjects,
targetRTSLinkerOnlySupportsSharedLibs,
targetSupportsThreadedRts,
targetSupportsSMP,
@@ -71,15 +70,6 @@ flag f = do
getFlag :: Flag -> Expr c b Bool
getFlag = expr . flag
--- | Does the platform support object merging (and therefore we can build GHCi objects
--- when appropriate).
-platformSupportsGhciObjects :: Action Bool
--- FIXME: The name of the function is not entirely clear about which platform, it would be better named targetSupportsGhciObjects
-platformSupportsGhciObjects = do
- has_merge_objs <- isJust <$> queryTargetTarget tgtMergeObjs
- only_shared_libs <- targetRTSLinkerOnlySupportsSharedLibs
- pure $ has_merge_objs && not only_shared_libs
-
targetRTSLinkerOnlySupportsSharedLibs :: Action Bool
targetRTSLinkerOnlySupportsSharedLibs = queryTargetTarget Toolchain.tgtRTSLinkerOnlySupportsSharedLibs
=====================================
hadrian/src/Rules.hs
=====================================
@@ -71,16 +71,9 @@ topLevelTargets = action $ do
name stage pkg | isLibrary pkg = return (pkgName pkg)
| otherwise = programName (vanillaContext stage pkg)
--- TODO: Get rid of the @includeGhciLib@ hack.
-- | Return the list of targets associated with a given 'Stage' and 'Package'.
--- By setting the Boolean parameter to False it is possible to exclude the GHCi
--- library from the targets, and avoid configuring the package to determine
--- whether GHCi library needs to be built for it. We typically want to set
--- this parameter to True, however it is important to set it to False when
--- computing 'topLevelTargets', as otherwise the whole build gets sequentialised
--- because packages are configured in the order respecting their dependencies.
-packageTargets :: Bool -> Stage -> Package -> Action [FilePath]
-packageTargets includeGhciLib stage pkg = do
+packageTargets :: Stage -> Package -> Action [FilePath]
+packageTargets stage pkg = do
let context = vanillaContext stage pkg
activePackages <- stagePackages stage
if pkg `notElem` activePackages
@@ -90,7 +83,7 @@ packageTargets includeGhciLib stage pkg = do
let pkgWays = if pkg == rts then getRtsWays else getLibraryWays
ways <- interpretInContext context pkgWays
libs <- mapM (\w -> pkgLibraryFile (Context stage pkg w (error "unused"))) (Set.toList ways)
- more <- Rules.Library.libraryTargets includeGhciLib context
+ more <- Rules.Library.libraryTargets context
setupConfig <- pkgSetupConfigFile context
return $ [setupConfig] ++ libs ++ more
else do -- The only target of a program package is the executable.
=====================================
hadrian/src/Rules/Library.hs
=====================================
@@ -35,8 +35,6 @@ libraryRules = do
root -/- "stage*/lib/**/libHS*-*.so" %> registerDynamicLib root "so"
root -/- "stage*/lib/**/libHS*-*.dll" %> registerDynamicLib root "dll"
root -/- "stage*/lib/**/*.a" %> registerStaticLib root
- root -/- "**/HS*-*.o" %> buildGhciLibO root
- root -/- "**/HS*-*.p_o" %> buildGhciLibO root
-- * 'Action's for building libraries
@@ -100,20 +98,6 @@ buildDynamicLib root suffix dynlibpath = do
(quote pkgname ++ " (" ++ show stage ++ ", way " ++ show way ++ ").")
dynlibpath synopsis
--- | Build a "GHCi library" ('LibGhci') under the given build root, with the
--- complete path of the file to build is given as the second argument.
--- See Note [Merging object files for GHCi] in GHC.Driver.Pipeline.
-buildGhciLibO :: FilePath -> FilePath -> Action ()
-buildGhciLibO root ghcilibPath = do
- l@(BuildPath _ stage _ (LibGhci _ _ _ _))
- <- parsePath (parseBuildLibGhci root)
- "<.o ghci lib (build) path parser>"
- ghcilibPath
- let context = libGhciContext l
- objs <- allObjects context
- need objs
- build $ target context (MergeObjects stage) objs [ghcilibPath]
-
{-
Note [Stamp Files]
@@ -145,7 +129,7 @@ buildPackage root fp = do
srcs <- hsSources ctx
gens <- interpretInContext ctx generatedDependencies
- lib_targets <- libraryTargets True ctx
+ lib_targets <- libraryTargets ctx
need (srcs ++ gens ++ lib_targets)
@@ -166,10 +150,6 @@ buildPackage root fp = do
-- * Helpers
--- | Return all Haskell and non-Haskell object files for the given 'Context'.
-allObjects :: Context -> Action [FilePath]
-allObjects context = (++) <$> nonHsObjects context <*> hsObjects context
-
-- | Return all the non-Haskell object files for the given library context
-- (object files built from C, C-- and sometimes other things).
nonHsObjects :: Context -> Action [FilePath]
@@ -228,7 +208,7 @@ libraryObjects context = do
-- | Coarse-grain 'need': make sure all given libraries are fully built.
needLibrary :: [Context] -> Action ()
-needLibrary cs = need =<< concatMapM (libraryTargets True) cs
+needLibrary cs = need =<< concatMapM libraryTargets cs
-- * Library paths types and parsers
@@ -241,9 +221,6 @@ data DynLibExt = So | Dylib deriving (Eq, Show)
-- | > libHS<pkg name>-<pkg version>-<pkg hash>[_<way suffix>]-ghc<ghc version>.
data LibDyn = LibDyn String [Integer] String Way DynLibExt deriving (Eq, Show)
--- | > HS<pkg name>-<pkg version>-<pkg hash>[_<way suffix>].o
-data LibGhci = LibGhci String [Integer] String Way deriving (Eq, Show)
-
-- | Get the 'Context' corresponding to the build path for a given static library.
libAContext :: BuildPath LibA -> Context
libAContext (BuildPath _ stage pkgpath (LibA pkgname _ _ way)) =
@@ -251,13 +228,6 @@ libAContext (BuildPath _ stage pkgpath (LibA pkgname _ _ way)) =
where
pkg = library pkgname pkgpath
--- | Get the 'Context' corresponding to the build path for a given GHCi library.
-libGhciContext :: BuildPath LibGhci -> Context
-libGhciContext (BuildPath _ stage pkgpath (LibGhci pkgname _ _ way)) =
- Context stage pkg way Final
- where
- pkg = library pkgname pkgpath
-
-- | Get the 'Context' corresponding to the build path for a given dynamic library.
libDynContext :: BuildPath LibDyn -> Context
libDynContext (BuildPath _ stage pkgpath (LibDyn pkgname _ _ way _)) =
@@ -274,9 +244,8 @@ stampContext (BuildPath _ stage _ (PkgStamp pkgname _ _ way)) =
data PkgStamp = PkgStamp String [Integer] String Way deriving (Eq, Show)
-
--- | Parse a path to a ghci library to be built, making sure the path starts
--- with the given build root.
+-- | Parse a path to a package stamp file, making sure the path starts with the
+-- given build root.
parseStampPath :: FilePath -> Parsec.Parsec String () (BuildPath PkgStamp)
parseStampPath root = parseBuildPath root parseStamp
@@ -297,12 +266,6 @@ parseBuildLibA :: FilePath -> Parsec.Parsec String () (BuildPath LibA)
parseBuildLibA root = parseBuildPath root parseLibAFilename
Parsec.<?> "build path for a static library"
--- | Parse a path to a ghci library to be built, making sure the path starts
--- with the given build root.
-parseBuildLibGhci :: FilePath -> Parsec.Parsec String () (BuildPath LibGhci)
-parseBuildLibGhci root = parseBuildPath root parseLibGhciFilename
- Parsec.<?> "build path for a ghci library"
-
-- | Parse a path to a dynamic library to be built, making sure the path starts
-- with the given build root.
parseBuildLibDyn :: FilePath -> String -> Parsec.Parsec String () (BuildPath LibDyn)
@@ -324,16 +287,6 @@ parseLibAFilename = do
_ <- Parsec.string ".a"
return (LibA pkgname pkgver pkghash way)
--- | Parse the filename of a ghci library to be built into a 'LibGhci' value.
-parseLibGhciFilename :: Parsec.Parsec String () LibGhci
-parseLibGhciFilename = do
- _ <- Parsec.string "HS"
- (pkgname, pkgver, pkghash) <- parsePkgId
- _ <- Parsec.string "."
- way <- parseWayPrefix vanilla
- _ <- Parsec.string "o"
- return (LibGhci pkgname pkgver pkghash way)
-
-- | Parse the filename of a dynamic library to be built into a 'LibDyn' value.
parseLibDynFilename :: String -> Parsec.Parsec String () LibDyn
parseLibDynFilename ext = do
=====================================
hadrian/src/Rules/Register.hs
=====================================
@@ -6,20 +6,17 @@ module Rules.Register (
import Base
import Context
-import Expression ( getContextData )
import Flavour
import Oracles.Setting
import Hadrian.BuildPath
import Hadrian.Expression
import Hadrian.Haskell.Cabal
-import Oracles.Flag (platformSupportsGhciObjects)
import Packages
import Rules.Rts
import Settings
import Target
import Utilities
-import Hadrian.Haskell.Cabal.Type
import qualified Text.Parsec as Parsec
import qualified Data.Set as Set
import qualified Data.Char as Char
@@ -298,17 +295,9 @@ extraTargets context
-- | Given a library 'Package' this action computes all of its targets. Needing
-- all the targets should build the library such that it is ready to be
-- registered into the package database.
--- See 'Rules.packageTargets' for the explanation of the @includeGhciLib@
--- parameter.
-libraryTargets :: Bool -> Context -> Action [FilePath]
-libraryTargets includeGhciLib context@Context {..} = do
+libraryTargets :: Context -> Action [FilePath]
+libraryTargets context = do
libFile <- pkgLibraryFile context
- ghciLib <- pkgGhciLibraryFile context
- ghciObjsSupported <- platformSupportsGhciObjects
- ghci <- if ghciObjsSupported && includeGhciLib && not (wayUnit Dynamic way)
- then interpretInContext context $ getContextData buildGhciLib
- else return False
extra <- extraTargets context
return $ [ libFile ]
- ++ [ ghciLib | ghci ]
++ extra
=====================================
hadrian/src/Settings/Builders/Cabal.hs
=====================================
@@ -5,13 +5,12 @@ import Hadrian.Haskell.Cabal
import Builder
import Context
-import Flavour
import Packages
import Settings.Builders.Common
import qualified Settings.Builders.Common as S
import Control.Exception (assert)
import qualified Data.Set as Set
-import Settings.Program (programContext, ghcWithInterpreter)
+import Settings.Program (programContext)
import GHC.Toolchain (ccLinkProgram, tgtCCompilerLink)
import GHC.Toolchain.Program (prgFlags)
@@ -128,7 +127,6 @@ commonCabalArgs stage = do
]
-- TODO: Isn't vanilla always built? If yes, some conditions are redundant.
--- TODO: Need compiler_stage1_CONFIGURE_OPTS += --disable-library-for-ghci?
-- TODO: should `elem` be `wayUnit`?
-- This approach still doesn't work. Previously libraries were build only in the
-- Default flavours and not using context.
@@ -136,11 +134,6 @@ libraryArgs :: Args
libraryArgs = do
flavourWays <- getLibraryWays
contextWay <- getWay
- package <- getPackage
- stage <- getStage
- withGhci <- expr $ ghcWithInterpreter stage
- dynPrograms <- expr (flavour >>= dynamicGhcPrograms)
- ghciObjsSupported <- expr platformSupportsGhciObjects
let ways = Set.insert contextWay flavourWays
hasVanilla = vanilla `elem` ways
hasProfiling = any (wayUnit Profiling) ways
@@ -155,11 +148,7 @@ libraryArgs = do
, if hasProfilingShared
then "--enable-profiling-shared"
else "--disable-profiling-shared"
- , if ghciObjsSupported &&
- (hasVanilla || hasProfiling) &&
- package /= rts && withGhci && not dynPrograms
- then "--enable-library-for-ghci"
- else "--disable-library-for-ghci"
+ , "--disable-library-for-ghci"
, if hasDynamic
then "--enable-shared"
else "--disable-shared" ]
=====================================
hadrian/src/Settings/Builders/MergeObjects.hs deleted
=====================================
@@ -1,11 +0,0 @@
-module Settings.Builders.MergeObjects (mergeObjectsBuilderArgs) where
-
-import Settings.Builders.Common
-import GHC.Toolchain
-import GHC.Toolchain.Program
-
-mergeObjectsBuilderArgs :: Args
-mergeObjectsBuilderArgs = builder MergeObjects ? mconcat
- [ maybe [] (prgFlags . mergeObjsProgram) . tgtMergeObjs <$> getStagedTarget
- , arg "-o", arg =<< getOutput
- , getInputs ]
=====================================
hadrian/src/Settings/Builders/SplitSections.hs
=====================================
@@ -32,8 +32,5 @@ splitSectionsArgs = do
, builder (Ghc CompileCWithGhc) ? arg "-fsplit-sections"
, builder (Ghc CompileCppWithGhc) ? arg "-fsplit-sections"
, builder (Cc CompileC) ? arg "-ffunction-sections" <> arg "-fdata-sections"
- , builder MergeObjects ? ifM (expr isWinTarget)
- (pure ["-T", "driver/utils/merge_sections_pe.ld"])
- (pure ["-T", "driver/utils/merge_sections.ld"])
]
) else mempty
=====================================
hadrian/src/Settings/Default.hs
=====================================
@@ -40,7 +40,6 @@ import Settings.Builders.HsCpp
import Settings.Builders.Ar
import Settings.Builders.Ld
import Settings.Builders.Make
-import Settings.Builders.MergeObjects
import Settings.Builders.SplitSections
import Settings.Builders.RunTest
import Settings.Builders.Xelatex
@@ -328,7 +327,6 @@ defaultBuilderArgs = mconcat
, ldBuilderArgs
, arBuilderArgs
, makeBuilderArgs
- , mergeObjectsBuilderArgs
, runTestBuilderArgs
, validateBuilderArgs
, xelatexBuilderArgs
=====================================
hadrian/src/Settings/Packages.hs
=====================================
@@ -75,8 +75,7 @@ packageArgs = do
pure ["-O0"] ]
, builder (Cabal Setup) ? mconcat
- [ arg "--disable-library-for-ghci"
- , anyTargetOs [OSOpenBSD] ? arg "--ld-options=-E"
+ [ anyTargetOs [OSOpenBSD] ? arg "--ld-options=-E"
, compilerStageOption ghcProfiled ? arg "--ghc-pkg-option=--force"
, cabalExtraDirs libzstdIncludeDir libzstdLibraryDir
]
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b820ff50459fc48bce6db3af652c2e5...
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b820ff50459fc48bce6db3af652c2e5...
You're receiving this email because of your account on gitlab.haskell.org.