[Git][ghc/ghc][wip/bytecode-library-combined] 15 commits: Preserve user-written kinds in data declarations
by Matthew Pickering (@mpickering) 11 Nov '25
by Matthew Pickering (@mpickering) 11 Nov '25
11 Nov '25
Matthew Pickering pushed to branch wip/bytecode-library-combined at Glasgow Haskell Compiler / GHC
Commits:
3c2f4bb4 by sheaf at 2025-11-11T11:47:28-05:00
Preserve user-written kinds in data declarations
This commit ensures that we preserve the user-written kind for data
declarations, e.g. in
type T2T = Type -> Type
type D :: T2T
data D a where { .. }
that we preserve the user-written kind of D as 'T2T', instead of
expanding the type synonym 'T2T' during kind checking.
We do this by storing 'tyConKind' separately from 'tyConResKind'. This
means that 'tyConKind' is not necessarily equal to
'mkTyConKind binders res_kind', as e.g. in the above example the former
is 'T2T' while the latter is 'Type -> Type'.
This is explained in Note [Preserve user-written TyCon kind] in GHC.Core.TyCon.
This is particularly important for Haddock, as the kinds stored in
interface files affect the generated documentation, and we want to
preserve the user-written types as much as possible.
- - - - -
19859584 by sheaf at 2025-11-11T11:47:28-05:00
Store user-written datacon tvs in interface files
This commit ensures we store the user-written quantified type variables
of data constructors in interface files, e.g. in
data D a where
MkD1 :: forall x. x -> D x
MkD2 :: forall u v. u -> v -> D v
The previous behaviour was to rename the universal variables to match
the universal variables of the data constructor. This was undesirable
because the names that end up in interface files end up mattering for
generated Haddock documentation; it's better to preserve the user-written
type variables.
Moreover, the universal variables may not have been user-written at all,
e.g. in an example such as:
type T2T = Type -> Type
data G :: T2T where
MkG :: forall x. D x
Here GHC will invent the type variable name 'a' for the first binder of
the TyCon G. We really don't want to then rename the user-written 'x'
into the generated 'a'.
- - - - -
034b2056 by sheaf at 2025-11-11T11:47:28-05:00
DataCon univ_tvs names: pick TyCon over inferred
This commit changes how we compute the names of universal type variables
in GADT data constructors. This augments the existing logic that chose
which type variable name to use, in GHC.Tc.TyCl.mkGADTVars. We continue
to prefer DataCon tv names for user-written binders, but we now prefer
TyCon tv names for inferred (non-user-written) DataCon binders.
This makes a difference in examples such as:
type (:~~:) :: k1 -> k2 -> Type
data a :~~: b where
HRefl :: a :~~: a
Before this patch, we ended up giving HRefl the type:
forall {k2}. forall (a :: k2). a :~~: a
whereas we now give it the type:
forall {k1}. forall (a :: k1). a :~~: a
The important part isn't really 'k1' or 'k2', but more that the inferred
type variable names of the DataCon can be arbitrary/unpredictable (as
they are chosen by GHC and depend on how unification proceeds), so it's
much better to use the more predictable TyCon type variable names.
- - - - -
95078d00 by sheaf at 2025-11-11T11:47:28-05:00
Backpack Rename: use explicit record construction
This commit updates the Backpack boilerplate in GHC.Iface.Rename to
use explicit record construction rather than record update. This makes
sure that the code stays up to date when the underlying constructors
change (e.g. new fields are added). The rationale is further explained
in Note [Prefer explicit record construction].
- - - - -
2bf36263 by sheaf at 2025-11-11T11:47:28-05:00
Store # eta binders in TyCon and use for Haddock
This commit stores the number of TyCon binders that were introduced by
eta-expansion (by the function GHC.Tc.Gen.HsType.splitTyConKind).
This is then used to pretty-print the TyCon as the user wrote it, e.g.
for
type Effect :: (Type -> Type) -> Type -> Type
data State s :: Effect where {..} -- arity 3
GHC will eta-expand the data declaration to
data State s a b where {..}
but also store in the 'TyCon' that the number of binders introduced by
this eta expansion is 2. This allows us, in
'Haddock.Convert.synifyTyConKindSig', to recover the original user-written
syntax, preserving the user's intent in Haddock documentation.
See Note [Inline kind signatures with GADTSyntax] in Haddock.Convert.
- - - - -
6c91582f by Matthew Pickering at 2025-11-11T11:48:12-05:00
driver: Properly handle errors during LinkNode steps
Previously we were not properly catching errors during the LinkNode step
(see T9930fail test).
This is fixed by wrapping the `LinkNode` action in `wrapAction`, the
same handler which is used for module compilation.
Fixes #26496
- - - - -
e1e1eb32 by Matthew Pickering at 2025-11-11T11:48:54-05:00
driver: Remove unecessary call to hscInsertHPT
This call was left-over from e9445c013fbccf9318739ca3d095a3e0a2e1be8a
If you follow the functions which call `upsweep_mod`, they immediately
add the interface to the HomePackageTable when `upsweep_mod` returns.
- - - - -
b22777d4 by ARATA Mizuki at 2025-11-11T11:49:44-05:00
LLVM backend: Pass the +evex512 attribute to LLVM 18+ if -mavx512f is set
The newer LLVM requires the +evex512 attribute to enable use of ZMM registers.
LLVM exhibits a backward-compatible behavior if the cpu is `x86-64`, but not if `penryn`.
Therefore, on macOS, where the cpu is set to `penryn`, we need to explicitly pass +evex512.
Fixes #26410
- - - - -
6ead7d06 by Vladislav Zavialov at 2025-11-11T11:50:26-05:00
Comments only in GHC.Parser.PostProcess.Haddock
Remove outdated Note [Register keyword location], as the issue it describes
was addressed by commit 05eb50dff2fcc78d025e77b9418ddb369db49b9f.
- - - - -
43fa8be8 by sheaf at 2025-11-11T11:51:18-05:00
localRegistersConflict: account for assignment LHS
This commit fixes a serious oversight in GHC.Cmm.Sink.conflicts,
specifically the code that computes which local registers conflict
between an assignment and a Cmm statement.
If we have:
assignment: <local_reg> = <expr>
node: <local_reg> = <other_expr>
then clearly the two conflict, because we cannot move one statement past
the other, as they assign two different values to the same local
register. (Recall that 'conflicts (local_reg,expr) node' is False if and
only if the assignment 'local_reg = expr' can be safely commuted past
the statement 'node'.)
The fix is to update 'GHC.Cmm.Sink.localRegistersConflict' to take into
account the following two situations:
(1) 'node' defines the LHS local register of the assignment,
(2) 'node' defines a local register used in the RHS of the assignment.
The bug is precisely that we were previously missing condition (1).
Fixes #26550
- - - - -
79dfcfe0 by sheaf at 2025-11-11T11:51:18-05:00
Update assigned register format when spilling
When we come to spilling a register to put new data into it, in
GHC.CmmToAsm.Reg.Linear.allocRegsAndSpill_spill, we need to:
1. Spill the data currently in the register. That is, do a spill
with a format that matches what's currently in the register.
2. Update the register assignment, allocating a virtual register to
this real register, but crucially **updating the format** of this
assignment.
Due to shadowing in the Haskell code for allocRegsAndSpill_spill, we
were mistakenly re-using the old format. This could lead to a situation
where:
a. We were using xmm6 to store a Double#.
b. We want to store a DoubleX2# into xmm6, so we spill the current
content of xmm6 to the stack using a scalar move (correct).
c. We update the register assignment, but we fail to update the format
of the assignment, so we continue to think that xmm6 stores a
Double# and not a DoubleX2#.
d. Later on, we need to spill xmm6 because it is getting clobbered by
another instruction. We then decide to only spill the lower 64 bits
of the register, because we still think that xmm6 only stores a
Double# and not a DoubleX2#.
Fixes #26542
- - - - -
aada5db9 by ARATA Mizuki at 2025-11-11T11:52:07-05:00
Fix the order of spill/reload instructions
The AArch64 NCG could emit multiple instructions for a single spill/reload,
but their order was not consistent between the definition and a use.
Fixes #26537
Co-authored-by: sheaf <sam.derbyshire(a)gmail.com>
- - - - -
64ec82ff by Andreas Klebinger at 2025-11-11T11:52:48-05:00
Add hpc to release script
- - - - -
531c32e3 by Matthew Pickering at 2025-11-11T17:39:10+00:00
Add support for building bytecode libraries
A bytecode library is a collection of bytecode files (.gbc) and a
library which combines together additional object files.
A bytecode library is created by invoking GHC with the `-bytecodelib`
flag.
A library can be created from in-memory `ModuleByteCode` linkables or
by passing `.gbc` files as arguments on the command line.
Fixes #26298
- - - - -
5dac1719 by Matthew Pickering at 2025-11-11T17:39:10+00:00
Load bytecode libraries to satisfy package dependencies
This commit allows you to use a bytecode library to satisfy a package
dependency when using the interpreter.
If a user enables `-fprefer-byte-code`, then if a package provides a
bytecode library, that will be loaded and used to satisfy the
dependency.
The main change is to separate the relevant parts of the `LoaderState`
into external and home package byte code. Bytecode is loaded into either
the home package or external part (similar to HPT/EPS split), HPT
bytecode can be unloaded. External bytecode is never unloaded.
The unload function has also only been called with an empty list of
"stable linkables" for a long time. It has been modified to directly
implement a complete unloading of the home package bytecode linkables.
At the moment, the bytecode libraries are found in the "library-dirs"
field from the package description. In the future when `Cabal`
implements support for "bytecode-library-dirs" field, we can read the
bytecode libraries from there. No changes to the Cabal submodule are
necessary at the moment.
Four new tests are added in testsuite/tests/cabal, which generate fake
package descriptions and test loading the libraries into GHCi.
Fixes #26298
- - - - -
123 changed files:
- .gitlab/rel_eng/upload_ghc_libs.py
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/Types/Literals.hs
- compiler/GHC/ByteCode/Linker.hs
- compiler/GHC/ByteCode/Serialize.hs
- compiler/GHC/Cmm/Sink.hs
- compiler/GHC/CmmToAsm/Reg/Linear.hs
- compiler/GHC/CmmToAsm/Reg/Liveness.hs
- compiler/GHC/Core/TyCon.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Driver/Downsweep.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Errors/Ppr.hs
- compiler/GHC/Driver/Errors/Types.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Phases.hs
- compiler/GHC/Driver/Pipeline.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Iface/Decl.hs
- compiler/GHC/Iface/Rename.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/IfaceToCore.hs
- + compiler/GHC/Linker/ByteCode.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Linker/Types.hs
- compiler/GHC/Parser/PostProcess/Haddock.hs
- compiler/GHC/Runtime/Debugger.hs
- compiler/GHC/Runtime/Eval.hs
- compiler/GHC/Settings.hs
- compiler/GHC/Tc/Gen/HsType.hs
- compiler/GHC/Tc/TyCl.hs
- compiler/GHC/Tc/TyCl/Build.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/GHC/Types/Error/Codes.hs
- compiler/GHC/Unit/Home/PackageTable.hs
- compiler/GHC/Unit/Info.hs
- compiler/GHC/Unit/State.hs
- compiler/ghc.cabal.in
- docs/users_guide/phases.rst
- libraries/ghc-boot/GHC/Unit/Database.hs
- testsuite/config/ghc
- testsuite/mk/boilerplate.mk
- testsuite/tests/backpack/should_fail/T19244a.stderr
- + testsuite/tests/cabal/Bytecode.hs
- + testsuite/tests/cabal/BytecodeForeign.c
- + testsuite/tests/cabal/BytecodeForeign.hs
- testsuite/tests/cabal/Makefile
- testsuite/tests/cabal/all.T
- + testsuite/tests/cabal/bytecode.pkg
- + testsuite/tests/cabal/bytecode.script
- + testsuite/tests/cabal/bytecode_foreign.pkg
- + testsuite/tests/cabal/bytecode_foreign.script
- testsuite/tests/cabal/ghcpkg03.stderr
- testsuite/tests/cabal/ghcpkg05.stderr
- + testsuite/tests/cabal/pkg_bytecode.stdout
- + testsuite/tests/cabal/pkg_bytecode_foreign.stdout
- + testsuite/tests/cabal/pkg_bytecode_with_gbc.stderr
- + testsuite/tests/cabal/pkg_bytecode_with_gbc.stdout
- + testsuite/tests/cabal/pkg_bytecode_with_o.stdout
- + testsuite/tests/codeGen/should_run/T26537.hs
- + testsuite/tests/codeGen/should_run/T26537.stdout
- testsuite/tests/codeGen/should_run/all.T
- testsuite/tests/dependent/should_fail/T11334b.stderr
- testsuite/tests/driver/bytecode-object/Makefile
- testsuite/tests/driver/bytecode-object/all.T
- testsuite/tests/driver/bytecode-object/bytecode_object19.stdout
- + testsuite/tests/driver/bytecode-object/bytecode_object20.stdout
- + testsuite/tests/driver/bytecode-object/bytecode_object21.stderr
- + testsuite/tests/driver/bytecode-object/bytecode_object21.stdout
- + testsuite/tests/driver/bytecode-object/bytecode_object23.stdout
- + testsuite/tests/driver/bytecode-object/bytecode_object24.stdout
- testsuite/tests/generics/T10604/T10604_deriving.stderr
- testsuite/tests/ghc-e/should_fail/T9930fail.stderr
- testsuite/tests/ghc-e/should_fail/all.T
- testsuite/tests/ghci.debugger/scripts/print012.stdout
- testsuite/tests/ghci/scripts/T10321.stdout
- testsuite/tests/ghci/scripts/T24459.stdout
- testsuite/tests/ghci/scripts/T7730.stdout
- testsuite/tests/ghci/scripts/ghci065.stdout
- testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.hs
- testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr
- testsuite/tests/interface-stability/base-exports.stdout
- testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
- testsuite/tests/interface-stability/base-exports.stdout-mingw32
- testsuite/tests/interface-stability/base-exports.stdout-ws-32
- testsuite/tests/rename/should_fail/rnfail055.stderr
- testsuite/tests/saks/should_compile/saks023.stdout
- testsuite/tests/saks/should_compile/saks034.stdout
- testsuite/tests/saks/should_compile/saks035.stdout
- testsuite/tests/showIface/Makefile
- + testsuite/tests/showIface/T26246a.hs
- + testsuite/tests/showIface/T26246a.stdout
- testsuite/tests/showIface/all.T
- + testsuite/tests/simd/should_run/T26410_ffi.hs
- + testsuite/tests/simd/should_run/T26410_ffi.stdout
- + testsuite/tests/simd/should_run/T26410_ffi_c.c
- + testsuite/tests/simd/should_run/T26410_prim.hs
- + testsuite/tests/simd/should_run/T26410_prim.stdout
- + testsuite/tests/simd/should_run/T26542.hs
- + testsuite/tests/simd/should_run/T26542.stdout
- + testsuite/tests/simd/should_run/T26550.hs
- + testsuite/tests/simd/should_run/T26550.stdout
- testsuite/tests/simd/should_run/all.T
- testsuite/tests/typecheck/T16127/T16127.stderr
- testsuite/tests/typecheck/should_compile/T22560d.stdout
- testsuite/tests/typecheck/should_fail/T15629.stderr
- utils/ghc-pkg/Main.hs
- utils/haddock/haddock-api/src/Haddock/Convert.hs
- utils/haddock/html-test/ref/Bug1004.html
- utils/haddock/html-test/ref/Bug1050.html
- + utils/haddock/html-test/ref/Bug26246.html
- utils/haddock/html-test/ref/Bug85.html
- utils/haddock/html-test/ref/Bug923.html
- utils/haddock/html-test/ref/BundledPatterns.html
- utils/haddock/html-test/ref/BundledPatterns2.html
- utils/haddock/html-test/ref/ConstructorPatternExport.html
- utils/haddock/html-test/ref/GADTRecords.html
- utils/haddock/html-test/ref/LinearTypes.html
- utils/haddock/html-test/ref/PromotedTypes.html
- + utils/haddock/html-test/src/Bug26246.hs
- utils/haddock/latex-test/ref/LinearTypes/LinearTypes.tex
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/37ffcd144c46e541ac2581b0fdc7f8…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/37ffcd144c46e541ac2581b0fdc7f8…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 15 commits: Preserve user-written kinds in data declarations
by Marge Bot (@marge-bot) 11 Nov '25
by Marge Bot (@marge-bot) 11 Nov '25
11 Nov '25
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
3c2f4bb4 by sheaf at 2025-11-11T11:47:28-05:00
Preserve user-written kinds in data declarations
This commit ensures that we preserve the user-written kind for data
declarations, e.g. in
type T2T = Type -> Type
type D :: T2T
data D a where { .. }
that we preserve the user-written kind of D as 'T2T', instead of
expanding the type synonym 'T2T' during kind checking.
We do this by storing 'tyConKind' separately from 'tyConResKind'. This
means that 'tyConKind' is not necessarily equal to
'mkTyConKind binders res_kind', as e.g. in the above example the former
is 'T2T' while the latter is 'Type -> Type'.
This is explained in Note [Preserve user-written TyCon kind] in GHC.Core.TyCon.
This is particularly important for Haddock, as the kinds stored in
interface files affect the generated documentation, and we want to
preserve the user-written types as much as possible.
- - - - -
19859584 by sheaf at 2025-11-11T11:47:28-05:00
Store user-written datacon tvs in interface files
This commit ensures we store the user-written quantified type variables
of data constructors in interface files, e.g. in
data D a where
MkD1 :: forall x. x -> D x
MkD2 :: forall u v. u -> v -> D v
The previous behaviour was to rename the universal variables to match
the universal variables of the data constructor. This was undesirable
because the names that end up in interface files end up mattering for
generated Haddock documentation; it's better to preserve the user-written
type variables.
Moreover, the universal variables may not have been user-written at all,
e.g. in an example such as:
type T2T = Type -> Type
data G :: T2T where
MkG :: forall x. D x
Here GHC will invent the type variable name 'a' for the first binder of
the TyCon G. We really don't want to then rename the user-written 'x'
into the generated 'a'.
- - - - -
034b2056 by sheaf at 2025-11-11T11:47:28-05:00
DataCon univ_tvs names: pick TyCon over inferred
This commit changes how we compute the names of universal type variables
in GADT data constructors. This augments the existing logic that chose
which type variable name to use, in GHC.Tc.TyCl.mkGADTVars. We continue
to prefer DataCon tv names for user-written binders, but we now prefer
TyCon tv names for inferred (non-user-written) DataCon binders.
This makes a difference in examples such as:
type (:~~:) :: k1 -> k2 -> Type
data a :~~: b where
HRefl :: a :~~: a
Before this patch, we ended up giving HRefl the type:
forall {k2}. forall (a :: k2). a :~~: a
whereas we now give it the type:
forall {k1}. forall (a :: k1). a :~~: a
The important part isn't really 'k1' or 'k2', but more that the inferred
type variable names of the DataCon can be arbitrary/unpredictable (as
they are chosen by GHC and depend on how unification proceeds), so it's
much better to use the more predictable TyCon type variable names.
- - - - -
95078d00 by sheaf at 2025-11-11T11:47:28-05:00
Backpack Rename: use explicit record construction
This commit updates the Backpack boilerplate in GHC.Iface.Rename to
use explicit record construction rather than record update. This makes
sure that the code stays up to date when the underlying constructors
change (e.g. new fields are added). The rationale is further explained
in Note [Prefer explicit record construction].
- - - - -
2bf36263 by sheaf at 2025-11-11T11:47:28-05:00
Store # eta binders in TyCon and use for Haddock
This commit stores the number of TyCon binders that were introduced by
eta-expansion (by the function GHC.Tc.Gen.HsType.splitTyConKind).
This is then used to pretty-print the TyCon as the user wrote it, e.g.
for
type Effect :: (Type -> Type) -> Type -> Type
data State s :: Effect where {..} -- arity 3
GHC will eta-expand the data declaration to
data State s a b where {..}
but also store in the 'TyCon' that the number of binders introduced by
this eta expansion is 2. This allows us, in
'Haddock.Convert.synifyTyConKindSig', to recover the original user-written
syntax, preserving the user's intent in Haddock documentation.
See Note [Inline kind signatures with GADTSyntax] in Haddock.Convert.
- - - - -
6c91582f by Matthew Pickering at 2025-11-11T11:48:12-05:00
driver: Properly handle errors during LinkNode steps
Previously we were not properly catching errors during the LinkNode step
(see T9930fail test).
This is fixed by wrapping the `LinkNode` action in `wrapAction`, the
same handler which is used for module compilation.
Fixes #26496
- - - - -
e1e1eb32 by Matthew Pickering at 2025-11-11T11:48:54-05:00
driver: Remove unecessary call to hscInsertHPT
This call was left-over from e9445c013fbccf9318739ca3d095a3e0a2e1be8a
If you follow the functions which call `upsweep_mod`, they immediately
add the interface to the HomePackageTable when `upsweep_mod` returns.
- - - - -
b22777d4 by ARATA Mizuki at 2025-11-11T11:49:44-05:00
LLVM backend: Pass the +evex512 attribute to LLVM 18+ if -mavx512f is set
The newer LLVM requires the +evex512 attribute to enable use of ZMM registers.
LLVM exhibits a backward-compatible behavior if the cpu is `x86-64`, but not if `penryn`.
Therefore, on macOS, where the cpu is set to `penryn`, we need to explicitly pass +evex512.
Fixes #26410
- - - - -
6ead7d06 by Vladislav Zavialov at 2025-11-11T11:50:26-05:00
Comments only in GHC.Parser.PostProcess.Haddock
Remove outdated Note [Register keyword location], as the issue it describes
was addressed by commit 05eb50dff2fcc78d025e77b9418ddb369db49b9f.
- - - - -
43fa8be8 by sheaf at 2025-11-11T11:51:18-05:00
localRegistersConflict: account for assignment LHS
This commit fixes a serious oversight in GHC.Cmm.Sink.conflicts,
specifically the code that computes which local registers conflict
between an assignment and a Cmm statement.
If we have:
assignment: <local_reg> = <expr>
node: <local_reg> = <other_expr>
then clearly the two conflict, because we cannot move one statement past
the other, as they assign two different values to the same local
register. (Recall that 'conflicts (local_reg,expr) node' is False if and
only if the assignment 'local_reg = expr' can be safely commuted past
the statement 'node'.)
The fix is to update 'GHC.Cmm.Sink.localRegistersConflict' to take into
account the following two situations:
(1) 'node' defines the LHS local register of the assignment,
(2) 'node' defines a local register used in the RHS of the assignment.
The bug is precisely that we were previously missing condition (1).
Fixes #26550
- - - - -
79dfcfe0 by sheaf at 2025-11-11T11:51:18-05:00
Update assigned register format when spilling
When we come to spilling a register to put new data into it, in
GHC.CmmToAsm.Reg.Linear.allocRegsAndSpill_spill, we need to:
1. Spill the data currently in the register. That is, do a spill
with a format that matches what's currently in the register.
2. Update the register assignment, allocating a virtual register to
this real register, but crucially **updating the format** of this
assignment.
Due to shadowing in the Haskell code for allocRegsAndSpill_spill, we
were mistakenly re-using the old format. This could lead to a situation
where:
a. We were using xmm6 to store a Double#.
b. We want to store a DoubleX2# into xmm6, so we spill the current
content of xmm6 to the stack using a scalar move (correct).
c. We update the register assignment, but we fail to update the format
of the assignment, so we continue to think that xmm6 stores a
Double# and not a DoubleX2#.
d. Later on, we need to spill xmm6 because it is getting clobbered by
another instruction. We then decide to only spill the lower 64 bits
of the register, because we still think that xmm6 only stores a
Double# and not a DoubleX2#.
Fixes #26542
- - - - -
aada5db9 by ARATA Mizuki at 2025-11-11T11:52:07-05:00
Fix the order of spill/reload instructions
The AArch64 NCG could emit multiple instructions for a single spill/reload,
but their order was not consistent between the definition and a use.
Fixes #26537
Co-authored-by: sheaf <sam.derbyshire(a)gmail.com>
- - - - -
64ec82ff by Andreas Klebinger at 2025-11-11T11:52:48-05:00
Add hpc to release script
- - - - -
d4d67602 by Ben Gamari at 2025-11-11T12:25:10-05:00
template-haskell: Better describe getQ semantics
Clarify that the state is a type-indexed map, as suggested by #26484.
- - - - -
4c0b1209 by ARATA Mizuki at 2025-11-11T12:25:16-05:00
Fix incorrect markups in the User's Guide
* Correct markup for C--: "C-\-" in reST
* Fix internal links
* Fix code highlighting
* Fix inline code: Use ``code`` rather than `code`
* Remove extra backslashes
Fixes #16812
Co-authored-by: sheaf <sam.derbyshire(a)gmail.com>
- - - - -
108 changed files:
- .gitlab/rel_eng/upload_ghc_libs.py
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/Types/Literals.hs
- compiler/GHC/Cmm/Sink.hs
- compiler/GHC/CmmToAsm/Reg/Linear.hs
- compiler/GHC/CmmToAsm/Reg/Liveness.hs
- compiler/GHC/Core/TyCon.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Iface/Decl.hs
- compiler/GHC/Iface/Rename.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/IfaceToCore.hs
- compiler/GHC/Parser/PostProcess/Haddock.hs
- compiler/GHC/Tc/Gen/HsType.hs
- compiler/GHC/Tc/TyCl.hs
- compiler/GHC/Tc/TyCl/Build.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- docs/users_guide/bugs.rst
- docs/users_guide/debug-info.rst
- docs/users_guide/debugging.rst
- docs/users_guide/extending_ghc.rst
- docs/users_guide/exts/arrows.rst
- docs/users_guide/exts/derive_any_class.rst
- docs/users_guide/exts/deriving_extra.rst
- docs/users_guide/exts/deriving_inferred.rst
- docs/users_guide/exts/deriving_strategies.rst
- docs/users_guide/exts/gadt.rst
- docs/users_guide/exts/generics.rst
- docs/users_guide/exts/overloaded_labels.rst
- docs/users_guide/exts/overloaded_strings.rst
- docs/users_guide/exts/pattern_synonyms.rst
- docs/users_guide/exts/poly_kinds.rst
- docs/users_guide/exts/primitives.rst
- docs/users_guide/exts/rank_polymorphism.rst
- docs/users_guide/exts/rebindable_syntax.rst
- docs/users_guide/exts/required_type_arguments.rst
- docs/users_guide/exts/scoped_type_variables.rst
- docs/users_guide/exts/standalone_deriving.rst
- docs/users_guide/exts/template_haskell.rst
- docs/users_guide/exts/tuple_sections.rst
- docs/users_guide/exts/type_data.rst
- docs/users_guide/exts/type_defaulting.rst
- docs/users_guide/gone_wrong.rst
- docs/users_guide/hints.rst
- docs/users_guide/javascript.rst
- docs/users_guide/phases.rst
- docs/users_guide/profiling.rst
- docs/users_guide/separate_compilation.rst
- docs/users_guide/using.rst
- docs/users_guide/wasm.rst
- docs/users_guide/win32-dlls.rst
- libraries/ghc-internal/src/GHC/Internal/TH/Monad.hs
- testsuite/tests/backpack/should_fail/T19244a.stderr
- + testsuite/tests/codeGen/should_run/T26537.hs
- + testsuite/tests/codeGen/should_run/T26537.stdout
- testsuite/tests/codeGen/should_run/all.T
- testsuite/tests/dependent/should_fail/T11334b.stderr
- testsuite/tests/generics/T10604/T10604_deriving.stderr
- testsuite/tests/ghc-e/should_fail/T9930fail.stderr
- testsuite/tests/ghc-e/should_fail/all.T
- testsuite/tests/ghci.debugger/scripts/print012.stdout
- testsuite/tests/ghci/scripts/T10321.stdout
- testsuite/tests/ghci/scripts/T24459.stdout
- testsuite/tests/ghci/scripts/T7730.stdout
- testsuite/tests/ghci/scripts/ghci065.stdout
- testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.hs
- testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr
- testsuite/tests/interface-stability/base-exports.stdout
- testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
- testsuite/tests/interface-stability/base-exports.stdout-mingw32
- testsuite/tests/interface-stability/base-exports.stdout-ws-32
- testsuite/tests/rename/should_fail/rnfail055.stderr
- testsuite/tests/saks/should_compile/saks023.stdout
- testsuite/tests/saks/should_compile/saks034.stdout
- testsuite/tests/saks/should_compile/saks035.stdout
- testsuite/tests/showIface/Makefile
- + testsuite/tests/showIface/T26246a.hs
- + testsuite/tests/showIface/T26246a.stdout
- testsuite/tests/showIface/all.T
- + testsuite/tests/simd/should_run/T26410_ffi.hs
- + testsuite/tests/simd/should_run/T26410_ffi.stdout
- + testsuite/tests/simd/should_run/T26410_ffi_c.c
- + testsuite/tests/simd/should_run/T26410_prim.hs
- + testsuite/tests/simd/should_run/T26410_prim.stdout
- + testsuite/tests/simd/should_run/T26542.hs
- + testsuite/tests/simd/should_run/T26542.stdout
- + testsuite/tests/simd/should_run/T26550.hs
- + testsuite/tests/simd/should_run/T26550.stdout
- testsuite/tests/simd/should_run/all.T
- testsuite/tests/typecheck/T16127/T16127.stderr
- testsuite/tests/typecheck/should_compile/T22560d.stdout
- testsuite/tests/typecheck/should_fail/T15629.stderr
- utils/haddock/haddock-api/src/Haddock/Convert.hs
- utils/haddock/html-test/ref/Bug1004.html
- utils/haddock/html-test/ref/Bug1050.html
- + utils/haddock/html-test/ref/Bug26246.html
- utils/haddock/html-test/ref/Bug85.html
- utils/haddock/html-test/ref/Bug923.html
- utils/haddock/html-test/ref/BundledPatterns.html
- utils/haddock/html-test/ref/BundledPatterns2.html
- utils/haddock/html-test/ref/ConstructorPatternExport.html
- utils/haddock/html-test/ref/GADTRecords.html
- utils/haddock/html-test/ref/LinearTypes.html
- utils/haddock/html-test/ref/PromotedTypes.html
- + utils/haddock/html-test/src/Bug26246.hs
- utils/haddock/latex-test/ref/LinearTypes/LinearTypes.tex
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a6bbbcd54944fee7608a3c7d97482f…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a6bbbcd54944fee7608a3c7d97482f…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
64ec82ff by Andreas Klebinger at 2025-11-11T11:52:48-05:00
Add hpc to release script
- - - - -
1 changed file:
- .gitlab/rel_eng/upload_ghc_libs.py
Changes:
=====================================
.gitlab/rel_eng/upload_ghc_libs.py
=====================================
@@ -122,6 +122,7 @@ PACKAGES = {
Package('ghc-compact', Path("libraries/ghc-compact"), no_prep),
Package('ghc', Path("compiler"), prep_ghc),
Package('ghci', Path("libraries/ghci"), no_prep),
+ Package('hpc', Path("libraries/hpc"), no_prep),
]
}
# Dict[str, Package]
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/64ec82ffa7f48399e18fcec43051d2b…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/64ec82ffa7f48399e18fcec43051d2b…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][master] Fix the order of spill/reload instructions
by Marge Bot (@marge-bot) 11 Nov '25
by Marge Bot (@marge-bot) 11 Nov '25
11 Nov '25
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
aada5db9 by ARATA Mizuki at 2025-11-11T11:52:07-05:00
Fix the order of spill/reload instructions
The AArch64 NCG could emit multiple instructions for a single spill/reload,
but their order was not consistent between the definition and a use.
Fixes #26537
Co-authored-by: sheaf <sam.derbyshire(a)gmail.com>
- - - - -
4 changed files:
- compiler/GHC/CmmToAsm/Reg/Liveness.hs
- + testsuite/tests/codeGen/should_run/T26537.hs
- + testsuite/tests/codeGen/should_run/T26537.stdout
- testsuite/tests/codeGen/should_run/all.T
Changes:
=====================================
compiler/GHC/CmmToAsm/Reg/Liveness.hs
=====================================
@@ -48,6 +48,7 @@ import GHC.Cmm
import GHC.CmmToAsm.Reg.Target
import GHC.Data.Graph.Directed
+import GHC.Data.OrdList
import GHC.Utils.Monad
import GHC.Utils.Outputable
import GHC.Utils.Panic
@@ -562,30 +563,26 @@ stripLiveBlock config (BasicBlock i lis)
= BasicBlock i instrs'
where (instrs', _)
- = runState (spillNat [] lis) 0
+ = runState (spillNat nilOL lis) 0
- -- spillNat :: [instr] -> [LiveInstr instr] -> State Int [instr]
- spillNat :: Instruction instr => [instr] -> [LiveInstr instr] -> State Int [instr]
+ spillNat :: Instruction instr => OrdList instr -> [LiveInstr instr] -> State Int [instr]
spillNat acc []
- = return (reverse acc)
+ = return (fromOL acc)
- -- The SPILL/RELOAD cases do not appear to be exercised by our codegens
- --
spillNat acc (LiveInstr (SPILL reg slot) _ : instrs)
= do delta <- get
- spillNat (mkSpillInstr config reg delta slot ++ acc) instrs
+ spillNat (acc `appOL` toOL (mkSpillInstr config reg delta slot)) instrs
spillNat acc (LiveInstr (RELOAD slot reg) _ : instrs)
= do delta <- get
- spillNat (mkLoadInstr config reg delta slot ++ acc) instrs
+ spillNat (acc `appOL` toOL (mkLoadInstr config reg delta slot)) instrs
spillNat acc (LiveInstr (Instr instr) _ : instrs)
| Just i <- takeDeltaInstr instr
= do put i
spillNat acc instrs
-
- spillNat acc (LiveInstr (Instr instr) _ : instrs)
- = spillNat (instr : acc) instrs
+ | otherwise
+ = spillNat (acc `snocOL` instr) instrs
-- | Erase Delta instructions.
=====================================
testsuite/tests/codeGen/should_run/T26537.hs
=====================================
@@ -0,0 +1,72 @@
+{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE UnboxedTuples #-}
+import GHC.Exts
+
+type D8 = (# Double#, Double#, Double#, Double#, Double#, Double#, Double#, Double# #)
+type D64 = (# D8, D8, D8, D8, D8, D8, D8, D8 #)
+type D512 = (# D64, D64, D64, D64, D64, D64, D64, D64 #)
+
+unD# :: Double -> Double#
+unD# (D# x) = x
+
+mkD8 :: Double -> D8
+mkD8 x = (# unD# x, unD# (x + 1), unD# (x + 2), unD# (x + 3), unD# (x + 4), unD# (x + 5), unD# (x + 6), unD# (x + 7) #)
+{-# NOINLINE mkD8 #-}
+
+mkD64 :: Double -> D64
+mkD64 x = (# mkD8 x, mkD8 (x + 8), mkD8 (x + 16), mkD8 (x + 24), mkD8 (x + 32), mkD8 (x + 40), mkD8 (x + 48), mkD8 (x + 56) #)
+{-# NOINLINE mkD64 #-}
+
+mkD512 :: Double -> D512
+mkD512 x = (# mkD64 x, mkD64 (x + 64), mkD64 (x + 128), mkD64 (x + 192), mkD64 (x + 256), mkD64 (x + 320), mkD64 (x + 384), mkD64 (x + 448) #)
+{-# NOINLINE mkD512 #-}
+
+addD8 :: D8 -> D8 -> D8
+addD8 (# x0, x1, x2, x3, x4, x5, x6, x7 #) (# y0, y1, y2, y3, y4, y5, y6, y7 #) = (# x0 +## y0, x1 +## y1, x2 +## y2, x3 +## y3, x4 +## y4, x5 +## y5, x6 +## y6, x7 +## y7 #)
+{-# NOINLINE addD8 #-}
+
+addD64 :: D64 -> D64 -> D64
+addD64 (# x0, x1, x2, x3, x4, x5, x6, x7 #) (# y0, y1, y2, y3, y4, y5, y6, y7 #) = (# addD8 x0 y0, addD8 x1 y1, addD8 x2 y2, addD8 x3 y3, addD8 x4 y4, addD8 x5 y5, addD8 x6 y6, addD8 x7 y7 #)
+{-# NOINLINE addD64 #-}
+
+addD512 :: D512 -> D512 -> D512
+addD512 (# x0, x1, x2, x3, x4, x5, x6, x7 #) (# y0, y1, y2, y3, y4, y5, y6, y7 #) = (# addD64 x0 y0, addD64 x1 y1, addD64 x2 y2, addD64 x3 y3, addD64 x4 y4, addD64 x5 y5, addD64 x6 y6, addD64 x7 y7 #)
+{-# NOINLINE addD512 #-}
+
+toListD8 :: D8 -> [Double]
+toListD8 (# x0, x1, x2, x3, x4, x5, x6, x7 #) = [D# x0, D# x1, D# x2, D# x3, D# x4, D# x5, D# x6, D# x7]
+{-# NOINLINE toListD8 #-}
+
+toListD64 :: D64 -> [Double]
+toListD64 (# x0, x1, x2, x3, x4, x5, x6, x7 #) = concat [toListD8 x0, toListD8 x1, toListD8 x2, toListD8 x3, toListD8 x4, toListD8 x5, toListD8 x6, toListD8 x7]
+{-# NOINLINE toListD64 #-}
+
+toListD512 :: D512 -> [Double]
+toListD512 (# x0, x1, x2, x3, x4, x5, x6, x7 #) = concat [toListD64 x0, toListD64 x1, toListD64 x2, toListD64 x3, toListD64 x4, toListD64 x5, toListD64 x6, toListD64 x7]
+{-# NOINLINE toListD512 #-}
+
+data T = MkT D512 D64
+
+mkT :: Double -> T
+mkT x = MkT (mkD512 x) (mkD64 (x + 512))
+{-# NOINLINE mkT #-}
+
+addT :: T -> T -> T
+addT (MkT x0 x1) (MkT y0 y1) = MkT (addD512 x0 y0) (addD64 x1 y1)
+{-# NOINLINE addT #-}
+
+toListT :: T -> [Double]
+toListT (MkT x0 x1) = toListD512 x0 ++ toListD64 x1
+{-# NOINLINE toListT #-}
+
+main :: IO ()
+main = do
+ let n = 512 + 64
+ let !x = mkT 0
+ !y = mkT n
+ print $ toListT x
+ print $ toListT y
+ print $ toListT (addT x y)
+ print $ toListT x == [0..n-1]
+ print $ toListT y == [n..2*n-1]
+ print $ toListT (addT x y) == zipWith (+) [0..n-1] [n..2*n-1]
=====================================
testsuite/tests/codeGen/should_run/T26537.stdout
=====================================
@@ -0,0 +1,6 @@
+[0.0,1.0,2.0,3.0,4.0,5.0,6.0,7.0,8.0,9.0,10.0,11.0,12.0,13.0,14.0,15.0,16.0,17.0,18.0,19.0,20.0,21.0,22.0,23.0,24.0,25.0,26.0,27.0,28.0,29.0,30.0,31.0,32.0,33.0,34.0,35.0,36.0,37.0,38.0,39.0,40.0,41.0,42.0,43.0,44.0,45.0,46.0,47.0,48.0,49.0,50.0,51.0,52.0,53.0,54.0,55.0,56.0,57.0,58.0,59.0,60.0,61.0,62.0,63.0,64.0,65.0,66.0,67.0,68.0,69.0,70.0,71.0,72.0,73.0,74.0,75.0,76.0,77.0,78.0,79.0,80.0,81.0,82.0,83.0,84.0,85.0,86.0,87.0,88.0,89.0,90.0,91.0,92.0,93.0,94.0,95.0,96.0,97.0,98.0,99.0,100.0,101.0,102.0,103.0,104.0,105.0,106.0,107.0,108.0,109.0,110.0,111.0,112.0,113.0,114.0,115.0,116.0,117.0,118.0,119.0,120.0,121.0,122.0,123.0,124.0,125.0,126.0,127.0,128.0,129.0,130.0,131.0,132.0,133.0,134.0,135.0,136.0,137.0,138.0,139.0,140.0,141.0,142.0,143.0,144.0,145.0,146.0,147.0,148.0,149.0,150.0,151.0,152.0,153.0,154.0,155.0,156.0,157.0,158.0,159.0,160.0,161.0,162.0,163.0,164.0,165.0,166.0,167.0,168.0,169.0,170.0,171.0,172.0,173.0,174.0,175.0,176.0,177.0,178.0,179.0,180.0,181.0,182.0,183.0,184.0,185.0,186.0,187.0,188.0,189.0,190.0,191.0,192.0,193.0,194.0,195.0,196.0,197.0,198.0,199.0,200.0,201.0,202.0,203.0,204.0,205.0,206.0,207.0,208.0,209.0,210.0,211.0,212.0,213.0,214.0,215.0,216.0,217.0,218.0,219.0,220.0,221.0,222.0,223.0,224.0,225.0,226.0,227.0,228.0,229.0,230.0,231.0,232.0,233.0,234.0,235.0,236.0,237.0,238.0,239.0,240.0,241.0,242.0,243.0,244.0,245.0,246.0,247.0,248.0,249.0,250.0,251.0,252.0,253.0,254.0,255.0,256.0,257.0,258.0,259.0,260.0,261.0,262.0,263.0,264.0,265.0,266.0,267.0,268.0,269.0,270.0,271.0,272.0,273.0,274.0,275.0,276.0,277.0,278.0,279.0,280.0,281.0,282.0,283.0,284.0,285.0,286.0,287.0,288.0,289.0,290.0,291.0,292.0,293.0,294.0,295.0,296.0,297.0,298.0,299.0,300.0,301.0,302.0,303.0,304.0,305.0,306.0,307.0,308.0,309.0,310.0,311.0,312.0,313.0,314.0,315.0,316.0,317.0,318.0,319.0,320.0,321.0,322.0,323.0,324.0,325.0,326.0,327.0,328.0,329.0,330.0,331.0,332.0,333.0,334.0,335.0,336.0,337.0,338.0,339.0,340.0,341.0,342.0,343.0,344.0,345.0,346.0,347.0,348.0,349.0,350.0,351.0,352.0,353.0,354.0,355.0,356.0,357.0,358.0,359.0,360.0,361.0,362.0,363.0,364.0,365.0,366.0,367.0,368.0,369.0,370.0,371.0,372.0,373.0,374.0,375.0,376.0,377.0,378.0,379.0,380.0,381.0,382.0,383.0,384.0,385.0,386.0,387.0,388.0,389.0,390.0,391.0,392.0,393.0,394.0,395.0,396.0,397.0,398.0,399.0,400.0,401.0,402.0,403.0,404.0,405.0,406.0,407.0,408.0,409.0,410.0,411.0,412.0,413.0,414.0,415.0,416.0,417.0,418.0,419.0,420.0,421.0,422.0,423.0,424.0,425.0,426.0,427.0,428.0,429.0,430.0,431.0,432.0,433.0,434.0,435.0,436.0,437.0,438.0,439.0,440.0,441.0,442.0,443.0,444.0,445.0,446.0,447.0,448.0,449.0,450.0,451.0,452.0,453.0,454.0,455.0,456.0,457.0,458.0,459.0,460.0,461.0,462.0,463.0,464.0,465.0,466.0,467.0,468.0,469.0,470.0,471.0,472.0,473.0,474.0,475.0,476.0,477.0,478.0,479.0,480.0,481.0,482.0,483.0,484.0,485.0,486.0,487.0,488.0,489.0,490.0,491.0,492.0,493.0,494.0,495.0,496.0,497.0,498.0,499.0,500.0,501.0,502.0,503.0,504.0,505.0,506.0,507.0,508.0,509.0,510.0,511.0,512.0,513.0,514.0,515.0,516.0,517.0,518.0,519.0,520.0,521.0,522.0,523.0,524.0,525.0,526.0,527.0,528.0,529.0,530.0,531.0,532.0,533.0,534.0,535.0,536.0,537.0,538.0,539.0,540.0,541.0,542.0,543.0,544.0,545.0,546.0,547.0,548.0,549.0,550.0,551.0,552.0,553.0,554.0,555.0,556.0,557.0,558.0,559.0,560.0,561.0,562.0,563.0,564.0,565.0,566.0,567.0,568.0,569.0,570.0,571.0,572.0,573.0,574.0,575.0]
+[576.0,577.0,578.0,579.0,580.0,581.0,582.0,583.0,584.0,585.0,586.0,587.0,588.0,589.0,590.0,591.0,592.0,593.0,594.0,595.0,596.0,597.0,598.0,599.0,600.0,601.0,602.0,603.0,604.0,605.0,606.0,607.0,608.0,609.0,610.0,611.0,612.0,613.0,614.0,615.0,616.0,617.0,618.0,619.0,620.0,621.0,622.0,623.0,624.0,625.0,626.0,627.0,628.0,629.0,630.0,631.0,632.0,633.0,634.0,635.0,636.0,637.0,638.0,639.0,640.0,641.0,642.0,643.0,644.0,645.0,646.0,647.0,648.0,649.0,650.0,651.0,652.0,653.0,654.0,655.0,656.0,657.0,658.0,659.0,660.0,661.0,662.0,663.0,664.0,665.0,666.0,667.0,668.0,669.0,670.0,671.0,672.0,673.0,674.0,675.0,676.0,677.0,678.0,679.0,680.0,681.0,682.0,683.0,684.0,685.0,686.0,687.0,688.0,689.0,690.0,691.0,692.0,693.0,694.0,695.0,696.0,697.0,698.0,699.0,700.0,701.0,702.0,703.0,704.0,705.0,706.0,707.0,708.0,709.0,710.0,711.0,712.0,713.0,714.0,715.0,716.0,717.0,718.0,719.0,720.0,721.0,722.0,723.0,724.0,725.0,726.0,727.0,728.0,729.0,730.0,731.0,732.0,733.0,734.0,735.0,736.0,737.0,738.0,739.0,740.0,741.0,742.0,743.0,744.0,745.0,746.0,747.0,748.0,749.0,750.0,751.0,752.0,753.0,754.0,755.0,756.0,757.0,758.0,759.0,760.0,761.0,762.0,763.0,764.0,765.0,766.0,767.0,768.0,769.0,770.0,771.0,772.0,773.0,774.0,775.0,776.0,777.0,778.0,779.0,780.0,781.0,782.0,783.0,784.0,785.0,786.0,787.0,788.0,789.0,790.0,791.0,792.0,793.0,794.0,795.0,796.0,797.0,798.0,799.0,800.0,801.0,802.0,803.0,804.0,805.0,806.0,807.0,808.0,809.0,810.0,811.0,812.0,813.0,814.0,815.0,816.0,817.0,818.0,819.0,820.0,821.0,822.0,823.0,824.0,825.0,826.0,827.0,828.0,829.0,830.0,831.0,832.0,833.0,834.0,835.0,836.0,837.0,838.0,839.0,840.0,841.0,842.0,843.0,844.0,845.0,846.0,847.0,848.0,849.0,850.0,851.0,852.0,853.0,854.0,855.0,856.0,857.0,858.0,859.0,860.0,861.0,862.0,863.0,864.0,865.0,866.0,867.0,868.0,869.0,870.0,871.0,872.0,873.0,874.0,875.0,876.0,877.0,878.0,879.0,880.0,881.0,882.0,883.0,884.0,885.0,886.0,887.0,888.0,889.0,890.0,891.0,892.0,893.0,894.0,895.0,896.0,897.0,898.0,899.0,900.0,901.0,902.0,903.0,904.0,905.0,906.0,907.0,908.0,909.0,910.0,911.0,912.0,913.0,914.0,915.0,916.0,917.0,918.0,919.0,920.0,921.0,922.0,923.0,924.0,925.0,926.0,927.0,928.0,929.0,930.0,931.0,932.0,933.0,934.0,935.0,936.0,937.0,938.0,939.0,940.0,941.0,942.0,943.0,944.0,945.0,946.0,947.0,948.0,949.0,950.0,951.0,952.0,953.0,954.0,955.0,956.0,957.0,958.0,959.0,960.0,961.0,962.0,963.0,964.0,965.0,966.0,967.0,968.0,969.0,970.0,971.0,972.0,973.0,974.0,975.0,976.0,977.0,978.0,979.0,980.0,981.0,982.0,983.0,984.0,985.0,986.0,987.0,988.0,989.0,990.0,991.0,992.0,993.0,994.0,995.0,996.0,997.0,998.0,999.0,1000.0,1001.0,1002.0,1003.0,1004.0,1005.0,1006.0,1007.0,1008.0,1009.0,1010.0,1011.0,1012.0,1013.0,1014.0,1015.0,1016.0,1017.0,1018.0,1019.0,1020.0,1021.0,1022.0,1023.0,1024.0,1025.0,1026.0,1027.0,1028.0,1029.0,1030.0,1031.0,1032.0,1033.0,1034.0,1035.0,1036.0,1037.0,1038.0,1039.0,1040.0,1041.0,1042.0,1043.0,1044.0,1045.0,1046.0,1047.0,1048.0,1049.0,1050.0,1051.0,1052.0,1053.0,1054.0,1055.0,1056.0,1057.0,1058.0,1059.0,1060.0,1061.0,1062.0,1063.0,1064.0,1065.0,1066.0,1067.0,1068.0,1069.0,1070.0,1071.0,1072.0,1073.0,1074.0,1075.0,1076.0,1077.0,1078.0,1079.0,1080.0,1081.0,1082.0,1083.0,1084.0,1085.0,1086.0,1087.0,1088.0,1089.0,1090.0,1091.0,1092.0,1093.0,1094.0,1095.0,1096.0,1097.0,1098.0,1099.0,1100.0,1101.0,1102.0,1103.0,1104.0,1105.0,1106.0,1107.0,1108.0,1109.0,1110.0,1111.0,1112.0,1113.0,1114.0,1115.0,1116.0,1117.0,1118.0,1119.0,1120.0,1121.0,1122.0,1123.0,1124.0,1125.0,1126.0,1127.0,1128.0,1129.0,1130.0,1131.0,1132.0,1133.0,1134.0,1135.0,1136.0,1137.0,1138.0,1139.0,1140.0,1141.0,1142.0,1143.0,1144.0,1145.0,1146.0,1147.0,1148.0,1149.0,1150.0,1151.0]
+[576.0,578.0,580.0,582.0,584.0,586.0,588.0,590.0,592.0,594.0,596.0,598.0,600.0,602.0,604.0,606.0,608.0,610.0,612.0,614.0,616.0,618.0,620.0,622.0,624.0,626.0,628.0,630.0,632.0,634.0,636.0,638.0,640.0,642.0,644.0,646.0,648.0,650.0,652.0,654.0,656.0,658.0,660.0,662.0,664.0,666.0,668.0,670.0,672.0,674.0,676.0,678.0,680.0,682.0,684.0,686.0,688.0,690.0,692.0,694.0,696.0,698.0,700.0,702.0,704.0,706.0,708.0,710.0,712.0,714.0,716.0,718.0,720.0,722.0,724.0,726.0,728.0,730.0,732.0,734.0,736.0,738.0,740.0,742.0,744.0,746.0,748.0,750.0,752.0,754.0,756.0,758.0,760.0,762.0,764.0,766.0,768.0,770.0,772.0,774.0,776.0,778.0,780.0,782.0,784.0,786.0,788.0,790.0,792.0,794.0,796.0,798.0,800.0,802.0,804.0,806.0,808.0,810.0,812.0,814.0,816.0,818.0,820.0,822.0,824.0,826.0,828.0,830.0,832.0,834.0,836.0,838.0,840.0,842.0,844.0,846.0,848.0,850.0,852.0,854.0,856.0,858.0,860.0,862.0,864.0,866.0,868.0,870.0,872.0,874.0,876.0,878.0,880.0,882.0,884.0,886.0,888.0,890.0,892.0,894.0,896.0,898.0,900.0,902.0,904.0,906.0,908.0,910.0,912.0,914.0,916.0,918.0,920.0,922.0,924.0,926.0,928.0,930.0,932.0,934.0,936.0,938.0,940.0,942.0,944.0,946.0,948.0,950.0,952.0,954.0,956.0,958.0,960.0,962.0,964.0,966.0,968.0,970.0,972.0,974.0,976.0,978.0,980.0,982.0,984.0,986.0,988.0,990.0,992.0,994.0,996.0,998.0,1000.0,1002.0,1004.0,1006.0,1008.0,1010.0,1012.0,1014.0,1016.0,1018.0,1020.0,1022.0,1024.0,1026.0,1028.0,1030.0,1032.0,1034.0,1036.0,1038.0,1040.0,1042.0,1044.0,1046.0,1048.0,1050.0,1052.0,1054.0,1056.0,1058.0,1060.0,1062.0,1064.0,1066.0,1068.0,1070.0,1072.0,1074.0,1076.0,1078.0,1080.0,1082.0,1084.0,1086.0,1088.0,1090.0,1092.0,1094.0,1096.0,1098.0,1100.0,1102.0,1104.0,1106.0,1108.0,1110.0,1112.0,1114.0,1116.0,1118.0,1120.0,1122.0,1124.0,1126.0,1128.0,1130.0,1132.0,1134.0,1136.0,1138.0,1140.0,1142.0,1144.0,1146.0,1148.0,1150.0,1152.0,1154.0,1156.0,1158.0,1160.0,1162.0,1164.0,1166.0,1168.0,1170.0,1172.0,1174.0,1176.0,1178.0,1180.0,1182.0,1184.0,1186.0,1188.0,1190.0,1192.0,1194.0,1196.0,1198.0,1200.0,1202.0,1204.0,1206.0,1208.0,1210.0,1212.0,1214.0,1216.0,1218.0,1220.0,1222.0,1224.0,1226.0,1228.0,1230.0,1232.0,1234.0,1236.0,1238.0,1240.0,1242.0,1244.0,1246.0,1248.0,1250.0,1252.0,1254.0,1256.0,1258.0,1260.0,1262.0,1264.0,1266.0,1268.0,1270.0,1272.0,1274.0,1276.0,1278.0,1280.0,1282.0,1284.0,1286.0,1288.0,1290.0,1292.0,1294.0,1296.0,1298.0,1300.0,1302.0,1304.0,1306.0,1308.0,1310.0,1312.0,1314.0,1316.0,1318.0,1320.0,1322.0,1324.0,1326.0,1328.0,1330.0,1332.0,1334.0,1336.0,1338.0,1340.0,1342.0,1344.0,1346.0,1348.0,1350.0,1352.0,1354.0,1356.0,1358.0,1360.0,1362.0,1364.0,1366.0,1368.0,1370.0,1372.0,1374.0,1376.0,1378.0,1380.0,1382.0,1384.0,1386.0,1388.0,1390.0,1392.0,1394.0,1396.0,1398.0,1400.0,1402.0,1404.0,1406.0,1408.0,1410.0,1412.0,1414.0,1416.0,1418.0,1420.0,1422.0,1424.0,1426.0,1428.0,1430.0,1432.0,1434.0,1436.0,1438.0,1440.0,1442.0,1444.0,1446.0,1448.0,1450.0,1452.0,1454.0,1456.0,1458.0,1460.0,1462.0,1464.0,1466.0,1468.0,1470.0,1472.0,1474.0,1476.0,1478.0,1480.0,1482.0,1484.0,1486.0,1488.0,1490.0,1492.0,1494.0,1496.0,1498.0,1500.0,1502.0,1504.0,1506.0,1508.0,1510.0,1512.0,1514.0,1516.0,1518.0,1520.0,1522.0,1524.0,1526.0,1528.0,1530.0,1532.0,1534.0,1536.0,1538.0,1540.0,1542.0,1544.0,1546.0,1548.0,1550.0,1552.0,1554.0,1556.0,1558.0,1560.0,1562.0,1564.0,1566.0,1568.0,1570.0,1572.0,1574.0,1576.0,1578.0,1580.0,1582.0,1584.0,1586.0,1588.0,1590.0,1592.0,1594.0,1596.0,1598.0,1600.0,1602.0,1604.0,1606.0,1608.0,1610.0,1612.0,1614.0,1616.0,1618.0,1620.0,1622.0,1624.0,1626.0,1628.0,1630.0,1632.0,1634.0,1636.0,1638.0,1640.0,1642.0,1644.0,1646.0,1648.0,1650.0,1652.0,1654.0,1656.0,1658.0,1660.0,1662.0,1664.0,1666.0,1668.0,1670.0,1672.0,1674.0,1676.0,1678.0,1680.0,1682.0,1684.0,1686.0,1688.0,1690.0,1692.0,1694.0,1696.0,1698.0,1700.0,1702.0,1704.0,1706.0,1708.0,1710.0,1712.0,1714.0,1716.0,1718.0,1720.0,1722.0,1724.0,1726.0]
+True
+True
+True
=====================================
testsuite/tests/codeGen/should_run/all.T
=====================================
@@ -256,3 +256,4 @@ test('T24893', normal, compile_and_run, ['-O'])
test('CCallConv', [req_c], compile_and_run, ['CCallConv_c.c'])
test('T25364', normal, compile_and_run, [''])
test('T26061', normal, compile_and_run, [''])
+test('T26537', js_broken(26558), compile_and_run, ['-O2 -fregs-graph'])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/aada5db93a2f0fd00c0715ad9ca4f66…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/aada5db93a2f0fd00c0715ad9ca4f66…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][master] 2 commits: localRegistersConflict: account for assignment LHS
by Marge Bot (@marge-bot) 11 Nov '25
by Marge Bot (@marge-bot) 11 Nov '25
11 Nov '25
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
43fa8be8 by sheaf at 2025-11-11T11:51:18-05:00
localRegistersConflict: account for assignment LHS
This commit fixes a serious oversight in GHC.Cmm.Sink.conflicts,
specifically the code that computes which local registers conflict
between an assignment and a Cmm statement.
If we have:
assignment: <local_reg> = <expr>
node: <local_reg> = <other_expr>
then clearly the two conflict, because we cannot move one statement past
the other, as they assign two different values to the same local
register. (Recall that 'conflicts (local_reg,expr) node' is False if and
only if the assignment 'local_reg = expr' can be safely commuted past
the statement 'node'.)
The fix is to update 'GHC.Cmm.Sink.localRegistersConflict' to take into
account the following two situations:
(1) 'node' defines the LHS local register of the assignment,
(2) 'node' defines a local register used in the RHS of the assignment.
The bug is precisely that we were previously missing condition (1).
Fixes #26550
- - - - -
79dfcfe0 by sheaf at 2025-11-11T11:51:18-05:00
Update assigned register format when spilling
When we come to spilling a register to put new data into it, in
GHC.CmmToAsm.Reg.Linear.allocRegsAndSpill_spill, we need to:
1. Spill the data currently in the register. That is, do a spill
with a format that matches what's currently in the register.
2. Update the register assignment, allocating a virtual register to
this real register, but crucially **updating the format** of this
assignment.
Due to shadowing in the Haskell code for allocRegsAndSpill_spill, we
were mistakenly re-using the old format. This could lead to a situation
where:
a. We were using xmm6 to store a Double#.
b. We want to store a DoubleX2# into xmm6, so we spill the current
content of xmm6 to the stack using a scalar move (correct).
c. We update the register assignment, but we fail to update the format
of the assignment, so we continue to think that xmm6 stores a
Double# and not a DoubleX2#.
d. Later on, we need to spill xmm6 because it is getting clobbered by
another instruction. We then decide to only spill the lower 64 bits
of the register, because we still think that xmm6 only stores a
Double# and not a DoubleX2#.
Fixes #26542
- - - - -
7 changed files:
- compiler/GHC/Cmm/Sink.hs
- compiler/GHC/CmmToAsm/Reg/Linear.hs
- + testsuite/tests/simd/should_run/T26542.hs
- + testsuite/tests/simd/should_run/T26542.stdout
- + testsuite/tests/simd/should_run/T26550.hs
- + testsuite/tests/simd/should_run/T26550.stdout
- testsuite/tests/simd/should_run/all.T
Changes:
=====================================
compiler/GHC/Cmm/Sink.hs
=====================================
@@ -26,76 +26,74 @@ import Data.Maybe
import GHC.Exts (inline)
--- -----------------------------------------------------------------------------
--- Sinking and inlining
+--------------------------------------------------------------------------------
+{- Note [Sinking and inlining]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+Sinking is an optimisation pass that
+ (a) moves assignments closer to their uses, to reduce register pressure
+ (b) pushes assignments into a single branch of a conditional if possible
+ (c) inlines assignments to registers that are mentioned only once
+ (d) discards dead assignments
--- This is an optimisation pass that
--- (a) moves assignments closer to their uses, to reduce register pressure
--- (b) pushes assignments into a single branch of a conditional if possible
--- (c) inlines assignments to registers that are mentioned only once
--- (d) discards dead assignments
---
--- This tightens up lots of register-heavy code. It is particularly
--- helpful in the Cmm generated by the Stg->Cmm code generator, in
--- which every function starts with a copyIn sequence like:
---
--- x1 = R1
--- x2 = Sp[8]
--- x3 = Sp[16]
--- if (Sp - 32 < SpLim) then L1 else L2
---
--- we really want to push the x1..x3 assignments into the L2 branch.
---
--- Algorithm:
---
--- * Start by doing liveness analysis.
---
--- * Keep a list of assignments A; earlier ones may refer to later ones.
--- Currently we only sink assignments to local registers, because we don't
--- have liveness information about global registers.
---
--- * Walk forwards through the graph, look at each node N:
---
--- * If it is a dead assignment, i.e. assignment to a register that is
--- not used after N, discard it.
---
--- * Try to inline based on current list of assignments
--- * If any assignments in A (1) occur only once in N, and (2) are
--- not live after N, inline the assignment and remove it
--- from A.
---
--- * If an assignment in A is cheap (RHS is local register), then
--- inline the assignment and keep it in A in case it is used afterwards.
---
--- * Otherwise don't inline.
---
--- * If N is assignment to a local register pick up the assignment
--- and add it to A.
---
--- * If N is not an assignment to a local register:
--- * remove any assignments from A that conflict with N, and
--- place them before N in the current block. We call this
--- "dropping" the assignments.
---
--- * An assignment conflicts with N if it:
--- - assigns to a register mentioned in N
--- - mentions a register assigned by N
--- - reads from memory written by N
--- * do this recursively, dropping dependent assignments
---
--- * At an exit node:
--- * drop any assignments that are live on more than one successor
--- and are not trivial
--- * if any successor has more than one predecessor (a join-point),
--- drop everything live in that successor. Since we only propagate
--- assignments that are not dead at the successor, we will therefore
--- eliminate all assignments dead at this point. Thus analysis of a
--- join-point will always begin with an empty list of assignments.
---
---
--- As a result of above algorithm, sinking deletes some dead assignments
--- (transitively, even). This isn't as good as removeDeadAssignments,
--- but it's much cheaper.
+This tightens up lots of register-heavy code. It is particularly
+helpful in the Cmm generated by the Stg->Cmm code generator, in
+which every function starts with a copyIn sequence like:
+
+ x1 = R1
+ x2 = Sp[8]
+ x3 = Sp[16]
+ if (Sp - 32 < SpLim) then L1 else L2
+
+we really want to push the x1..x3 assignments into the L2 branch.
+
+Algorithm:
+
+ * Start by doing liveness analysis.
+
+ * Keep a list of assignments A; earlier ones may refer to later ones.
+ Currently we only sink assignments to local registers, because we don't
+ have liveness information about global registers.
+
+ * Walk forwards through the graph, look at each node N:
+
+ * If it is a dead assignment, i.e. assignment to a register that is
+ not used after N, discard it.
+
+ * Try to inline based on current list of assignments
+ * If any assignments in A (1) occur only once in N, and (2) are
+ not live after N, inline the assignment and remove it
+ from A.
+
+ * If an assignment in A is cheap (RHS is local register), then
+ inline the assignment and keep it in A in case it is used afterwards.
+
+ * Otherwise don't inline.
+
+ * If N is an assignment to a local register, pick up the assignment
+ and add it to A.
+
+ * If N is not an assignment to a local register:
+ * remove any assignments from A that conflict with N, and
+ place them before N in the current block. We call this
+ "dropping" the assignments.
+ (See Note [When does an assignment conflict?] for what it means for
+ A to conflict with N.)
+
+ * do this recursively, dropping dependent assignments
+
+ * At an exit node:
+ * drop any assignments that are live on more than one successor
+ and are not trivial
+ * if any successor has more than one predecessor (a join-point),
+ drop everything live in that successor. Since we only propagate
+ assignments that are not dead at the successor, we will therefore
+ eliminate all assignments dead at this point. Thus analysis of a
+ join-point will always begin with an empty list of assignments.
+
+As a result of above algorithm, sinking deletes some dead assignments
+(transitively, even). This isn't as good as removeDeadAssignments,
+but it's much cheaper.
+-}
-- -----------------------------------------------------------------------------
-- things that we aren't optimising very well yet.
@@ -648,110 +646,171 @@ okToInline _ _ _ = True
-- -----------------------------------------------------------------------------
+{- Note [When does an assignment conflict?]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+An assignment 'A' conflicts with a statement 'N' if any of the following
+conditions are satisfied:
+
+ (C1) 'A' assigns to a register mentioned in 'N'
+ (C2) 'A' mentions a register assigned by 'N'
+ (C3) 'A' reads from memory written by 'N'
+
+In such a situation, it is not safe to commute 'A' past 'N'. For example,
+it is not safe to commute
+
+ A: r = 1
+ N: s = r
+
+because 'r' may be undefined or hold a different value before 'A'.
+
+Remarks:
+
+ (C3) includes all foreign calls, as they may modify the heap/stack.
+
+ (C1) includes the following two situations:
+
+ (C1a) 'N' defines the LHS register in the assignment 'A', for example:
+
+ A: r = <expr>
+ N: r = <other_expr>
+
+ (C1b) 'N' defines a register used in the RHS of 'A', for example:
+
+ A: r = s
+ N: s = <expr>
+
+ (C1c) 'suspendThread' clobbers every global register not backed by a
+ real register, as noted in #19237.
+
+Forgetting (C1a) led to bug #26550, in which we incorrectly commuted
+
+ A: _c1rB::Fx2V128 = <0.0 :: W64, 0.0 :: W64>
+ N: _c1rB::Fx2V128 = %MO_VF_Insert_2_W64(<0.0 :: W64,0.0 :: W64>,%MO_F_Add_W64(F64[R1 + 7], 3.0 :: W64),0 :: W32)
+
+-}
+
-- | @conflicts (r,e) node@ is @False@ if and only if the assignment
-- @r = e@ can be safely commuted past statement @node@.
+--
+-- See Note [When does an assignment conflict?].
conflicts :: Platform -> Assignment -> CmmNode O x -> Bool
-conflicts platform (r, rhs, addr) node
+conflicts platform assig@(r, rhs, addr) node
- -- (1) node defines registers used by rhs of assignment. This catches
- -- assignments and all three kinds of calls. See Note [Sinking and calls]
- | globalRegistersConflict platform rhs node = True
- | localRegistersConflict platform rhs node = True
+ -- (C1) node defines registers that are either the assigned register or
+ -- are used by the rhs of the assignment.
+ -- This catches assignments and all three kinds of calls.
+ -- See Note [Sinking and calls]
+ | globalRegistersConflict platform rhs node = True
+ | localRegistersConflict platform assig node = True
- -- (2) node uses register defined by assignment
+ -- (C2) node uses register defined by assignment
| foldRegsUsed platform (\b r' -> r == r' || b) False node = True
- -- (3) a store to an address conflicts with a read of the same memory
+ -- (C3) Node writes to memory that is read by the assignment.
+
+ -- (a) a store to an address conflicts with a read of the same memory
| CmmStore addr' e _ <- node
, memConflicts addr (loadAddr platform addr' (cmmExprWidth platform e)) = True
- -- (4) an assignment to Hp/Sp conflicts with a heap/stack read respectively
- | HeapMem <- addr, CmmAssign (CmmGlobal (GlobalRegUse Hp _)) _ <- node = True
- | StackMem <- addr, CmmAssign (CmmGlobal (GlobalRegUse Sp _)) _ <- node = True
- | SpMem{} <- addr, CmmAssign (CmmGlobal (GlobalRegUse Sp _)) _ <- node = True
+ -- (b) an assignment to Hp/Sp conflicts with a heap/stack read respectively
+ | CmmAssign (CmmGlobal (GlobalRegUse Hp _)) _ <- node
+ , memConflicts addr HeapMem
+ = True
+ | CmmAssign (CmmGlobal (GlobalRegUse Sp _)) _ <- node
+ , memConflicts addr StackMem
+ = True
- -- (5) foreign calls clobber heap: see Note [Foreign calls clobber heap]
+ -- (c) foreign calls clobber heap: see Note [Foreign calls clobber heap]
| CmmUnsafeForeignCall{} <- node, memConflicts addr AnyMem = True
- -- (6) suspendThread clobbers every global register not backed by a real
- -- register. It also clobbers heap and stack but this is handled by (5)
+ -- (d) native calls clobber any memory
+ | CmmCall{} <- node, memConflicts addr AnyMem = True
+
+ -- (C1c) suspendThread clobbers every global register not backed by a real
+ -- register. (It also clobbers heap and stack, but this is handled by (C3)(c) above.)
| CmmUnsafeForeignCall (PrimTarget MO_SuspendThread) _ _ <- node
, foldRegsUsed platform (\b g -> globalRegMaybe platform g == Nothing || b) False rhs
= True
- -- (7) native calls clobber any memory
- | CmmCall{} <- node, memConflicts addr AnyMem = True
-
- -- (8) otherwise, no conflict
| otherwise = False
{- Note [Inlining foldRegsDefd]
- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~
- foldRegsDefd is, after optimization, *not* a small function so
- it's only marked INLINEABLE, but not INLINE.
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+foldRegsDefd is, after optimization, *not* a small function so
+it's only marked INLINEABLE, but not INLINE.
- However in some specific cases we call it *very* often making it
- important to avoid the overhead of allocating the folding function.
-
- So we simply force inlining via the magic inline function.
- For T3294 this improves allocation with -O by ~1%.
+However in some specific cases we call it *very* often making it
+important to avoid the overhead of allocating the folding function.
+So we simply force inlining via the magic inline function.
+For T3294 this improves allocation with -O by ~1%.
-}
--- Returns True if node defines any global registers that are used in the
--- Cmm expression
+-- | Returns @True@ if @node@ defines any global registers that are used in the
+-- Cmm expression.
+--
+-- See (C1) in Note [When does an assignment conflict?].
globalRegistersConflict :: Platform -> CmmExpr -> CmmNode e x -> Bool
globalRegistersConflict platform expr node =
-- See Note [Inlining foldRegsDefd]
inline foldRegsDefd platform (\b r -> b || globalRegUsedIn platform (globalRegUse_reg r) expr)
False node
+ -- NB: no need to worry about (C1a), as the LHS of an assignment is always
+ -- a local register, never a global register.
--- Returns True if node defines any local registers that are used in the
--- Cmm expression
-localRegistersConflict :: Platform -> CmmExpr -> CmmNode e x -> Bool
-localRegistersConflict platform expr node =
- -- See Note [Inlining foldRegsDefd]
- inline foldRegsDefd platform (\b r -> b || regUsedIn platform (CmmLocal r) expr)
- False node
-
--- Note [Sinking and calls]
--- ~~~~~~~~~~~~~~~~~~~~~~~~
--- We have three kinds of calls: normal (CmmCall), safe foreign (CmmForeignCall)
--- and unsafe foreign (CmmUnsafeForeignCall). We perform sinking pass after
--- stack layout (see Note [Sinking after stack layout]) which leads to two
--- invariants related to calls:
---
--- a) during stack layout phase all safe foreign calls are turned into
--- unsafe foreign calls (see Note [Lower safe foreign calls]). This
--- means that we will never encounter CmmForeignCall node when running
--- sinking after stack layout
---
--- b) stack layout saves all variables live across a call on the stack
--- just before making a call (remember we are not sinking assignments to
--- stack):
---
--- L1:
--- x = R1
--- P64[Sp - 16] = L2
--- P64[Sp - 8] = x
--- Sp = Sp - 16
--- call f() returns L2
--- L2:
---
--- We will attempt to sink { x = R1 } but we will detect conflict with
--- { P64[Sp - 8] = x } and hence we will drop { x = R1 } without even
--- checking whether it conflicts with { call f() }. In this way we will
--- never need to check any assignment conflicts with CmmCall. Remember
--- that we still need to check for potential memory conflicts.
---
--- So the result is that we only need to worry about CmmUnsafeForeignCall nodes
--- when checking conflicts (see Note [Unsafe foreign calls clobber caller-save registers]).
--- This assumption holds only when we do sinking after stack layout. If we run
--- it before stack layout we need to check for possible conflicts with all three
--- kinds of calls. Our `conflicts` function does that by using a generic
--- foldRegsDefd and foldRegsUsed functions defined in DefinerOfRegs and
--- UserOfRegs typeclasses.
+-- | Given an assignment @local_reg := expr@, return @True@ if @node@ defines any
+-- local registers mentioned in the assignment.
--
+-- See (C1) in Note [When does an assignment conflict?].
+localRegistersConflict :: Platform -> Assignment -> CmmNode e x -> Bool
+localRegistersConflict platform (r, expr, _) node =
+ -- See Note [Inlining foldRegsDefd]
+ inline foldRegsDefd platform
+ (\b r' ->
+ b
+ || r' == r -- (C1a)
+ || regUsedIn platform (CmmLocal r') expr -- (C1b)
+ )
+ False node
+
+{- Note [Sinking and calls]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~
+We have three kinds of calls: normal (CmmCall), safe foreign (CmmForeignCall)
+and unsafe foreign (CmmUnsafeForeignCall). We perform sinking pass after
+stack layout (see Note [Sinking after stack layout]) which leads to two
+invariants related to calls:
+
+ a) during stack layout phase all safe foreign calls are turned into
+ unsafe foreign calls (see Note [Lower safe foreign calls]). This
+ means that we will never encounter CmmForeignCall node when running
+ sinking after stack layout
+
+ b) stack layout saves all variables live across a call on the stack
+ just before making a call (remember we are not sinking assignments to
+ stack):
+
+ L1:
+ x = R1
+ P64[Sp - 16] = L2
+ P64[Sp - 8] = x
+ Sp = Sp - 16
+ call f() returns L2
+ L2:
+
+ We will attempt to sink { x = R1 } but we will detect conflict with
+ { P64[Sp - 8] = x } and hence we will drop { x = R1 } without even
+ checking whether it conflicts with { call f() }. In this way we will
+ never need to check any assignment conflicts with CmmCall. Remember
+ that we still need to check for potential memory conflicts.
+
+So the result is that we only need to worry about CmmUnsafeForeignCall nodes
+when checking conflicts (see Note [Unsafe foreign calls clobber caller-save registers]).
+This assumption holds only when we do sinking after stack layout. If we run
+it before stack layout we need to check for possible conflicts with all three
+kinds of calls. Our `conflicts` function does that by using a generic
+foldRegsDefd and foldRegsUsed functions defined in DefinerOfRegs and
+UserOfRegs typeclasses.
+-}
-- An abstraction of memory read or written.
data AbsMem
=====================================
compiler/GHC/CmmToAsm/Reg/Linear.hs
=====================================
@@ -504,8 +504,8 @@ genRaInsn block_live new_instrs block_id instr r_dying w_dying = do
platform <- getPlatform
case regUsageOfInstr platform instr of { RU read written ->
do
- let real_written = [ rr | RegWithFormat {regWithFormat_reg = RegReal rr} <- written ]
- let virt_written = [ VirtualRegWithFormat vr fmt | RegWithFormat (RegVirtual vr) fmt <- written ]
+ let real_written = [ rr | RegWithFormat {regWithFormat_reg = RegReal rr} <- written ]
+ let virt_written = [ VirtualRegWithFormat vr fmt | RegWithFormat (RegVirtual vr) fmt <- written ]
-- we don't need to do anything with real registers that are
-- only read by this instr. (the list is typically ~2 elements,
@@ -939,35 +939,39 @@ allocRegsAndSpill_spill reading keep spills alloc r@(VirtualRegWithFormat vr fmt
-- we have a temporary that is in both register and mem,
-- just free up its register for use.
- | (temp, (RealRegUsage my_reg _old_fmt), slot) : _ <- candidates_inBoth
- = do spills' <- loadTemp r spill_loc my_reg spills
+ | (temp, (RealRegUsage cand_reg _old_fmt), slot) : _ <- candidates_inBoth
+ = do spills' <- loadTemp r spill_loc cand_reg spills
let assig1 = addToUFM_Directly assig temp (InMem slot)
- let assig2 = addToUFM assig1 vr $! newLocation spill_loc (RealRegUsage my_reg fmt)
+ let assig2 = addToUFM assig1 vr $! newLocation spill_loc (RealRegUsage cand_reg fmt)
setAssigR $ toRegMap assig2
- allocateRegsAndSpill reading keep spills' (my_reg:alloc) rs
+ allocateRegsAndSpill reading keep spills' (cand_reg:alloc) rs
-- otherwise, we need to spill a temporary that currently
-- resides in a register.
- | (temp_to_push_out, RealRegUsage my_reg fmt) : _
+ | (temp_to_push_out, RealRegUsage cand_reg old_reg_fmt) : _
<- candidates_inReg
= do
- (spill_store, slot) <- spillR (RegWithFormat (RegReal my_reg) fmt) temp_to_push_out
+ -- Spill what's currently in the register, with the format of what's in the register.
+ (spill_store, slot) <- spillR (RegWithFormat (RegReal cand_reg) old_reg_fmt) temp_to_push_out
-- record that this temp was spilled
recordSpill (SpillAlloc temp_to_push_out)
- -- update the register assignment
+ -- Update the register assignment:
+ -- - the old data is now only in memory,
+ -- - the new data is now allocated to this register;
+ -- make sure to use the new format (#26542)
let assig1 = addToUFM_Directly assig temp_to_push_out (InMem slot)
- let assig2 = addToUFM assig1 vr $! newLocation spill_loc (RealRegUsage my_reg fmt)
+ let assig2 = addToUFM assig1 vr $! newLocation spill_loc (RealRegUsage cand_reg fmt)
setAssigR $ toRegMap assig2
-- if need be, load up a spilled temp into the reg we've just freed up.
- spills' <- loadTemp r spill_loc my_reg spills
+ spills' <- loadTemp r spill_loc cand_reg spills
allocateRegsAndSpill reading keep
(spill_store ++ spills')
- (my_reg:alloc) rs
+ (cand_reg:alloc) rs
-- there wasn't anything to spill, so we're screwed.
=====================================
testsuite/tests/simd/should_run/T26542.hs
=====================================
@@ -0,0 +1,52 @@
+{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE UnboxedTuples #-}
+
+module Main where
+
+import GHC.Exts
+
+type D8# = (# DoubleX2#, Double#, DoubleX2#, Double#, DoubleX2# #)
+type D8 = (Double, Double, Double, Double, Double, Double, Double, Double)
+
+unD# :: Double -> Double#
+unD# (D# x) = x
+
+mkD8# :: Double -> D8#
+mkD8# x =
+ (# packDoubleX2# (# unD# x, unD# (x + 1) #)
+ , unD# (x + 2)
+ , packDoubleX2# (# unD# (x + 3), unD# (x + 4) #)
+ , unD# (x + 5)
+ , packDoubleX2# (# unD# (x + 6), unD# (x + 7) #)
+ #)
+{-# NOINLINE mkD8# #-}
+
+unD8# :: D8# -> D8
+unD8# (# v0, x2, v1, x5, v2 #) =
+ case unpackDoubleX2# v0 of
+ (# x0, x1 #) ->
+ case unpackDoubleX2# v1 of
+ (# x3, x4 #) ->
+ case unpackDoubleX2# v2 of
+ (# x6, x7 #) ->
+ (D# x0, D# x1, D# x2, D# x3, D# x4, D# x5, D# x6, D# x7)
+{-# NOINLINE unD8# #-}
+
+type D32# = (# D8#, D8#, D8#, D8# #)
+type D32 = (D8, D8, D8, D8)
+
+mkD32# :: Double -> D32#
+mkD32# x = (# mkD8# x, mkD8# (x + 8), mkD8# (x + 16), mkD8# (x + 24) #)
+{-# NOINLINE mkD32# #-}
+
+unD32# :: D32# -> D32
+unD32# (# x0, x1, x2, x3 #) =
+ (unD8# x0, unD8# x1, unD8# x2, unD8# x3)
+{-# NOINLINE unD32# #-}
+
+main :: IO ()
+main = do
+ let
+ !x = mkD32# 0
+ !ds = unD32# x
+ print ds
=====================================
testsuite/tests/simd/should_run/T26542.stdout
=====================================
@@ -0,0 +1 @@
+((0.0,1.0,2.0,3.0,4.0,5.0,6.0,7.0),(8.0,9.0,10.0,11.0,12.0,13.0,14.0,15.0),(16.0,17.0,18.0,19.0,20.0,21.0,22.0,23.0),(24.0,25.0,26.0,27.0,28.0,29.0,30.0,31.0))
=====================================
testsuite/tests/simd/should_run/T26550.hs
=====================================
@@ -0,0 +1,29 @@
+{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE UnboxedTuples #-}
+
+module Main where
+
+import GHC.Exts
+
+type D3# = (# Double#, DoubleX2# #)
+
+unD# :: Double -> Double#
+unD# (D# x) = x
+
+mkD3# :: Double -> D3#
+mkD3# x =
+ (# unD# (x + 2)
+ , packDoubleX2# (# unD# (x + 3), unD# (x + 4) #)
+ #)
+{-# NOINLINE mkD3# #-}
+
+main :: IO ()
+main = do
+ let
+ !(# _ten, eleven_twelve #) = mkD3# 8
+ !(# eleven, twelve #) = unpackDoubleX2# eleven_twelve
+
+ putStrLn $ unlines
+ [ "eleven: " ++ show (D# eleven)
+ , "twelve: " ++ show (D# twelve)
+ ]
=====================================
testsuite/tests/simd/should_run/T26550.stdout
=====================================
@@ -0,0 +1,3 @@
+eleven: 11.0
+twelve: 12.0
+
=====================================
testsuite/tests/simd/should_run/all.T
=====================================
@@ -51,6 +51,11 @@ test('int64x2_shuffle_baseline', [], compile_and_run, [''])
test('T25658', [], compile_and_run, ['']) # #25658 is a bug with SSE2 code generation
test('T25659', [], compile_and_run, [''])
+# This test case uses SIMD instructions, even though the bug isn't in any way
+# tied to SIMD registers. It's useful to include it in this file so that
+# we re-use the logic for which architectures to run the test on.
+test('T26550', [], compile_and_run, ['-O1 -fno-worker-wrapper'])
+
# Ensure we set the CPU features we have available.
#
# This is especially important with the LLVM backend, as LLVM can otherwise
@@ -139,6 +144,7 @@ test('T22187', [],compile,[''])
test('T22187_run', [],compile_and_run,[''])
test('T25062_V16', [], compile_and_run, [''])
test('T25561', [], compile_and_run, [''])
+test('T26542', [], compile_and_run, [''])
# Even if the CPU we run on doesn't support *executing* those tests we should try to
# compile them.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6ead7d06a0d83db8a3c2931103b772…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6ead7d06a0d83db8a3c2931103b772…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][master] Comments only in GHC.Parser.PostProcess.Haddock
by Marge Bot (@marge-bot) 11 Nov '25
by Marge Bot (@marge-bot) 11 Nov '25
11 Nov '25
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
6ead7d06 by Vladislav Zavialov at 2025-11-11T11:50:26-05:00
Comments only in GHC.Parser.PostProcess.Haddock
Remove outdated Note [Register keyword location], as the issue it describes
was addressed by commit 05eb50dff2fcc78d025e77b9418ddb369db49b9f.
- - - - -
3 changed files:
- compiler/GHC/Parser/PostProcess/Haddock.hs
- testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.hs
- testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr
Changes:
=====================================
compiler/GHC/Parser/PostProcess/Haddock.hs
=====================================
@@ -1115,7 +1115,6 @@ runHdkA (HdkA _ m) = unHdkM m mempty
-- To take it into account, we must register its location using registerLocHdkA
-- or registerHdkA.
--
--- See Note [Register keyword location].
-- See Note [Adding Haddock comments to the syntax tree].
registerLocHdkA :: SrcSpan -> HdkA ()
registerLocHdkA l = HdkA (getBufSpan l) (pure ())
@@ -1544,18 +1543,3 @@ that GHC could parse successfully:
This declaration was accepted by ghc but rejected by ghc -haddock.
-}
-
-{- Note [Register keyword location]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-At the moment, 'addHaddock' erroneously associates some comments with
-constructs that are separated by a keyword. For example:
-
- data Foo -- | Comment for MkFoo
- where MkFoo :: Foo
-
-We could use EPA (exactprint annotations) to fix this, but not without
-modification. For example, EpaLocation contains RealSrcSpan but not BufSpan.
-Also, the fix would be more straightforward after #19623.
-
-For examples, see tests/haddock/should_compile_flag_haddock/T17544_kw.hs
--}
=====================================
testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.hs
=====================================
@@ -2,8 +2,6 @@
{-# OPTIONS -haddock -ddump-parsed-ast #-}
-- Haddock comments in this test case are all rejected.
---
--- See Note [Register keyword location] in GHC.Parser.PostProcess.Haddock
module
-- | Bad comment for the module
=====================================
testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr
=====================================
@@ -10,15 +10,15 @@
(AnnsModule
(NoEpTok)
(EpTok
- (EpaSpan { T17544_kw.hs:8:1-6 }))
+ (EpaSpan { T17544_kw.hs:6:1-6 }))
(EpTok
- (EpaSpan { T17544_kw.hs:13:12-16 }))
+ (EpaSpan { T17544_kw.hs:11:12-16 }))
[]
[]
(Just
((,)
- { T17544_kw.hs:25:1 }
- { T17544_kw.hs:24:18 })))
+ { T17544_kw.hs:23:1 }
+ { T17544_kw.hs:22:18 })))
(EpaCommentsBalanced
[]
[]))
@@ -29,7 +29,7 @@
(Just
(L
(EpAnn
- (EpaSpan { T17544_kw.hs:10:3-11 })
+ (EpaSpan { T17544_kw.hs:8:3-11 })
(AnnListItem
[])
(EpaComments
@@ -38,14 +38,14 @@
(Just
(L
(EpAnn
- (EpaSpan { T17544_kw.hs:(10,13)-(13,10) })
+ (EpaSpan { T17544_kw.hs:(8,13)-(11,10) })
(AnnList
(Nothing)
(ListParens
(EpTok
- (EpaSpan { T17544_kw.hs:10:13 }))
+ (EpaSpan { T17544_kw.hs:8:13 }))
(EpTok
- (EpaSpan { T17544_kw.hs:13:10 })))
+ (EpaSpan { T17544_kw.hs:11:10 })))
[]
((,)
(NoEpTok)
@@ -55,11 +55,11 @@
[]))
[(L
(EpAnn
- (EpaSpan { T17544_kw.hs:11:3-9 })
+ (EpaSpan { T17544_kw.hs:9:3-9 })
(AnnListItem
[(AddCommaAnn
(EpTok
- (EpaSpan { T17544_kw.hs:11:10 })))])
+ (EpaSpan { T17544_kw.hs:9:10 })))])
(EpaComments
[]))
(IEThingAll
@@ -67,14 +67,14 @@
(Nothing)
((,,)
(EpTok
- (EpaSpan { T17544_kw.hs:11:6 }))
+ (EpaSpan { T17544_kw.hs:9:6 }))
(EpTok
- (EpaSpan { T17544_kw.hs:11:7-8 }))
+ (EpaSpan { T17544_kw.hs:9:7-8 }))
(EpTok
- (EpaSpan { T17544_kw.hs:11:9 }))))
+ (EpaSpan { T17544_kw.hs:9:9 }))))
(L
(EpAnn
- (EpaSpan { T17544_kw.hs:11:3-5 })
+ (EpaSpan { T17544_kw.hs:9:3-5 })
(AnnListItem
[])
(EpaComments
@@ -83,7 +83,7 @@
(NoExtField)
(L
(EpAnn
- (EpaSpan { T17544_kw.hs:11:3-5 })
+ (EpaSpan { T17544_kw.hs:9:3-5 })
(NameAnnTrailing
[])
(EpaComments
@@ -93,11 +93,11 @@
(Nothing)))
,(L
(EpAnn
- (EpaSpan { T17544_kw.hs:12:3-9 })
+ (EpaSpan { T17544_kw.hs:10:3-9 })
(AnnListItem
[(AddCommaAnn
(EpTok
- (EpaSpan { T17544_kw.hs:12:10 })))])
+ (EpaSpan { T17544_kw.hs:10:10 })))])
(EpaComments
[]))
(IEThingAll
@@ -105,14 +105,14 @@
(Nothing)
((,,)
(EpTok
- (EpaSpan { T17544_kw.hs:12:6 }))
+ (EpaSpan { T17544_kw.hs:10:6 }))
(EpTok
- (EpaSpan { T17544_kw.hs:12:7-8 }))
+ (EpaSpan { T17544_kw.hs:10:7-8 }))
(EpTok
- (EpaSpan { T17544_kw.hs:12:9 }))))
+ (EpaSpan { T17544_kw.hs:10:9 }))))
(L
(EpAnn
- (EpaSpan { T17544_kw.hs:12:3-5 })
+ (EpaSpan { T17544_kw.hs:10:3-5 })
(AnnListItem
[])
(EpaComments
@@ -121,7 +121,7 @@
(NoExtField)
(L
(EpAnn
- (EpaSpan { T17544_kw.hs:12:3-5 })
+ (EpaSpan { T17544_kw.hs:10:3-5 })
(NameAnnTrailing
[])
(EpaComments
@@ -131,7 +131,7 @@
(Nothing)))
,(L
(EpAnn
- (EpaSpan { T17544_kw.hs:13:3-9 })
+ (EpaSpan { T17544_kw.hs:11:3-9 })
(AnnListItem
[])
(EpaComments
@@ -141,14 +141,14 @@
(Nothing)
((,,)
(EpTok
- (EpaSpan { T17544_kw.hs:13:6 }))
+ (EpaSpan { T17544_kw.hs:11:6 }))
(EpTok
- (EpaSpan { T17544_kw.hs:13:7-8 }))
+ (EpaSpan { T17544_kw.hs:11:7-8 }))
(EpTok
- (EpaSpan { T17544_kw.hs:13:9 }))))
+ (EpaSpan { T17544_kw.hs:11:9 }))))
(L
(EpAnn
- (EpaSpan { T17544_kw.hs:13:3-5 })
+ (EpaSpan { T17544_kw.hs:11:3-5 })
(AnnListItem
[])
(EpaComments
@@ -157,7 +157,7 @@
(NoExtField)
(L
(EpAnn
- (EpaSpan { T17544_kw.hs:13:3-5 })
+ (EpaSpan { T17544_kw.hs:11:3-5 })
(NameAnnTrailing
[])
(EpaComments
@@ -168,7 +168,7 @@
[]
[(L
(EpAnn
- (EpaSpan { T17544_kw.hs:(15,1)-(16,20) })
+ (EpaSpan { T17544_kw.hs:(13,1)-(14,20) })
(AnnListItem
[])
(EpaComments
@@ -179,7 +179,7 @@
(NoExtField)
(L
(EpAnn
- (EpaSpan { T17544_kw.hs:15:6-8 })
+ (EpaSpan { T17544_kw.hs:13:6-8 })
(NameAnnTrailing
[])
(EpaComments
@@ -197,11 +197,11 @@
(NoEpTok)
(NoEpTok)
(EpTok
- (EpaSpan { T17544_kw.hs:15:1-4 }))
+ (EpaSpan { T17544_kw.hs:13:1-4 }))
(NoEpTok)
(NoEpUniTok)
(EpTok
- (EpaSpan { T17544_kw.hs:16:3-7 }))
+ (EpaSpan { T17544_kw.hs:14:3-7 }))
(NoEpTok)
(NoEpTok)
(NoEpTok))
@@ -212,7 +212,7 @@
(False)
[(L
(EpAnn
- (EpaSpan { T17544_kw.hs:16:9-20 })
+ (EpaSpan { T17544_kw.hs:14:9-20 })
(AnnListItem
[])
(EpaComments
@@ -222,12 +222,12 @@
[]
[]
(EpUniTok
- (EpaSpan { T17544_kw.hs:16:15-16 })
+ (EpaSpan { T17544_kw.hs:14:15-16 })
(NormalSyntax)))
(:|
(L
(EpAnn
- (EpaSpan { T17544_kw.hs:16:9-13 })
+ (EpaSpan { T17544_kw.hs:14:9-13 })
(NameAnnTrailing
[])
(EpaComments
@@ -237,7 +237,7 @@
[])
(L
(EpAnn
- (EpaSpan { T17544_kw.hs:16:18-20 })
+ (EpaSpan { T17544_kw.hs:14:18-20 })
(AnnListItem
[])
(EpaComments
@@ -251,7 +251,7 @@
[])
(L
(EpAnn
- (EpaSpan { T17544_kw.hs:16:18-20 })
+ (EpaSpan { T17544_kw.hs:14:18-20 })
(AnnListItem
[])
(EpaComments
@@ -261,7 +261,7 @@
(NotPromoted)
(L
(EpAnn
- (EpaSpan { T17544_kw.hs:16:18-20 })
+ (EpaSpan { T17544_kw.hs:14:18-20 })
(NameAnnTrailing
[])
(EpaComments
@@ -272,7 +272,7 @@
[]))))
,(L
(EpAnn
- (EpaSpan { T17544_kw.hs:(18,1)-(19,26) })
+ (EpaSpan { T17544_kw.hs:(16,1)-(17,26) })
(AnnListItem
[])
(EpaComments
@@ -283,7 +283,7 @@
(NoExtField)
(L
(EpAnn
- (EpaSpan { T17544_kw.hs:18:9-11 })
+ (EpaSpan { T17544_kw.hs:16:9-11 })
(NameAnnTrailing
[])
(EpaComments
@@ -300,12 +300,12 @@
[]
(NoEpTok)
(EpTok
- (EpaSpan { T17544_kw.hs:18:1-7 }))
+ (EpaSpan { T17544_kw.hs:16:1-7 }))
(NoEpTok)
(NoEpTok)
(NoEpUniTok)
(EpTok
- (EpaSpan { T17544_kw.hs:19:3-7 }))
+ (EpaSpan { T17544_kw.hs:17:3-7 }))
(NoEpTok)
(NoEpTok)
(NoEpTok))
@@ -315,7 +315,7 @@
(NewTypeCon
(L
(EpAnn
- (EpaSpan { T17544_kw.hs:19:9-26 })
+ (EpaSpan { T17544_kw.hs:17:9-26 })
(AnnListItem
[])
(EpaComments
@@ -325,12 +325,12 @@
[]
[]
(EpUniTok
- (EpaSpan { T17544_kw.hs:19:15-16 })
+ (EpaSpan { T17544_kw.hs:17:15-16 })
(NormalSyntax)))
(:|
(L
(EpAnn
- (EpaSpan { T17544_kw.hs:19:9-13 })
+ (EpaSpan { T17544_kw.hs:17:9-13 })
(NameAnnTrailing
[])
(EpaComments
@@ -340,7 +340,7 @@
[])
(L
(EpAnn
- (EpaSpan { T17544_kw.hs:19:18-26 })
+ (EpaSpan { T17544_kw.hs:17:18-26 })
(AnnListItem
[])
(EpaComments
@@ -363,11 +363,11 @@
(HsUnannotated
(EpArrow
(EpUniTok
- (EpaSpan { T17544_kw.hs:19:21-22 })
+ (EpaSpan { T17544_kw.hs:17:21-22 })
(NormalSyntax))))
(L
(EpAnn
- (EpaSpan { T17544_kw.hs:19:18-19 })
+ (EpaSpan { T17544_kw.hs:17:18-19 })
(AnnListItem
[])
(EpaComments
@@ -375,15 +375,15 @@
(HsTupleTy
(AnnParens
(EpTok
- (EpaSpan { T17544_kw.hs:19:18 }))
+ (EpaSpan { T17544_kw.hs:17:18 }))
(EpTok
- (EpaSpan { T17544_kw.hs:19:19 })))
+ (EpaSpan { T17544_kw.hs:17:19 })))
(HsBoxedOrConstraintTuple)
[]))
(Nothing))])
(L
(EpAnn
- (EpaSpan { T17544_kw.hs:19:24-26 })
+ (EpaSpan { T17544_kw.hs:17:24-26 })
(AnnListItem
[])
(EpaComments
@@ -393,7 +393,7 @@
(NotPromoted)
(L
(EpAnn
- (EpaSpan { T17544_kw.hs:19:24-26 })
+ (EpaSpan { T17544_kw.hs:17:24-26 })
(NameAnnTrailing
[])
(EpaComments
@@ -404,7 +404,7 @@
[]))))
,(L
(EpAnn
- (EpaSpan { T17544_kw.hs:(21,1)-(24,18) })
+ (EpaSpan { T17544_kw.hs:(19,1)-(22,18) })
(AnnListItem
[])
(EpaComments
@@ -415,12 +415,12 @@
((,,)
(AnnClassDecl
(EpTok
- (EpaSpan { T17544_kw.hs:21:1-5 }))
+ (EpaSpan { T17544_kw.hs:19:1-5 }))
[]
[]
(NoEpTok)
(EpTok
- (EpaSpan { T17544_kw.hs:23:3-7 }))
+ (EpaSpan { T17544_kw.hs:21:3-7 }))
(NoEpTok)
(NoEpTok)
[])
@@ -430,7 +430,7 @@
(Nothing)
(L
(EpAnn
- (EpaSpan { T17544_kw.hs:21:7-9 })
+ (EpaSpan { T17544_kw.hs:19:7-9 })
(NameAnnTrailing
[])
(EpaComments
@@ -441,7 +441,7 @@
(NoExtField)
[(L
(EpAnn
- (EpaSpan { T17544_kw.hs:21:11 })
+ (EpaSpan { T17544_kw.hs:19:11 })
(AnnListItem
[])
(EpaComments
@@ -458,7 +458,7 @@
(NoExtField)
(L
(EpAnn
- (EpaSpan { T17544_kw.hs:21:11 })
+ (EpaSpan { T17544_kw.hs:19:11 })
(NameAnnTrailing
[])
(EpaComments
@@ -471,7 +471,7 @@
[]
[(L
(EpAnn
- (EpaSpan { T17544_kw.hs:24:5-18 })
+ (EpaSpan { T17544_kw.hs:22:5-18 })
(AnnListItem
[])
(EpaComments
@@ -479,14 +479,14 @@
(ClassOpSig
(AnnSig
(EpUniTok
- (EpaSpan { T17544_kw.hs:24:15-16 })
+ (EpaSpan { T17544_kw.hs:22:15-16 })
(NormalSyntax))
(Nothing)
(Nothing))
(False)
[(L
(EpAnn
- (EpaSpan { T17544_kw.hs:24:5-13 })
+ (EpaSpan { T17544_kw.hs:22:5-13 })
(NameAnnTrailing
[])
(EpaComments
@@ -495,7 +495,7 @@
{OccName: clsmethod}))]
(L
(EpAnn
- (EpaSpan { T17544_kw.hs:24:18 })
+ (EpaSpan { T17544_kw.hs:22:18 })
(AnnListItem
[])
(EpaComments
@@ -506,7 +506,7 @@
(NoExtField))
(L
(EpAnn
- (EpaSpan { T17544_kw.hs:24:18 })
+ (EpaSpan { T17544_kw.hs:22:18 })
(AnnListItem
[])
(EpaComments
@@ -516,7 +516,7 @@
(NotPromoted)
(L
(EpAnn
- (EpaSpan { T17544_kw.hs:24:18 })
+ (EpaSpan { T17544_kw.hs:22:18 })
(NameAnnTrailing
[])
(EpaComments
@@ -529,15 +529,15 @@
[])))]))
-T17544_kw.hs:9:3: warning: [GHC-94458] [-Winvalid-haddock]
+T17544_kw.hs:7:3: warning: [GHC-94458] [-Winvalid-haddock]
A Haddock comment cannot appear in this position and will be ignored.
-T17544_kw.hs:15:10: warning: [GHC-94458] [-Winvalid-haddock]
+T17544_kw.hs:13:10: warning: [GHC-94458] [-Winvalid-haddock]
A Haddock comment cannot appear in this position and will be ignored.
-T17544_kw.hs:18:13: warning: [GHC-94458] [-Winvalid-haddock]
+T17544_kw.hs:16:13: warning: [GHC-94458] [-Winvalid-haddock]
A Haddock comment cannot appear in this position and will be ignored.
-T17544_kw.hs:22:5: warning: [GHC-94458] [-Winvalid-haddock]
+T17544_kw.hs:20:5: warning: [GHC-94458] [-Winvalid-haddock]
A Haddock comment cannot appear in this position and will be ignored.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6ead7d06a0d83db8a3c2931103b7723…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6ead7d06a0d83db8a3c2931103b7723…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][master] LLVM backend: Pass the +evex512 attribute to LLVM 18+ if -mavx512f is set
by Marge Bot (@marge-bot) 11 Nov '25
by Marge Bot (@marge-bot) 11 Nov '25
11 Nov '25
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
b22777d4 by ARATA Mizuki at 2025-11-11T11:49:44-05:00
LLVM backend: Pass the +evex512 attribute to LLVM 18+ if -mavx512f is set
The newer LLVM requires the +evex512 attribute to enable use of ZMM registers.
LLVM exhibits a backward-compatible behavior if the cpu is `x86-64`, but not if `penryn`.
Therefore, on macOS, where the cpu is set to `penryn`, we need to explicitly pass +evex512.
Fixes #26410
- - - - -
7 changed files:
- compiler/GHC/Driver/Pipeline/Execute.hs
- + testsuite/tests/simd/should_run/T26410_ffi.hs
- + testsuite/tests/simd/should_run/T26410_ffi.stdout
- + testsuite/tests/simd/should_run/T26410_ffi_c.c
- + testsuite/tests/simd/should_run/T26410_prim.hs
- + testsuite/tests/simd/should_run/T26410_prim.stdout
- testsuite/tests/simd/should_run/all.T
Changes:
=====================================
compiler/GHC/Driver/Pipeline/Execute.hs
=====================================
@@ -42,6 +42,7 @@ import GHC.Utils.Logger
import GHC.Utils.TmpFs
import GHC.Platform
import Data.List (intercalate, isInfixOf)
+import qualified Data.List.NonEmpty as NE
import GHC.Unit.Env
import GHC.Utils.Error
import Data.Maybe
@@ -69,6 +70,7 @@ import GHC.Platform.Ways
import GHC.Runtime.Loader (initializePlugins)
import GHC.Driver.LlvmConfigCache (readLlvmConfigCache)
import GHC.CmmToLlvm.Config (LlvmTarget (..), LlvmConfig (..))
+import GHC.CmmToLlvm.Version.Type (LlvmVersion (..))
import {-# SOURCE #-} GHC.Driver.Pipeline (compileForeign, compileEmptyStub)
import GHC.Settings
import System.IO
@@ -229,8 +231,9 @@ runLlvmLlcPhase pipe_env hsc_env input_fn = do
1 -> "-O1"
_ -> "-O2"
- defaultOptions = map GHC.SysTools.Option . concatMap words . snd
- $ unzip (llvmOptions llvm_config dflags)
+ llvm_version <- figureLlvmVersion logger dflags
+ let defaultOptions = map GHC.SysTools.Option . concatMap words . snd
+ $ unzip (llvmOptions llvm_config llvm_version dflags)
optFlag = if null (getOpts dflags opt_lc)
then map GHC.SysTools.Option $ words llvmOpts
else []
@@ -265,8 +268,9 @@ runLlvmOptPhase pipe_env hsc_env input_fn = do
Nothing -> panic ("runPhase LlvmOpt: llvm-passes file "
++ "is missing passes for level "
++ show optIdx)
- defaultOptions = map GHC.SysTools.Option . concat . fmap words . fst
- $ unzip (llvmOptions llvm_config dflags)
+ llvm_version <- figureLlvmVersion logger dflags
+ let defaultOptions = map GHC.SysTools.Option . concat . fmap words . fst
+ $ unzip (llvmOptions llvm_config llvm_version dflags)
-- don't specify anything if user has specified commands. We do this
-- for opt but not llc since opt is very specifically for optimisation
@@ -964,9 +968,10 @@ getOutputFilename logger tmpfs stop_phase output basename dflags next_phase mayb
-- | LLVM Options. These are flags to be passed to opt and llc, to ensure
-- consistency we list them in pairs, so that they form groups.
llvmOptions :: LlvmConfig
+ -> Maybe LlvmVersion
-> DynFlags
-> [(String, String)] -- ^ pairs of (opt, llc) arguments
-llvmOptions llvm_config dflags =
+llvmOptions llvm_config llvm_version dflags =
[("-relocation-model=" ++ rmodel
,"-relocation-model=" ++ rmodel) | not (null rmodel)]
@@ -1006,6 +1011,10 @@ llvmOptions llvm_config dflags =
++ ["+sse2" | isSse2Enabled platform ]
++ ["+sse" | isSseEnabled platform ]
++ ["+avx512f" | isAvx512fEnabled dflags ]
+ ++ ["+evex512" | isAvx512fEnabled dflags
+ , maybe False (>= LlvmVersion (18 NE.:| [])) llvm_version ]
+ -- +evex512 is recognized by LLVM 18 or newer and needed on macOS (#26410).
+ -- It may become deprecated in a future LLVM version, though.
++ ["+avx2" | isAvx2Enabled dflags ]
++ ["+avx" | isAvxEnabled dflags ]
++ ["+avx512cd"| isAvx512cdEnabled dflags ]
=====================================
testsuite/tests/simd/should_run/T26410_ffi.hs
=====================================
@@ -0,0 +1,40 @@
+{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE UnboxedTuples #-}
+{-# LANGUAGE UnliftedFFITypes #-}
+import GHC.Exts
+import GHC.Int
+
+foreign import ccall unsafe "minInt64X8"
+ minInt64X8# :: Int64X8# -> Int64X8# -> Int64X8#
+
+data Int64X8 = Int64X8# Int64X8#
+
+minInt64X8 :: Int64X8 -> Int64X8 -> Int64X8
+minInt64X8 (Int64X8# a) (Int64X8# b) = Int64X8# (minInt64X8# a b)
+{-# NOINLINE minInt64X8 #-}
+
+broadcastInt64X8 :: Int64 -> Int64X8
+broadcastInt64X8 (I64# x) = Int64X8# (broadcastInt64X8# x)
+
+packInt64X8 :: (Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64) -> Int64X8
+packInt64X8 (I64# x0, I64# x1, I64# x2, I64# x3, I64# x4, I64# x5, I64# x6, I64# x7) = Int64X8# (packInt64X8# (# x0, x1, x2, x3, x4, x5, x6, x7 #))
+
+unpackInt64X8 :: Int64X8 -> (Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64)
+unpackInt64X8 (Int64X8# a) = case unpackInt64X8# a of
+ (# x0, x1, x2, x3, x4, x5, x6, x7 #) -> (I64# x0, I64# x1, I64# x2, I64# x3, I64# x4, I64# x5, I64# x6, I64# x7)
+
+-- You can check the assembly code for this function to see if ZMM registers are used
+plusInt64X8 :: Int64X8 -> Int64X8 -> Int64X8
+plusInt64X8 (Int64X8# a) (Int64X8# b) = Int64X8# (plusInt64X8# a b)
+
+main :: IO ()
+main = do
+ let a = broadcastInt64X8 3
+ b = packInt64X8 (1, 2, 3, 4, 5, 6, 7, 8)
+ c = minInt64X8 a b
+ print $ unpackInt64X8 c
+ let d = packInt64X8 (-1, -2, -3, -4, -5, -6, -7, -8)
+ e = broadcastInt64X8 (-3)
+ f = minInt64X8 d e
+ print $ unpackInt64X8 f
+ print $ unpackInt64X8 (plusInt64X8 a b)
=====================================
testsuite/tests/simd/should_run/T26410_ffi.stdout
=====================================
@@ -0,0 +1,3 @@
+(1,2,3,3,3,3,3,3)
+(-3,-3,-3,-4,-5,-6,-7,-8)
+(4,5,6,7,8,9,10,11)
=====================================
testsuite/tests/simd/should_run/T26410_ffi_c.c
=====================================
@@ -0,0 +1,6 @@
+#include <x86intrin.h>
+
+__m512i minInt64X8(__m512i a, __m512i b)
+{
+ return _mm512_min_epi64(a, b);
+}
=====================================
testsuite/tests/simd/should_run/T26410_prim.hs
=====================================
@@ -0,0 +1,38 @@
+{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE UnboxedTuples #-}
+{-# LANGUAGE UnliftedFFITypes #-}
+import GHC.Exts
+import GHC.Int
+import GHC.Prim (minInt64X8#)
+
+data Int64X8 = Int64X8# Int64X8#
+
+minInt64X8 :: Int64X8 -> Int64X8 -> Int64X8
+minInt64X8 (Int64X8# a) (Int64X8# b) = Int64X8# (minInt64X8# a b)
+{-# NOINLINE minInt64X8 #-}
+
+broadcastInt64X8 :: Int64 -> Int64X8
+broadcastInt64X8 (I64# x) = Int64X8# (broadcastInt64X8# x)
+
+packInt64X8 :: (Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64) -> Int64X8
+packInt64X8 (I64# x0, I64# x1, I64# x2, I64# x3, I64# x4, I64# x5, I64# x6, I64# x7) = Int64X8# (packInt64X8# (# x0, x1, x2, x3, x4, x5, x6, x7 #))
+
+unpackInt64X8 :: Int64X8 -> (Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64)
+unpackInt64X8 (Int64X8# a) = case unpackInt64X8# a of
+ (# x0, x1, x2, x3, x4, x5, x6, x7 #) -> (I64# x0, I64# x1, I64# x2, I64# x3, I64# x4, I64# x5, I64# x6, I64# x7)
+
+-- You can check the assembly code for this function to see if ZMM registers are used
+plusInt64X8 :: Int64X8 -> Int64X8 -> Int64X8
+plusInt64X8 (Int64X8# a) (Int64X8# b) = Int64X8# (plusInt64X8# a b)
+
+main :: IO ()
+main = do
+ let a = broadcastInt64X8 3
+ b = packInt64X8 (1, 2, 3, 4, 5, 6, 7, 8)
+ c = minInt64X8 a b
+ print $ unpackInt64X8 c
+ let d = packInt64X8 (-1, -2, -3, -4, -5, -6, -7, -8)
+ e = broadcastInt64X8 (-3)
+ f = minInt64X8 d e
+ print $ unpackInt64X8 f
+ print $ unpackInt64X8 (plusInt64X8 a b)
=====================================
testsuite/tests/simd/should_run/T26410_prim.stdout
=====================================
@@ -0,0 +1,3 @@
+(1,2,3,3,3,3,3,3)
+(-3,-3,-3,-4,-5,-6,-7,-8)
+(4,5,6,7,8,9,10,11)
=====================================
testsuite/tests/simd/should_run/all.T
=====================================
@@ -164,3 +164,19 @@ test('T25062_V64'
test('T25169', [], compile_and_run, [''])
test('T25455', [], compile_and_run, [''])
test('T25486', [], compile_and_run, [''])
+
+test('T26410_ffi'
+ , [ only_ways(llvm_ways) # SIMD NCG TODO: support 512-bit wide vectors
+ , unless(arch('x86_64') and have_cpu_feature('avx512f'), skip)
+ , extra_hc_opts('-mavx512f -optc -mavx512f -optlc -mcpu=penryn')
+ ]
+ , compile_and_run if have_cpu_feature('avx512f') else compile
+ , ['T26410_ffi_c.c'])
+
+test('T26410_prim'
+ , [ only_ways(llvm_ways) # SIMD NCG TODO: support 512-bit wide vectors
+ , unless(arch('x86_64') and have_cpu_feature('avx512f'), skip)
+ , extra_hc_opts('-mavx512f -optlc -mcpu=penryn')
+ ]
+ , compile_and_run if have_cpu_feature('avx512f') else compile
+ , [''])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b22777d4b7182f40a31eb430fa27f5f…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b22777d4b7182f40a31eb430fa27f5f…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][master] driver: Remove unecessary call to hscInsertHPT
by Marge Bot (@marge-bot) 11 Nov '25
by Marge Bot (@marge-bot) 11 Nov '25
11 Nov '25
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
e1e1eb32 by Matthew Pickering at 2025-11-11T11:48:54-05:00
driver: Remove unecessary call to hscInsertHPT
This call was left-over from e9445c013fbccf9318739ca3d095a3e0a2e1be8a
If you follow the functions which call `upsweep_mod`, they immediately
add the interface to the HomePackageTable when `upsweep_mod` returns.
- - - - -
1 changed file:
- compiler/GHC/Driver/Make.hs
Changes:
=====================================
compiler/GHC/Driver/Make.hs
=====================================
@@ -1236,10 +1236,8 @@ upsweep_mod :: HscEnv
-> Int -- total number of modules
-> IO HomeModInfo
upsweep_mod hsc_env mHscMessage old_hmi summary mod_index nmods = do
- hmi <- compileOne' mHscMessage hsc_env summary
- mod_index nmods (hm_iface <$> old_hmi) (maybe emptyHomeModInfoLinkable hm_linkable old_hmi)
- hscInsertHPT hmi hsc_env
- return hmi
+ compileOne' mHscMessage hsc_env summary
+ mod_index nmods (hm_iface <$> old_hmi) (maybe emptyHomeModInfoLinkable hm_linkable old_hmi)
-- Note [When source is considered modified]
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e1e1eb328018d0ec138886a6390f2f5…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e1e1eb328018d0ec138886a6390f2f5…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][master] driver: Properly handle errors during LinkNode steps
by Marge Bot (@marge-bot) 11 Nov '25
by Marge Bot (@marge-bot) 11 Nov '25
11 Nov '25
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
6c91582f by Matthew Pickering at 2025-11-11T11:48:12-05:00
driver: Properly handle errors during LinkNode steps
Previously we were not properly catching errors during the LinkNode step
(see T9930fail test).
This is fixed by wrapping the `LinkNode` action in `wrapAction`, the
same handler which is used for module compilation.
Fixes #26496
- - - - -
3 changed files:
- compiler/GHC/Driver/Make.hs
- testsuite/tests/ghc-e/should_fail/T9930fail.stderr
- testsuite/tests/ghc-e/should_fail/all.T
Changes:
=====================================
compiler/GHC/Driver/Make.hs
=====================================
@@ -1851,24 +1851,25 @@ Also closely related are
-}
executeLinkNode :: HomeUnitGraph -> (Int, Int) -> UnitId -> [NodeKey] -> RunMakeM ()
-executeLinkNode hug kn uid deps = do
+executeLinkNode hug kn@(k, _) uid deps = do
withCurrentUnit uid $ do
- MakeEnv{..} <- ask
+ make_env@MakeEnv{..} <- ask
let dflags = hsc_dflags hsc_env
- let hsc_env' = setHUG hug hsc_env
msg' = (\messager -> \recomp -> messager hsc_env kn recomp (LinkNode deps uid)) <$> env_messager
- linkresult <- liftIO $ withAbstractSem compile_sem $ do
- link (ghcLink dflags)
- (hsc_logger hsc_env')
- (hsc_tmpfs hsc_env')
- (hsc_FC hsc_env')
- (hsc_hooks hsc_env')
- dflags
- (hsc_unit_env hsc_env')
- True -- We already decided to link
- msg'
- (hsc_HPT hsc_env')
+ linkresult <- lift $ MaybeT $ withAbstractSem compile_sem $ withLoggerHsc k make_env $ \lcl_hsc_env -> do
+ let hsc_env' = setHUG hug lcl_hsc_env
+ wrapAction diag_wrapper hsc_env' $ do
+ link (ghcLink dflags)
+ (hsc_logger hsc_env')
+ (hsc_tmpfs hsc_env')
+ (hsc_FC hsc_env')
+ (hsc_hooks hsc_env')
+ dflags
+ (hsc_unit_env hsc_env')
+ True -- We already decided to link
+ msg'
+ (hsc_HPT hsc_env')
case linkresult of
Failed -> fail "Link Failed"
Succeeded -> return ()
=====================================
testsuite/tests/ghc-e/should_fail/T9930fail.stderr
=====================================
@@ -1,11 +1,4 @@
-ghc: Uncaught exception ghc-9.13-inplace:GHC.Utils.Panic.GhcException:
-
-default output name would overwrite the input file; must specify -o explicitly
+<no location info>: error:
+ default output name would overwrite the input file; must specify -o explicitly
Usage: For basic information, try the `--help' option.
-While handling default output name would overwrite the input file; must specify -o explicitly
- | Usage: For basic information, try the `--help' option.
-
-HasCallStack backtrace:
- bracket, called at compiler/GHC/Driver/MakeAction.hs:2955:3 in ghc-9.13-inplace:GHC.Driver.MakeAction
-
=====================================
testsuite/tests/ghc-e/should_fail/all.T
=====================================
@@ -15,10 +15,8 @@ test('ghc-e-fail2', req_interp, makefile_test, ['ghc-e-fail2'])
test('T9930fail',
[extra_files(['T9930']),
when(opsys('mingw32'), skip),
- normalise_errmsg_fun(lambda s: normalise_version_("ghc")(s).replace('ghc-<VERSION>-<HASH>','ghc')),
- # broken for JS until cross-compilers become stage2 compilers (#19174)
- # or until we bootstrap with a 9.10 compiler
- js_broken(19174)],
+ normalise_errmsg_fun(lambda s: normalise_version_("ghc")(s).replace('ghc-<VERSION>-<HASH>','ghc'))
+ ],
makefile_test, ['T9930fail'])
test('T18441fail0', req_interp, makefile_test, ['T18441fail0'])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6c91582f915f80daff774db7738094b…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6c91582f915f80daff774db7738094b…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][master] 5 commits: Preserve user-written kinds in data declarations
by Marge Bot (@marge-bot) 11 Nov '25
by Marge Bot (@marge-bot) 11 Nov '25
11 Nov '25
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
3c2f4bb4 by sheaf at 2025-11-11T11:47:28-05:00
Preserve user-written kinds in data declarations
This commit ensures that we preserve the user-written kind for data
declarations, e.g. in
type T2T = Type -> Type
type D :: T2T
data D a where { .. }
that we preserve the user-written kind of D as 'T2T', instead of
expanding the type synonym 'T2T' during kind checking.
We do this by storing 'tyConKind' separately from 'tyConResKind'. This
means that 'tyConKind' is not necessarily equal to
'mkTyConKind binders res_kind', as e.g. in the above example the former
is 'T2T' while the latter is 'Type -> Type'.
This is explained in Note [Preserve user-written TyCon kind] in GHC.Core.TyCon.
This is particularly important for Haddock, as the kinds stored in
interface files affect the generated documentation, and we want to
preserve the user-written types as much as possible.
- - - - -
19859584 by sheaf at 2025-11-11T11:47:28-05:00
Store user-written datacon tvs in interface files
This commit ensures we store the user-written quantified type variables
of data constructors in interface files, e.g. in
data D a where
MkD1 :: forall x. x -> D x
MkD2 :: forall u v. u -> v -> D v
The previous behaviour was to rename the universal variables to match
the universal variables of the data constructor. This was undesirable
because the names that end up in interface files end up mattering for
generated Haddock documentation; it's better to preserve the user-written
type variables.
Moreover, the universal variables may not have been user-written at all,
e.g. in an example such as:
type T2T = Type -> Type
data G :: T2T where
MkG :: forall x. D x
Here GHC will invent the type variable name 'a' for the first binder of
the TyCon G. We really don't want to then rename the user-written 'x'
into the generated 'a'.
- - - - -
034b2056 by sheaf at 2025-11-11T11:47:28-05:00
DataCon univ_tvs names: pick TyCon over inferred
This commit changes how we compute the names of universal type variables
in GADT data constructors. This augments the existing logic that chose
which type variable name to use, in GHC.Tc.TyCl.mkGADTVars. We continue
to prefer DataCon tv names for user-written binders, but we now prefer
TyCon tv names for inferred (non-user-written) DataCon binders.
This makes a difference in examples such as:
type (:~~:) :: k1 -> k2 -> Type
data a :~~: b where
HRefl :: a :~~: a
Before this patch, we ended up giving HRefl the type:
forall {k2}. forall (a :: k2). a :~~: a
whereas we now give it the type:
forall {k1}. forall (a :: k1). a :~~: a
The important part isn't really 'k1' or 'k2', but more that the inferred
type variable names of the DataCon can be arbitrary/unpredictable (as
they are chosen by GHC and depend on how unification proceeds), so it's
much better to use the more predictable TyCon type variable names.
- - - - -
95078d00 by sheaf at 2025-11-11T11:47:28-05:00
Backpack Rename: use explicit record construction
This commit updates the Backpack boilerplate in GHC.Iface.Rename to
use explicit record construction rather than record update. This makes
sure that the code stays up to date when the underlying constructors
change (e.g. new fields are added). The rationale is further explained
in Note [Prefer explicit record construction].
- - - - -
2bf36263 by sheaf at 2025-11-11T11:47:28-05:00
Store # eta binders in TyCon and use for Haddock
This commit stores the number of TyCon binders that were introduced by
eta-expansion (by the function GHC.Tc.Gen.HsType.splitTyConKind).
This is then used to pretty-print the TyCon as the user wrote it, e.g.
for
type Effect :: (Type -> Type) -> Type -> Type
data State s :: Effect where {..} -- arity 3
GHC will eta-expand the data declaration to
data State s a b where {..}
but also store in the 'TyCon' that the number of binders introduced by
this eta expansion is 2. This allows us, in
'Haddock.Convert.synifyTyConKindSig', to recover the original user-written
syntax, preserving the user's intent in Haddock documentation.
See Note [Inline kind signatures with GADTSyntax] in Haddock.Convert.
- - - - -
49 changed files:
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/Types/Literals.hs
- compiler/GHC/Core/TyCon.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Iface/Decl.hs
- compiler/GHC/Iface/Rename.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/IfaceToCore.hs
- compiler/GHC/Tc/Gen/HsType.hs
- compiler/GHC/Tc/TyCl.hs
- compiler/GHC/Tc/TyCl/Build.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- testsuite/tests/backpack/should_fail/T19244a.stderr
- testsuite/tests/dependent/should_fail/T11334b.stderr
- testsuite/tests/generics/T10604/T10604_deriving.stderr
- testsuite/tests/ghci.debugger/scripts/print012.stdout
- testsuite/tests/ghci/scripts/T10321.stdout
- testsuite/tests/ghci/scripts/T24459.stdout
- testsuite/tests/ghci/scripts/T7730.stdout
- testsuite/tests/ghci/scripts/ghci065.stdout
- testsuite/tests/interface-stability/base-exports.stdout
- testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
- testsuite/tests/interface-stability/base-exports.stdout-mingw32
- testsuite/tests/interface-stability/base-exports.stdout-ws-32
- testsuite/tests/rename/should_fail/rnfail055.stderr
- testsuite/tests/saks/should_compile/saks023.stdout
- testsuite/tests/saks/should_compile/saks034.stdout
- testsuite/tests/saks/should_compile/saks035.stdout
- testsuite/tests/showIface/Makefile
- + testsuite/tests/showIface/T26246a.hs
- + testsuite/tests/showIface/T26246a.stdout
- testsuite/tests/showIface/all.T
- testsuite/tests/typecheck/T16127/T16127.stderr
- testsuite/tests/typecheck/should_compile/T22560d.stdout
- testsuite/tests/typecheck/should_fail/T15629.stderr
- utils/haddock/haddock-api/src/Haddock/Convert.hs
- utils/haddock/html-test/ref/Bug1004.html
- utils/haddock/html-test/ref/Bug1050.html
- + utils/haddock/html-test/ref/Bug26246.html
- utils/haddock/html-test/ref/Bug85.html
- utils/haddock/html-test/ref/Bug923.html
- utils/haddock/html-test/ref/BundledPatterns.html
- utils/haddock/html-test/ref/BundledPatterns2.html
- utils/haddock/html-test/ref/ConstructorPatternExport.html
- utils/haddock/html-test/ref/GADTRecords.html
- utils/haddock/html-test/ref/LinearTypes.html
- utils/haddock/html-test/ref/PromotedTypes.html
- + utils/haddock/html-test/src/Bug26246.hs
- utils/haddock/latex-test/ref/LinearTypes/LinearTypes.tex
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ac7b737e8da74b2508994867ede0be…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ac7b737e8da74b2508994867ede0be…
You're receiving this email because of your account on gitlab.haskell.org.
1
0