[Git][ghc/ghc][master] User's guide: Fix link to language extensions
by Marge Bot (@marge-bot) 06 Jan '26
by Marge Bot (@marge-bot) 06 Jan '26
06 Jan '26
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
8f209336 by Simon Jakobi at 2026-01-05T16:24:48-05:00
User's guide: Fix link to language extensions
Instead of linking to haddocks, it seemed more useful to link
to the extension overview in the user's guide.
Closes #26614.
- - - - -
2 changed files:
- docs/users_guide/exts/pragmas.rst
- docs/users_guide/exts/table.rst
Changes:
=====================================
docs/users_guide/exts/pragmas.rst
=====================================
@@ -58,10 +58,9 @@ prefixing it with "``-X``"; for example ``-XForeignFunctionInterface``.
A list of all supported language extensions can be obtained by invoking
``ghc --supported-extensions`` (see :ghc-flag:`--supported-extensions`).
+Alternatively see :ref:`table`.
-Any extension from the ``Extension`` type defined in
-:cabal-ref:`Language.Haskell.Extension.` may be used. GHC will report an error
-if any of the requested extensions are not supported.
+GHC will report an error if any of the requested extensions are not supported.
.. _options-pragma:
=====================================
docs/users_guide/exts/table.rst
=====================================
@@ -1,3 +1,5 @@
+.. _table:
+
Overview of all language extensions
-----------------------------------
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8f2093363fd8a3b8386770c72aefa74…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8f2093363fd8a3b8386770c72aefa74…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][master] 2 commits: hadrian: drops unused PE linker script for windows
by Marge Bot (@marge-bot) 06 Jan '26
by Marge Bot (@marge-bot) 06 Jan '26
06 Jan '26
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 <codex(a)openai.com>
- - - - -
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>.<so|dylib>
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/b820ff50459fc48bce6db3af652c2e…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b820ff50459fc48bce6db3af652c2e…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/az/ghc-cpp] 9 commits: [#26183] Associated Type Iface Fix
by Alan Zimmerman (@alanz) 06 Jan '26
by Alan Zimmerman (@alanz) 06 Jan '26
06 Jan '26
Alan Zimmerman pushed to branch wip/az/ghc-cpp at Glasgow Haskell Compiler / GHC
Commits:
8a317b6f by Aaron Allen at 2026-01-01T03:05:15-05:00
[#26183] Associated Type Iface Fix
When determining "extras" for class decl interface entries, axioms for
the associated types need to included so that dependent modules will be
recompiled if those axioms change.
resolves #26183
- - - - -
ae1aeaab by Cheng Shao at 2026-01-01T03:06:32-05:00
testsuite: run numeric tests with optasm when available
This patch adds the `optasm` extra way to nueric tests when NCG is
available. Some numeric bugs only surface with optimization, omitting
this can hide these bugs and even make them slip into release! (e.g. #26711)
- - - - -
6213bb57 by maralorn at 2026-01-02T16:30:32+01:00
GHC.Internal.Exception.Context: Fix comment
on addExceptionAnnotation
- - - - -
b820ff50 by Janis Voigtlaender at 2026-01-05T02:43:18-05:00
GHC.Internal.Control.Monad.replicateM: Fix comment
- - - - -
f639e153 by Alan Zimmerman at 2026-01-05T20:06:17+00:00
GHC-CPP: Initial implementation
Processes
#define FOO
#ifdef FOO
x = 1
#endif
Into
[ITcppIgnored [L loc ITcppDefine]
,ITcppIgnored [L loc ITcppIfdef]
,ITvarid "x"
,ITequal
,ITinteger (IL {il_text = SourceText "1", il_neg = False, il_value = 1})
,ITcppIgnored [L loc ITcppEndif]
,ITeof]
In time, ITcppIgnored will be pushed into a comment
Tidy up before re-visiting the continuation mechanic
Switch preprocessor to continuation passing style
Proof of concept, needs tidying up
Small cleanup
Get rid of some cruft
Summary: Patch:
Author: Alan Zimmerman <alan.zimm(a)gmail.com>
Date: 2025-10-12 16:23:56 +0100
Summary: Patch: rebase-and-tests-pass
Author: Alan Zimmerman <alan.zimm(a)gmail.com>
Date: 2025-10-12 14:19:04 +0100
Rebase, and all tests pass except whitespace for generated parser
Starting to integrate.
Need to get the pragma recognised and set
Make cppTokens extend to end of line, and process CPP comments
Remove unused ITcppDefined
Allow spaces between # and keyword for preprocessor directive
Process CPP continuation lines
They are emited as separate ITcppContinue tokens.
Perhaps the processing should be more like a comment, and keep on
going to the end.
BUT, the last line needs to be slurped as a whole.
Accumulate CPP continuations, process when ready
Can be simplified further, we only need one CPP token
Simplify Lexer interface. Only ITcpp
We transfer directive lines through it, then parse them from scratch
in the preprocessor.
Deal with directive on last line, with no trailing \n
Start parsing and processing the directives
Prepare for processing include files
Move PpState into PreProcess
And initParserState, initPragState too
Process nested include files
Also move PpState out of Lexer.x, so it is easy to evolve it in a ghci
session, loading utils/check-cpp/Main.hs
Split into separate files
Starting on expression parser.
But it hangs. Time for Text.Parsec.Expr
Start integrating the ghc-cpp work
From https://github.com/alanz/ghc-cpp
WIP
Fixup after rebase
WIP
Fixup after rebase, including all tests pass
Change pragma usage to GHC_CPP from GhcCPP
Some comments
Reformat
Delete unused file
Rename module Parse to ParsePP
Clarify naming in the parser
WIP. Switching to alex/happy to be able to work in-tree
Since Parsec is not available
Layering is now correct
- GHC lexer, emits CPP tokens
- accumulated in Preprocessor state
- Lexed by CPP lexer, CPP command extracted, tokens concated with
spaces (to get rid of token pasting via comments)
- if directive lexed and parsed by CPP lexer/parser, and evaluated
First example working
Loading Example1.hs into ghci, getting the right results
```
{-# LANGUAGE GHC_CPP #-}
module Example1 where
y = 3
x =
"hello"
"bye now"
foo = putStrLn x
```
Rebase, and all tests pass except whitespace for generated parser
info: patch template saved to `-`
More plumbing. Ready for testing tomorrow.
Proress. Renamed module State from Types
And at first blush it seems to handle preprocessor scopes properly.
Insert basic GHC version macros into parser
__GLASGOW_HASKELL__
__GLASGOW_HASKELL_FULL_VERSION__
__GLASGOW_HASKELL_PATCHLEVEL1__
__GLASGOW_HASKELL_PATCHLEVEL2__
Re-sync check-cpp for easy ghci work
Get rid of warnings
Rework macro processing, in check-cpp
Macros kept at the top level, looked up via name, multiple arity
versions per name can be stored
WIP. Can crack arguments for #define
Next step it to crack out args in an expansion
WIP on arg parsing.
Progress. Still screwing up nested parens.
Seems to work, but has redundant code
Remove redundant code
Reformat
Expand args, single pass
Still need to repeat until fixpoint
Fixed point expansion
Sync the playground to compiler
Working on dumping the GHC_CPP result
But We need to keep the BufSpan in a comment
Keep BufSpan in queued comments in GHC.Parser.Lexer
Getting close to being able to print the combined tokens
showing what is in and what is out
First implementation of dumpGhcCpp.
Example output
First dumps all macros in the state, then the source, showing which
lines are in and which are out
------------------------------
- |#define FOO(A,B) A + B
- |#define FOO(A,B,C) A + B + C
- |#if FOO(1,FOO(3,4)) == 8
- |-- a comment
|x = 1
- |#else
- |x = 5
- |#endif
Clean up a bit
Add -ddump-ghc-cpp option and a test based on it
Restore Lexer.x rules, we need them for continuation lines
Lexer.x: trying to sort out the span for continuations
- We need to match on \n at the end of the line
- We cannot simply back up for it
Inserts predefined macros. But does not dump properly
Because the cpp tokens have a trailing newline
Remove unnecessary LExer rules
We *need* the ones that explicitly match to the end of the line.
Generate correct span for ITcpp
Dump now works, except we do not render trailing `\` for continuation
lines. This is good enough for use in test output.
Reduce duplication in lexer
Tweaks
Insert min_version predefined macros into state
The mechanism now works. Still need to flesh out the full set.
Trying my alternative pragma syntax.
It works, but dumpGhcCpp is broken, I suspect from the ITcpp token
span update.
Pragma extraction now works, with both CPP and GHC_CPP
For the following
{-# LANGUAGE CPP #-}
#if __GLASGOW_HASKELL__ >= 913
{-# LANGUAGE GHC_CPP #-}
#endif
We will enable GHC_CPP only
Remove some tracing
Fix test exes for changes
For GHC_CPP tests, normalise config-time-based macros
WIP
WIP again. What is wrong?
Revert to dynflags for normal not pragma lexing
Working on getting check-exact to work properly
Passes CppCommentPlacement test
Starting on exact printing with GHC_CPP
While overriding normal CPP
Correctly store CPP ignored tokens as comments
By populating the lexeme string in it, based on the bufpos
WIP
Simplifying
Update the active state logic
Work the new logic into the mainline code
Process `defined` operator
Manage lexer state while skipping tokens
There is very intricate layout-related state used when lexing. If a
CPP directive blanks out some tokens, store this state when the
blanking starts, and restore it when they are no longer being blanked.
Track the last token buffer index, for ITCppIgnored
We need to attach the source being skipped in an ITCppIgnored token.
We cannot simply use its BufSpan as an index into the underlying
StringBuffer as it counts unicode chars, not bytes.
So we update the lexer state to store the starting StringBuffer
location for the last token, and use the already-stored length to
extract the correct portion of the StringBuffer being parsed.
Process the ! operator in GHC_CPP expressions
Predefine a constant when GHC_CPP is being used.
WIP
Skip lines directly in the lexer when required
Properly manage location when accepting tokens again
Seems to be working now, for Example9
Remove tracing
Fix parsing '*' in block comments
Instead of replacing them with '-'
Keep the trailing backslash in a ITcpp token
Deal with only enabling one section of a group.
A group is an instance of a conditional introduced by
#if/#ifdef/#ifndef,
and ending at the final #endif, including intermediate #elsif sections
Replace remaining identifiers with 0 when evaluating
As per the spec
Snapshot before rebase
Skip non-processed lines starting with #
Export generateMacros so we can use it in ghc-exactprint
Fix rebase
Expose initParserStateWithMacrosString
Fix buggy lexer cppSkip
It was skipping all lines, not just ones prefixed by #
Fix evaluation of && to use the correct operator
Deal with closing #-} at the start of a line
Add the MIN_VERSION_GLASGOW_HASKELL predefined macro
Include MIN_VERSION_GLASGOW_HASKELL in GhcCpp01.stderr
Use a strict map for macro defines
Process TIdentifierLParen
Which only matters at the start of #define
Do not provide TIdentifierLParen paren twice
Handle whitespace between identifier and '(' for directive only
Expose some Lexer bitmap manipulation helpers
Deal with line pragmas as tokens
Blows up for dumpGhcCpp though
Allow strings delimited by a single quote too
Allow leading whitespace on cpp directives
As per https://timsong-cpp.github.io/cppwp/n4140/cpp#1
Implement GHC_CPP undef
Sort out expansion of no-arg macros, in a context with args
And make the expansion bottom out, in the case of recursion
Fix GhcCpp01 test
The LINE pragma stuff works in ghc-exactprint when specifically
setting flag to emit ITline_pragma tokens
Process comments in CPP directives
Correctly lex pragmas with finel #-} on a newline
Do not process CPP-style comments
Allow cpp-style comments when GHC_CPP enabled
Return other pragmas as cpp ignored when GHC_CPP active
Reorganise getOptionsFromFile for use in ghc-exactprint
We want to be able to inject predefined macro definitions into the
parser preprocessor state for when we do a hackage roundtrip.
Tweak testing
Only allow unknown cpp pragmas with # in left margin
Require # against left margin for all GHC_CPP directives
Fix CPP directives appearing in pragmas
And add a test for error reporting for missing `#if`
Starting to report GHC_CPP errors using GHC machinery
More GHC_CPP diagnostic results
WIP on converting error calls to GHC diagnostics in GHC_CPP
Working on CPP diagnostic reporting
Tweak some tests/lint warnings
More error reporting in Macro
Some cleanups
Some cleanup
GHC_CPP: Working on improving error reporting
Harvest some commonality
Use PPM as Maybe inside PP
Clean up a bit
Fix GhcCpp01 test
I think this needs to be made more robust. Likely by not dumping the
(pre-)defined macros.
info: patch template saved to `-`
info: patch template saved to `-`
- - - - -
56f9fd83 by Alan Zimmerman at 2026-01-05T20:06:17+00:00
Fix GhcCpp01 after rebase
- - - - -
a25d815c by Alan Zimmerman at 2026-01-05T20:06:17+00:00
GHC_CPP: delete utils/check-cpp
It is not needed
- - - - -
3b0288a9 by Alan Zimmerman at 2026-01-05T20:06:17+00:00
GHC_CPP: remove #include processing
We do not support it
- - - - -
b105186a by Alan Zimmerman at 2026-01-05T20:06:17+00:00
GHC_CPP: move Eval.hs into GHC.Parser.PreProcess.Macro
- - - - -
66 changed files:
- compiler/GHC.hs
- compiler/GHC/Cmm/Lexer.x
- compiler/GHC/Cmm/Parser.y
- compiler/GHC/Cmm/Parser/Monad.hs
- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Driver/Config/Parser.hs
- compiler/GHC/Driver/Downsweep.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Pipeline.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Iface/Recomp.hs
- compiler/GHC/Parser.hs-boot
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/Errors/Ppr.hs
- compiler/GHC/Parser/Errors/Types.hs
- compiler/GHC/Parser/HaddockLex.x
- compiler/GHC/Parser/Header.hs
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Parser/PostProcess/Haddock.hs
- + compiler/GHC/Parser/PreProcess.hs
- + compiler/GHC/Parser/PreProcess/Lexer.x
- + compiler/GHC/Parser/PreProcess/Macro.hs
- + compiler/GHC/Parser/PreProcess/ParsePP.hs
- + compiler/GHC/Parser/PreProcess/Parser.y
- + compiler/GHC/Parser/PreProcess/ParserM.hs
- + compiler/GHC/Parser/PreProcess/State.hs
- compiler/GHC/Parser/Utils.hs
- compiler/GHC/SysTools/Cpp.hs
- compiler/GHC/Types/Error/Codes.hs
- compiler/ghc.cabal.in
- docs/users_guide/debugging.rst
- ghc/GHCi/UI.hs
- hadrian/src/Rules/SourceDist.hs
- libraries/ghc-internal/src/GHC/Internal/Control/Monad.hs
- libraries/ghc-internal/src/GHC/Internal/Exception/Context.hs
- libraries/ghc-internal/src/GHC/Internal/LanguageExtensions.hs
- testsuite/tests/count-deps/CountDepsParser.stdout
- testsuite/tests/driver/T4437.hs
- + testsuite/tests/driver/recomp26183/M.hs
- + testsuite/tests/driver/recomp26183/M2A.hs
- + testsuite/tests/driver/recomp26183/M2B.hs
- + testsuite/tests/driver/recomp26183/Makefile
- + testsuite/tests/driver/recomp26183/all.T
- + testsuite/tests/driver/recomp26183/recomp26183.stderr
- testsuite/tests/ghc-api/T11579.hs
- + testsuite/tests/ghc-cpp/GhcCpp01.hs
- + testsuite/tests/ghc-cpp/GhcCpp01.stderr
- + testsuite/tests/ghc-cpp/GhcCpp02.hs
- + testsuite/tests/ghc-cpp/GhcCpp02.stderr
- + testsuite/tests/ghc-cpp/all.T
- testsuite/tests/interface-stability/template-haskell-exports.stdout
- testsuite/tests/linters/notes.stdout
- testsuite/tests/linters/regex-linters/check-cpp.py
- testsuite/tests/numeric/should_run/all.T
- + testsuite/tests/printer/CppCommentPlacement.hs
- utils/check-exact/Main.hs
- utils/check-exact/Parsers.hs
- utils/check-exact/Preprocess.hs
- utils/check-exact/Utils.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs
- utils/haddock/haddock-api/src/Haddock/Parser.hs
- utils/haddock/haddock-api/src/Haddock/Types.hs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4636b78194b86c17e338bfbfcc2484…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4636b78194b86c17e338bfbfcc2484…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/T23162-part2] 11 commits: Decoupling Language.Haskell.Syntax.Binds from GHC.Types.Basic
by Simon Peyton Jones (@simonpj) 05 Jan '26
by Simon Peyton Jones (@simonpj) 05 Jan '26
05 Jan '26
Simon Peyton Jones pushed to branch wip/T23162-part2 at Glasgow Haskell Compiler / GHC
Commits:
7b9c20f4 by Recursion Ninja at 2025-12-24T10:35:36-05:00
Decoupling Language.Haskell.Syntax.Binds from GHC.Types.Basic
by transferring InlinePragma types between the modules.
* Moved InlinePragma data-types to Language.Haskell.Syntax.Binds.InlinePragma
* Partitioned of Arity type synonyms to GHC.Types.Arity
* InlinePragma is now extensible via Trees That Grow
* Activation is now extensible via Trees That Grow
* Maybe Arity change to more descriptive InlineSaturation data-type
* InlineSaturation information removed from InlinePragma during GHS parsing pass
* Cleaned up the exposed module interfaces of the new modules
- - - - -
a3afae0c by Simon Peyton Jones at 2025-12-25T15:26:36-05:00
Check for rubbish literals in Lint
Addresses #26607.
See new Note [Checking for rubbish literals] in GHC.Core.Lint
- - - - -
8a317b6f by Aaron Allen at 2026-01-01T03:05:15-05:00
[#26183] Associated Type Iface Fix
When determining "extras" for class decl interface entries, axioms for
the associated types need to included so that dependent modules will be
recompiled if those axioms change.
resolves #26183
- - - - -
ae1aeaab by Cheng Shao at 2026-01-01T03:06:32-05:00
testsuite: run numeric tests with optasm when available
This patch adds the `optasm` extra way to nueric tests when NCG is
available. Some numeric bugs only surface with optimization, omitting
this can hide these bugs and even make them slip into release! (e.g. #26711)
- - - - -
6213bb57 by maralorn at 2026-01-02T16:30:32+01:00
GHC.Internal.Exception.Context: Fix comment
on addExceptionAnnotation
- - - - -
b820ff50 by Janis Voigtlaender at 2026-01-05T02:43:18-05:00
GHC.Internal.Control.Monad.replicateM: Fix comment
- - - - -
3f0ab99e by Simon Peyton Jones at 2026-01-05T17:39:12+00:00
Improved fundeps for closed type families
The big payload of this commit is to execute the plan suggested
in #23162, by improving the way that we generate functional
dependencies for closed type families.
It is all described in Note [Exploiting closed type families]
Most of the changes are in GHC.Tc.Solver.FunDeps
Other small changes
* GHC.Tc.Solver.bumpReductionDepth. This function brings together the code that
* Bumps the depth
* Checks for overflow
Previously the two were separated, sometimes quite widely.
* GHC.Core.Unify.niFixSubst: minor improvement, removing an unnecessary
itraetion in the base case.
* GHC.Core.Unify: no need to pass an InScopeSet to
tcUnifyTysForInjectivity. It can calculate one for itself; and it is
never inspected anyway so it's free to do so.
* GHC.Tc.Errors.Ppr: slight impovement to the error message for
reduction-stack overflow, when a constraint (rather than a type) is
involved.
* GHC.Tc.Solver.Monad.wrapUnifier: small change to the API
- - - - -
57ae1912 by Simon Peyton Jones at 2026-01-05T17:39:12+00:00
Add missing (KK4) to kick-out criteria
There was a missing case in kick-out that meant we could fail
to solve an eminently-solvable constraint.
See the new notes about (KK4)
- - - - -
b6e5200b by Simon Peyton Jones at 2026-01-05T17:39:12+00:00
Some small refactorings of error reporting in the typechecker
This is just a tidy-up commit.
* Add ei_insoluble to ErrorItem, to cache insolubility.
Small tidy-up.
* Remove `is_ip` and `mkIPErr` from GHC.Tc.Errors; instead enhance mkDictErr
to handle implicit parameters. Small refactor.
- - - - -
9a5eb747 by Simon Peyton Jones at 2026-01-05T17:39:12+00:00
Improve recording of insolubility for fundeps
This commit addresses #22652, by recording when the fundeps for
a constraint are definitely insoluble. That in turn improves the
perspicacity of the pattern-match overlap checker.
See Note [Insoluble fundeps]
- - - - -
aac26a5e by Simon Peyton Jones at 2026-01-05T17:39:12+00:00
Fix a buglet in niFixSubst
The MR of which this is part failed an assertion check extendTvSubst
because we extended the TvSubst with a CoVar. Boo.
This tiny patch fixes it, and adds the regression test from #13882
that showed it up.
- - - - -
145 changed files:
- compiler/GHC/Builtin/PrimOps/Ids.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/FamInstEnv.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Opt/CSE.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/OccurAnal.hs
- compiler/GHC/Core/Opt/Pipeline.hs
- compiler/GHC/Core/Opt/Pipeline/Types.hs
- compiler/GHC/Core/Opt/Simplify.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Iteration.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Core/Opt/Specialise.hs
- compiler/GHC/Core/Opt/WorkWrap.hs
- compiler/GHC/Core/Ppr.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/TyCo/Subst.hs
- compiler/GHC/Core/TyCon.hs
- compiler/GHC/Core/Unfold/Make.hs
- compiler/GHC/Core/Unify.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/Driver/Config/Core/Lint.hs
- compiler/GHC/Driver/Config/Core/Lint/Interactive.hs
- compiler/GHC/Driver/Config/Core/Opt/Simplify.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/HsToCore.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Errors/Types.hs
- compiler/GHC/HsToCore/Foreign/C.hs
- compiler/GHC/HsToCore/Foreign/JavaScript.hs
- compiler/GHC/HsToCore/Monad.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/HsToCore/Ticks.hs
- compiler/GHC/Iface/Make.hs
- compiler/GHC/Iface/Recomp.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/Iface/Tidy.hs
- compiler/GHC/IfaceToCore.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Tc/Deriv/Generics.hs
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Tc/Gen/Arrow.hs
- compiler/GHC/Tc/Gen/Sig.hs
- compiler/GHC/Tc/Gen/Splice.hs
- compiler/GHC/Tc/Instance/Typeable.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/FunDeps.hs
- compiler/GHC/Tc/Solver/InertSet.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Solver/Rewrite.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/GHC/Tc/Types/Constraint.hs
- compiler/GHC/Tc/Types/CtLoc.hs
- compiler/GHC/Tc/Utils/Instantiate.hs
- compiler/GHC/Tc/Utils/Monad.hs
- compiler/GHC/Tc/Utils/Unify.hs
- compiler/GHC/ThToHs.hs
- + compiler/GHC/Types/Arity.hs
- compiler/GHC/Types/Basic.hs
- compiler/GHC/Types/Hint.hs
- compiler/GHC/Types/Id.hs
- compiler/GHC/Types/Id/Info.hs
- compiler/GHC/Types/Id/Make.hs
- + compiler/GHC/Types/InlinePragma.hs
- compiler/GHC/Types/TyThing.hs
- compiler/GHC/Utils/Binary.hs
- compiler/GHC/Utils/Outputable.hs
- compiler/Language/Haskell/Syntax/Binds.hs
- + compiler/Language/Haskell/Syntax/Binds/InlinePragma.hs
- compiler/Language/Haskell/Syntax/Decls.hs
- compiler/Language/Haskell/Syntax/Extension.hs
- compiler/ghc.cabal.in
- docs/users_guide/9.16.1-notes.rst
- libraries/ghc-internal/src/GHC/Internal/Control/Monad.hs
- libraries/ghc-internal/src/GHC/Internal/Exception/Context.hs
- linters/lint-codes/LintCodes/Static.hs
- testsuite/tests/count-deps/CountDepsAst.stdout
- testsuite/tests/count-deps/CountDepsParser.stdout
- + testsuite/tests/driver/recomp26183/M.hs
- + testsuite/tests/driver/recomp26183/M2A.hs
- + testsuite/tests/driver/recomp26183/M2B.hs
- + testsuite/tests/driver/recomp26183/Makefile
- + testsuite/tests/driver/recomp26183/all.T
- + testsuite/tests/driver/recomp26183/recomp26183.stderr
- testsuite/tests/indexed-types/should_compile/CEqCanOccursCheck.hs
- testsuite/tests/indexed-types/should_fail/T12522a.hs
- testsuite/tests/indexed-types/should_fail/T26176.stderr
- testsuite/tests/numeric/should_run/all.T
- testsuite/tests/parser/should_fail/RecordDotSyntaxFail10.stderr
- testsuite/tests/parser/should_fail/RecordDotSyntaxFail13.stderr
- testsuite/tests/parser/should_fail/T20654a.stderr
- testsuite/tests/pmcheck/should_compile/T15753c.hs
- + testsuite/tests/pmcheck/should_compile/T15753c.stderr
- testsuite/tests/pmcheck/should_compile/T15753d.hs
- + testsuite/tests/pmcheck/should_compile/T15753d.stderr
- + testsuite/tests/pmcheck/should_compile/T22652.hs
- + testsuite/tests/pmcheck/should_compile/T22652a.hs
- testsuite/tests/pmcheck/should_compile/all.T
- + testsuite/tests/polykinds/T13882.hs
- testsuite/tests/polykinds/all.T
- testsuite/tests/quantified-constraints/T15316A.stderr
- testsuite/tests/quantified-constraints/T17267.stderr
- testsuite/tests/quantified-constraints/T17267a.stderr
- testsuite/tests/quantified-constraints/T17267b.stderr
- testsuite/tests/quantified-constraints/T17267c.stderr
- testsuite/tests/quantified-constraints/T17267e.stderr
- testsuite/tests/quantified-constraints/T17458.stderr
- testsuite/tests/typecheck/should_compile/T16188.hs
- testsuite/tests/typecheck/should_fail/ContextStack1.stderr
- testsuite/tests/typecheck/should_fail/FD3.stderr
- testsuite/tests/typecheck/should_fail/FDsFromGivens2.stderr
- testsuite/tests/typecheck/should_fail/FunDepOrigin1b.stderr
- testsuite/tests/typecheck/should_fail/T13506.stderr
- testsuite/tests/typecheck/should_fail/T15767.stderr
- testsuite/tests/typecheck/should_fail/T19415.stderr
- testsuite/tests/typecheck/should_fail/T19415b.stderr
- testsuite/tests/typecheck/should_fail/T22924b.stderr
- + testsuite/tests/typecheck/should_fail/T23162b.hs
- + testsuite/tests/typecheck/should_fail/T23162b.stderr
- + testsuite/tests/typecheck/should_fail/T23162c.hs
- + testsuite/tests/typecheck/should_fail/T23162d.hs
- testsuite/tests/typecheck/should_fail/T25325.stderr
- testsuite/tests/typecheck/should_fail/T5236.stderr
- testsuite/tests/typecheck/should_fail/T5246.stderr
- testsuite/tests/typecheck/should_fail/T5978.stderr
- testsuite/tests/typecheck/should_fail/T9612.stderr
- testsuite/tests/typecheck/should_fail/TcCoercibleFail.stderr
- testsuite/tests/typecheck/should_fail/all.T
- testsuite/tests/typecheck/should_fail/tcfail143.stderr
- utils/check-exact/ExactPrint.hs
- utils/haddock/haddock-api/src/Haddock/Convert.hs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c5b6e51164139edfd5c9460646cb3d…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c5b6e51164139edfd5c9460646cb3d…
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: GHC.Internal.Control.Monad.replicateM: Fix comment
by Marge Bot (@marge-bot) 05 Jan '26
by Marge Bot (@marge-bot) 05 Jan '26
05 Jan '26
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
b820ff50 by Janis Voigtlaender at 2026-01-05T02:43:18-05:00
GHC.Internal.Control.Monad.replicateM: Fix comment
- - - - -
5bf9d3fb by Cheng Shao at 2026-01-05T10:53:41-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.
- - - - -
33e00b3f by Cheng Shao at 2026-01-05T10:53:41-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 <codex(a)openai.com>
- - - - -
ff86c8e7 by Simon Jakobi at 2026-01-05T10:53:44-05:00
User's guide: Fix link to language extensions
Instead of linking to haddocks, it seemed more useful to link
to the extension overview in the user's guide.
Closes #26614.
- - - - -
20 changed files:
- docs/users_guide/exts/pragmas.rst
- docs/users_guide/exts/table.rst
- − 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
- libraries/ghc-internal/src/GHC/Internal/Control/Monad.hs
Changes:
=====================================
docs/users_guide/exts/pragmas.rst
=====================================
@@ -58,10 +58,9 @@ prefixing it with "``-X``"; for example ``-XForeignFunctionInterface``.
A list of all supported language extensions can be obtained by invoking
``ghc --supported-extensions`` (see :ghc-flag:`--supported-extensions`).
+Alternatively see :ref:`table`.
-Any extension from the ``Extension`` type defined in
-:cabal-ref:`Language.Haskell.Extension.` may be used. GHC will report an error
-if any of the requested extensions are not supported.
+GHC will report an error if any of the requested extensions are not supported.
.. _options-pragma:
=====================================
docs/users_guide/exts/table.rst
=====================================
@@ -1,3 +1,5 @@
+.. _table:
+
Overview of all language extensions
-----------------------------------
=====================================
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>.<so|dylib>
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
]
=====================================
libraries/ghc-internal/src/GHC/Internal/Control/Monad.hs
=====================================
@@ -314,7 +314,7 @@ Core: https://gitlab.haskell.org/ghc/ghc/issues/11795#note_118976
-- | @'replicateM' n act@ performs the action @act@ @n@ times,
-- and then returns the list of results.
--
--- @replicateM n (pure x) == 'replicate' n x@
+-- @replicateM n (pure x) == pure ('replicate' n x)@
--
-- ==== __Examples__
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7479a17ecb0813a9aeb87f8531c3e8…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7479a17ecb0813a9aeb87f8531c3e8…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
05 Jan '26
Cheng Shao pushed new branch wip/fix-cross-windows at Glasgow Haskell Compiler / GHC
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/fix-cross-windows
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/deepseq-primop] 11 commits: hadrian: fix bootstrapping with ghc-9.14
by Cheng Shao (@TerrorJack) 05 Jan '26
by Cheng Shao (@TerrorJack) 05 Jan '26
05 Jan '26
Cheng Shao pushed to branch wip/deepseq-primop at Glasgow Haskell Compiler / GHC
Commits:
c72ddabf by Cheng Shao at 2025-12-23T16:13:23-05:00
hadrian: fix bootstrapping with ghc-9.14
This patch fixes bootstrapping GHC with ghc-9.14, tested locally with
ghc-9.14.1 release as bootstrapping GHC.
- - - - -
0fd6d8e4 by Cheng Shao at 2025-12-23T16:14:05-05:00
hadrian: pass -keep-tmp-files to test ghc when --keep-test-files is enabled
This patch makes hadrian pass `-keep-tmp-files` to test ghc when
`--keep-test-files` is enabled, so you can check the ghc intermediate
files when debugging certain test failures. Closes #26688.
- - - - -
81d10134 by Cheng Shao at 2025-12-24T06:11:52-05:00
configure: remove dead code in configure scripts
This patch removes dead code in our configure scripts, including:
- Variables and auto-detected programs that are not used
- autoconf functions that are not used, or export a variable that's
not used
- `AC_CHECK_HEADERS` invocations that don't have actual corresponding
`HAVE_XXX_H` usage
- Other dead code (e.g. stray `AC_DEFUN()`)
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
fb1381c3 by Wolfgang Jeltsch at 2025-12-24T06:12:34-05:00
Remove unused known keys and names for list operations
This removes the known-key and corresponding name variables for
`concat`, `filter`, `zip`, and `(++)`, as they are apparently nowhere
used in GHC’s source code.
- - - - -
7b9c20f4 by Recursion Ninja at 2025-12-24T10:35:36-05:00
Decoupling Language.Haskell.Syntax.Binds from GHC.Types.Basic
by transferring InlinePragma types between the modules.
* Moved InlinePragma data-types to Language.Haskell.Syntax.Binds.InlinePragma
* Partitioned of Arity type synonyms to GHC.Types.Arity
* InlinePragma is now extensible via Trees That Grow
* Activation is now extensible via Trees That Grow
* Maybe Arity change to more descriptive InlineSaturation data-type
* InlineSaturation information removed from InlinePragma during GHS parsing pass
* Cleaned up the exposed module interfaces of the new modules
- - - - -
a3afae0c by Simon Peyton Jones at 2025-12-25T15:26:36-05:00
Check for rubbish literals in Lint
Addresses #26607.
See new Note [Checking for rubbish literals] in GHC.Core.Lint
- - - - -
8a317b6f by Aaron Allen at 2026-01-01T03:05:15-05:00
[#26183] Associated Type Iface Fix
When determining "extras" for class decl interface entries, axioms for
the associated types need to included so that dependent modules will be
recompiled if those axioms change.
resolves #26183
- - - - -
ae1aeaab by Cheng Shao at 2026-01-01T03:06:32-05:00
testsuite: run numeric tests with optasm when available
This patch adds the `optasm` extra way to nueric tests when NCG is
available. Some numeric bugs only surface with optimization, omitting
this can hide these bugs and even make them slip into release! (e.g. #26711)
- - - - -
6213bb57 by maralorn at 2026-01-02T16:30:32+01:00
GHC.Internal.Exception.Context: Fix comment
on addExceptionAnnotation
- - - - -
b820ff50 by Janis Voigtlaender at 2026-01-05T02:43:18-05:00
GHC.Internal.Control.Monad.replicateM: Fix comment
- - - - -
1b418e7b by Cheng Shao at 2026-01-05T13:22:15+01:00
WIP
- - - - -
105 changed files:
- .gitlab/ci.sh
- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Builtin/PrimOps/Ids.hs
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/Core.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Opt/CSE.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/OccurAnal.hs
- compiler/GHC/Core/Opt/Pipeline.hs
- compiler/GHC/Core/Opt/Pipeline/Types.hs
- compiler/GHC/Core/Opt/Simplify.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Iteration.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Core/Opt/Specialise.hs
- compiler/GHC/Core/Opt/WorkWrap.hs
- compiler/GHC/Core/Ppr.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/Unfold/Make.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/Driver/Config/Core/Lint.hs
- compiler/GHC/Driver/Config/Core/Lint/Interactive.hs
- compiler/GHC/Driver/Config/Core/Opt/Simplify.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/HsToCore.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Errors/Types.hs
- compiler/GHC/HsToCore/Foreign/C.hs
- compiler/GHC/HsToCore/Foreign/JavaScript.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/HsToCore/Ticks.hs
- compiler/GHC/Iface/Make.hs
- compiler/GHC/Iface/Recomp.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/Iface/Tidy.hs
- compiler/GHC/IfaceToCore.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/StgToCmm/Prim.hs
- compiler/GHC/StgToJS/Prim.hs
- compiler/GHC/Tc/Deriv/Generics.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Tc/Gen/Arrow.hs
- compiler/GHC/Tc/Gen/Sig.hs
- compiler/GHC/Tc/Instance/Typeable.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/GHC/Tc/Utils/Instantiate.hs
- compiler/GHC/ThToHs.hs
- + compiler/GHC/Types/Arity.hs
- compiler/GHC/Types/Basic.hs
- compiler/GHC/Types/Hint.hs
- compiler/GHC/Types/Id.hs
- compiler/GHC/Types/Id/Info.hs
- compiler/GHC/Types/Id/Make.hs
- + compiler/GHC/Types/InlinePragma.hs
- compiler/GHC/Utils/Binary.hs
- compiler/GHC/Utils/Outputable.hs
- compiler/Language/Haskell/Syntax/Binds.hs
- + compiler/Language/Haskell/Syntax/Binds/InlinePragma.hs
- compiler/Language/Haskell/Syntax/Decls.hs
- compiler/Language/Haskell/Syntax/Extension.hs
- compiler/ghc.cabal.in
- configure.ac
- hadrian/cabal.project
- hadrian/src/Settings/Builders/RunTest.hs
- libraries/base/src/GHC/Base.hs
- libraries/base/src/GHC/Exts.hs
- libraries/ghc-experimental/ghc-experimental.cabal.in
- + libraries/ghc-experimental/src/GHC/DeepSeq.hs
- libraries/ghc-internal/configure.ac
- libraries/ghc-internal/src/GHC/Internal/Control/Monad.hs
- libraries/ghc-internal/src/GHC/Internal/Exception/Context.hs
- − m4/find_ghc_bootstrap_prog.m4
- − m4/fp_copy_shellvar.m4
- − m4/fp_prog_ld_flag.m4
- − m4/fp_prog_sort.m4
- m4/prep_target_file.m4
- + rts/DeepSeq.cmm
- rts/RtsSymbols.c
- rts/configure.ac
- rts/include/stg/MiscClosures.h
- rts/rts.cabal
- testsuite/tests/count-deps/CountDepsAst.stdout
- testsuite/tests/count-deps/CountDepsParser.stdout
- + testsuite/tests/driver/recomp26183/M.hs
- + testsuite/tests/driver/recomp26183/M2A.hs
- + testsuite/tests/driver/recomp26183/M2B.hs
- + testsuite/tests/driver/recomp26183/Makefile
- + testsuite/tests/driver/recomp26183/all.T
- + testsuite/tests/driver/recomp26183/recomp26183.stderr
- testsuite/tests/interface-stability/ghc-experimental-exports.stdout
- testsuite/tests/interface-stability/ghc-prim-exports.stdout
- testsuite/tests/numeric/should_run/all.T
- + testsuite/tests/primops/should_run/DeepSeqPrimOp.hs
- + testsuite/tests/primops/should_run/DeepSeqPrimOp.stdout
- testsuite/tests/primops/should_run/all.T
- utils/check-exact/ExactPrint.hs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ea5fe7e8a34d93db03eb3af1d4d838…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ea5fe7e8a34d93db03eb3af1d4d838…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/spj-try-opt-coercion] More on exported coercions
by Simon Peyton Jones (@simonpj) 05 Jan '26
by Simon Peyton Jones (@simonpj) 05 Jan '26
05 Jan '26
Simon Peyton Jones pushed to branch wip/spj-try-opt-coercion at Glasgow Haskell Compiler / GHC
Commits:
25b2a74c by Simon Peyton Jones at 2026-01-05T11:31:43+00:00
More on exported coercions
- - - - -
5 changed files:
- compiler/GHC/CoreToIface.hs
- compiler/GHC/Iface/Rename.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/Iface/Type.hs
- compiler/GHC/IfaceToCore.hs
Changes:
=====================================
compiler/GHC/CoreToIface.hs
=====================================
@@ -223,9 +223,6 @@ toIfaceTypeX fr (TyConApp tc tys)
toIfaceTyVar :: TyVar -> IfLclName
toIfaceTyVar = mkIfLclName . occNameFS . getOccName
-toIfaceCoVar :: CoVar -> IfLclName
-toIfaceCoVar = mkIfLclName . occNameFS . getOccName
-
----------------
toIfaceTyCon :: TyCon -> IfaceTyCon
toIfaceTyCon tc
@@ -287,7 +284,11 @@ toIfaceCoercionX fr co
go (CoVarCo cv)
-- See Note [Free TyVars and CoVars in IfaceType] in GHC.Iface.Type
| cv `elemVarSet` fr = IfaceFreeCoVar cv
- | otherwise = IfaceCoVarCo (toIfaceCoVar cv)
+ | isExternalName nm = IfaceExtCoVar nm
+ | otherwise = IfaceCoVarCo (mkIfLclName $ occNameFS $ nameOccName nm)
+ where
+ nm = idName cv
+
go (HoleCo h) = IfaceHoleCo (coHoleCoVar h)
go (AppCo co1 co2) = IfaceAppCo (go co1) (go co2)
@@ -454,6 +455,7 @@ toIfaceTopBndr id
toIfaceIdDetails :: IdDetails -> IfaceIdDetails
toIfaceIdDetails VanillaId = IfVanillaId
toIfaceIdDetails (WorkerLikeId dmds) = IfWorkerLikeId dmds
+toIfaceIdDetails CoVarId = IfCoVarId
toIfaceIdDetails (DFunId {}) = IfDFunId
toIfaceIdDetails (RecSelId { sel_naughty = n
, sel_tycon = tc
=====================================
compiler/GHC/Iface/Rename.hs
=====================================
@@ -886,13 +886,14 @@ rnIfaceMCo IfaceMRefl = pure IfaceMRefl
rnIfaceMCo (IfaceMCo co) = IfaceMCo <$> rnIfaceCo co
rnIfaceCo :: Rename IfaceCoercion
+rnIfaceCo co@(IfaceExtCoVar {}) = pure co
+rnIfaceCo co@(IfaceFreeCoVar {}) = pure co
+rnIfaceCo co@(IfaceCoVarCo {}) = pure co
rnIfaceCo (IfaceReflCo ty) = IfaceReflCo <$> rnIfaceType ty
rnIfaceCo (IfaceGReflCo role ty mco) = IfaceGReflCo role <$> rnIfaceType ty <*> rnIfaceMCo mco
rnIfaceCo (IfaceFunCo role w co1 co2) = IfaceFunCo role <$> rnIfaceCo w <*> rnIfaceCo co1 <*> rnIfaceCo co2
rnIfaceCo (IfaceTyConAppCo role tc cos) = IfaceTyConAppCo role <$> rnIfaceTyCon tc <*> mapM rnIfaceCo cos
rnIfaceCo (IfaceAppCo co1 co2) = IfaceAppCo <$> rnIfaceCo co1 <*> rnIfaceCo co2
-rnIfaceCo (IfaceFreeCoVar c) = pure (IfaceFreeCoVar c)
-rnIfaceCo (IfaceCoVarCo lcl) = IfaceCoVarCo <$> pure lcl
rnIfaceCo (IfaceHoleCo lcl) = IfaceHoleCo <$> pure lcl
rnIfaceCo (IfaceSymCo c) = IfaceSymCo <$> rnIfaceCo c
rnIfaceCo (IfaceTransCo c1 c2) = IfaceTransCo <$> rnIfaceCo c1 <*> rnIfaceCo c2
=====================================
compiler/GHC/Iface/Syntax.hs
=====================================
@@ -490,6 +490,7 @@ data IfGuidance
data IfaceIdDetails
= IfVanillaId
+ | IfCoVarId
| IfWorkerLikeId [CbvMark]
| IfRecSelId
{ ifRecSelIdParent :: Either IfaceTyCon IfaceDecl
@@ -1877,6 +1878,7 @@ instance Outputable IfaceIdDetails where
then text "<naughty>"
else Outputable.empty
ppr IfDFunId = text "DFunId"
+ ppr IfCoVarId = text "CoVarId"
instance Outputable IfaceInfoItem where
ppr (HsUnfold lb unf) = text "Unfolding"
@@ -1994,6 +1996,7 @@ freeNamesIfIdDetails (IfRecSelId tc first_con _ fl) =
freeNamesIfIdDetails IfVanillaId = emptyNameSet
freeNamesIfIdDetails (IfWorkerLikeId {}) = emptyNameSet
freeNamesIfIdDetails IfDFunId = emptyNameSet
+freeNamesIfIdDetails IfCoVarId = emptyNameSet
-- All other changes are handled via the version info on the tycon
freeNamesIfFamFlav :: IfaceFamTyConFlav -> NameSet
@@ -2086,6 +2089,7 @@ freeNamesIfCoercion (IfaceAppCo c1 c2)
freeNamesIfCoercion (IfaceForAllCo _tcv _visL _visR kind_co co)
= freeNamesIfMCoercion kind_co &&& freeNamesIfCoercion co
freeNamesIfCoercion (IfaceFreeCoVar _) = emptyNameSet
+freeNamesIfCoercion (IfaceExtCoVar n) = unitNameSet n
freeNamesIfCoercion (IfaceCoVarCo _) = emptyNameSet
freeNamesIfCoercion (IfaceHoleCo _) = emptyNameSet
freeNamesIfCoercion (IfaceUnivCo _ _ t1 t2 cos)
@@ -2718,6 +2722,7 @@ instance Binary IfaceIdDetails where
; put_ bh d }
put_ bh (IfWorkerLikeId dmds) = putByte bh 2 >> put_ bh dmds
put_ bh IfDFunId = putByte bh 3
+ put_ bh IfCoVarId = putByte bh 4
get bh = do
h <- getByte bh
case h of
@@ -2729,7 +2734,8 @@ instance Binary IfaceIdDetails where
; return (IfRecSelId a b c d) }
2 -> do { dmds <- get bh
; return (IfWorkerLikeId dmds) }
- _ -> return IfDFunId
+ 3 -> return IfDFunId
+ _ -> return IfCoVarId
instance Binary IfaceInfoItem where
put_ bh (HsArity aa) = putByte bh 0 >> put_ bh aa
@@ -3167,7 +3173,8 @@ instance NFData IfaceIdDetails where
IfWorkerLikeId dmds -> rnf dmds `seq` ()
IfRecSelId (Left tycon) b c d -> rnf tycon `seq` rnf b `seq` rnf c `seq` rnf d
IfRecSelId (Right decl) b c d -> rnf decl `seq` rnf b `seq` rnf c `seq` rnf d
- IfDFunId -> ()
+ IfDFunId -> ()
+ IfCoVarId -> ()
instance NFData IfaceInfoItem where
rnf = \case
=====================================
compiler/GHC/Iface/Type.hs
=====================================
@@ -475,13 +475,15 @@ data IfaceMCoercion
| IfaceMCo IfaceCoercion deriving (Eq, Ord)
data IfaceCoercion
- = IfaceReflCo IfaceType
+ = IfaceFreeCoVar CoVar -- ^ See Note [Free TyVars and CoVars in IfaceType]
+ | IfaceExtCoVar IfExtName -- Imported or top-level external coercion var
+ | IfaceCoVarCo IfLclName -- Regular, locally-bound coercion var
+ | IfaceReflCo IfaceType
| IfaceGReflCo Role IfaceType (IfaceMCoercion)
| IfaceFunCo Role IfaceCoercion IfaceCoercion IfaceCoercion
| IfaceTyConAppCo Role IfaceTyCon [IfaceCoercion]
| IfaceAppCo IfaceCoercion IfaceCoercion
| IfaceForAllCo IfaceBndr !ForAllTyFlag !ForAllTyFlag IfaceMCoercion IfaceCoercion
- | IfaceCoVarCo IfLclName
| IfaceAxiomCo IfaceAxiomRule [IfaceCoercion]
-- ^ There are only a fixed number of CoAxiomRules, so it suffices
-- to use an IfaceLclName to distinguish them.
@@ -494,7 +496,6 @@ data IfaceCoercion
| IfaceInstCo IfaceCoercion IfaceCoercion
| IfaceKindCo IfaceCoercion
| IfaceSubCo IfaceCoercion
- | IfaceFreeCoVar CoVar -- ^ See Note [Free TyVars and CoVars in IfaceType]
| IfaceHoleCo CoVar -- ^ See Note [Holes in IfaceCoercion]
deriving (Eq, Ord)
-- Why Ord? See Note [Ord instance of IfaceType]
@@ -779,9 +780,10 @@ substIfaceType env ty
go_co (IfaceTyConAppCo r tc cos) = IfaceTyConAppCo r tc (go_cos cos)
go_co (IfaceAppCo c1 c2) = IfaceAppCo (go_co c1) (go_co c2)
go_co (IfaceForAllCo {}) = pprPanic "substIfaceCoercion" (ppr ty)
- go_co (IfaceFreeCoVar cv) = IfaceFreeCoVar cv
- go_co (IfaceCoVarCo cv) = IfaceCoVarCo cv
- go_co (IfaceHoleCo cv) = IfaceHoleCo cv
+ go_co co@(IfaceFreeCoVar {}) = co
+ go_co co@(IfaceExtCoVar {}) = co
+ go_co co@(IfaceCoVarCo {}) = co
+ go_co co@(IfaceHoleCo {}) = co
go_co (IfaceUnivCo p r t1 t2 ds) = IfaceUnivCo p r (go t1) (go t2) (go_cos ds)
go_co (IfaceSymCo co) = IfaceSymCo (go_co co)
go_co (IfaceTransCo co1 co2) = IfaceTransCo (go_co co1) (go_co co2)
@@ -2076,8 +2078,9 @@ ppr_co ctxt_prec co@(IfaceForAllCo {})
= let (tvs, co'') = split_co co' in ((bndr,kind_co,visL,visR):tvs,co'')
split_co co' = ([], co')
--- Why these three? See Note [Free TyVars and CoVars in IfaceType]
+-- Why these four? See Note [Free TyVars and CoVars in IfaceType]
ppr_co _ (IfaceFreeCoVar covar) = ppr covar
+ppr_co _ (IfaceExtCoVar covar) = ppr covar
ppr_co _ (IfaceCoVarCo covar) = ppr covar
ppr_co _ (IfaceHoleCo covar) = braces (ppr covar)
@@ -2457,6 +2460,9 @@ instance Binary IfaceCoercion where
put_ bh (IfaceCoVarCo a) = do
putByte bh 7
put_ bh a
+ put_ bh (IfaceExtCoVar a) = do
+ putByte bh 8
+ put_ bh a
put_ bh (IfaceUnivCo a b c d deps) = do
putByte bh 9
put_ bh a
@@ -2530,6 +2536,8 @@ instance Binary IfaceCoercion where
return $ IfaceForAllCo a visL visR b c
7 -> do a <- get bh
return $ IfaceCoVarCo a
+ 8 -> do a <- get bh
+ return $ IfaceExtCoVar a
9 -> do a <- get bh
b <- get bh
c <- get bh
@@ -2605,13 +2613,14 @@ instance NFData IfaceTyLit where
instance NFData IfaceCoercion where
rnf = \case
+ IfaceExtCoVar f1 -> rnf f1
+ IfaceCoVarCo f1 -> rnf f1
IfaceReflCo f1 -> rnf f1
IfaceGReflCo f1 f2 f3 -> rnf f1 `seq` rnf f2 `seq` rnf f3
IfaceFunCo f1 f2 f3 f4 -> rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4
IfaceTyConAppCo f1 f2 f3 -> rnf f1 `seq` rnf f2 `seq` rnf f3
IfaceAppCo f1 f2 -> rnf f1 `seq` rnf f2
IfaceForAllCo f1 f2 f3 f4 f5 -> rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` rnf f5
- IfaceCoVarCo f1 -> rnf f1
IfaceAxiomCo f1 f2 -> rnf f1 `seq` rnf f2
IfaceUnivCo f1 f2 f3 f4 deps -> rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` rnf deps
IfaceSymCo f1 -> rnf f1
=====================================
compiler/GHC/IfaceToCore.hs
=====================================
@@ -1582,41 +1582,35 @@ tcIfaceCo = go
go_mco IfaceMRefl = pure MRefl
go_mco (IfaceMCo co) = MCo <$> (go co)
+ go (IfaceExtCoVar n) = CoVarCo <$> tcIfaceExtId n
+ go (IfaceCoVarCo n) = CoVarCo <$> tcIfaceLclId n
go (IfaceReflCo t) = Refl <$> tcIfaceType t
go (IfaceGReflCo r t mco) = GRefl r <$> tcIfaceType t <*> go_mco mco
go (IfaceFunCo r w c1 c2) = mkFunCoNoFTF r <$> go w <*> go c1 <*> go c2
go (IfaceTyConAppCo r tc cs) = TyConAppCo r <$> tcIfaceTyCon tc <*> mapM go cs
go (IfaceAppCo c1 c2) = AppCo <$> go c1 <*> go c2
+ go (IfaceSymCo c) = SymCo <$> go c
+ go (IfaceTransCo c1 c2) = TransCo <$> go c1 <*> go c2
+ go (IfaceInstCo c1 t2) = InstCo <$> go c1 <*> go t2
+ go (IfaceSelCo d c) = mkSelCo d <$> go c
+ go (IfaceLRCo lr c) = LRCo lr <$> go c
+ go (IfaceKindCo c) = KindCo <$> go c
+ go (IfaceSubCo c) = SubCo <$> go c
go (IfaceForAllCo tcv visL visR k co)
= do { k' <- go_mco k
; bindIfaceBndr tcv $ \ tv' ->
do { co' <- go co
; return (ForAllCo { fco_tcv = tv', fco_visL = visL, fco_visR = visR
, fco_kind = k', fco_body = co' }) } }
- go (IfaceCoVarCo n) = CoVarCo <$> go_var n
go (IfaceUnivCo p r t1 t2 ds) = do { t1' <- tcIfaceType t1; t2' <- tcIfaceType t2
; ds' <- mapM go ds
; return (UnivCo { uco_prov = p, uco_role = r
, uco_lty = t1', uco_rty = t2'
, uco_deps = ds' }) }
- go (IfaceSymCo c) = SymCo <$> go c
- go (IfaceTransCo c1 c2) = TransCo <$> go c1
- <*> go c2
- go (IfaceInstCo c1 t2) = InstCo <$> go c1
- <*> go t2
- go (IfaceSelCo d c) = do { c' <- go c
- ; return $ mkSelCo d c' }
- go (IfaceLRCo lr c) = LRCo lr <$> go c
- go (IfaceKindCo c) = KindCo <$> go c
- go (IfaceSubCo c) = SubCo <$> go c
- go (IfaceAxiomCo ax cos) = AxiomCo <$> tcIfaceAxiomRule ax
- <*> mapM go cos
+ go (IfaceAxiomCo ax cos) = AxiomCo <$> tcIfaceAxiomRule ax <*> mapM go cos
go (IfaceFreeCoVar c) = pprPanic "tcIfaceCo:IfaceFreeCoVar" (ppr c)
go (IfaceHoleCo c) = pprPanic "tcIfaceCo:IfaceHoleCo" (ppr c)
- go_var :: IfLclName -> IfL CoVar
- go_var = tcIfaceLclId
-
{-
************************************************************************
* *
@@ -1801,6 +1795,7 @@ tcIfaceDataAlt mult con inst_tys arg_strs rhs
tcIdDetails :: Name -> Type -> IfaceIdDetails -> IfL IdDetails
tcIdDetails _ _ IfVanillaId = return VanillaId
+tcIdDetails _ _ IfCoVarId = return CoVarId
tcIdDetails _ _ (IfWorkerLikeId dmds) = return $ WorkerLikeId dmds
tcIdDetails _ ty IfDFunId = return (DFunId (isUnaryClass cls))
where
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/25b2a74c138f0a02431bcd64f211e5e…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/25b2a74c138f0a02431bcd64f211e5e…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/fix-clang64-split-sections] 5 commits: GHC.Internal.Exception.Context: Fix comment
by Cheng Shao (@TerrorJack) 05 Jan '26
by Cheng Shao (@TerrorJack) 05 Jan '26
05 Jan '26
Cheng Shao pushed to branch wip/fix-clang64-split-sections at Glasgow Haskell Compiler / GHC
Commits:
6213bb57 by maralorn at 2026-01-02T16:30:32+01:00
GHC.Internal.Exception.Context: Fix comment
on addExceptionAnnotation
- - - - -
b820ff50 by Janis Voigtlaender at 2026-01-05T02:43:18-05:00
GHC.Internal.Control.Monad.replicateM: Fix comment
- - - - -
f9bda57b by Cheng Shao at 2026-01-05T09:25:50+01:00
compiler: change sectionProtection to take SectionType argument
This commit changes `sectionProtection` to only take `SectionType`
argument instead of whole `Section`, since it doesn't need the Cmm
section content anyway, and it can then be called in parts of NCG
where we only have a `SectionType` in scope.
- - - - -
9f426e30 by Cheng Shao at 2026-01-05T10:33:30+01:00
compiler: change isInitOrFiniSection to take SectionType argument
This commit changes `isInitOrFiniSection` to only take `SectionType`
argument instead of whole `Section`, since it doesn't need the Cmm
section content anyway, and it can then be called in parts of NCG
where we only have a `SectionType` in scope. Also marks it as
exported.
- - - - -
043299ef by Cheng Shao at 2026-01-05T10:42:34+01:00
compiler: fix split sections on windows
This patch fixes split sections on windows by emitting the right
COMDAT section header in NCG, see added comment for more explanation.
Fix #26696 #26494.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
8 changed files:
- compiler/GHC/Cmm.hs
- compiler/GHC/Cmm/InitFini.hs
- compiler/GHC/CmmToAsm/Ppr.hs
- compiler/GHC/CmmToAsm/Wasm/FromCmm.hs
- compiler/GHC/CmmToC.hs
- compiler/GHC/CmmToLlvm/Data.hs
- libraries/ghc-internal/src/GHC/Internal/Control/Monad.hs
- libraries/ghc-internal/src/GHC/Internal/Exception/Context.hs
Changes:
=====================================
compiler/GHC/Cmm.hs
=====================================
@@ -278,8 +278,8 @@ data SectionProtection
deriving (Eq)
-- | Should a data in this section be considered constant at runtime
-sectionProtection :: Section -> SectionProtection
-sectionProtection (Section t _) = case t of
+sectionProtection :: SectionType -> SectionProtection
+sectionProtection t = case t of
Text -> ReadOnlySection
ReadOnlyData -> ReadOnlySection
RelocatableReadOnlyData -> WriteProtectedSection
=====================================
compiler/GHC/Cmm/InitFini.hs
=====================================
@@ -2,6 +2,7 @@
module GHC.Cmm.InitFini
( InitOrFini(..)
, isInitOrFiniArray
+ , isInitOrFiniSection
) where
import GHC.Prelude
@@ -63,8 +64,8 @@ finalizer CmmDecl will be emitted per module.
data InitOrFini = IsInitArray | IsFiniArray
isInitOrFiniArray :: RawCmmDecl -> Maybe (InitOrFini, [CLabel])
-isInitOrFiniArray (CmmData sect (CmmStaticsRaw _ lits))
- | Just initOrFini <- isInitOrFiniSection sect
+isInitOrFiniArray (CmmData (Section t _) (CmmStaticsRaw _ lits))
+ | Just initOrFini <- isInitOrFiniSection t
= Just (initOrFini, map get_label lits)
where
get_label :: CmmStatic -> CLabel
@@ -72,7 +73,7 @@ isInitOrFiniArray (CmmData sect (CmmStaticsRaw _ lits))
get_label static = pprPanic "isInitOrFiniArray: invalid entry" (ppr static)
isInitOrFiniArray _ = Nothing
-isInitOrFiniSection :: Section -> Maybe InitOrFini
-isInitOrFiniSection (Section InitArray _) = Just IsInitArray
-isInitOrFiniSection (Section FiniArray _) = Just IsFiniArray
+isInitOrFiniSection :: SectionType -> Maybe InitOrFini
+isInitOrFiniSection InitArray = Just IsInitArray
+isInitOrFiniSection FiniArray = Just IsFiniArray
isInitOrFiniSection _ = Nothing
=====================================
compiler/GHC/CmmToAsm/Ppr.hs
=====================================
@@ -1,4 +1,5 @@
{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE MultiWayIf #-}
-----------------------------------------------------------------------------
--
@@ -23,6 +24,7 @@ import GHC.Prelude
import GHC.Utils.Asm
import GHC.Cmm.CLabel
+import GHC.Cmm.InitFini
import GHC.Cmm
import GHC.CmmToAsm.Config
import GHC.Utils.Outputable as SDoc
@@ -240,21 +242,45 @@ pprGNUSectionHeader config t suffix =
| OSMinGW32 <- platformOS platform
-> text ".rdata"
| otherwise -> text ".ipe"
- flags = case t of
- Text
- | OSMinGW32 <- platformOS platform, splitSections
- -> text ",\"xr\""
- | splitSections
- -> text ",\"ax\"," <> sectionType platform "progbits"
- CString
- | OSMinGW32 <- platformOS platform
- -> empty
- | otherwise -> text ",\"aMS\"," <> sectionType platform "progbits" <> text ",1"
- IPE
- | OSMinGW32 <- platformOS platform
- -> empty
- | otherwise -> text ",\"a\"," <> sectionType platform "progbits"
- _ -> empty
+ flags
+ -- See
+ -- https://github.com/llvm/llvm-project/blob/llvmorg-21.1.8/lld/COFF/Chunks.cp…
+ -- and https://llvm.org/docs/Extensions.html#section-directive.
+ -- LLD COFF backend gc-sections only work on COMDAT sections so
+ -- we need to mark it as a COMDAT section. You can use clang64
+ -- toolchain to compile small examples with
+ -- `-ffunction-sections -fdata-sections -S` to see these section
+ -- headers in the wild.
+ | OSMinGW32 <- platformOS platform,
+ splitSections =
+ if
+ | Just _ <- isInitOrFiniSection t -> text ",\"dw\""
+ | otherwise ->
+ let coff_section_flags
+ | Text <- t = "xr"
+ | UninitialisedData <- t = "bw"
+ | ReadWriteSection <- sectionProtection t = "dw"
+ | otherwise = "dr"
+ in hcat
+ [ text ",\"",
+ text coff_section_flags,
+ text "\",one_only,",
+ pprAsmLabel platform suffix
+ ]
+ | otherwise =
+ case t of
+ Text
+ | splitSections
+ -> text ",\"ax\"," <> sectionType platform "progbits"
+ CString
+ | OSMinGW32 <- platformOS platform
+ -> empty
+ | otherwise -> text ",\"aMS\"," <> sectionType platform "progbits" <> text ",1"
+ IPE
+ | OSMinGW32 <- platformOS platform
+ -> empty
+ | otherwise -> text ",\"a\"," <> sectionType platform "progbits"
+ _ -> empty
{-# SPECIALIZE pprGNUSectionHeader :: NCGConfig -> SectionType -> CLabel -> SDoc #-}
{-# SPECIALIZE pprGNUSectionHeader :: NCGConfig -> SectionType -> CLabel -> HLine #-} -- see Note [SPECIALIZE to HDoc] in GHC.Utils.Outputable
=====================================
compiler/GHC/CmmToAsm/Wasm/FromCmm.hs
=====================================
@@ -107,7 +107,7 @@ symKindFromCLabel lbl
-- | Calculate a data section's kind, see haddock docs of
-- 'DataSectionKind' for more explanation.
dataSectionKindFromCmmSection :: Section -> DataSectionKind
-dataSectionKindFromCmmSection s = case sectionProtection s of
+dataSectionKindFromCmmSection (Section t _) = case sectionProtection t of
ReadWriteSection -> SectionData
_ -> SectionROData
=====================================
compiler/GHC/CmmToC.hs
=====================================
@@ -121,7 +121,7 @@ pprTop platform = \case
pprDataExterns platform lits $$
pprWordArray platform (isSecConstant section) lbl lits
where
- isSecConstant section = case sectionProtection section of
+ isSecConstant (Section t _) = case sectionProtection t of
ReadOnlySection -> True
WriteProtectedSection -> True
_ -> False
=====================================
compiler/GHC/CmmToLlvm/Data.hs
=====================================
@@ -75,7 +75,7 @@ genLlvmData (sect, statics)
IsFiniArray -> fsLit "llvm.global_dtors"
in genGlobalLabelArray var clbls
-genLlvmData (sec, CmmStaticsRaw lbl xs) = do
+genLlvmData (sec@(Section t _), CmmStaticsRaw lbl xs) = do
label <- strCLabel_llvm lbl
static <- mapM genData xs
lmsec <- llvmSection sec
@@ -92,7 +92,7 @@ genLlvmData (sec, CmmStaticsRaw lbl xs) = do
then Just 2 else Just 1
Section Data _ -> Just $ platformWordSizeInBytes platform
_ -> Nothing
- const = if sectionProtection sec == ReadOnlySection
+ const = if sectionProtection t == ReadOnlySection
then Constant else Global
varDef = LMGlobalVar label tyAlias link lmsec align const
globDef = LMGlobal varDef struct
=====================================
libraries/ghc-internal/src/GHC/Internal/Control/Monad.hs
=====================================
@@ -314,7 +314,7 @@ Core: https://gitlab.haskell.org/ghc/ghc/issues/11795#note_118976
-- | @'replicateM' n act@ performs the action @act@ @n@ times,
-- and then returns the list of results.
--
--- @replicateM n (pure x) == 'replicate' n x@
+-- @replicateM n (pure x) == pure ('replicate' n x)@
--
-- ==== __Examples__
--
=====================================
libraries/ghc-internal/src/GHC/Internal/Exception/Context.hs
=====================================
@@ -64,7 +64,7 @@ instance Monoid ExceptionContext where
emptyExceptionContext :: ExceptionContext
emptyExceptionContext = ExceptionContext []
--- | Construct a singleton 'ExceptionContext' from an 'ExceptionAnnotation'.
+-- | Add an 'ExceptionAnnotation' to a given 'ExceptionContext'.
--
-- @since base-4.20.0.0
addExceptionAnnotation :: ExceptionAnnotation a => a -> ExceptionContext -> ExceptionContext
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/dc022bcb1aba9a5d67adaca8f0af24…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/dc022bcb1aba9a5d67adaca8f0af24…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/spj-try-opt-coercion] Add a type signature
by Simon Peyton Jones (@simonpj) 05 Jan '26
by Simon Peyton Jones (@simonpj) 05 Jan '26
05 Jan '26
Simon Peyton Jones pushed to branch wip/spj-try-opt-coercion at Glasgow Haskell Compiler / GHC
Commits:
cd277d10 by Simon Peyton Jones at 2026-01-05T09:36:53+00:00
Add a type signature
- - - - -
1 changed file:
- compiler/GHC/Core/FVs.hs
Changes:
=====================================
compiler/GHC/Core/FVs.hs
=====================================
@@ -647,6 +647,7 @@ idUnfoldingFVs id = stableUnfoldingFVs (realIdUnfolding id) `orElse` emptyFV
stableUnfoldingVars :: Unfolding -> Maybe VarSet
stableUnfoldingVars unf = fvVarSet `fmap` stableUnfoldingFVs unf
+stableUnfoldingFVs :: Unfolding -> Maybe FV
stableUnfoldingFVs unf
| isStableUnfolding unf = Just (unfoldingFVs unf)
| otherwise = Nothing
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/cd277d10a8723332d38165a04d48669…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/cd277d10a8723332d38165a04d48669…
You're receiving this email because of your account on gitlab.haskell.org.
1
0