[Git][ghc/ghc][wip/ubsan] 26 commits: Preserve user-written kinds in data declarations
by Cheng Shao (@TerrorJack) 18 Nov '25
by Cheng Shao (@TerrorJack) 18 Nov '25
18 Nov '25
Cheng Shao pushed to branch wip/ubsan 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
- - - - -
741da00c by Ben Gamari at 2025-11-12T03:38:20-05:00
template-haskell: Better describe getQ semantics
Clarify that the state is a type-indexed map, as suggested by #26484.
- - - - -
8b080e04 by ARATA Mizuki at 2025-11-12T03:39:11-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>
- - - - -
a00840ea by Simon Peyton Jones at 2025-11-14T15:23:56+00:00
Make TYPE and CONSTRAINT apart again
This patch finally fixes #24279.
* The story started with #11715
* Then #21623 articulated a plan, which made Type and Constraint
not-apart; a horrible hack but it worked. The main patch was
commit 778c6adca2c995cd8a1b84394d4d5ca26b915dac
Author: Simon Peyton Jones <simonpj(a)microsoft.com>
Date: Wed Nov 9 10:33:22 2022 +0000
Type vs Constraint: finally nailed
* #24279 reported a bug in the above big commit; this small patch fixes it
commit af6932d6c068361c6ae300d52e72fbe13f8e1f18
Author: Simon Peyton Jones <simon.peytonjones(a)gmail.com>
Date: Mon Jan 8 10:49:49 2024 +0000
Make TYPE and CONSTRAINT not-apart
Issue #24279 showed up a bug in the logic in GHC.Core.Unify.unify_ty
which is supposed to make TYPE and CONSTRAINT be not-apart.
* Then !10479 implemented "unary classes".
* That change in turn allows us to make Type and Constraint apart again,
cleaning up the compiler and allowing a little bit more expressiveness.
It fixes the original hope in #24279, namely that `Type` and `Constraint`
should be distinct throughout.
- - - - -
c0a1e574 by Georgios Karachalias at 2025-11-15T05:14:31-05:00
Report all missing modules with -M
We now report all missing modules at once in GHC.Driver.Makefile.processDeps,
as opposed to only reporting a single missing module. Fixes #26551.
- - - - -
c9fa3449 by Sylvain Henry at 2025-11-15T05:15:26-05:00
JS: fix array index for registers
We used to store R32 in h$regs[-1]. While it's correct in JavaScript,
fix this to store R32 in h$regs[0] instead.
- - - - -
9e469909 by Sylvain Henry at 2025-11-15T05:15:26-05:00
JS: support more than 128 registers (#26558)
The JS backend only supported 128 registers (JS variables/array slots
used to pass function arguments). It failed in T26537 when 129
registers were required.
This commit adds support for more than 128 registers: it is now limited to
maxBound :: Int (compiler's Int). If we ever go above this threshold the
compiler now panics with a more descriptive message.
A few built-in JS functions were assuming 128 registers and have been
rewritten to use loops. Note that loops are only used for "high"
registers that are stored in an array: the 31 "low" registers are still
handled with JS global variables and with explicit switch-cases to
maintain good performance in the most common cases (i.e. few registers
used). Adjusting the number of low registers is now easy: just one
constant to adjust (GHC.StgToJS.Regs.lowRegsCount).
No new test added: T26537 is used as a regression test instead.
- - - - -
0a64a78b by Sven Tennie at 2025-11-15T20:31:10-05:00
AArch64: Simplify CmmAssign and CmmStore
The special handling for floats was fake: The general case is always
used. So, the additional code path isn't needed (and only adds
complexity for the reader.)
- - - - -
15b311be by sheaf at 2025-11-15T20:32:02-05:00
SimpleOpt: refactor & push coercions into lambdas
This commit improves the simple optimiser (in GHC.Core.SimpleOpt)
in a couple of ways:
- The logic to push coercion lambdas is shored up.
The function 'pushCoercionIntoLambda' used to be called in 'finish_app',
but this meant we could not continue to optimise the program after
performing this transformation.
Now, we call 'pushCoercionIntoLambda' as part of 'simple_app'.
Doing so can be important when dealing with unlifted newtypes,
as explained in Note [Desugaring unlifted newtypes].
- The code is re-structured to avoid duplication and out-of-sync
code paths.
Now, 'simple_opt_expr' defers to 'simple_app' for the 'App', 'Var',
'Cast' and 'Lam' cases. This means all the logic for those is
centralised in a single place (e.g. the 'go_lam' helper function).
To do this, the general structure is brought a bit closer to the
full-blown simplifier, with a notion of 'continuation'
(see 'SimpleContItem').
This commit also modifies GHC.Core.Opt.Arity.pushCoercionIntoLambda to
apply a substitution (a slight generalisation of its existing implementation).
- - - - -
b33284c7 by sheaf at 2025-11-15T20:32:02-05:00
Improve typechecking of data constructors
This commit changes the way in which we perform typecheck data
constructors, in particular how we make multiplicities line up.
Now, impedance matching occurs as part of the existing subsumption
machinery. See the revamped Note [Typechecking data constructors] in
GHC.Tc.Gen.App, as well as Note [Polymorphisation of linear fields]
in GHC.Core.Multiplicity.
This allows us to get rid of a fair amount of hacky code that was
added with the introduction of LinearTypes; in particular the logic of
GHC.Tc.Gen.Head.tcInferDataCon.
-------------------------
Metric Decrease:
T10421
T14766
T15164
T15703
T19695
T5642
T9630
WWRec
-------------------------
- - - - -
b6faf5d0 by sheaf at 2025-11-15T20:32:02-05:00
Handle unsaturated rep-poly newtypes
This commit allows GHC to handle unsaturated occurrences of unlifted
newtype constructors. The plan is detailed in
Note [Eta-expanding rep-poly unlifted newtypes]
in GHC.Tc.Utils.Concrete: for unsaturated unlifted newtypes, we perform
the appropriate representation-polymorphism check in tcInstFun.
- - - - -
5369db79 by Cheng Shao at 2025-11-18T19:25:43+01:00
hadrian: add support for building with UndefinedBehaviorSanitizer
This patch adds a +ubsan flavour transformer to hadrian to build all
stage1+ C/C++ code with UndefinedBehaviorSanitizer. This is
particularly useful to catch potential undefined behavior in the RTS
codebase.
- - - - -
9302a7ee by Cheng Shao at 2025-11-18T19:25:44+01:00
configure: bump LlvmMaxVersion to 22
This commit bumps LlvmMaxVersion to 22; 21.x releases have been
available since Aug 26th, 2025 and there's no regressions with 21.x so
far. This bump is also required for updating fedora image to 43.
- - - - -
cecb52a3 by Cheng Shao at 2025-11-18T19:25:44+01:00
ci: add x86_64-linux-fedora43-validate+ubsan job
This patch updates fedora image to 43, and adds a
`x86_64-linux-fedora43-validate+ubsan` job that's run in
validate/nightly pipelines to catch undefined behavior in the RTS
codebase.
- - - - -
205 changed files:
- .gitlab-ci.yml
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- .gitlab/rel_eng/upload_ghc_libs.py
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/Types/Literals.hs
- compiler/GHC/Builtin/Types/Prim.hs
- compiler/GHC/Cmm/Sink.hs
- compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
- compiler/GHC/CmmToAsm/Reg/Linear.hs
- compiler/GHC/CmmToAsm/Reg/Liveness.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/Coercion/Opt.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Multiplicity.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/Simplify/Iteration.hs
- compiler/GHC/Core/RoughMap.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/TyCo/FVs.hs
- compiler/GHC/Core/TyCo/Rep.hs
- compiler/GHC/Core/TyCon.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Unify.hs
- compiler/GHC/Driver/Config/Core/Lint.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/MakeFile.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Syn/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Match.hs
- compiler/GHC/HsToCore/Utils.hs
- compiler/GHC/Iface/Decl.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Iface/Rename.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/Iface/Type.hs
- compiler/GHC/IfaceToCore.hs
- compiler/GHC/Parser/PostProcess/Haddock.hs
- compiler/GHC/StgToJS/Apply.hs
- compiler/GHC/StgToJS/Expr.hs
- compiler/GHC/StgToJS/Regs.hs
- compiler/GHC/StgToJS/Rts/Rts.hs
- compiler/GHC/StgToJS/Rts/Types.hs
- compiler/GHC/Tc/Gen/App.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/Expr.hs-boot
- compiler/GHC/Tc/Gen/Head.hs
- compiler/GHC/Tc/Gen/HsType.hs
- compiler/GHC/Tc/Gen/Match.hs
- compiler/GHC/Tc/Gen/Pat.hs
- compiler/GHC/Tc/Instance/Class.hs
- compiler/GHC/Tc/TyCl.hs
- compiler/GHC/Tc/TyCl/Build.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/GHC/Tc/Types/Evidence.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/Tc/Utils/Concrete.hs
- compiler/GHC/Tc/Utils/TcType.hs
- compiler/GHC/Tc/Utils/Unify.hs
- compiler/GHC/Tc/Zonk/Type.hs
- compiler/GHC/Types/Id/Make.hs
- configure.ac
- docs/users_guide/9.16.1-notes.rst
- 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
- hadrian/doc/flavours.md
- hadrian/src/Flavour.hs
- libraries/ghc-internal/src/GHC/Internal/TH/Monad.hs
- rts/rts.cabal
- testsuite/driver/testglobals.py
- testsuite/driver/testlib.py
- 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/diagnostic-codes/codes.stdout
- testsuite/tests/driver/Makefile
- + testsuite/tests/driver/T26551.hs
- + testsuite/tests/driver/T26551.stderr
- testsuite/tests/driver/all.T
- 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/T8959b.stderr
- testsuite/tests/ghci/scripts/ghci051.stderr
- 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/indexed-types/should_compile/T12538.stderr
- testsuite/tests/indexed-types/should_fail/T21092.hs
- − testsuite/tests/indexed-types/should_fail/T21092.stderr
- testsuite/tests/indexed-types/should_fail/all.T
- 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/linear/should_compile/LinearEtaExpansions.hs
- testsuite/tests/linear/should_compile/all.T
- testsuite/tests/linear/should_fail/TypeClass.hs
- testsuite/tests/linear/should_fail/TypeClass.stderr
- testsuite/tests/linear/should_run/LinearGhci.stdout
- testsuite/tests/numeric/should_compile/T16402.stderr-ws-64
- testsuite/tests/parser/should_compile/DumpTypecheckedAst.stderr
- testsuite/tests/perf/compiler/all.T
- testsuite/tests/rename/should_fail/rnfail055.stderr
- testsuite/tests/rep-poly/RepPolyCase1.stderr
- − testsuite/tests/rep-poly/RepPolyCase2.stderr
- testsuite/tests/rep-poly/RepPolyRule3.stderr
- testsuite/tests/rep-poly/RepPolyTuple4.stderr
- testsuite/tests/rep-poly/T13233.stderr
- − testsuite/tests/rep-poly/T17021.stderr
- testsuite/tests/rep-poly/T20363b.stderr
- − testsuite/tests/rep-poly/T21650_a.stderr
- − testsuite/tests/rep-poly/T21650_b.stderr
- + testsuite/tests/rep-poly/T26072.hs
- testsuite/tests/rep-poly/UnliftedNewtypesLevityBinder.stderr
- testsuite/tests/rep-poly/all.T
- 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
- testsuite/tests/typecheck/should_fail/T15883e.stderr
- testsuite/tests/typecheck/should_fail/T2414.stderr
- testsuite/tests/typecheck/should_fail/T24279.hs
- − testsuite/tests/typecheck/should_fail/T24279.stderr
- testsuite/tests/typecheck/should_fail/T2534.stderr
- testsuite/tests/typecheck/should_fail/T7264.stderr
- testsuite/tests/typecheck/should_fail/all.T
- 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/hypsrc-test/ref/src/Classes.html
- utils/haddock/hypsrc-test/ref/src/Quasiquoter.html
- 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/f89f309b5ff0231dfda48ce4578f77…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f89f309b5ff0231dfda48ce4578f77…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
18 Nov '25
Rodrigo Mesquita pushed new branch wip/romes/T26565 at Glasgow Haskell Compiler / GHC
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/romes/T26565
You're receiving this email because of your account on gitlab.haskell.org.
1
0
18 Nov '25
Simon Peyton Jones pushed to branch wip/T23162-part2 at Glasgow Haskell Compiler / GHC
Commits:
6e8a5d0b by Simon Peyton Jones at 2025-11-18T17:44:04+00:00
More good stuff
- - - - -
8 changed files:
- compiler/GHC/Tc/Solver.hs
- compiler/GHC/Tc/Solver/FunDeps.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Utils/Unify.hs
- + testsuite/tests/typecheck/should_fail/T23162b.hs
- + testsuite/tests/typecheck/should_fail/T23162c.hs
- + testsuite/tests/typecheck/should_fail/T23162d.hs
- testsuite/tests/typecheck/should_fail/all.T
Changes:
=====================================
compiler/GHC/Tc/Solver.hs
=====================================
@@ -1068,7 +1068,7 @@ findInferredDiff annotated_theta inferred_theta
| null annotated_theta -- Short cut the common case when the user didn't
= return inferred_theta -- write any constraints in the partial signature
| otherwise
- = pushTcLevelM_ $
+ = TcM.pushTcLevelM_ $
do { lcl_env <- TcM.getLclEnv
; given_ids <- mapM TcM.newEvVar annotated_theta
; wanteds <- newWanteds AnnOrigin inferred_theta
=====================================
compiler/GHC/Tc/Solver/FunDeps.hs
=====================================
@@ -13,11 +13,11 @@ import {-# SOURCE #-} GHC.Tc.Solver.Solve( solveSimpleWanteds )
import GHC.Tc.Instance.FunDeps
import GHC.Tc.Solver.InertSet
-import GHC.Tc.Solver.Monad
import GHC.Tc.Solver.Types
+import GHC.Tc.Solver.Monad as TcS
+import GHC.Tc.Utils.Monad as TcM
import GHC.Tc.Utils.TcType
import GHC.Tc.Utils.Unify( UnifyEnv(..) )
-import GHC.Tc.Utils.Monad as TcM
import GHC.Tc.Types.Evidence
import GHC.Tc.Types.Constraint
@@ -39,7 +39,7 @@ import GHC.Utils.Panic
import GHC.Utils.Misc( lengthExceeds )
import GHC.Data.Pair
-import Data.Maybe( isNothing, mapMaybe )
+import Data.Maybe( isNothing, isJust, mapMaybe )
{- Note [Overview of functional dependencies in type inference]
@@ -469,8 +469,8 @@ tryEqFunDeps work_item@(EqCt { eq_lhs = work_lhs
, eq_eq_rel = eq_rel })
| NomEq <- eq_rel
, TyFamLHS fam_tc work_args <- work_lhs -- We have F args ~N# rhs
- = do { simpleStage $ traceTcS "tryEqFunDeps" (ppr work_item)
- ; eqs_for_me <- simpleStage $ getInertFamEqsFor fam_tc work_args work_rhs
+ = do { eqs_for_me <- simpleStage $ getInertFamEqsFor fam_tc work_args work_rhs
+ ; simpleStage $ traceTcS "tryEqFunDeps" (ppr work_item $$ ppr eqs_for_me)
; tryFamEqFunDeps eqs_for_me fam_tc work_args work_item }
| otherwise
= nopStage ()
@@ -485,10 +485,11 @@ tryFamEqFunDeps eqs_for_me fam_tc work_args
else do { -- Note [Do local fundeps before top-level instances]
tryFDEqns fam_tc work_args work_item $
mkLocalBuiltinFamEqFDs eqs_for_me fam_tc ops work_args work_rhs
- ; if all (isWanted . eqCtEvidence) eqs_for_me
- then tryFDEqns fam_tc work_args work_item $
- mkTopBuiltinFamEqFDs fam_tc ops work_args work_rhs
- else nopStage () }
+
+ ; if hasRelevantGiven eqs_for_me work_args work_item
+ ; then nopStage ()
+ else tryFDEqns fam_tc work_args work_item $
+ mkTopBuiltinFamEqFDs fam_tc ops work_args work_rhs }
| isGiven ev -- See (INJFAM:Given)
= nopStage ()
@@ -502,10 +503,10 @@ tryFamEqFunDeps eqs_for_me fam_tc work_args
Injective inj -> tryFDEqns fam_tc work_args work_item $
mkLocalFamEqFDs eqs_for_me fam_tc inj work_args work_rhs
- ; if all (isWanted . eqCtEvidence) eqs_for_me
- then tryFDEqns fam_tc work_args work_item $
- mkTopFamEqFDs fam_tc work_args work_rhs
- else nopStage () }
+ ; if hasRelevantGiven eqs_for_me work_args work_item
+ then nopStage ()
+ else tryFDEqns fam_tc work_args work_item $
+ mkTopFamEqFDs fam_tc work_args work_rhs }
mkTopFamEqFDs :: TyCon -> [TcType] -> Xi -> TcS [FunDepEqns]
mkTopFamEqFDs fam_tc work_args work_rhs
@@ -548,10 +549,8 @@ mkTopClosedFamEqFDs ax work_args work_rhs
= do { let branches = fromBranches (coAxiomBranches ax)
; traceTcS "mkTopClosed" (ppr branches $$ ppr work_args $$ ppr work_rhs)
; case getRelevantBranches ax work_args work_rhs of
- [CoAxBranch { cab_tvs = qtvs, cab_lhs = lhs_tys, cab_rhs = rhs_ty }]
- -> return [FDEqns { fd_qtvs = qtvs
- , fd_eqs = zipWith Pair (rhs_ty:lhs_tys) (work_rhs:work_args) }]
- _ -> return [] }
+ [eqn] -> return [eqn]
+ _ -> return [] }
| otherwise
= return []
@@ -566,7 +565,21 @@ isInformativeType (TyConApp tc tys) = isGenerativeTyCon tc Nominal ||
tys `lengthExceeds` tyConArity tc
isInformativeType _ = True -- AppTy, ForAllTy, FunTy, LitTy
-getRelevantBranches :: CoAxiom Branched -> [TcType] -> Xi -> [CoAxBranch]
+hasRelevantGiven :: [EqCt] -> [TcType] -> EqCt -> Bool
+-- A Given is relevant if it is not apart from the Wanted
+hasRelevantGiven eqs_for_me work_args (EqCt { eq_rhs = work_rhs })
+ = any relevant eqs_for_me
+ where
+ work_tys = work_rhs : work_args
+
+ relevant (EqCt { eq_ev = ev, eq_lhs = lhs, eq_rhs = rhs_ty })
+ | isGiven ev
+ , TyFamLHS _ lhs_tys <- lhs
+ = isJust (tcUnifyTysForInjectivity True work_tys (rhs_ty:lhs_tys))
+ | otherwise
+ = False
+
+getRelevantBranches :: CoAxiom Branched -> [TcType] -> Xi -> [FunDepEqns]
getRelevantBranches ax work_args work_rhs
= go [] (fromBranches (coAxiomBranches ax))
where
@@ -574,13 +587,21 @@ getRelevantBranches ax work_args work_rhs
go _ [] = []
go preceding (branch:branches)
- | is_relevant branch = branch : go (branch:preceding) branches
- | otherwise = go (branch:preceding) branches
+ = case is_relevant branch of
+ Just eqn -> eqn : go (branch:preceding) branches
+ Nothing -> go (branch:preceding) branches
where
- is_relevant (CoAxBranch { cab_lhs = lhs_tys, cab_rhs = rhs_ty })
- = case tcUnifyTysForInjectivity True work_tys (rhs_ty:lhs_tys) of
- Nothing -> False
- Just subst -> all (no_match (substTys subst lhs_tys)) preceding
+ is_relevant (CoAxBranch { cab_tvs = qtvs, cab_lhs = lhs_tys, cab_rhs = rhs_ty })
+ | Just subst <- tcUnifyTysForInjectivity True work_tys (rhs_ty:lhs_tys)
+ , let (subst', qtvs') = trim_qtvs subst qtvs
+ lhs_tys' = substTys subst' lhs_tys
+ rhs_ty' = substTy subst' rhs_ty
+ , all (no_match lhs_tys') preceding
+ = pprTrace "grb" (ppr qtvs $$ ppr subst $$ ppr qtvs' $$ ppr subst' $$ ppr lhs_tys $$ ppr lhs_tys') $
+ Just (FDEqns { fd_qtvs = qtvs'
+ , fd_eqs = zipWith Pair (rhs_ty':lhs_tys') work_tys })
+ | otherwise
+ = Nothing
no_match lhs_tys (CoAxBranch { cab_lhs = lhs_tys1 })
= isNothing (tcUnifyTysForInjectivity False lhs_tys1 lhs_tys)
@@ -608,15 +629,15 @@ mkTopOpenFamEqFDs fam_tc inj_flags work_args work_rhs
| otherwise
= Nothing
- trim_qtvs :: Subst -> [TcTyVar] -> (Subst,[TcTyVar])
- -- Tricky stuff: see (TIF1) in
- -- Note [Type inference for type families with injectivity]
- trim_qtvs subst [] = (subst, [])
- trim_qtvs subst (tv:tvs)
- | tv `elemSubst` subst = trim_qtvs subst tvs
- | otherwise = let !(subst1, tv') = substTyVarBndr subst tv
- !(subst', tvs') = trim_qtvs subst1 tvs
- in (subst', tv':tvs')
+trim_qtvs :: Subst -> [TcTyVar] -> (Subst,[TcTyVar])
+-- Tricky stuff: see (TIF1) in
+-- Note [Type inference for type families with injectivity]
+trim_qtvs subst [] = (subst, [])
+trim_qtvs subst (tv:tvs)
+ | tv `elemSubst` subst = trim_qtvs subst tvs
+ | otherwise = let !(subst1, tv') = substTyVarBndr subst tv
+ !(subst', tvs') = trim_qtvs subst1 tvs
+ in (subst', tv':tvs')
mkLocalFamEqFDs :: [EqCt] -> TyCon -> [Bool] -> [TcType] -> Xi -> TcS [FunDepEqns]
mkLocalFamEqFDs eqs_for_me fam_tc inj_flags work_args work_rhs
@@ -823,7 +844,7 @@ For /built-in/ type families, it's pretty similar, except that
FDEqn { fd_qtvs = [b:kappa], fd_eqs = [ beta ~ Proxy @kappa b ] }
Notice that
* we must quantify the FunDepEqns over `b`, which is not matched; for this
- we will generate a fresh unfication variable in `instantiateFunDepEqn`.
+ we will generate a fresh unification variable in `instantiateFunDepEqn`.
* we must substitute `k:->kappa` in the kind of `b`.
This fancy footwork for `fd_qtvs` is done by `trim_qtvs` in
`mkInjWantedFamEqTopEqns`.
@@ -889,6 +910,10 @@ solveFunDeps work_ev fd_eqns
= do { (unifs, _res)
<- reportFineGrainUnifications $
nestFunDepsTcS $
+ TcS.pushTcLevelM_ $
+ -- pushTcLevelTcM: increase the level so that unification variables
+ -- allocated by the fundep-creation itself don't count as useful unifications
+ -- See Note [Deeper TcLevel for partial improvement unification variables]
do { (_, eqs) <- wrapUnifier work_ev Nominal do_fundeps
; solveSimpleWanteds eqs }
-- Why solveSimpleWanteds? Answer
=====================================
compiler/GHC/Tc/Solver/Monad.hs
=====================================
@@ -25,7 +25,7 @@ module GHC.Tc.Solver.Monad (
selectNextWorkItem,
getWorkList,
updWorkListTcS,
- pushLevelNoWorkList,
+ pushLevelNoWorkList, pushTcLevelM_,
runTcPluginTcS, recordUsedGREs,
matchGlobalInst, TcM.ClsInstResult(..),
@@ -1320,11 +1320,6 @@ nestImplicTcS skol_info ev_binds_var inner_tclvl (TcS thing_inside)
nestFunDepsTcS :: TcS a -> TcS a
nestFunDepsTcS (TcS thing_inside)
= TcS $ \ env@(TcSEnv { tcs_inerts = inerts_var }) ->
- TcM.pushTcLevelM_ $
- -- pushTcLevelTcM: increase the level so that unification variables
- -- allocated by the fundep-creation itself don't count as useful unifications
- -- See Note [Deeper TcLevel for partial improvement unification variables]
- -- in GHC.Tc.Solver.FunDeps
do { inerts <- TcM.readTcRef inerts_var
; let nest_inerts = resetInertCans inerts
-- resetInertCans: like nestImplicTcS
@@ -1834,6 +1829,10 @@ selectNextWorkItem
} }
+pushTcLevelM_ :: TcS a -> TcS a
+pushTcLevelM_ (TcS thing_inside)
+ = TcS (\env -> TcM.pushTcLevelM_ (thing_inside env))
+
pushLevelNoWorkList :: SDoc -> TcS a -> TcS (TcLevel, a)
-- Push the level and run thing_inside
-- However, thing_inside should not generate any work items
=====================================
compiler/GHC/Tc/Utils/Unify.hs
=====================================
@@ -2440,7 +2440,7 @@ The eager unifier, `uType`, is called by
via the wrappers `unifyType`, `unifyKind` etc
* The constraint solver (e.g. in GHC.Tc.Solver.Equality),
- via `GHC.Tc.Solver.Monad.wrapUnifie`.
+ via `GHC.Tc.Solver.Monad.wrapUnifier`.
`uType` runs in the TcM monad, but it carries a UnifyEnv that tells it
what to do when unifying a variable or deferring a constraint. Specifically,
=====================================
testsuite/tests/typecheck/should_fail/T23162b.hs
=====================================
@@ -0,0 +1,33 @@
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE GADTs #-}
+{-# LANGUAGE TypeFamilyDependencies #-}
+{-# LANGUAGE TypeOperators #-}
+{-# LANGUAGE ViewPatterns #-}
+{-# LANGUAGE UndecidableInstances #-}
+
+module T23162b where
+
+import Data.Kind ( Type )
+import Data.Proxy
+
+type family LV (as :: [Type]) (b :: Type) = (r :: Type) | r -> as b where
+ LV (a ': as) b = a -> LV as b
+
+eq :: a -> a -> ()
+eq x y = ()
+
+foo :: Proxy a -> b -> LV a b
+foo = foo
+
+bar :: (c->()) -> ()
+bar = bar
+
+f1 :: Int -> ()
+-- LV alpha Bool ~ LV alpha Char
+f1 x = bar (\y -> eq (foo y True) (foo y 'c'))
+
+f2 :: Int -> ()
+-- LV alpha Bool ~ Int -> LV alpha Char
+f2 x = bar (\y -> eq (foo y True) (\(z::Int) -> foo y 'c'))
+
+
=====================================
testsuite/tests/typecheck/should_fail/T23162c.hs
=====================================
@@ -0,0 +1,22 @@
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE TypeFamilyDependencies #-}
+
+module T23162c where
+
+type family Bak a = r | r -> a where
+ Bak Int = Char
+ Bak Char = Int
+ Bak a = a
+
+eq :: a -> a -> ()
+eq x y = ()
+
+bar :: (c->()) -> ()
+bar = bar
+
+foo :: a -> Bak a
+foo = foo
+
+-- Bak alpha ~ ()
+f :: ()
+f = bar (\y -> eq (foo y) ())
=====================================
testsuite/tests/typecheck/should_fail/T23162d.hs
=====================================
@@ -0,0 +1,27 @@
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE AllowAmbiguousTypes #-}
+
+module T23162d where
+
+import GHC.TypeNats
+import Data.Kind
+
+data T2 a b = MkT2 a b
+
+type TArgKind :: Nat -> Type
+type family TArgKind n where
+ TArgKind 2 = T2 Type Type
+
+eq :: a -> a -> ()
+eq x y = ()
+
+bar :: (c->()) -> ()
+bar = bar
+
+foo :: forall n k0 k1. (TArgKind n ~ T2 k0 k1) => Int
+foo = foo @n
+
+f :: () -> Int
+f () = foo
=====================================
testsuite/tests/typecheck/should_fail/all.T
=====================================
@@ -746,3 +746,6 @@ test('T26255a', normal, compile_fail, [''])
test('T26255b', normal, compile_fail, [''])
test('T26330', normal, compile_fail, [''])
test('T23162a', normal, compile_fail, [''])
+test('T23162b', normal, compile_fail, [''])
+test('T23162c', normal, compile, [''])
+test('T23162d', normal, compile, [''])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6e8a5d0b60f4d3c6fd0fefc18fb2998…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6e8a5d0b60f4d3c6fd0fefc18fb2998…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/fendor/ghc-stack-profiler] Sample Profiler commit
by Hannes Siebenhandl (@fendor) 18 Nov '25
by Hannes Siebenhandl (@fendor) 18 Nov '25
18 Nov '25
Hannes Siebenhandl pushed to branch wip/fendor/ghc-stack-profiler at Glasgow Haskell Compiler / GHC
Commits:
305d5a8e by fendor at 2025-11-18T16:24:57+01:00
Sample Profiler commit
- - - - -
7 changed files:
- .gitmodules
- + ghc-stack-profiler
- ghc/Main.hs
- ghc/ghc-bin.cabal.in
- hadrian/src/Packages.hs
- hadrian/src/Settings/Default.hs
- hadrian/src/Settings/Packages.hs
Changes:
=====================================
.gitmodules
=====================================
@@ -124,3 +124,6 @@
[submodule "libraries/template-haskell-quasiquoter"]
path = libraries/template-haskell-quasiquoter
url = https://gitlab.haskell.org/ghc/template-haskell-quasiquoter.git
+[submodule "ghc-stack-profiler"]
+ path = ghc-stack-profiler
+ url = https://github.com/well-typed/ghc-stack-profiler
=====================================
ghc-stack-profiler
=====================================
@@ -0,0 +1 @@
+Subproject commit 156e03860ea734a8c2d7b5a4d5ef0e27cc17f208
=====================================
ghc/Main.hs
=====================================
@@ -80,6 +80,7 @@ import GHC.Iface.Errors.Ppr
import GHC.Driver.Session.Mode
import GHC.Driver.Session.Lint
import GHC.Driver.Session.Units
+import GHC.Driver.Monad
-- Standard Haskell libraries
import System.IO
@@ -91,6 +92,17 @@ import Control.Monad.Trans.Except (throwE, runExceptT)
import Data.List ( isPrefixOf, partition, intercalate )
import Prelude
import qualified Data.List.NonEmpty as NE
+#if defined(SAMPLE_TRACER)
+import qualified GHC.Stack.Profiler.Sampler as Sampler
+#endif
+
+runWithStackProfiler :: IO () -> IO ()
+runWithStackProfiler =
+#if defined(SAMPLE_TRACER)
+ Sampler.withStackProfiler (Sampler.SampleIntervalMs 10)
+#else
+ id
+#endif
-----------------------------------------------------------------------------
-- ToDo:
@@ -153,7 +165,8 @@ main = do
ShowGhciUsage -> showGhciUsage dflags
PrintWithDynFlags f -> putStrLn (f dflags)
Right postLoadMode ->
- main' postLoadMode units dflags argv3 flagWarnings
+ reifyGhc $ \session -> runWithStackProfiler $
+ reflectGhc (main' postLoadMode units dflags argv3 flagWarnings) session
main' :: PostLoadMode -> [String] -> DynFlags -> [Located String] -> [Warn]
-> Ghc ()
=====================================
ghc/ghc-bin.cabal.in
=====================================
@@ -27,6 +27,11 @@ Flag threaded
Default: True
Manual: True
+Flag sampleTracer
+ Description: Whether we instrument the ghc binary with sample tracer when the eventlog is enabled
+ Default: False
+ Manual: True
+
Executable ghc
Default-Language: GHC2021
@@ -45,6 +50,10 @@ Executable ghc
ghc-boot == @ProjectVersionMunged@,
ghc == @ProjectVersionMunged@
+ if flag(sampleTracer)
+ build-depends: ghc-stack-profiler
+ CPP-OPTIONS: -DSAMPLE_TRACER
+
if os(windows)
Build-Depends: Win32 >= 2.3 && < 2.15
else
=====================================
hadrian/src/Packages.hs
=====================================
@@ -13,6 +13,7 @@ module Packages (
transformers, unlit, unix, win32, xhtml,
lintersCommon, lintNotes, lintCodes, lintCommitMsg, lintSubmoduleRefs, lintWhitespace,
ghcPackages, isGhcPackage,
+ ghc_stack_profiler, ghc_stack_profiler_core,
-- * Package information
crossPrefix, programName, nonHsMainPackage, programPath, timeoutPath,
@@ -43,7 +44,10 @@ ghcPackages =
, terminfo, text, time, transformers, unlit, unix, win32, xhtml, fileio
, timeout
, lintersCommon
- , lintNotes, lintCodes, lintCommitMsg, lintSubmoduleRefs, lintWhitespace ]
+ , lintNotes, lintCodes, lintCommitMsg, lintSubmoduleRefs, lintWhitespace
+ , ghc_stack_profiler_core
+ , ghc_stack_profiler
+ ]
-- TODO: Optimise by switching to sets of packages.
isGhcPackage :: Package -> Bool
@@ -135,6 +139,8 @@ unlit = util "unlit"
unix = lib "unix"
win32 = lib "Win32"
xhtml = lib "xhtml"
+ghc_stack_profiler = lib "ghc-stack-profiler" `setPath` "ghc-stack-profiler/ghc-stack-profiler"
+ghc_stack_profiler_core = lib "ghc-stack-profiler-core" `setPath` "ghc-stack-profiler/ghc-stack-profiler-core"
lintersCommon = lib "linters-common" `setPath` "linters/linters-common"
lintNotes = linter "lint-notes"
=====================================
hadrian/src/Settings/Default.hs
=====================================
@@ -180,6 +180,8 @@ stage1Packages = do
, unlit
, xhtml
, if winTarget then win32 else unix
+ , ghc_stack_profiler
+ , ghc_stack_profiler_core
]
, when (not cross)
[ hpcBin
=====================================
hadrian/src/Settings/Packages.hs
=====================================
@@ -108,6 +108,12 @@ packageArgs = do
, builder (Haddock BuildPackage) ? arg ("--optghc=-I" ++ path) ]
+ , package ghc_stack_profiler ? mconcat
+ [ builder (Cabal Flags) ? mconcat
+ [ arg "-use-ghc-trace-events"
+ ]
+ ]
+
---------------------------------- ghc ---------------------------------
, package ghc ? mconcat
[ builder Ghc ? mconcat
@@ -116,6 +122,7 @@ packageArgs = do
, builder (Cabal Flags) ? mconcat
[ (expr (ghcWithInterpreter stage)) `cabalFlag` "internal-interpreter"
+ , notStage0 `cabalFlag` "sampleTracer"
, ifM stage0
-- We build a threaded stage 1 if the bootstrapping compiler
-- supports it.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/305d5a8e2c1dac4bbcdfd717781019a…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/305d5a8e2c1dac4bbcdfd717781019a…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/fendor/ghc-stack-profiler] 68 commits: Skip uniques test if sources are not available
by Hannes Siebenhandl (@fendor) 18 Nov '25
by Hannes Siebenhandl (@fendor) 18 Nov '25
18 Nov '25
Hannes Siebenhandl pushed to branch wip/fendor/ghc-stack-profiler at Glasgow Haskell Compiler / GHC
Commits:
5dc2e9ea by Julian Ospald at 2025-10-27T18:17:23-04:00
Skip uniques test if sources are not available
- - - - -
544b9ec9 by Vladislav Zavialov at 2025-10-27T18:18:06-04:00
Re-export GHC.Hs.Basic from GHC.Hs
Clean up some import sections in GHC by re-exporting GHC.Hs.Basic
from GHC.Hs.
- - - - -
643ce801 by Julian Ospald at 2025-10-28T18:18:55-04:00
rts: remove unneccesary cabal flags
We perform those checks via proper autoconf macros
instead that do the right thing and then add those
libs to the rts buildinfo.
- - - - -
d69ea8fe by Vladislav Zavialov at 2025-10-28T18:19:37-04:00
Test case for #17705
Starting with GHC 9.12 (the first release to include 5745dbd3),
all examples in this ticket are handled as expected.
- - - - -
4038a28b by Andreas Klebinger at 2025-10-30T12:38:52-04:00
Add a perf test for #26425
- - - - -
f997618e by Andreas Klebinger at 2025-10-30T12:38:52-04:00
OccAnal: Be stricter for better compiler perf.
In particular we are now stricter:
* When combining usageDetails.
* When computing binder info.
In combineUsageDetails when combining the underlying adds we compute a
new `LocalOcc` for each entry by combining the two existing ones.
Rather than wait for those entries to be forced down the road we now
force them immediately. Speeding up T26425 by about 10% with little
effect on the common case.
We also force binders we put into the Core AST everywhere now.
Failure to do so risks leaking the occ env used to set the binders
OccInfo.
For T26425 compiler residency went down by a factor of ~10x.
Compile time also improved by a factor of ~1.6.
-------------------------
Metric Decrease:
T18698a
T26425
T9233
-------------------------
- - - - -
5618645b by Vladislav Zavialov at 2025-10-30T12:39:33-04:00
Fix namespace specifiers in subordinate exports (#12488)
This patch fixes an oversight in the `lookupChildrenExport` function that
caused explicit namespace specifiers of subordinate export items to be
ignored:
module M (T (type A)) where -- should be rejected
data T = A
Based on the `IEWrappedName` data type, there are 5 cases to consider:
1. Unadorned name: P(X)
2. Named default: P(default X)
3. Pattern synonym: P(pattern X)
4. Type name: P(type X)
5. Data name: P(data X)
Case 1 is already handled correctly; cases 2 and 3 are parse errors; and
it is cases 4 and 5 that we are concerned with in this patch.
Following the precedent established in `LookupExactName`, we introduce
a boolean flag in `LookupChildren` to control whether to look up in all
namespaces or in a specific one. If an export item is accompanied by an
explicit namespace specifier `type` or `data`, we restrict the lookup in
`lookupGRE` to a specific namespace.
The newly introduced diagnostic `TcRnExportedSubordinateNotFound`
provides error messages and suggestions more tailored to this context
than the previously used `reportUnboundName`.
- - - - -
f75ab223 by Peter Trommler at 2025-10-31T18:43:13-04:00
ghc-toolchain: detect PowerPC 64 bit ABI
Check preprocessor macro defined for ABI v2 and assume v1 otherwise.
Fixes #26521
- - - - -
d086c474 by Peter Trommler at 2025-10-31T18:43:13-04:00
ghc-toolchain: refactor, move lastLine to Utils
- - - - -
995dfe0d by Vladislav Zavialov at 2025-10-31T18:43:54-04:00
Tests for -Wduplicate-exports, -Wdodgy-exports
Add test cases for the previously untested diagnostics:
[GHC-51876] TcRnDupeModuleExport
[GHC-64649] TcRnNullExportedModule
This also revealed a typo (incorrect capitalization of "module") in the
warning text for TcRnDupeModuleExport, which is now fixed.
- - - - -
f6961b02 by Cheng Shao at 2025-11-01T00:08:01+01:00
wasm: reformat dyld source code
This commit reformats dyld source code with prettier, to avoid
introducing unnecessary diffs in subsequent patches when they're
formatted before committing.
- - - - -
0c9032a0 by Cheng Shao at 2025-11-01T00:08:01+01:00
wasm: simplify _initialize logic in dyld
This commit simplifies how we _initialize a wasm shared library in
dyld and removes special treatment for libc.so, see added comment for
detailed explanation.
- - - - -
ec1b40bd by Cheng Shao at 2025-11-01T00:08:01+01:00
wasm: support running dyld fully client side in the browser
This commit refactors the wasm dyld script so that it can be used to
load and run wasm shared libraries fully client-side in the browser
without needing a wasm32-wasi-ghci backend:
- A new `DyLDBrowserHost` class is exported, which runs in the browser
and uses the in-memory vfs without any RPC calls. This meant to be
used to create a `rpc` object for the fully client side use cases.
- The exported `main` function now can be used to load user-specified
shared libraries, and the user can use the returned `DyLD` instance
to run their own exported Haskell functions.
- The in-browser wasi implementation is switched to
https://github.com/haskell-wasm/browser_wasi_shim for bugfixes and
major performance improvements not landed upstream yet.
- When being run by deno, it now correctly switches to non-nodejs code
paths, so it's more convenient to test dyld logic with deno.
See added comments for details, as well as the added `playground001`
test case for an example of using it to build an in-browser Haskell
playground.
- - - - -
8f3e481f by Cheng Shao at 2025-11-01T00:08:01+01:00
testsuite: add playground001 to test haskell playground
This commit adds the playground001 test case to test the haskell
playground in browser, see comments for details.
- - - - -
af40606a by Cheng Shao at 2025-11-01T00:08:04+01:00
Revert "testsuite: add T26431 test case"
This reverts commit 695036686f8c6d78611edf3ed627608d94def6b7. T26431
is now retired, wasm ghc internal-interpreter logic is tested by
playground001.
- - - - -
86c82745 by Vladislav Zavialov at 2025-11-01T07:24:29-04:00
Supplant TcRnExportHiddenComponents with TcRnDodgyExports (#26534)
Remove a bogus special case in lookup_ie_kids_all,
making TcRnExportHiddenComponents obsolete.
- - - - -
fcf6331e by Richard Eisenberg at 2025-11-03T08:33:05+00:00
Refactor fundep solving
This commit is a large-scale refactor of the increasingly-messy code that
handles functional dependencies. It has virtually no effect on what compiles
but improves error messages a bit. And it does the groundwork for #23162.
The big picture is described in
Note [Overview of functional dependencies in type inference]
in GHC.Tc.Solver.FunDeps
* New module GHC.Tc.Solver.FunDeps contains all the fundep-handling
code for the constraint solver.
* Fundep-equalities are solved in a nested scope; they may generate
unifications but otherwise have no other effect.
See GHC.Tc.Solver.FunDeps.solveFunDeps
The nested needs to start from the Givens in the inert set, but
not the Wanteds; hence a new function `resetInertCans`, used in
`nestFunDepsTcS`.
* That in turn means that fundep equalities never show up in error
messages, so the complicated FunDepOrigin tracking can all disappear.
* We need to be careful about tracking unifications, so we kick out
constraints from the inert set after doing unifications. Unification
tracking has been majorly reformed: see Note [WhatUnifications] in
GHC.Tc.Utils.Unify.
A good consequence is that the hard-to-grok `resetUnificationFlag`
has been replaced with a simpler use of
`reportCoarseGrainUnifications`
Smaller things:
* Rename `FunDepEqn` to `FunDepEqns` since it contains multiple
type equalities.
Some compile time improvement
Metrics: compile_time/bytes allocated
Baseline
Test value New value Change
---------------------- --------------------------------------
T5030(normal) 173,839,232 148,115,248 -14.8% GOOD
hard_hole_fits(normal) 286,768,048 284,015,416 -1.0%
geo. mean -0.2%
minimum -14.8%
maximum +0.3%
Metric Decrease:
T5030
- - - - -
231adc30 by Simon Peyton Jones at 2025-11-03T08:33:05+00:00
QuickLook's tcInstFun should make instantiation variables directly
tcInstFun must make "instantiation variables", not regular
unification variables, when instantiating function types. That was
previously implemented by a hack: set the /ambient/ level to QLInstTyVar.
But the hack finally bit me, when I was refactoring WhatUnifications.
And it was always wrong: see the now-expunged (TCAPP2) note.
This commit does it right, by making tcInstFun call its own
instantiation functions. That entails a small bit of duplication,
but the result is much, much cleaner.
- - - - -
39d4a24b by Simon Peyton Jones at 2025-11-03T08:33:05+00:00
Build implication for constraints from (static e)
This commit addresses #26466, by buiding an implication for the
constraints arising from a (static e) form. The implication has
a special ic_info field of StaticFormSkol, which tells the constraint
solver to use an empty set of Givens.
See (SF3) in Note [Grand plan for static forms]
in GHC.Iface.Tidy.StaticPtrTable
This commit also reinstates an `assert` in GHC.Tc.Solver.Equality.
The test `StaticPtrTypeFamily` was failing with an assertion failure,
but it now works.
- - - - -
2e2aec1e by Simon Peyton Jones at 2025-11-03T08:33:05+00:00
Comments about defaulting representation equalities
- - - - -
52a4d1da by Simon Peyton Jones at 2025-11-03T08:33:05+00:00
Improve tracking of rewriter-sets
This refactor substantially improves the treatment of so-called
"rewriter-sets" in the constraint solver.
The story is described in the rewritten
Note [Wanteds rewrite Wanteds: rewriter-sets]
in GHC.Tc.Types.Constraint
Some highlights
* Trace the free coercion holes of a filled CoercionHole,
in CoercionPlusHoles. See Note [Coercion holes] (COH5)
This avoids taking having to take the free coercion variables
of a coercion when zonking a rewrriter-set
* Many knock on changes
* Make fillCoercionHole take CoercionPlusHoles as its argument
rather than to separate arguments.
* Similarly setEqIfWanted, setWantedE, wrapUnifierAndEmit.
* Be more careful about passing the correct CoHoleSet to
`rewriteEqEvidence` and friends
* Make kickOurAfterFillingCoercionHole more clever. See
new Note [Kick out after filling a coercion hole]
Smaller matters
* Rename RewriterSet to CoHoleSet
* Add special-case helper `rewriteEqEvidenceSwapOnly`
- - - - -
3e78e1ba by Simon Peyton Jones at 2025-11-03T08:33:05+00:00
Tidy up constraint solving for foralls
* In `can_eq_nc_forall` make sure to track Givens that are used
in the nested solve step.
* Tiny missing-swap bug-fix in `lookup_eq_in_qcis`
* Fix some leftover mess from
commit 14123ee646f2b9738a917b7cec30f9d3941c13de
Author: Simon Peyton Jones <simon.peytonjones(a)gmail.com>
Date: Wed Aug 20 00:35:48 2025 +0100
Solve forall-constraints via an implication, again
Specifically, trySolveImplication is now dead.
- - - - -
973f2c25 by Simon Peyton Jones at 2025-11-03T08:33:05+00:00
Do not treat CoercionHoles as free variables in coercions
This fixes a long-standing wart in the free-variable finder;
now CoercionHoles are no longer treated as a "free variable"
of a coercion.
I got big and unexpected performance regressions when making
this change. Turned out that CallArity didn't discover that
the free variable finder could be eta-expanded, which gave very
poor code.
So I re-used Note [The one-shot state monad trick] for Endo,
resulting in GHC.Utils.EndoOS. Very simple, big win.
- - - - -
c2b8a0f9 by Simon Peyton Jones at 2025-11-03T08:33:05+00:00
Update debug-tracing in CallArity
No effect on behaviour, and commented out anyway
- - - - -
9aa5ee99 by Simon Peyton Jones at 2025-11-03T08:33:28+00:00
Comments only -- remove dangling Note references
- - - - -
6683f183 by Simon Peyton Jones at 2025-11-03T08:33:28+00:00
Accept error message wibbles
- - - - -
3ba3d9f9 by Luite Stegeman at 2025-11-04T00:59:41-05:00
rts: fix eager black holes: record mutated closure and fix assertion
This fixes two problems with handling eager black holes, introduced
by a1de535f762bc23d4cf23a5b1853591dda12cdc9.
- the closure mutation must be recorded even for eager black holes,
since the mutator has mutated it before calling threadPaused
- The assertion that an unmarked eager black hole must be owned by
the TSO calling threadPaused is incorrect, since multiple threads
can race to claim the black hole.
fixes #26495
- - - - -
b5508f2c by Rodrigo Mesquita at 2025-11-04T14:10:56+00:00
build: Relax ghc/ghc-boot Cabal bound to 3.16
Fixes #26202
- - - - -
c5b3541f by Rodrigo Mesquita at 2025-11-04T14:10:56+00:00
cabal-reinstall: Use haddock-api +in-tree-ghc
Fixes #26202
- - - - -
c6d4b945 by Rodrigo Mesquita at 2025-11-04T14:10:56+00:00
cabal-reinstall: Pass --strict to Happy
This is necessary to make the generated Parser build successfully
This mimics Hadrian, which always passes --strict to happy.
Fixes #26202
- - - - -
79df1e0e by Rodrigo Mesquita at 2025-11-04T14:10:56+00:00
genprimopcode: Require higher happy version
I've bumped the happy version to forbid deprecated Happy versions which
don't successfully compile.
- - - - -
fa5d33de by Simon Peyton Jones at 2025-11-05T08:35:40-05:00
Add a HsWrapper optimiser
This MR addresses #26349, by introduceing optSubTypeHsWrapper.
There is a long
Note [Deep subsumption and WpSubType]
in GHC.Tc.Types.Evidence that explains what is going on.
- - - - -
ea58cae5 by Simon Peyton Jones at 2025-11-05T08:35:40-05:00
Improve mkWpFun_FRR
This commit ensures that `mkWpFun_FRR` directly produces a `FunCo` in
the cases where it can.
(Previously called `mkWpFun` which in turn optimised to a `FunCo`, but
that made the smarts in `mkWpFun` /essential/ rather than (as they
should be) optional.
- - - - -
5cdcfaed by Ben Gamari at 2025-11-06T09:01:36-05:00
compiler: Exclude units with no exposed modules from unused package check
Such packages cannot be "used" in the Haskell sense of the word yet
are nevertheless necessary as they may provide, e.g., C object code or
link flags.
Fixes #24120.
- - - - -
74b8397a by Brandon Chinn at 2025-11-06T09:02:19-05:00
Replace deprecated argparse.FileType
- - - - -
36ddf988 by Ben Gamari at 2025-11-06T09:03:01-05:00
Bump unix submodule to 2.8.8.0
Closes #26474.
- - - - -
c32b3a29 by fendor at 2025-11-06T09:03:43-05:00
Fix assertion in `postStringLen` to account for \0 byte
We fix the assertion to handle trailing \0 bytes in `postStringLen`.
Before this change, the assertion looked like this:
ASSERT(eb->begin + eb->size > eb->pos + len + 1);
Let's assume some values to see why this is actually off by one:
eb->begin = 0
eb->size = 1
eb->pos = 0
len = 1
then the assertion would trigger correctly:
0 + 1 > 0 + 1 + 1 => 1 > 2 => false
as there is not enough space for the \0 byte (which is the trailing +1).
However, if we change `eb->size = 2`, then we do have enough space for a
string of length 1, but the assertion still fails:
0 + 2 > 0 + 1 + 1 => 2 > 2 => false
Which causes the assertion to fail if there is exactly enough space for
the string with a trailing \0 byte.
Clearly, the assertion should be `>=`!
If we switch around the operand, it should become more obvious that `<=`
is the correct comparison:
ASSERT(eb->pos + len + 1 <= eb->begin + eb->size);
This is expresses more naturally that the current position plus the
length of the string (and the null byte) must be smaller or equal to the
overall size of the buffer.
This change also is in line with the implementation in
`hasRoomForEvent` and `hasRoomForVariableEvent`:
```
StgBool hasRoomForEvent(EventsBuf *eb, EventTypeNum eNum)
{
uint32_t size = ...;
if (eb->pos + size > eb->begin + eb->size)
...
```
the check `eb->pos + size > eb->begin + eb->size` is identical to
`eb->pos + size <= eb->begin + eb->size` plus a negation.
- - - - -
3034a6f2 by Ben Gamari at 2025-11-06T09:04:24-05:00
Bump os-string submodule to 2.0.8
- - - - -
39567e85 by Cheng Shao at 2025-11-06T09:05:06-05:00
rts: use computed goto for instruction dispatch in the bytecode interpreter
This patch uses computed goto for instruction dispatch in the bytecode
interpreter. Previously instruction dispatch is done by a classic
switch loop, so executing the next instruction requires two jumps: one
to the start of the switch loop and another to the case block based on
the instruction tag. By using computed goto, we can build a jump table
consisted of code addresses indexed by the instruction tags
themselves, so executing the next instruction requires only one jump,
to the destination directly fetched from the jump table.
Closes #12953.
- - - - -
93fc7265 by sheaf at 2025-11-06T21:33:24-05:00
Correct hasFixedRuntimeRep in matchExpectedFunTys
This commit fixes a bug in the representation-polymormorphism check in
GHC.Tc.Utils.Unify.matchExpectedFunTys. The problem was that we put
the coercion resulting from hasFixedRuntimeRep in the wrong place,
leading to the Core Lint error reported in #26528.
The change is that we have to be careful when using 'mkWpFun': it
expects **both** the expected and actual argument types to have a
syntactically fixed RuntimeRep, as explained in Note [WpFun-FRR-INVARIANT]
in GHC.Tc.Types.Evidence.
On the way, this patch improves some of the commentary relating to
other usages of 'mkWpFun' in the compiler, in particular in the view
pattern case of 'tc_pat'. No functional changes, but some stylistic
changes to make the code more readable, and make it easier to understand
how we are upholding the WpFun-FRR-INVARIANT.
Fixes #26528
- - - - -
c052c724 by Simon Peyton Jones at 2025-11-06T21:34:06-05:00
Fix a horrible shadowing bug in implicit parameters
Fixes #26451. The change is in GHC.Tc.Solver.Monad.updInertDicts
where we now do /not/ delete /Wanted/ implicit-parameeter constraints.
This bug has been in GHC since 9.8! But it's quite hard to provoke;
I contructed a tests in T26451, but it was hard to do so.
- - - - -
b253013e by Georgios Karachalias at 2025-11-07T17:21:57-05:00
Remove the `CoreBindings` constructor from `LinkablePart`
Adjust HscRecompStatus to disallow unhydrated WholeCoreBindings
from being passed as input to getLinkDeps (which would previously
panic in this case).
Fixes #26497
- - - - -
ac7b737e by Sylvain Henry at 2025-11-07T17:22:51-05:00
Testsuite: pass ext-interp test way (#26552)
Note that some tests are still marked as broken with the ext-interp way
(see #26552 and #14335)
- - - - -
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
- - - - -
741da00c by Ben Gamari at 2025-11-12T03:38:20-05:00
template-haskell: Better describe getQ semantics
Clarify that the state is a type-indexed map, as suggested by #26484.
- - - - -
8b080e04 by ARATA Mizuki at 2025-11-12T03:39:11-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>
- - - - -
a00840ea by Simon Peyton Jones at 2025-11-14T15:23:56+00:00
Make TYPE and CONSTRAINT apart again
This patch finally fixes #24279.
* The story started with #11715
* Then #21623 articulated a plan, which made Type and Constraint
not-apart; a horrible hack but it worked. The main patch was
commit 778c6adca2c995cd8a1b84394d4d5ca26b915dac
Author: Simon Peyton Jones <simonpj(a)microsoft.com>
Date: Wed Nov 9 10:33:22 2022 +0000
Type vs Constraint: finally nailed
* #24279 reported a bug in the above big commit; this small patch fixes it
commit af6932d6c068361c6ae300d52e72fbe13f8e1f18
Author: Simon Peyton Jones <simon.peytonjones(a)gmail.com>
Date: Mon Jan 8 10:49:49 2024 +0000
Make TYPE and CONSTRAINT not-apart
Issue #24279 showed up a bug in the logic in GHC.Core.Unify.unify_ty
which is supposed to make TYPE and CONSTRAINT be not-apart.
* Then !10479 implemented "unary classes".
* That change in turn allows us to make Type and Constraint apart again,
cleaning up the compiler and allowing a little bit more expressiveness.
It fixes the original hope in #24279, namely that `Type` and `Constraint`
should be distinct throughout.
- - - - -
c0a1e574 by Georgios Karachalias at 2025-11-15T05:14:31-05:00
Report all missing modules with -M
We now report all missing modules at once in GHC.Driver.Makefile.processDeps,
as opposed to only reporting a single missing module. Fixes #26551.
- - - - -
c9fa3449 by Sylvain Henry at 2025-11-15T05:15:26-05:00
JS: fix array index for registers
We used to store R32 in h$regs[-1]. While it's correct in JavaScript,
fix this to store R32 in h$regs[0] instead.
- - - - -
9e469909 by Sylvain Henry at 2025-11-15T05:15:26-05:00
JS: support more than 128 registers (#26558)
The JS backend only supported 128 registers (JS variables/array slots
used to pass function arguments). It failed in T26537 when 129
registers were required.
This commit adds support for more than 128 registers: it is now limited to
maxBound :: Int (compiler's Int). If we ever go above this threshold the
compiler now panics with a more descriptive message.
A few built-in JS functions were assuming 128 registers and have been
rewritten to use loops. Note that loops are only used for "high"
registers that are stored in an array: the 31 "low" registers are still
handled with JS global variables and with explicit switch-cases to
maintain good performance in the most common cases (i.e. few registers
used). Adjusting the number of low registers is now easy: just one
constant to adjust (GHC.StgToJS.Regs.lowRegsCount).
No new test added: T26537 is used as a regression test instead.
- - - - -
0a64a78b by Sven Tennie at 2025-11-15T20:31:10-05:00
AArch64: Simplify CmmAssign and CmmStore
The special handling for floats was fake: The general case is always
used. So, the additional code path isn't needed (and only adds
complexity for the reader.)
- - - - -
15b311be by sheaf at 2025-11-15T20:32:02-05:00
SimpleOpt: refactor & push coercions into lambdas
This commit improves the simple optimiser (in GHC.Core.SimpleOpt)
in a couple of ways:
- The logic to push coercion lambdas is shored up.
The function 'pushCoercionIntoLambda' used to be called in 'finish_app',
but this meant we could not continue to optimise the program after
performing this transformation.
Now, we call 'pushCoercionIntoLambda' as part of 'simple_app'.
Doing so can be important when dealing with unlifted newtypes,
as explained in Note [Desugaring unlifted newtypes].
- The code is re-structured to avoid duplication and out-of-sync
code paths.
Now, 'simple_opt_expr' defers to 'simple_app' for the 'App', 'Var',
'Cast' and 'Lam' cases. This means all the logic for those is
centralised in a single place (e.g. the 'go_lam' helper function).
To do this, the general structure is brought a bit closer to the
full-blown simplifier, with a notion of 'continuation'
(see 'SimpleContItem').
This commit also modifies GHC.Core.Opt.Arity.pushCoercionIntoLambda to
apply a substitution (a slight generalisation of its existing implementation).
- - - - -
b33284c7 by sheaf at 2025-11-15T20:32:02-05:00
Improve typechecking of data constructors
This commit changes the way in which we perform typecheck data
constructors, in particular how we make multiplicities line up.
Now, impedance matching occurs as part of the existing subsumption
machinery. See the revamped Note [Typechecking data constructors] in
GHC.Tc.Gen.App, as well as Note [Polymorphisation of linear fields]
in GHC.Core.Multiplicity.
This allows us to get rid of a fair amount of hacky code that was
added with the introduction of LinearTypes; in particular the logic of
GHC.Tc.Gen.Head.tcInferDataCon.
-------------------------
Metric Decrease:
T10421
T14766
T15164
T15703
T19695
T5642
T9630
WWRec
-------------------------
- - - - -
b6faf5d0 by sheaf at 2025-11-15T20:32:02-05:00
Handle unsaturated rep-poly newtypes
This commit allows GHC to handle unsaturated occurrences of unlifted
newtype constructors. The plan is detailed in
Note [Eta-expanding rep-poly unlifted newtypes]
in GHC.Tc.Utils.Concrete: for unsaturated unlifted newtypes, we perform
the appropriate representation-polymorphism check in tcInstFun.
- - - - -
44b240f7 by fendor at 2025-11-18T16:20:19+01:00
Expose more stack decoding details
- - - - -
021ff900 by fendor at 2025-11-18T16:20:32+01:00
Sample Profiler commit
- - - - -
397 changed files:
- .gitlab/rel_eng/upload_ghc_libs.py
- .gitmodules
- cabal.project-reinstall
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/Types/Literals.hs
- compiler/GHC/Builtin/Types/Prim.hs
- compiler/GHC/Cmm/Sink.hs
- compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
- compiler/GHC/CmmToAsm/Reg/Linear.hs
- compiler/GHC/CmmToAsm/Reg/Liveness.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/Coercion/Opt.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Multiplicity.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CallArity.hs
- compiler/GHC/Core/Opt/OccurAnal.hs
- compiler/GHC/Core/Opt/Simplify/Iteration.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/RoughMap.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/TyCo/FVs.hs
- compiler/GHC/Core/TyCo/Rep.hs
- compiler/GHC/Core/TyCon.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Unify.hs
- compiler/GHC/Driver/Config/Core/Lint.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/MakeFile.hs
- compiler/GHC/Driver/Pipeline.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Hs.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Syn/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Foreign/Wasm.hs
- compiler/GHC/HsToCore/Match.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/HsToCore/Utils.hs
- compiler/GHC/Iface/Decl.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Iface/Rename.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/Iface/Tidy/StaticPtrTable.hs
- compiler/GHC/Iface/Type.hs
- compiler/GHC/IfaceToCore.hs
- compiler/GHC/Linker/Deps.hs
- compiler/GHC/Linker/Types.hs
- compiler/GHC/Parser/Errors/Types.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Parser/PostProcess/Haddock.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Rename/HsType.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/Rename/Pat.hs
- compiler/GHC/Rename/Utils.hs
- compiler/GHC/Runtime/Eval.hs
- compiler/GHC/StgToJS/Apply.hs
- compiler/GHC/StgToJS/Expr.hs
- compiler/GHC/StgToJS/Regs.hs
- compiler/GHC/StgToJS/Rts/Rts.hs
- compiler/GHC/StgToJS/Rts/Types.hs
- compiler/GHC/Tc/Deriv/Generate.hs
- compiler/GHC/Tc/Deriv/Generics.hs
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Errors/Hole.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Tc/Gen/App.hs
- compiler/GHC/Tc/Gen/Export.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/Expr.hs-boot
- compiler/GHC/Tc/Gen/Head.hs
- compiler/GHC/Tc/Gen/HsType.hs
- compiler/GHC/Tc/Gen/Match.hs
- compiler/GHC/Tc/Gen/Pat.hs
- compiler/GHC/Tc/Gen/Sig.hs
- compiler/GHC/Tc/Instance/Class.hs
- compiler/GHC/Tc/Instance/FunDeps.hs
- compiler/GHC/Tc/Solver.hs
- compiler/GHC/Tc/Solver/Default.hs
- compiler/GHC/Tc/Solver/Dict.hs
- compiler/GHC/Tc/Solver/Equality.hs
- + compiler/GHC/Tc/Solver/FunDeps.hs
- compiler/GHC/Tc/Solver/InertSet.hs
- compiler/GHC/Tc/Solver/Irred.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Solver/Rewrite.hs
- compiler/GHC/Tc/Solver/Solve.hs
- compiler/GHC/Tc/Solver/Solve.hs-boot
- compiler/GHC/Tc/TyCl.hs
- compiler/GHC/Tc/TyCl/Build.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/GHC/Tc/TyCl/Utils.hs
- compiler/GHC/Tc/Types.hs
- compiler/GHC/Tc/Types/Constraint.hs
- compiler/GHC/Tc/Types/Evidence.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/Tc/Utils/Concrete.hs
- compiler/GHC/Tc/Utils/Instantiate.hs
- compiler/GHC/Tc/Utils/Monad.hs
- compiler/GHC/Tc/Utils/TcMType.hs
- compiler/GHC/Tc/Utils/TcType.hs
- compiler/GHC/Tc/Utils/Unify.hs
- compiler/GHC/Tc/Validity.hs
- compiler/GHC/Tc/Zonk/TcType.hs
- compiler/GHC/Tc/Zonk/Type.hs
- compiler/GHC/ThToHs.hs
- compiler/GHC/Types/Basic.hs
- compiler/GHC/Types/Error/Codes.hs
- compiler/GHC/Types/Hint.hs
- compiler/GHC/Types/Hint/Ppr.hs
- compiler/GHC/Types/Id/Make.hs
- compiler/GHC/Types/Name/Reader.hs
- compiler/GHC/Types/Unique/DSM.hs
- compiler/GHC/Types/Unique/FM.hs
- compiler/GHC/Types/Var/Env.hs
- compiler/GHC/Unit/Home/ModInfo.hs
- compiler/GHC/Unit/Module/Status.hs
- compiler/GHC/Unit/Module/WholeCoreBindings.hs
- + compiler/GHC/Utils/EndoOS.hs
- compiler/Setup.hs
- compiler/ghc.cabal.in
- docs/users_guide/9.16.1-notes.rst
- docs/users_guide/bugs.rst
- docs/users_guide/compare-flags.py
- 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
- + ghc-stack-profiler
- ghc/Main.hs
- ghc/ghc-bin.cabal.in
- hadrian/src/Packages.hs
- hadrian/src/Settings/Default.hs
- hadrian/src/Settings/Packages.hs
- libraries/base/tests/all.T
- libraries/ghc-boot/Setup.hs
- libraries/ghc-boot/ghc-boot.cabal.in
- libraries/ghc-internal/src/GHC/Internal/InfoProv/Types.hsc
- libraries/ghc-internal/src/GHC/Internal/Stack/Decode.hs
- libraries/ghc-internal/src/GHC/Internal/TH/Monad.hs
- libraries/ghci/GHCi/Message.hs
- libraries/os-string
- libraries/unix
- m4/fp_check_pthreads.m4
- rts/Interpreter.c
- rts/ThreadPaused.c
- rts/configure.ac
- rts/eventlog/EventLog.c
- rts/gen_event_types.py
- rts/include/rts/Bytecodes.h
- + rts/rts.buildinfo.in
- rts/rts.cabal
- testsuite/driver/runtests.py
- testsuite/driver/testlib.py
- 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/count-deps/CountDepsAst.stdout
- testsuite/tests/count-deps/CountDepsParser.stdout
- testsuite/tests/default/default-fail05.stderr
- testsuite/tests/dependent/should_fail/T11334b.stderr
- testsuite/tests/dependent/should_fail/T13135_simple.stderr
- testsuite/tests/deriving/should_fail/T3621.stderr
- testsuite/tests/diagnostic-codes/codes.stdout
- testsuite/tests/driver/Makefile
- testsuite/tests/driver/T20696/all.T
- + testsuite/tests/driver/T24120.hs
- + testsuite/tests/driver/T26551.hs
- + testsuite/tests/driver/T26551.stderr
- testsuite/tests/driver/all.T
- testsuite/tests/driver/fat-iface/all.T
- testsuite/tests/generics/T10604/T10604_deriving.stderr
- + testsuite/tests/ghc-api-browser/README.md
- + testsuite/tests/ghc-api-browser/all.T
- + testsuite/tests/ghc-api-browser/index.html
- + testsuite/tests/ghc-api-browser/playground001.hs
- + testsuite/tests/ghc-api-browser/playground001.js
- + testsuite/tests/ghc-api-browser/playground001.sh
- testsuite/tests/ghci-wasm/T26431.stdout → testsuite/tests/ghc-api-browser/playground001.stdout
- testsuite/tests/ghc-e/should_fail/T9930fail.stderr
- testsuite/tests/ghc-e/should_fail/all.T
- − testsuite/tests/ghci-wasm/T26431.hs
- testsuite/tests/ghci-wasm/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/T8959b.stderr
- testsuite/tests/ghci/scripts/ghci051.stderr
- 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/indexed-types/should_compile/T12538.stderr
- testsuite/tests/indexed-types/should_fail/T14369.stderr
- testsuite/tests/indexed-types/should_fail/T1897b.stderr
- testsuite/tests/indexed-types/should_fail/T21092.hs
- − testsuite/tests/indexed-types/should_fail/T21092.stderr
- testsuite/tests/indexed-types/should_fail/all.T
- 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/linear/should_compile/LinearEtaExpansions.hs
- testsuite/tests/linear/should_compile/all.T
- testsuite/tests/linear/should_fail/TypeClass.hs
- testsuite/tests/linear/should_fail/TypeClass.stderr
- testsuite/tests/linear/should_run/LinearGhci.stdout
- testsuite/tests/linters/all.T
- testsuite/tests/linters/notes.stdout
- testsuite/tests/module/mod4.stderr
- testsuite/tests/numeric/should_compile/T16402.stderr-ws-64
- testsuite/tests/parser/should_compile/DumpTypecheckedAst.stderr
- testsuite/tests/parser/should_fail/RecordDotSyntaxFail10.stderr
- testsuite/tests/parser/should_fail/RecordDotSyntaxFail13.stderr
- + testsuite/tests/parser/should_fail/T12488c.hs
- + testsuite/tests/parser/should_fail/T12488c.stderr
- + testsuite/tests/parser/should_fail/T12488d.hs
- + testsuite/tests/parser/should_fail/T12488d.stderr
- testsuite/tests/parser/should_fail/T20654a.stderr
- testsuite/tests/parser/should_fail/all.T
- testsuite/tests/partial-sigs/should_fail/T14584a.stderr
- + testsuite/tests/perf/compiler/T26425.hs
- testsuite/tests/perf/compiler/all.T
- testsuite/tests/polykinds/T6068.stdout
- testsuite/tests/quantified-constraints/T15359.hs
- + testsuite/tests/rename/should_compile/T12488b.hs
- + testsuite/tests/rename/should_compile/T12488f.hs
- testsuite/tests/rename/should_compile/all.T
- + testsuite/tests/rename/should_fail/T12488a.hs
- + testsuite/tests/rename/should_fail/T12488a.stderr
- + testsuite/tests/rename/should_fail/T12488a_foo.hs
- + testsuite/tests/rename/should_fail/T12488a_foo.stderr
- + testsuite/tests/rename/should_fail/T12488e.hs
- + testsuite/tests/rename/should_fail/T12488e.stderr
- + testsuite/tests/rename/should_fail/T12488g.hs
- + testsuite/tests/rename/should_fail/T12488g.stderr
- testsuite/tests/rename/should_fail/T25899e2.stderr
- testsuite/tests/rename/should_fail/all.T
- testsuite/tests/rename/should_fail/rnfail055.stderr
- testsuite/tests/rep-poly/RepPolyCase1.stderr
- − testsuite/tests/rep-poly/RepPolyCase2.stderr
- testsuite/tests/rep-poly/RepPolyNPlusK.stderr
- testsuite/tests/rep-poly/RepPolyRightSection.stderr
- testsuite/tests/rep-poly/RepPolyRule3.stderr
- testsuite/tests/rep-poly/RepPolyTuple4.stderr
- testsuite/tests/rep-poly/T13233.stderr
- − testsuite/tests/rep-poly/T17021.stderr
- testsuite/tests/rep-poly/T19709b.stderr
- testsuite/tests/rep-poly/T20363b.stderr
- − testsuite/tests/rep-poly/T21650_a.stderr
- − testsuite/tests/rep-poly/T21650_b.stderr
- testsuite/tests/rep-poly/T23903.stderr
- + testsuite/tests/rep-poly/T26072.hs
- + testsuite/tests/rep-poly/T26528.hs
- testsuite/tests/rep-poly/UnliftedNewtypesLevityBinder.stderr
- testsuite/tests/rep-poly/all.T
- 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/simplCore/should_compile/T26349.hs
- + testsuite/tests/simplCore/should_compile/T26349.stderr
- testsuite/tests/simplCore/should_compile/all.T
- testsuite/tests/simplCore/should_compile/rule2.stderr
- testsuite/tests/splice-imports/all.T
- testsuite/tests/typecheck/T16127/T16127.stderr
- testsuite/tests/typecheck/no_skolem_info/T13499.stderr
- testsuite/tests/typecheck/should_compile/T13651.hs
- − testsuite/tests/typecheck/should_compile/T13651.stderr
- + testsuite/tests/typecheck/should_compile/T14745.hs
- + testsuite/tests/typecheck/should_compile/T17705.hs
- testsuite/tests/typecheck/should_compile/T22560d.stdout
- + testsuite/tests/typecheck/should_compile/T26451.hs
- testsuite/tests/typecheck/should_compile/all.T
- testsuite/tests/typecheck/should_compile/hole_constraints_nested.stderr
- testsuite/tests/typecheck/should_compile/tc126.hs
- testsuite/tests/typecheck/should_fail/AmbigFDs.hs
- − testsuite/tests/typecheck/should_fail/AmbigFDs.stderr
- testsuite/tests/typecheck/should_fail/FD3.stderr
- testsuite/tests/typecheck/should_fail/FDsFromGivens2.stderr
- testsuite/tests/typecheck/should_fail/T13506.stderr
- testsuite/tests/typecheck/should_fail/T15629.stderr
- testsuite/tests/typecheck/should_fail/T15883e.stderr
- testsuite/tests/typecheck/should_fail/T16512a.stderr
- testsuite/tests/typecheck/should_fail/T18851b.hs
- − testsuite/tests/typecheck/should_fail/T18851b.stderr
- testsuite/tests/typecheck/should_fail/T18851c.hs
- − testsuite/tests/typecheck/should_fail/T18851c.stderr
- testsuite/tests/typecheck/should_fail/T19415.stderr
- testsuite/tests/typecheck/should_fail/T19415b.stderr
- testsuite/tests/typecheck/should_fail/T22684.stderr
- + testsuite/tests/typecheck/should_fail/T23162a.hs
- + testsuite/tests/typecheck/should_fail/T23162a.stderr
- testsuite/tests/typecheck/should_fail/T2414.stderr
- testsuite/tests/typecheck/should_fail/T24279.hs
- − testsuite/tests/typecheck/should_fail/T24279.stderr
- testsuite/tests/typecheck/should_fail/T25325.stderr
- testsuite/tests/typecheck/should_fail/T2534.stderr
- testsuite/tests/typecheck/should_fail/T5246.stderr
- testsuite/tests/typecheck/should_fail/T5978.stderr
- testsuite/tests/typecheck/should_fail/T7264.stderr
- testsuite/tests/typecheck/should_fail/T7368a.stderr
- testsuite/tests/typecheck/should_fail/T7696.stderr
- testsuite/tests/typecheck/should_fail/T8603.stderr
- testsuite/tests/typecheck/should_fail/T9612.stderr
- testsuite/tests/typecheck/should_fail/TcStaticPointersFail03.stderr
- testsuite/tests/typecheck/should_fail/all.T
- testsuite/tests/typecheck/should_fail/tcfail122.stderr
- testsuite/tests/typecheck/should_fail/tcfail143.stderr
- + testsuite/tests/warnings/should_compile/DodgyExports02.hs
- + testsuite/tests/warnings/should_compile/DodgyExports02.stderr
- + testsuite/tests/warnings/should_compile/DodgyExports03.hs
- + testsuite/tests/warnings/should_compile/DodgyExports03.stderr
- + testsuite/tests/warnings/should_compile/DuplicateModExport.hs
- + testsuite/tests/warnings/should_compile/DuplicateModExport.stderr
- + testsuite/tests/warnings/should_compile/EmptyModExport.hs
- + testsuite/tests/warnings/should_compile/EmptyModExport.stderr
- testsuite/tests/warnings/should_compile/all.T
- utils/check-exact/ExactPrint.hs
- utils/genprimopcode/genprimopcode.cabal
- utils/ghc-toolchain/ghc-toolchain.cabal
- utils/ghc-toolchain/src/GHC/Toolchain/CheckArm.hs
- + utils/ghc-toolchain/src/GHC/Toolchain/CheckPower.hs
- utils/ghc-toolchain/src/GHC/Toolchain/ParseTriple.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Utils.hs
- utils/haddock/haddock-api/src/Haddock/Convert.hs
- utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs
- utils/haddock/haddock-api/src/Haddock/Types.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/hypsrc-test/ref/src/Classes.html
- utils/haddock/hypsrc-test/ref/src/Quasiquoter.html
- utils/haddock/latex-test/ref/LinearTypes/LinearTypes.tex
- utils/jsffi/dyld.mjs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/816114ddcc2cf9c17805d105609a4c…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/816114ddcc2cf9c17805d105609a4c…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/T26425] Fix a performance hole in the occurrence analyser
by Rodrigo Mesquita (@alt-romes) 18 Nov '25
by Rodrigo Mesquita (@alt-romes) 18 Nov '25
18 Nov '25
Rodrigo Mesquita pushed to branch wip/T26425 at Glasgow Haskell Compiler / GHC
Commits:
6b5e7254 by Simon Peyton Jones at 2025-11-18T14:38:39+00:00
Fix a performance hole in the occurrence analyser
As #26425 showed, the clever stuff in
Note [Occurrence analysis for join points]
does a lot of duplication of usage details. This patch
improved matters with a little fancy footwork. It is
described in the new (W4) of the same Note.
Compile-time allocations go down slightly. Here are the changes
of +/- 0.5% or more:
T13253(normal) 329,369,244 326,395,544 -0.9%
T13253-spj(normal) 66,410,496 66,095,864 -0.5%
T15630(normal) 129,797,200 128,663,136 -0.9%
T15630a(normal) 129,212,408 128,027,560 -0.9%
T16577(normal) 6,756,706,896 6,723,028,512 -0.5%
T18282(normal) 128,462,070 125,808,584 -2.1% GOOD
T18698a(normal) 208,418,305 202,037,336 -3.1% GOOD
T18730(optasm) 136,981,756 136,208,136 -0.6%
T18923(normal) 58,103,088 57,745,840 -0.6%
T19695(normal) 1,386,306,272 1,365,609,416 -1.5%
T26425(normal) 3,344,402,957 2,457,811,664 -26.5% GOOD
T6048(optasm) 79,763,816 79,212,760 -0.7%
T9020(optasm) 225,278,408 223,682,440 -0.7%
T9961(normal) 303,810,717 300,729,168 -1.0% GOOD
geo. mean -0.5%
minimum -26.5%
maximum +0.4%
Metric Decrease:
T18282
T18698a
T26425
T9961
- - - - -
5 changed files:
- compiler/GHC/Core/Opt/OccurAnal.hs
- compiler/GHC/Types/Basic.hs
- compiler/GHC/Types/Unique/FM.hs
- compiler/GHC/Types/Unique/Set.hs
- compiler/GHC/Types/Var/Env.hs
Changes:
=====================================
compiler/GHC/Core/Opt/OccurAnal.hs
=====================================
@@ -66,7 +66,6 @@ import GHC.Builtin.Names( runRWKey )
import GHC.Unit.Module( Module )
import Data.List (mapAccumL)
-import Data.List.NonEmpty (NonEmpty (..))
{-
************************************************************************
@@ -660,18 +659,35 @@ through A, so it should have ManyOcc. Bear this case in mind!
* In occ_env, the new (occ_join_points :: IdEnv OccInfoEnv) maps
each in-scope non-recursive join point, such as `j` above, to
a "zeroed form" of its RHS's usage details. The "zeroed form"
+ * has only occ_nested_lets in its domain (see (W4) below)
* deletes ManyOccs
* maps a OneOcc to OneOcc{ occ_n_br = 0 }
- In our example, occ_join_points will be extended with
+ In our example, assuming `v` is locally-let-bound, occ_join_points will
+ be extended with
[j :-> [v :-> OneOcc{occ_n_br=0}]]
- See addJoinPoint.
+ See `addJoinPoint` and (W4) below.
* At an occurrence of a join point, we do everything as normal, but add in the
UsageDetails from the occ_join_points. See mkOneOcc.
-* Crucially, at the NonRec binding of the join point, in `occAnalBind`, we use
- `orUDs`, not `andUDs` to combine the usage from the RHS with the usage from
- the body.
+* Crucially, at the NonRec binding of a join point `j`, in `occAnalBind`,
+ we use `combineJoinPointUDs`, not `andUDs` to combine the usage from the
+ RHS with the usage from the body. `combineJoinPointUDs` behaves like this:
+
+ * For all variables than `occ_nested_lets`, use `andUDs`, just like for
+ any normal let-binding.
+
+ * But for a variable `v` in `occ_nested_lets`, use `orUDs`:
+ - If `v` occurs `ManyOcc` in the join-point RHS, the variable won't be in
+ `occ_join_points`; but we'll get `ManyOcc` anyway.
+ - If `v` occurs `OneOcc` in the join-point RHS, the variable will be in
+ `occ_join_points` and we'll thereby get a `OneOcc{occ_n_br=0}` from
+ each of j's tail calls. We can `or` that with the `OncOcc{occ_n_br=n}`
+ from j's RHS.
+
+ The only reason for `occ_nested_lets` is to reduce the size of the info
+ duplicate at each tail call; see (W4). It would sound to put *all* variables
+ into `occ_nested_lets`.
Here are the consequences
@@ -682,13 +698,14 @@ Here are the consequences
There are two lexical occurrences of `v`!
(NB: `orUDs` adds occ_n_br together, so occ_n_br=1 is impossible, too.)
-* In the tricky (P3) we'll get an `andUDs` of
- * OneOcc{occ_n_br=0} from the occurrences of `j`)
+* In the tricky (P3), when analysing `case (f v) of ...`, we'll get
+ an `andUDs` of
+ * OneOcc{occ_n_br=0} from the occurrences of `j`
* OneOcc{occ_n_br=1} from the (f v)
These are `andUDs` together in `addOccInfo`, and hence
`v` gets ManyOccs, just as it should. Clever!
-There are a couple of tricky wrinkles
+There are, of course, some tricky wrinkles
(W1) Consider this example which shadows `j`:
join j = rhs in
@@ -718,6 +735,8 @@ There are a couple of tricky wrinkles
* In `postprcess_uds`, we add the chucked-out join points to the
returned UsageDetails, with `andUDs`.
+Wrinkles (W1) and (W2) are very similar to Note [Binder swap] (BS3).
+
(W3) Consider this example, which shadows `j`, but this time in an argument
join j = rhs
in f (case x of { K j -> ...; ... })
@@ -732,12 +751,36 @@ There are a couple of tricky wrinkles
NB: this is just about efficiency: it is always safe /not/ to zap the
occ_join_points.
-(W4) What if the join point binding has a stable unfolding, or RULES?
- They are just alternative right-hand sides, and at each call site we
- will use only one of them. So again, we can use `orUDs` to combine
- usage info from all these alternatives RHSs.
-
-Wrinkles (W1) and (W2) are very similar to Note [Binder swap] (BS3).
+(W4) Other things being equal, we want keep the OccInfoEnv stored in
+ `occ_join_points` as small as possible, because it is /duplicated/ at
+ /every occurrence/ of the join point. We really only want to include
+ OccInfo for
+ * Local, non-recursive let-bound Ids
+ * that occur just once in the RHS of the join point
+ particularly including
+ * thunks (that's the original point) and
+ * join points (so that the trick works recursively).
+ We call these the "tracked Ids of j".
+
+ Including lambda binders is pointless, and slows down the occurrence analyser.
+
+ e.g. \x. let y = x+1 in
+ join j v = ..x..y..(f z z)..
+ in ...
+ In the `occ_join_points` binding for `j`, we want to track `y`, but
+ not `x` (lambda bound) nor `z` (occurs many times).
+
+ To exploit this:
+ * `occ_nested_lets` tracks which Ids are
+ nested (not-top-level), non-recursive lets
+ * `addJoinPoint` only populates j's entry with occ-info for the "tracked Ids"
+ of `j`; that is, that are (a) in occ_nested_lets and (b) have OneOcc.
+ * `combineJoinPointUDs` uses
+ orLocalOcc for local-let Ids
+ andLocalOcc for non-local-let Ids
+
+ This fancy footwork can matter in extreme cases: it gave a 25% reduction in
+ total compiler allocation in #26425..
Note [Finding join points]
~~~~~~~~~~~~~~~~~~~~~~~~~~
@@ -759,45 +802,45 @@ rest of 'OccInfo' until it goes on the binder.
Note [Join arity prediction based on joinRhsArity]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-In general, the join arity from tail occurrences of a join point (O) may be
-higher or lower than the manifest join arity of the join body (M). E.g.,
+In general, the join arity from tail occurrences of a join point (OAr) may be
+higher or lower than the manifest join arity of the join body (MAr). E.g.,
- -- M > O:
- let f x y = x + y -- M = 2
- in if b then f 1 else f 2 -- O = 1
+ -- MAr > Oar:
+ let f x y = x + y -- MAr = 2
+ in if b then f 1 else f 2 -- OAr = 1
==> { Contify for join arity 1 }
join f x = \y -> x + y
in if b then jump f 1 else jump f 2
- -- M < O
- let f = id -- M = 0
- in if ... then f 12 else f 13 -- O = 1
+ -- MAr < Oar
+ let f = id -- MAr = 0
+ in if ... then f 12 else f 13 -- OAr = 1
==> { Contify for join arity 1, eta-expand f }
join f x = id x
in if b then jump f 12 else jump f 13
-But for *recursive* let, it is crucial that both arities match up, consider
+But for *recursive* let, it is crucial MAr=OAr. Consider:
letrec f x y = if ... then f x else True
in f 42
-Here, M=2 but O=1. If we settled for a joinrec arity of 1, the recursive jump
+Here, MAr=2 but OAr=1. If we settled for a joinrec arity of 1, the recursive jump
would not happen in a tail context! Contification is invalid here.
-So indeed it is crucial to demand that M=O.
+So indeed it is crucial to demand that MAr=OAr.
-(Side note: Actually, we could be more specific: Let O1 be the join arity of
-occurrences from the letrec RHS and O2 the join arity from the let body. Then
-we need M=O1 and M<=O2 and could simply eta-expand the RHS to match O2 later.
-M=O is the specific case where we don't want to eta-expand. Neither the join
+(Side note: Actually, we could be more specific: Let OAr1 be the join arity of
+occurrences from the letrec RHS and OAr2 the join arity from the let body. Then
+we need MAr=OAr1 and MAr<=OAr2 and could simply eta-expand the RHS to match OAr2 later.
+MAr=OAr is the specific case where we don't want to eta-expand. Neither the join
points paper nor GHC does this at the moment.)
We can capitalise on this observation and conclude that *if* f could become a
-joinrec (without eta-expansion), it will have join arity M.
-Now, M is just the result of 'joinRhsArity', a rather simple, local analysis.
+joinrec (without eta-expansion), it will have join arity MAr.
+Now, MAr is just the result of 'joinRhsArity', a rather simple, local analysis.
It is also the join arity inside the 'TailUsageDetails' returned by
'occAnalLamTail', so we can predict join arity without doing any fixed-point
iteration or really doing any deep traversal of let body or RHS at all.
-We check for M in the 'adjustTailUsage' call inside 'tagRecBinders'.
+We check for MAr in the 'adjustTailUsage' call inside 'tagRecBinders'.
All this is quite apparent if you look at the contification transformation in
Fig. 5 of "Compiling without Continuations" (which does not account for
@@ -807,14 +850,14 @@ eta-expansion at all, mind you). The letrec case looks like this
... and a bunch of conditions establishing that f only occurs
in app heads of join arity (len as + len xs) inside us and es ...
-The syntactic form `/\as.\xs. L[us]` forces M=O iff `f` occurs in `us`. However,
+The syntactic form `/\as.\xs. L[us]` forces MAr=OAr iff `f` occurs in `us`. However,
for non-recursive functions, this is the definition of contification from the
paper:
let f = /\as.\xs.u in L[es] ... conditions ...
-Note that u could be a lambda itself, as we have seen. No relationship between M
-and O to exploit here.
+Note that u could be a lambda itself, as we have seen. No relationship between MAr
+and OAr to exploit here.
Note [Join points and unfoldings/rules]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
@@ -954,6 +997,22 @@ of both functions, serving as a specification:
Cyclic Recursive case: 'tagRecBinders'
Acyclic Recursive case: 'adjustNonRecRhs'
Non-recursive case: 'adjustNonRecRhs'
+
+Note [Unfoldings and RULES]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~
+For let-bindings we treat (stable) unfoldings and RULES as "alternative right hand
+sides". That is, it's as if we had
+ f = case <hiatus> of
+ 1 -> <the-rhs>
+ 2 -> <the-stable-unfolding>
+ 3 -> <rhs of rule1>
+ 4 -> <rhs of rule2>
+So we combine all these with `orUDs` (#26567). But actually it makes
+very little difference whether we use `andUDs` or `orUDs` because of
+Note [Occurrences in stable unfoldings and RULES]: occurrences in an unfolding
+or RULE are treated as ManyOcc anyway.
+
+But NB that tail-call info is preserved so that we don't thereby lose join points.
-}
------------------------------------------------------------------
@@ -991,24 +1050,24 @@ occAnalBind !env lvl ire (NonRec bndr rhs) thing_inside combine
| mb_join@(JoinPoint {}) <- idJoinPointHood bndr
= -- Analyse the RHS and /then/ the body
let -- Analyse the rhs first, generating rhs_uds
- !(rhs_uds_s, bndr', rhs') = occAnalNonRecRhs env lvl ire mb_join bndr rhs
- rhs_uds = foldl1' orUDs rhs_uds_s -- NB: orUDs. See (W4) of
- -- Note [Occurrence analysis for join points]
+ !(rhs_uds, bndr', rhs') = occAnalNonRecRhs env lvl ire mb_join bndr rhs
-- Now analyse the body, adding the join point
-- into the environment with addJoinPoint
- !(WUD body_uds (occ, body)) = occAnalNonRecBody env bndr' $ \env ->
+ env_body = addLocalLet env lvl bndr
+ !(WUD body_uds (occ, body)) = occAnalNonRecBody env_body bndr' $ \env ->
thing_inside (addJoinPoint env bndr' rhs_uds)
in
if isDeadOcc occ -- Drop dead code; see Note [Dead code]
then WUD body_uds body
- else WUD (rhs_uds `orUDs` body_uds) -- Note `orUDs`
+ else WUD (combineJoinPointUDs env rhs_uds body_uds) -- Note `orUDs`
(combine [NonRec (fst (tagNonRecBinder lvl occ bndr')) rhs']
body)
-- The normal case, including newly-discovered join points
-- Analyse the body and /then/ the RHS
- | WUD body_uds (occ,body) <- occAnalNonRecBody env bndr thing_inside
+ | let env_body = addLocalLet env lvl bndr
+ , WUD body_uds (occ,body) <- occAnalNonRecBody env_body bndr thing_inside
= if isDeadOcc occ -- Drop dead code; see Note [Dead code]
then WUD body_uds body
else let
@@ -1017,8 +1076,8 @@ occAnalBind !env lvl ire (NonRec bndr rhs) thing_inside combine
-- => join arity O of Note [Join arity prediction based on joinRhsArity]
(tagged_bndr, mb_join) = tagNonRecBinder lvl occ bndr
- !(rhs_uds_s, final_bndr, rhs') = occAnalNonRecRhs env lvl ire mb_join tagged_bndr rhs
- in WUD (foldr andUDs body_uds rhs_uds_s) -- Note `andUDs`
+ !(rhs_uds, final_bndr, rhs') = occAnalNonRecRhs env lvl ire mb_join tagged_bndr rhs
+ in WUD (rhs_uds `andUDs` body_uds) -- Note `andUDs`
(combine [NonRec final_bndr rhs'] body)
-----------------
@@ -1033,15 +1092,21 @@ occAnalNonRecBody env bndr thing_inside
-----------------
occAnalNonRecRhs :: OccEnv -> TopLevelFlag -> ImpRuleEdges
- -> JoinPointHood -> Id -> CoreExpr
- -> (NonEmpty UsageDetails, Id, CoreExpr)
+ -> JoinPointHood -> Id -> CoreExpr
+ -> (UsageDetails, Id, CoreExpr)
occAnalNonRecRhs !env lvl imp_rule_edges mb_join bndr rhs
| null rules, null imp_rule_infos
= -- Fast path for common case of no rules. This is only worth
-- 0.1% perf on average, but it's also only a line or two of code
- ( adj_rhs_uds :| adj_unf_uds : [], final_bndr_no_rules, final_rhs )
+ ( adj_rhs_uds `orUDs` adj_unf_uds
+ , final_bndr_no_rules, final_rhs )
+
| otherwise
- = ( adj_rhs_uds :| adj_unf_uds : adj_rule_uds, final_bndr_with_rules, final_rhs )
+ = ( foldl' orUDs (adj_rhs_uds `orUDs` adj_unf_uds) adj_rule_uds
+ , final_bndr_with_rules, final_rhs )
+
+ -- orUDs: Combine the RHS, (stable) unfolding, and RULES with orUDs
+ -- See Note [Unfoldings and RULES]
where
--------- Right hand side ---------
-- For join points, set occ_encl to OccVanilla, via setTailCtxt. If we have
@@ -1054,7 +1119,7 @@ occAnalNonRecRhs !env lvl imp_rule_edges mb_join bndr rhs
rhs_ctxt = mkNonRecRhsCtxt lvl bndr unf
-- See Note [Join arity prediction based on joinRhsArity]
- -- Match join arity O from mb_join_arity with manifest join arity M as
+ -- Match join arity OAr from mb_join_arity with manifest join arity MAr as
-- returned by of occAnalLamTail. It's totally OK for them to mismatch;
-- hence adjust the UDs from the RHS
@@ -1764,7 +1829,7 @@ makeNode !env imp_rule_edges bndr_set (bndr, rhs)
-- here because that is what we are setting!
WTUD unf_tuds unf' = occAnalUnfolding rhs_env unf
adj_unf_uds = adjustTailArity (JoinPoint rhs_ja) unf_tuds
- -- `rhs_ja` is `joinRhsArity rhs` and is the prediction for source M
+ -- `rhs_ja` is `joinRhsArity rhs` and is the prediction for source MAr
-- of Note [Join arity prediction based on joinRhsArity]
--------- IMP-RULES --------
@@ -1775,7 +1840,7 @@ makeNode !env imp_rule_edges bndr_set (bndr, rhs)
--------- All rules --------
-- See Note [Join points and unfoldings/rules]
- -- `rhs_ja` is `joinRhsArity rhs'` and is the prediction for source M
+ -- `rhs_ja` is `joinRhsArity rhs'` and is the prediction for source MAr
-- of Note [Join arity prediction based on joinRhsArity]
rules_w_uds :: [(CoreRule, UsageDetails, UsageDetails)]
rules_w_uds = [ (r,l,adjustTailArity (JoinPoint rhs_ja) rhs_wuds)
@@ -2177,7 +2242,9 @@ occAnalLamTail :: OccEnv -> CoreExpr -> WithTailUsageDetails CoreExpr
-- See Note [Adjusting right-hand sides]
occAnalLamTail env expr
= let !(WUD usage expr') = occ_anal_lam_tail env expr
- in WTUD (TUD (joinRhsArity expr) usage) expr'
+ in WTUD (TUD (joinRhsArity expr') usage) expr'
+ -- If expr looks like (\x. let dead = e in \y. blah), where `dead` is dead
+ -- then joinRhsArity expr' might exceed joinRhsArity expr
occ_anal_lam_tail :: OccEnv -> CoreExpr -> WithUsageDetails CoreExpr
-- Does not markInsideLam etc for the outmost batch of lambdas
@@ -2281,7 +2348,7 @@ occAnalUnfolding !env unf
WTUD (TUD rhs_ja uds) rhs' = occAnalLamTail env rhs
unf' = unf { uf_tmpl = rhs' }
in WTUD (TUD rhs_ja (markAllMany uds)) unf'
- -- markAllMany: see Note [Occurrences in stable unfoldings]
+ -- markAllMany: see Note [Occurrences in stable unfoldings and RULES]
| otherwise -> WTUD (TUD 0 emptyDetails) unf
-- For non-Stable unfoldings we leave them undisturbed, but
@@ -2319,12 +2386,13 @@ occAnalRule env rule@(Rule { ru_bndrs = bndrs, ru_args = args, ru_rhs = rhs })
-- Note [Rules are extra RHSs]
-- Note [Rule dependency info]
rhs_uds' = markAllMany rhs_uds
+ -- markAllMany: Note [Occurrences in stable unfoldings and RULES]
rhs_ja = length args -- See Note [Join points and unfoldings/rules]
occAnalRule _ other_rule = (other_rule, emptyDetails, TUD 0 emptyDetails)
-{- Note [Occurrences in stable unfoldings]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+{- Note [Occurrences in stable unfoldings and RULES]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Consider
f p = BIG
{-# INLINE g #-}
@@ -2338,7 +2406,7 @@ preinlineUnconditionally here!
The INLINE pragma says "inline exactly this RHS"; perhaps the
programmer wants to expose that 'not', say. If we inline f that will make
-the Stable unfoldign big, and that wasn't what the programmer wanted.
+the Stable unfolding big, and that wasn't what the programmer wanted.
Another way to think about it: if we inlined g as-is into multiple
call sites, now there's be multiple calls to f.
@@ -2347,6 +2415,8 @@ Bottom line: treat all occurrences in a stable unfolding as "Many".
We still leave tail call information intact, though, as to not spoil
potential join points.
+The same goes for RULES.
+
Note [Unfoldings and rules]
~~~~~~~~~~~~~~~~~~~~~~~~~~~
Generally unfoldings and rules are already occurrence-analysed, so we
@@ -2874,7 +2944,11 @@ data OccEnv
-- Invariant: no Id maps to an empty OccInfoEnv
-- See Note [Occurrence analysis for join points]
, occ_join_points :: !JoinPointInfo
- }
+
+ , occ_nested_lets :: IdSet -- Non-top-level, non-rec-bound lets
+ -- I tried making this field strict, but doing so increased
+ -- compile-time allocation very slightly: 0.1% on average
+ }
type JoinPointInfo = IdEnv OccInfoEnv
@@ -2925,7 +2999,8 @@ initOccEnv
, occ_join_points = emptyVarEnv
, occ_bs_env = emptyVarEnv
- , occ_bs_rng = emptyVarSet }
+ , occ_bs_rng = emptyVarSet
+ , occ_nested_lets = emptyVarSet }
noBinderSwaps :: OccEnv -> Bool
noBinderSwaps (OccEnv { occ_bs_env = bs_env }) = isEmptyVarEnv bs_env
@@ -3165,23 +3240,26 @@ postprocess_uds bndrs bad_joins uds
| uniq `elemVarEnvByKey` env = plusVarEnv_C andLocalOcc env join_env
| otherwise = env
+addLocalLet :: OccEnv -> TopLevelFlag -> Id -> OccEnv
+addLocalLet env@(OccEnv { occ_nested_lets = ids }) top_lvl id
+ | isTopLevel top_lvl = env
+ | otherwise = env { occ_nested_lets = ids `extendVarSet` id }
+
addJoinPoint :: OccEnv -> Id -> UsageDetails -> OccEnv
-addJoinPoint env bndr rhs_uds
+addJoinPoint env@(OccEnv { occ_join_points = join_points, occ_nested_lets = nested_lets })
+ join_bndr (UD { ud_env = rhs_occs })
| isEmptyVarEnv zeroed_form
= env
| otherwise
- = env { occ_join_points = extendVarEnv (occ_join_points env) bndr zeroed_form }
+ = env { occ_join_points = extendVarEnv join_points join_bndr zeroed_form }
where
- zeroed_form = mkZeroedForm rhs_uds
+ zeroed_form = mapMaybeUniqSetToUFM do_one nested_lets
+ -- See Note [Occurrence analysis for join points] for "zeroed form"
-mkZeroedForm :: UsageDetails -> OccInfoEnv
--- See Note [Occurrence analysis for join points] for "zeroed form"
-mkZeroedForm (UD { ud_env = rhs_occs })
- = mapMaybeUFM do_one rhs_occs
- where
- do_one :: LocalOcc -> Maybe LocalOcc
- do_one (ManyOccL {}) = Nothing
- do_one occ@(OneOccL {}) = Just (occ { lo_n_br = 0 })
+ do_one :: Var -> Maybe LocalOcc
+ do_one bndr = case lookupVarEnv rhs_occs bndr of
+ Just occ@(OneOccL {}) -> Just (occ { lo_n_br = 0 })
+ _ -> Nothing
--------------------
transClosureFV :: VarEnv VarSet -> VarEnv VarSet
@@ -3639,7 +3717,14 @@ data LocalOcc -- See Note [LocalOcc]
-- Combining (AlwaysTailCalled 2) and (AlwaysTailCalled 3)
-- gives NoTailCallInfo
, lo_int_cxt :: !InterestingCxt }
+
| ManyOccL !TailCallInfo
+ -- Why do we need TailCallInfo on ManyOccL?
+ -- Answer 1: recursive bindings are entered many times:
+ -- rec { j x = ...j x'... } in j y
+ -- See the uses of `andUDs` in `tagRecBinders`
+ -- Answer 2: occurrences in stable unfoldings are many-ified
+ -- See Note [Occurrences in stable unfoldings and RULES]
instance Outputable LocalOcc where
ppr (OneOccL { lo_n_br = n, lo_tail = tci })
@@ -3662,10 +3747,13 @@ data UsageDetails
instance Outputable UsageDetails where
ppr ud@(UD { ud_env = env, ud_z_tail = z_tail })
- = text "UD" <+> (braces $ fsep $ punctuate comma $
- [ ppr uq <+> text ":->" <+> ppr (lookupOccInfoByUnique ud uq)
- | (uq, _) <- nonDetStrictFoldVarEnv_Directly do_one [] env ])
- $$ nest 2 (text "ud_z_tail" <+> ppr z_tail)
+ = text "UD" <> (braces (vcat
+ [ -- `final` shows the result of a proper lookupOccInfo, returning OccInfo
+ -- after accounting for `ud_z_tail` etc.
+ text "final =" <+> (fsep $ punctuate comma $
+ [ ppr uq <+> text ":->" <+> ppr (lookupOccInfoByUnique ud uq)
+ | (uq, _) <- nonDetStrictFoldVarEnv_Directly do_one [] env ])
+ , text "ud_z_tail" <+> ppr z_tail ] ))
where
do_one :: Unique -> LocalOcc -> [(Unique,LocalOcc)] -> [(Unique,LocalOcc)]
do_one uniq occ occs = (uniq, occ) : occs
@@ -3674,7 +3762,7 @@ instance Outputable UsageDetails where
-- | TailUsageDetails captures the result of applying 'occAnalLamTail'
-- to a function `\xyz.body`. The TailUsageDetails pairs together
-- * the number of lambdas (including type lambdas: a JoinArity)
--- * UsageDetails for the `body` of the lambda, unadjusted by `adjustTailUsage`.
+-- * UsageDetails for the `body` of the lambda, /unadjusted/ by `adjustTailUsage`.
-- If the binding turns out to be a join point with the indicated join
-- arity, this unadjusted usage details is just what we need; otherwise we
-- need to discard tail calls. That's what `adjustTailUsage` does.
@@ -3692,8 +3780,17 @@ data WithTailUsageDetails a = WTUD !TailUsageDetails !a
andUDs:: UsageDetails -> UsageDetails -> UsageDetails
orUDs :: UsageDetails -> UsageDetails -> UsageDetails
-andUDs = combineUsageDetailsWith andLocalOcc
-orUDs = combineUsageDetailsWith orLocalOcc
+andUDs = combineUsageDetailsWith (\_uniq -> andLocalOcc)
+orUDs = combineUsageDetailsWith (\_uniq -> orLocalOcc)
+
+combineJoinPointUDs :: OccEnv -> UsageDetails -> UsageDetails -> UsageDetails
+-- See (W4) in Note [Occurrence analysis for join points]
+combineJoinPointUDs (OccEnv { occ_nested_lets = nested_lets }) uds1 uds2
+ = combineUsageDetailsWith combine uds1 uds2
+ where
+ combine uniq occ1 occ2
+ | uniq `elemVarSetByKey` nested_lets = orLocalOcc occ1 occ2
+ | otherwise = andLocalOcc occ1 occ2
mkOneOcc :: OccEnv -> Id -> InterestingCxt -> JoinArity -> UsageDetails
mkOneOcc !env id int_cxt arity
@@ -3710,7 +3807,8 @@ mkOneOcc !env id int_cxt arity
= mkSimpleDetails (unitVarEnv id occ)
where
- occ = OneOccL { lo_n_br = 1, lo_int_cxt = int_cxt
+ occ = OneOccL { lo_n_br = 1
+ , lo_int_cxt = int_cxt
, lo_tail = AlwaysTailCalled arity }
-- Add several occurrences, assumed not to be tail calls
@@ -3797,7 +3895,7 @@ restrictFreeVars bndrs fvs = restrictUniqSetToUFM bndrs fvs
-------------------
-- Auxiliary functions for UsageDetails implementation
-combineUsageDetailsWith :: (LocalOcc -> LocalOcc -> LocalOcc)
+combineUsageDetailsWith :: (Unique -> LocalOcc -> LocalOcc -> LocalOcc)
-> UsageDetails -> UsageDetails -> UsageDetails
{-# INLINE combineUsageDetailsWith #-}
combineUsageDetailsWith plus_occ_info
@@ -3807,9 +3905,9 @@ combineUsageDetailsWith plus_occ_info
| isEmptyVarEnv env2 = uds1
| otherwise
-- See Note [Strictness in the occurrence analyser]
- -- Using strictPlusVarEnv here speeds up the test T26425 by about 10% by avoiding
- -- intermediate thunks.
- = UD { ud_env = strictPlusVarEnv_C plus_occ_info env1 env2
+ -- Using strictPlusVarEnv here speeds up the test T26425
+ -- by about 10% by avoiding intermediate thunks.
+ = UD { ud_env = strictPlusVarEnv_C_Directly plus_occ_info env1 env2
, ud_z_many = strictPlusVarEnv z_many1 z_many2
, ud_z_in_lam = plusVarEnv z_in_lam1 z_in_lam2
, ud_z_tail = strictPlusVarEnv z_tail1 z_tail2 }
@@ -3853,8 +3951,6 @@ lookupOccInfoByUnique (UD { ud_env = env
| uniq `elemVarEnvByKey` z_tail = NoTailCallInfo
| otherwise = ti
-
-
-------------------
-- See Note [Adjusting right-hand sides]
@@ -3864,21 +3960,22 @@ adjustNonRecRhs :: JoinPointHood
-- ^ This function concentrates shared logic between occAnalNonRecBind and the
-- AcyclicSCC case of occAnalRec.
-- It returns the adjusted rhs UsageDetails combined with the body usage
-adjustNonRecRhs mb_join_arity rhs_wuds@(WTUD _ rhs)
- = WUD (adjustTailUsage mb_join_arity rhs_wuds) rhs
-
+adjustNonRecRhs mb_join_arity (WTUD (TUD rhs_ja uds) rhs)
+ = WUD (adjustTailUsage exact_join rhs uds) rhs
+ where
+ exact_join = mb_join_arity == JoinPoint rhs_ja
-adjustTailUsage :: JoinPointHood
- -> WithTailUsageDetails CoreExpr -- Rhs usage, AFTER occAnalLamTail
+adjustTailUsage :: Bool -- True <=> Exactly-matching join point; don't do markNonTail
+ -> CoreExpr -- Rhs usage, AFTER occAnalLamTail
-> UsageDetails
-adjustTailUsage mb_join_arity (WTUD (TUD rhs_ja uds) rhs)
+ -> UsageDetails
+adjustTailUsage exact_join rhs uds
= -- c.f. occAnal (Lam {})
markAllInsideLamIf (not one_shot) $
markAllNonTailIf (not exact_join) $
uds
where
one_shot = isOneShotFun rhs
- exact_join = mb_join_arity == JoinPoint rhs_ja
adjustTailArity :: JoinPointHood -> TailUsageDetails -> UsageDetails
adjustTailArity mb_rhs_ja (TUD ja usage)
@@ -3925,8 +4022,9 @@ tagNonRecBinder lvl occ bndr
tagRecBinders :: TopLevelFlag -- At top level?
-> UsageDetails -- Of body of let ONLY
-> [NodeDetails]
- -> WithUsageDetails -- Adjusted details for whole scope,
- -- with binders removed
+ -> WithUsageDetails -- Adjusted details for whole scope
+ -- still including the binders;
+ -- (they are removed by `addInScope`)
[IdWithOccInfo] -- Tagged binders
-- Substantially more complicated than non-recursive case. Need to adjust RHS
-- details *before* tagging binders (because the tags depend on the RHSes).
@@ -3936,32 +4034,21 @@ tagRecBinders lvl body_uds details_s
-- 1. See Note [Join arity prediction based on joinRhsArity]
-- Determine possible join-point-hood of whole group, by testing for
- -- manifest join arity M.
- -- This (re-)asserts that makeNode had made tuds for that same arity M!
+ -- manifest join arity MAr.
+ -- This (re-)asserts that makeNode had made tuds for that same arity MAr!
unadj_uds = foldr (andUDs . test_manifest_arity) body_uds details_s
- test_manifest_arity ND{nd_rhs = WTUD tuds rhs}
- = adjustTailArity (JoinPoint (joinRhsArity rhs)) tuds
+ test_manifest_arity ND{nd_rhs = WTUD (TUD rhs_ja uds) rhs}
+ = assertPpr (rhs_ja == joinRhsArity rhs) (ppr rhs_ja $$ ppr uds $$ ppr rhs) $
+ uds
+ will_be_joins :: Bool
will_be_joins = decideRecJoinPointHood lvl unadj_uds bndrs
- mb_join_arity :: Id -> JoinPointHood
- -- mb_join_arity: See Note [Join arity prediction based on joinRhsArity]
- -- This is the source O
- mb_join_arity bndr
- -- Can't use willBeJoinId_maybe here because we haven't tagged
- -- the binder yet (the tag depends on these adjustments!)
- | will_be_joins
- , AlwaysTailCalled arity <- lookupTailCallInfo unadj_uds bndr
- = JoinPoint arity
- | otherwise
- = assert (not will_be_joins) -- Should be AlwaysTailCalled if
- NotJoinPoint -- we are making join points!
-
-- 2. Adjust usage details of each RHS, taking into account the
-- join-point-hood decision
- rhs_udss' = [ adjustTailUsage (mb_join_arity bndr) rhs_wuds
+ rhs_udss' = [ adjustTailUsage will_be_joins rhs rhs_uds
-- Matching occAnalLamTail in makeNode
- | ND { nd_bndr = bndr, nd_rhs = rhs_wuds } <- details_s ]
+ | ND { nd_rhs = WTUD (TUD _ rhs_uds) rhs } <- details_s ]
-- 3. Compute final usage details from adjusted RHS details
adj_uds = foldr andUDs body_uds rhs_udss'
@@ -3980,9 +4067,9 @@ setBinderOcc occ_info bndr
| otherwise = setIdOccInfo bndr occ_info
-- | Decide whether some bindings should be made into join points or not, based
--- on its occurrences. This is
+-- on its occurrences.
-- Returns `False` if they can't be join points. Note that it's an
--- all-or-nothing decision, as if multiple binders are given, they're
+-- all-or-nothing decision: if multiple binders are given, they are
-- assumed to be mutually recursive.
--
-- It must, however, be a final decision. If we say `True` for 'f',
=====================================
compiler/GHC/Types/Basic.hs
=====================================
@@ -1333,7 +1333,7 @@ zapFragileOcc occ = zapOccTailCallInfo occ
instance Outputable OccInfo where
-- only used for debugging; never parsed. KSW 1999-07
- ppr (ManyOccs tails) = pprShortTailCallInfo tails
+ ppr (ManyOccs tails) = text "Many" <> parens (pprShortTailCallInfo tails)
ppr IAmDead = text "Dead"
ppr (IAmALoopBreaker rule_only tails)
= text "LoopBreaker" <> pp_ro <> pprShortTailCallInfo tails
=====================================
compiler/GHC/Types/Unique/FM.hs
=====================================
@@ -53,7 +53,7 @@ module GHC.Types.Unique.FM (
plusUFM,
strictPlusUFM,
plusUFM_C,
- strictPlusUFM_C,
+ strictPlusUFM_C, strictPlusUFM_C_Directly,
plusUFM_CD,
plusUFM_CD2,
mergeUFM,
@@ -281,6 +281,9 @@ plusUFM_C f (UFM x) (UFM y) = UFM (M.unionWith f x y)
strictPlusUFM_C :: (elt -> elt -> elt) -> UniqFM key elt -> UniqFM key elt -> UniqFM key elt
strictPlusUFM_C f (UFM x) (UFM y) = UFM (MS.unionWith f x y)
+strictPlusUFM_C_Directly :: (Unique -> elt -> elt -> elt) -> UniqFM key elt -> UniqFM key elt -> UniqFM key elt
+strictPlusUFM_C_Directly f (UFM x) (UFM y) = UFM (MS.unionWithKey (f . mkUniqueGrimily) x y)
+
-- | `plusUFM_CD f m1 d1 m2 d2` merges the maps using `f` as the
-- combinding function and `d1` resp. `d2` as the default value if
-- there is no entry in `m1` reps. `m2`. The domain is the union of
=====================================
compiler/GHC/Types/Unique/Set.hs
=====================================
@@ -40,6 +40,7 @@ module GHC.Types.Unique.Set (
lookupUniqSet_Directly,
partitionUniqSet,
mapUniqSet,
+ mapUniqSetToUFM, mapMaybeUniqSetToUFM,
unsafeUFMToUniqSet,
nonDetEltsUniqSet,
nonDetKeysUniqSet,
@@ -211,6 +212,14 @@ mapUniqSet f = mkUniqSet . map f . nonDetEltsUniqSet
mapMaybeUniqSet_sameUnique :: (a -> Maybe b) -> UniqSet a -> UniqSet b
mapMaybeUniqSet_sameUnique f (UniqSet a) = UniqSet $ mapMaybeUFM_sameUnique f a
+mapUniqSetToUFM :: (a -> b) -> UniqSet a -> UniqFM a b
+-- Same keys, new values
+mapUniqSetToUFM f (UniqSet ufm) = mapUFM f ufm
+
+mapMaybeUniqSetToUFM :: (a -> Maybe b) -> UniqSet a -> UniqFM a b
+-- Same keys, new values
+mapMaybeUniqSetToUFM f (UniqSet ufm) = mapMaybeUFM f ufm
+
-- Two 'UniqSet's are considered equal if they contain the same
-- uniques.
instance Eq (UniqSet a) where
=====================================
compiler/GHC/Types/Var/Env.hs
=====================================
@@ -12,7 +12,8 @@ module GHC.Types.Var.Env (
elemVarEnv, disjointVarEnv, anyVarEnv,
extendVarEnv, extendVarEnv_C, extendVarEnv_Acc,
extendVarEnvList,
- strictPlusVarEnv, plusVarEnv, plusVarEnv_C, strictPlusVarEnv_C,
+ strictPlusVarEnv, plusVarEnv, plusVarEnv_C,
+ strictPlusVarEnv_C, strictPlusVarEnv_C_Directly,
plusVarEnv_CD, plusMaybeVarEnv_C,
plusVarEnvList, alterVarEnv,
delVarEnvList, delVarEnv,
@@ -525,6 +526,7 @@ delVarEnv :: VarEnv a -> Var -> VarEnv a
minusVarEnv :: VarEnv a -> VarEnv b -> VarEnv a
plusVarEnv_C :: (a -> a -> a) -> VarEnv a -> VarEnv a -> VarEnv a
strictPlusVarEnv_C :: (a -> a -> a) -> VarEnv a -> VarEnv a -> VarEnv a
+strictPlusVarEnv_C_Directly :: (Unique -> a -> a -> a) -> VarEnv a -> VarEnv a -> VarEnv a
plusVarEnv_CD :: (a -> a -> a) -> VarEnv a -> a -> VarEnv a -> a -> VarEnv a
plusMaybeVarEnv_C :: (a -> a -> Maybe a) -> VarEnv a -> VarEnv a -> VarEnv a
mapVarEnv :: (a -> b) -> VarEnv a -> VarEnv b
@@ -552,6 +554,7 @@ extendVarEnv_Acc = addToUFM_Acc
extendVarEnvList = addListToUFM
plusVarEnv_C = plusUFM_C
strictPlusVarEnv_C = strictPlusUFM_C
+strictPlusVarEnv_C_Directly = strictPlusUFM_C_Directly
plusVarEnv_CD = plusUFM_CD
plusMaybeVarEnv_C = plusMaybeUFM_C
delVarEnvList = delListFromUFM
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6b5e7254ad0f0d3bd68b1972934e89c…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6b5e7254ad0f0d3bd68b1972934e89c…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 6 commits: AArch64: Simplify CmmAssign and CmmStore
by Marge Bot (@marge-bot) 18 Nov '25
by Marge Bot (@marge-bot) 18 Nov '25
18 Nov '25
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
0a64a78b by Sven Tennie at 2025-11-15T20:31:10-05:00
AArch64: Simplify CmmAssign and CmmStore
The special handling for floats was fake: The general case is always
used. So, the additional code path isn't needed (and only adds
complexity for the reader.)
- - - - -
15b311be by sheaf at 2025-11-15T20:32:02-05:00
SimpleOpt: refactor & push coercions into lambdas
This commit improves the simple optimiser (in GHC.Core.SimpleOpt)
in a couple of ways:
- The logic to push coercion lambdas is shored up.
The function 'pushCoercionIntoLambda' used to be called in 'finish_app',
but this meant we could not continue to optimise the program after
performing this transformation.
Now, we call 'pushCoercionIntoLambda' as part of 'simple_app'.
Doing so can be important when dealing with unlifted newtypes,
as explained in Note [Desugaring unlifted newtypes].
- The code is re-structured to avoid duplication and out-of-sync
code paths.
Now, 'simple_opt_expr' defers to 'simple_app' for the 'App', 'Var',
'Cast' and 'Lam' cases. This means all the logic for those is
centralised in a single place (e.g. the 'go_lam' helper function).
To do this, the general structure is brought a bit closer to the
full-blown simplifier, with a notion of 'continuation'
(see 'SimpleContItem').
This commit also modifies GHC.Core.Opt.Arity.pushCoercionIntoLambda to
apply a substitution (a slight generalisation of its existing implementation).
- - - - -
b33284c7 by sheaf at 2025-11-15T20:32:02-05:00
Improve typechecking of data constructors
This commit changes the way in which we perform typecheck data
constructors, in particular how we make multiplicities line up.
Now, impedance matching occurs as part of the existing subsumption
machinery. See the revamped Note [Typechecking data constructors] in
GHC.Tc.Gen.App, as well as Note [Polymorphisation of linear fields]
in GHC.Core.Multiplicity.
This allows us to get rid of a fair amount of hacky code that was
added with the introduction of LinearTypes; in particular the logic of
GHC.Tc.Gen.Head.tcInferDataCon.
-------------------------
Metric Decrease:
T10421
T14766
T15164
T15703
T19695
T5642
T9630
WWRec
-------------------------
- - - - -
b6faf5d0 by sheaf at 2025-11-15T20:32:02-05:00
Handle unsaturated rep-poly newtypes
This commit allows GHC to handle unsaturated occurrences of unlifted
newtype constructors. The plan is detailed in
Note [Eta-expanding rep-poly unlifted newtypes]
in GHC.Tc.Utils.Concrete: for unsaturated unlifted newtypes, we perform
the appropriate representation-polymorphism check in tcInstFun.
- - - - -
682bf979 by Mike Pilgrem at 2025-11-16T16:44:14+00:00
Fix #26293 Valid stack.yaml for hadrian
- - - - -
f4ab5d9e by Simon Peyton Jones at 2025-11-18T09:00:02-05:00
Fix a bug in defaulting
Addresses #26582
Defaulting was doing some unification but then failing to
iterate. Silly.
I discovered that the main solver was unnecessarily iterating even
if there was a unification for an /outer/ unification variable, so
I fixed that too.
- - - - -
73 changed files:
- compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/Coercion/Opt.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Multiplicity.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/Simplify/Iteration.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/TyCo/FVs.hs
- compiler/GHC/Core/TyCo/Rep.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Driver/Config/Core/Lint.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Syn/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Match.hs
- compiler/GHC/HsToCore/Utils.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Iface/Type.hs
- compiler/GHC/Tc/Gen/App.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/Expr.hs-boot
- compiler/GHC/Tc/Gen/Head.hs
- compiler/GHC/Tc/Gen/Match.hs
- compiler/GHC/Tc/Gen/Pat.hs
- compiler/GHC/Tc/Solver/Default.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Solver/Solve.hs
- compiler/GHC/Tc/Types/Evidence.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/Tc/Utils/Concrete.hs
- compiler/GHC/Tc/Utils/TcType.hs
- compiler/GHC/Tc/Utils/Unify.hs
- compiler/GHC/Tc/Zonk/Type.hs
- compiler/GHC/Types/Id/Make.hs
- hadrian/stack.yaml
- hadrian/stack.yaml.lock
- testsuite/tests/diagnostic-codes/codes.stdout
- testsuite/tests/ghci/scripts/T8959b.stderr
- testsuite/tests/ghci/scripts/ghci051.stderr
- testsuite/tests/indexed-types/should_compile/T12538.stderr
- + testsuite/tests/linear/should_compile/LinearEtaExpansions.hs
- testsuite/tests/linear/should_compile/all.T
- testsuite/tests/linear/should_fail/TypeClass.hs
- testsuite/tests/linear/should_fail/TypeClass.stderr
- testsuite/tests/linear/should_run/LinearGhci.stdout
- testsuite/tests/numeric/should_compile/T16402.stderr-ws-64
- testsuite/tests/parser/should_compile/DumpTypecheckedAst.stderr
- testsuite/tests/perf/compiler/all.T
- testsuite/tests/rep-poly/RepPolyCase1.stderr
- − testsuite/tests/rep-poly/RepPolyCase2.stderr
- testsuite/tests/rep-poly/RepPolyRule3.stderr
- testsuite/tests/rep-poly/RepPolyTuple4.stderr
- testsuite/tests/rep-poly/T13233.stderr
- − testsuite/tests/rep-poly/T17021.stderr
- testsuite/tests/rep-poly/T20363b.stderr
- − testsuite/tests/rep-poly/T21650_a.stderr
- − testsuite/tests/rep-poly/T21650_b.stderr
- + testsuite/tests/rep-poly/T26072.hs
- testsuite/tests/rep-poly/UnliftedNewtypesLevityBinder.stderr
- testsuite/tests/rep-poly/all.T
- + testsuite/tests/typecheck/should_compile/T26582.hs
- testsuite/tests/typecheck/should_compile/all.T
- testsuite/tests/typecheck/should_fail/T15883e.stderr
- testsuite/tests/typecheck/should_fail/T2414.stderr
- testsuite/tests/typecheck/should_fail/T2534.stderr
- testsuite/tests/typecheck/should_fail/T7264.stderr
- utils/haddock/hypsrc-test/ref/src/Classes.html
- utils/haddock/hypsrc-test/ref/src/Quasiquoter.html
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7a96267912a2aff4fac3e1f9108ca4…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7a96267912a2aff4fac3e1f9108ca4…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/26552] testsuite: Accept output of tests failing in ext-interp way due to differing...
by Zubin (@wz1000) 18 Nov '25
by Zubin (@wz1000) 18 Nov '25
18 Nov '25
Zubin pushed to branch wip/26552 at Glasgow Haskell Compiler / GHC
Commits:
122f4364 by Zubin Duggal at 2025-11-18T18:52:40+05:30
testsuite: Accept output of tests failing in ext-interp way due to differing compilation requirements
Fixes #26552
- - - - -
7 changed files:
- + testsuite/tests/driver/T20696/T20696.stderr-ext-interp
- testsuite/tests/driver/T20696/all.T
- testsuite/tests/driver/fat-iface/all.T
- + testsuite/tests/driver/fat-iface/fat012.stderr-ext-interp
- + testsuite/tests/driver/fat-iface/fat015.stderr-ext-interp
- + testsuite/tests/splice-imports/SI07.stderr-ext-interp
- testsuite/tests/splice-imports/all.T
Changes:
=====================================
testsuite/tests/driver/T20696/T20696.stderr-ext-interp
=====================================
@@ -0,0 +1,3 @@
+[1 of 3] Compiling C ( C.hs, C.o )
+[2 of 3] Compiling B ( B.hs, B.o )
+[3 of 3] Compiling A ( A.hs, A.o )
=====================================
testsuite/tests/driver/T20696/all.T
=====================================
@@ -1,5 +1,4 @@
test('T20696', [extra_files(['A.hs', 'B.hs', 'C.hs'])
- , expect_broken_for(26552, ['ext-interp'])
, unless(ghc_dynamic(), skip)], multimod_compile, ['A', ''])
test('T20696-static', [extra_files(['A.hs', 'B.hs', 'C.hs'])
, when(ghc_dynamic(), skip)], multimod_compile, ['A', ''])
=====================================
testsuite/tests/driver/fat-iface/all.T
=====================================
@@ -9,12 +9,12 @@ test('fat010', [req_th,extra_files(['THA.hs', 'THB.hs', 'THC.hs']), copy_files],
# Check linking works when using -fbyte-code-and-object-code
test('fat011', [req_th, extra_files(['FatMain.hs', 'FatTH.hs', 'FatQuote.hs'])], multimod_compile, ['FatMain', '-fbyte-code-and-object-code -fprefer-byte-code'])
# Check that we use interpreter rather than enable dynamic-too if needed for TH
-test('fat012', [req_th, expect_broken_for(26552, ['ext-interp']), unless(ghc_dynamic(), skip), extra_files(['FatTH.hs', 'FatQuote.hs'])], multimod_compile, ['FatTH', '-fprefer-byte-code'])
+test('fat012', [req_th, unless(ghc_dynamic(), skip), extra_files(['FatTH.hs', 'FatQuote.hs'])], multimod_compile, ['FatTH', '-fprefer-byte-code'])
# Check that no objects are generated if using -fno-code and -fprefer-byte-code
test('fat013', [req_th, req_bco, extra_files(['FatTH.hs', 'FatQuote.hs'])], multimod_compile, ['FatTH', '-fno-code -fprefer-byte-code'])
# When using interpreter should not produce objects
test('fat014', [req_th, extra_files(['FatTH.hs', 'FatQuote.hs']), extra_run_opts('-fno-code')], ghci_script, ['fat014.script'])
-test('fat015', [req_th, expect_broken_for(26552, ['ext-interp']), unless(ghc_dynamic(), skip), extra_files(['FatQuote.hs', 'FatQuote1.hs', 'FatQuote2.hs', 'FatTH1.hs', 'FatTH2.hs', 'FatTHTop.hs'])], multimod_compile, ['FatTHTop', '-fno-code -fwrite-interface'])
+test('fat015', [req_th, unless(ghc_dynamic(), skip), extra_files(['FatQuote.hs', 'FatQuote1.hs', 'FatQuote2.hs', 'FatTH1.hs', 'FatTH2.hs', 'FatTHTop.hs'])], multimod_compile, ['FatTHTop', '-fno-code -fwrite-interface'])
test('T22807', [req_th, unless(ghc_dynamic(), skip), extra_files(['T22807A.hs', 'T22807B.hs'])]
, makefile_test, ['T22807'])
test('T22807_ghci', [req_th, unless(ghc_dynamic(), skip), extra_files(['T22807_ghci.hs'])]
=====================================
testsuite/tests/driver/fat-iface/fat012.stderr-ext-interp
=====================================
@@ -0,0 +1,2 @@
+[1 of 2] Compiling FatQuote ( FatQuote.hs, FatQuote.o )
+[2 of 2] Compiling FatTH ( FatTH.hs, FatTH.o )
=====================================
testsuite/tests/driver/fat-iface/fat015.stderr-ext-interp
=====================================
@@ -0,0 +1,6 @@
+[1 of 6] Compiling FatQuote ( FatQuote.hs, FatQuote.o, interpreted )
+[2 of 6] Compiling FatQuote1 ( FatQuote1.hs, interpreted )
+[3 of 6] Compiling FatQuote2 ( FatQuote2.hs, FatQuote2.o )
+[4 of 6] Compiling FatTH1 ( FatTH1.hs, nothing )
+[5 of 6] Compiling FatTH2 ( FatTH2.hs, nothing )
+[6 of 6] Compiling FatTHTop ( FatTHTop.hs, nothing )
=====================================
testsuite/tests/splice-imports/SI07.stderr-ext-interp
=====================================
@@ -0,0 +1,3 @@
+[1 of 3] Compiling SI05A ( SI05A.hs, SI05A.o )
+[2 of 3] Compiling SI07A ( SI07A.hs, nothing )
+[3 of 3] Compiling SI07 ( SI07.hs, nothing )
=====================================
testsuite/tests/splice-imports/all.T
=====================================
@@ -9,7 +9,7 @@ test('SI03', [extra_files(["SI01A.hs"])], multimod_compile_fail, ['SI03', '-v0']
test('SI04', [extra_files(["SI01A.hs"])], multimod_compile, ['SI04', '-v0'])
test('SI05', [extra_files(["SI01A.hs"])], multimod_compile_fail, ['SI05', '-v0'])
test('SI06', [extra_files(["SI01A.hs"])], multimod_compile, ['SI06', '-v0'])
-test('SI07', [expect_broken_for(26552, ['ext-interp']), unless(ghc_dynamic(), skip), extra_files(["SI05A.hs"])], multimod_compile, ['SI07', '-fwrite-interface -fno-code'])
+test('SI07', [unless(ghc_dynamic(), skip), extra_files(["SI05A.hs"])], multimod_compile, ['SI07', '-fwrite-interface -fno-code'])
# Instance tests
test('SI08', [extra_files(["ClassA.hs", "InstanceA.hs"])], multimod_compile_fail, ['SI08', '-v0'])
test('SI09', [extra_files(["ClassA.hs", "InstanceA.hs"])], multimod_compile, ['SI09', '-v0'])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/122f4364118c41ced102449d28c7014…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/122f4364118c41ced102449d28c7014…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
Zubin pushed new branch wip/26552 at Glasgow Haskell Compiler / GHC
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/26552
You're receiving this email because of your account on gitlab.haskell.org.
1
0
18 Nov '25
Simon Peyton Jones pushed to branch wip/T26582 at Glasgow Haskell Compiler / GHC
Commits:
dc3f7285 by Simon Peyton Jones at 2025-11-17T23:49:46+00:00
Fix a bug in defaulting
Addresses #26582
Defaulting was doing some unification but then failing to
iterate. Silly.
I discovered that the main solver was unnecessarily iterating even
if there was a unification for an /outer/ unification variable, so
I fixed that too.
- - - - -
6 changed files:
- compiler/GHC/Tc/Solver/Default.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Solver/Solve.hs
- compiler/GHC/Tc/Utils/TcType.hs
- + testsuite/tests/typecheck/should_compile/T26582.hs
- testsuite/tests/typecheck/should_compile/all.T
Changes:
=====================================
compiler/GHC/Tc/Solver/Default.hs
=====================================
@@ -395,9 +395,11 @@ tryConstraintDefaulting wc
| isEmptyWC wc
= return wc
| otherwise
- = do { (unif_happened, better_wc) <- reportCoarseGrainUnifications $
- go_wc False wc
- -- We may have done unifications; so solve again
+ = do { (outermost_unif_lvl, better_wc) <- reportCoarseGrainUnifications $
+ go_wc False wc
+
+ -- We may have done unifications; if so, solve again
+ ; let unif_happened = not (isInfiniteTcLevel outermost_unif_lvl)
; solveAgainIf unif_happened better_wc }
where
go_wc :: Bool -> WantedConstraints -> TcS WantedConstraints
@@ -414,14 +416,17 @@ tryConstraintDefaulting wc
else return (Just ct) }
go_implic :: Bool -> Implication -> TcS Implication
- go_implic encl_eqs implic@(Implic { ic_status = status, ic_wanted = wanteds
- , ic_given_eqs = given_eqs, ic_binds = binds })
+ go_implic encl_eqs implic@(Implic { ic_tclvl = tclvl
+ , ic_status = status, ic_wanted = wanteds
+ , ic_given_eqs = given_eqs, ic_binds = binds })
| isSolvedStatus status
= return implic -- Nothing to solve inside here
| otherwise
= do { let encl_eqs' = encl_eqs || given_eqs /= NoGivenEqs
- ; wanteds' <- setEvBindsTcS binds $
+ ; wanteds' <- setTcLevelTcS tclvl $
+ -- Set the levels so that reportCoarseGrainUnifications works
+ setEvBindsTcS binds $
-- defaultCallStack sets a binding, so
-- we must set the correct binding group
go_wc encl_eqs' wanteds
@@ -660,7 +665,9 @@ Wrinkles:
f x = case x of T1 -> True
Should we infer f :: T a -> Bool, or f :: T a -> a. Both are valid, but
- neither is more general than the other.
+ neither is more general than the other. But by the time defaulting takes
+ place all let-bound variables have got their final types; defaulting won't
+ affect let-generalisation.
(DE2) We still can't unify if there is a skolem-escape check, or an occurs check,
or it it'd mean unifying a TyVarTv with a non-tyvar. It's only the
=====================================
compiler/GHC/Tc/Solver/Monad.hs
=====================================
@@ -1877,18 +1877,18 @@ reportFineGrainUnifications (TcS thing_inside)
; recordUnifications outer_wu unif_tvs
; return (unif_tvs, res) }
-reportCoarseGrainUnifications :: TcS a -> TcS (Bool, a)
+reportCoarseGrainUnifications :: TcS a -> TcS (TcLevel, a)
-- Record whether any useful unifications are done by thing_inside
+-- Specifically: return the TcLevel of the outermost (smallest level)
+-- unification variable that has been unified, or infiniteTcLevel if none
-- Remember to propagate the information to the enclosing context
reportCoarseGrainUnifications (TcS thing_inside)
= TcS $ \ env@(TcSEnv { tcs_what = outer_what }) ->
case outer_what of
- WU_None
- -> do { (unif_happened, _, res) <- report_coarse_grain_unifs env thing_inside
- ; return (unif_happened, res) }
+ WU_None -> report_coarse_grain_unifs env thing_inside
WU_Coarse outer_ul_ref
- -> do { (unif_happened, inner_ul, res) <- report_coarse_grain_unifs env thing_inside
+ -> do { (inner_ul, res) <- report_coarse_grain_unifs env thing_inside
-- Propagate to outer_ul_ref
; outer_ul <- TcM.readTcRef outer_ul_ref
@@ -1897,31 +1897,32 @@ reportCoarseGrainUnifications (TcS thing_inside)
; TcM.traceTc "reportCoarse(Coarse)" $
vcat [ text "outer_ul" <+> ppr outer_ul
- , text "inner_ul" <+> ppr inner_ul
- , text "unif_happened" <+> ppr unif_happened ]
- ; return (unif_happened, res) }
+ , text "inner_ul" <+> ppr inner_ul]
+ ; return (inner_ul, res) }
WU_Fine outer_tvs_ref
-> do { (unif_tvs,res) <- report_fine_grain_unifs env thing_inside
- ; let unif_happened = not (isEmptyVarSet unif_tvs)
- ; when unif_happened $
- TcM.updTcRef outer_tvs_ref (`unionVarSet` unif_tvs)
+
+ -- Propagate to outer_tvs_rev
+ ; TcM.updTcRef outer_tvs_ref (`unionVarSet` unif_tvs)
+
+ ; let outermost_unif_lvl = minTcTyVarSetLevel unif_tvs
; TcM.traceTc "reportCoarse(Fine)" $
vcat [ text "unif_tvs" <+> ppr unif_tvs
- , text "unif_happened" <+> ppr unif_happened ]
- ; return (unif_happened, res) }
+ , text "unif_happened" <+> ppr outermost_unif_lvl ]
+ ; return (outermost_unif_lvl, res) }
report_coarse_grain_unifs :: TcSEnv -> (TcSEnv -> TcM a)
- -> TcM (Bool, TcLevel, a)
--- Returns (unif_happened, coarse_inner_ul, res)
+ -> TcM (TcLevel, a)
+-- Returns the level number of the outermost
+-- unification variable that is unified
report_coarse_grain_unifs env thing_inside
= do { inner_ul_ref <- TcM.newTcRef infiniteTcLevel
; res <- thing_inside (env { tcs_what = WU_Coarse inner_ul_ref })
- ; inner_ul <- TcM.readTcRef inner_ul_ref
- ; ambient_lvl <- TcM.getTcLevel
- ; let unif_happened = ambient_lvl `deeperThanOrSame` inner_ul
- ; return (unif_happened, inner_ul, res) }
-
+ ; inner_ul <- TcM.readTcRef inner_ul_ref
+ ; TcM.traceTc "report_coarse" $
+ text "inner_lvl =" <+> ppr inner_ul
+ ; return (inner_ul, res) }
report_fine_grain_unifs :: TcSEnv -> (TcSEnv -> TcM a)
-> TcM (TcTyVarSet, a)
=====================================
compiler/GHC/Tc/Solver/Solve.hs
=====================================
@@ -118,28 +118,34 @@ simplify_loop n limit definitely_redo_implications
, int (lengthBag simples) <+> text "simples to solve" ])
; traceTcS "simplify_loop: wc =" (ppr wc)
- ; (simple_unif_happened, wc1)
+ ; ambient_lvl <- getTcLevel
+ ; (simple_unif_lvl, wc1)
<- reportCoarseGrainUnifications $ -- See Note [Superclass iteration]
solveSimpleWanteds simples
-- Any insoluble constraints are in 'simples' and so get rewritten
-- See Note [Rewrite insolubles] in GHC.Tc.Solver.InertSet
-- Next, solve implications from wc_impl
- ; (impl_unif_happened, implics')
+ ; let simple_unif_happened = ambient_lvl `deeperThanOrSame` simple_unif_lvl
+ ; (implic_unif_lvl, implics')
<- if not (definitely_redo_implications -- See Note [Superclass iteration]
|| simple_unif_happened) -- for this conditional
- then return (False, implics)
+ then return (infiniteTcLevel, implics)
else reportCoarseGrainUnifications $
solveNestedImplications implics
; let wc' = wc1 { wc_impl = wc_impl wc1 `unionBags` implics' }
- ; csTraceTcS $ text "unif_happened" <+> ppr impl_unif_happened
-
-- We iterate the loop only if the /implications/ did some relevant
- -- unification. Even if the /simples/ did unifications we don't need
- -- to re-do them.
- ; maybe_simplify_again (n+1) limit impl_unif_happened wc' }
+ -- unification, hence looking only at `implic_unif_lvl`. (Even if the
+ -- /simples/ did unifications we don't need to re-do them.)
+ -- Also note that we only iterate if `implic_unify_lvl` is /equal to/
+ -- the current level; if it is less , we'll iterate some outer level,
+ -- which will bring us back here anyway.
+ -- See Note [When to iterate the solver: unifications]
+ ; let implic_unif_happened = implic_unif_lvl `sameDepthAs` ambient_lvl
+ ; csTraceTcS $ text "implic_unif_happened" <+> ppr implic_unif_happened
+ ; maybe_simplify_again (n+1) limit implic_unif_happened wc' }
data NextAction
= NA_Stop -- Just return the WantedConstraints
@@ -148,7 +154,9 @@ data NextAction
Bool -- See `definitely_redo_implications` in the comment
-- for `simplify_loop`
-maybe_simplify_again :: Int -> IntWithInf -> Bool
+maybe_simplify_again :: Int -> IntWithInf
+ -> Bool -- True <=> Solving the implications did some unifications
+ -- at the current level; so iterate
-> WantedConstraints -> TcS WantedConstraints
maybe_simplify_again n limit unif_happened wc@(WC { wc_simple = simples })
= do { -- Look for reasons to stop or continue
@@ -222,10 +230,10 @@ and if so it seems a pity to waste time iterating the implications (forall b. bl
(If we add new Given superclasses it's a different matter: it's really worth looking
at the implications.)
-Hence the definitely_redo_implications flag to simplify_loop. It's usually
-True, but False in the case where the only reason to iterate is new Wanted
-superclasses. In that case we check whether the new Wanteds actually led to
-any new unifications, and iterate the implications only if so.
+Hence the `definitely_redo_implications` flag to `simplify_loop`. It's usually True,
+but False in the case where the only reason to iterate is new Wanted superclasses.
+In that case we check whether the new Wanteds actually led to any new unifications
+(at all), and iterate the implications only if so.
Note [When to iterate the solver: unifications]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
=====================================
compiler/GHC/Tc/Utils/TcType.hs
=====================================
@@ -45,7 +45,7 @@ module GHC.Tc.Utils.TcType (
TcLevel(..), topTcLevel, pushTcLevel, isTopTcLevel,
strictlyDeeperThan, deeperThanOrSame, sameDepthAs,
tcTypeLevel, tcTyVarLevel, maxTcLevel, minTcLevel,
- infiniteTcLevel,
+ infiniteTcLevel, isInfiniteTcLevel,
--------------------------------
-- MetaDetails
@@ -879,6 +879,10 @@ isTopTcLevel :: TcLevel -> Bool
isTopTcLevel (TcLevel 0) = True
isTopTcLevel _ = False
+isInfiniteTcLevel :: TcLevel -> Bool
+isInfiniteTcLevel QLInstVar = True
+isInfiniteTcLevel _ = False
+
pushTcLevel :: TcLevel -> TcLevel
-- See Note [TcLevel assignment]
pushTcLevel (TcLevel us) = TcLevel (us + 1)
=====================================
testsuite/tests/typecheck/should_compile/T26582.hs
=====================================
@@ -0,0 +1,35 @@
+{-# LANGUAGE GADTs #-}
+
+module T26582 where
+
+sametype :: a -> a -> Int
+sametype = sametype
+
+f :: Eq a => (a->Int) -> Int
+f = f
+
+data T b where T1 :: T Bool
+
+g1 :: T b -> Int
+g1 v = f (\x -> case v of { T1 -> sametype x True })
+
+g2 :: Eq c => c -> T b -> Int
+g2 c v = f (\x -> case v of { T1 -> sametype x c })
+
+{- The point is that we get something like
+
+ Wanted: [W] d : Eq alpha[1]
+ Implication
+ level: 2
+ Given: b~Bool
+
+ Wanted: [W] alpha[1]~Bool -- For g1
+ Wanted: [W] alpha[1]~c -- For g2
+
+So alpha is untouchable under the (b~Bool) from the GADT.
+And yet in the end it's easy to solve
+via alpha:=Bool, or alpha:=c resp
+
+But having done that defaulting we must then remember to
+solved that `d : Eq alpha`! We forgot to so so in #26582.
+-}
=====================================
testsuite/tests/typecheck/should_compile/all.T
=====================================
@@ -956,3 +956,4 @@ test('T26457', normal, compile, [''])
test('T17705', normal, compile, [''])
test('T14745', normal, compile, [''])
test('T26451', normal, compile, [''])
+test('T26582', normal, compile, [''])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/dc3f7285eaaa8c34d07c9db64719680…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/dc3f7285eaaa8c34d07c9db64719680…
You're receiving this email because of your account on gitlab.haskell.org.
1
0