Simon Peyton Jones pushed to branch wip/T23162-part2 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: = <expr>
node: =
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
- - - - -
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
- - - - -
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
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
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.
- - - - -
682bf979 by Mike Pilgrem at 2025-11-16T16:44:14+00:00
Fix #26293 Valid stack.yaml for hadrian
- - - - -
acc70c3a by Simon Peyton Jones at 2025-11-18T16:21:20-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.
- - - - -
c12fa73e by Simon Peyton Jones at 2025-11-19T02:55:01-05:00
Make PmLit be in Ord, and use it in Map
This MR addresses #26514, by changing from
data PmAltConSet = PACS !(UniqDSet ConLike) ![PmLit]
to
data PmAltConSet = PACS !(UniqDSet ConLike) !(Map PmLit PmLit)
This matters when doing pattern-match overlap checking, when there
is a very large set of patterns. For most programs it makes
no difference at all.
For the N=5000 case of the repro case in #26514, compiler
mutator time (with `-fno-code`) goes from 1.9s to 0.43s.
All for the price for an Ord instance for PmLit
- - - - -
41b84f40 by sheaf at 2025-11-19T02:55:52-05:00
Add passing tests for #26311 and #26072
This commit adds two tests cases that now pass since landing the changes
to typechecking of data constructors in b33284c7.
Fixes #26072 #26311
- - - - -
1faa758a by sheaf at 2025-11-19T02:55:52-05:00
mkCast: weaken bad cast warning for multiplicity
This commit weakens the warning message emitted when constructing a bad
cast in mkCast to ignore multiplicity.
Justification: since b33284c7, GHC uses sub-multiplicity coercions to
typecheck data constructors. The coercion optimiser is free to discard
these coercions, both for performance reasons, and because GHC's Core
simplifier does not (yet) preserve linearity.
We thus weaken 'mkCast' to use 'eqTypeIgnoringMultiplicity' instead of
'eqType', to avoid getting many spurious warnings about mismatched
multiplicities.
- - - - -
277d947b by Simon Peyton Jones at 2025-11-19T09:22:17+00:00
Better injectivity for closed type families
The idea is in #23162.
more docs needed
- - - - -
36ec5f41 by Simon Peyton Jones at 2025-11-19T09:22:17+00:00
Wibbles
- - - - -
8e8c0f06 by Simon Peyton Jones at 2025-11-19T09:22:17+00:00
Only do top-level fundeps if there are no local ones
- - - - -
0833f333 by Simon Peyton Jones at 2025-11-19T09:22:18+00:00
More wibbles
- - - - -
5a7b9503 by Simon Peyton Jones at 2025-11-19T09:22:18+00:00
better still
- - - - -
78119961 by Simon Peyton Jones at 2025-11-19T09:22:18+00:00
WIP [skip ci]
improving the injectivity calculation
- - - - -
b3f9985c by Simon Peyton Jones at 2025-11-19T09:22:18+00:00
Solve Yikes1 and Yikes2
- - - - -
382894f6 by Simon Peyton Jones at 2025-11-19T09:22:18+00:00
Wibble unused variable
- - - - -
88c932bb by Simon Peyton Jones at 2025-11-19T09:22:18+00:00
Better
Fix Yikes 3
Ensure we do F a ~ F b for families with no eqns
- - - - -
af722cf5 by Simon Peyton Jones at 2025-11-19T09:22:18+00:00
Refine Yikes 3
- - - - -
b653d951 by Simon Peyton Jones at 2025-11-19T09:22:18+00:00
More good stuff
- - - - -
f2bab720 by Simon Peyton Jones at 2025-11-19T09:22:18+00:00
Wibbles
Fix to niFixSubst
- - - - -
b110ec03 by Simon Peyton Jones at 2025-11-19T10:15:56+00:00
Add missing stderr file
- - - - -
221 changed files:
- .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/FamInstEnv.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/Core/Utils.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/Pmc/Solver/Types.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/Gen/Splice.hs
- compiler/GHC/Tc/Instance/Class.hs
- compiler/GHC/Tc/Solver.hs
- compiler/GHC/Tc/Solver/Default.hs
- compiler/GHC/Tc/Solver/FunDeps.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Solver/Solve.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
- compiler/GHC/Types/SourceText.hs
- compiler/GHC/Types/TyThing.hs
- 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/stack.yaml
- hadrian/stack.yaml.lock
- libraries/ghc-internal/src/GHC/Internal/TH/Monad.hs
- linters/lint-codes/LintCodes/Static.hs
- testsuite/tests/backpack/should_fail/T19244a.stderr
- + testsuite/tests/codeGen/should_run/T26537.hs
- + testsuite/tests/codeGen/should_run/T26537.stdout
- testsuite/tests/codeGen/should_run/all.T
- testsuite/tests/dependent/should_fail/T11334b.stderr
- testsuite/tests/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/CEqCanOccursCheck.hs
- testsuite/tests/indexed-types/should_compile/T12538.stderr
- testsuite/tests/indexed-types/should_fail/T12522a.hs
- 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/linear/should_run/T26311.hs
- + testsuite/tests/linear/should_run/T26311.stdout
- testsuite/tests/linear/should_run/all.T
- testsuite/tests/numeric/should_compile/T16402.stderr-ws-64
- testsuite/tests/parser/should_compile/DumpTypecheckedAst.stderr
- testsuite/tests/perf/compiler/all.T
- testsuite/tests/pmcheck/should_compile/pmcOrPats.stderr
- 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/T26072b.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_compile/T26582.hs
- testsuite/tests/typecheck/should_compile/all.T
- testsuite/tests/typecheck/should_fail/T15629.stderr
- testsuite/tests/typecheck/should_fail/T15883e.stderr
- + testsuite/tests/typecheck/should_fail/T23162b.hs
- + testsuite/tests/typecheck/should_fail/T23162b.stderr
- + testsuite/tests/typecheck/should_fail/T23162c.hs
- + testsuite/tests/typecheck/should_fail/T23162d.hs
- testsuite/tests/typecheck/should_fail/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/dd4dc342d7dcc697d7c438250aeba13...
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/dd4dc342d7dcc697d7c438250aeba13...
You're receiving this email because of your account on gitlab.haskell.org.