[Git][ghc/ghc][wip/haddock-move-binary-instances] 275 commits: Deprecate -Wdata-kinds-tc, make DataKinds issues in typechecker become errors

Cheng Shao pushed to branch wip/haddock-move-binary-instances at Glasgow Haskell Compiler / GHC
Commits:
d3e60e97 by Ryan Scott at 2025-06-18T22:29:21-04:00
Deprecate -Wdata-kinds-tc, make DataKinds issues in typechecker become errors
!11314 introduced the `-Wdata-kinds-tc` warning as part of a fix for #22141.
This was a temporary stopgap measure to allow users who were accidentally
relying on code which needed the `DataKinds` extension in order to typecheck
without having to explicitly enable the extension.
Now that some amount of time has passed, this patch deprecates
`-Wdata-kinds-tc` and upgrades any `DataKinds`-related issues in the
typechecker (which were previously warnings) into errors.
- - - - -
fd5b5177 by Ryan Hendrickson at 2025-06-18T22:30:06-04:00
haddock: Add redact-type-synonyms pragma
`{-# OPTIONS_HADDOCK redact-type-synonyms #-}` pragma will hide the RHS
of type synonyms, and display the result kind instead, if the RHS
contains any unexported types.
- - - - -
fbc0b92a by Vladislav Zavialov at 2025-06-22T04:25:16+03:00
Visible forall in GADTs (#25127)
Add support for visible dependent quantification `forall a -> t` in
types of data constructors, e.g.
data KindVal a where
K :: forall k.
forall (a::k) -> -- now allowed!
k ->
KindVal a
For details, see docs/users_guide/exts/required_type_arguments.rst,
which has gained a new subsection.
DataCon in compiler/GHC/Core/DataCon.hs
---------------------------------------
The main change in this patch is that DataCon, the Core representation
of a data constructor, now uses a different type to store user-written
type variable binders:
- dcUserTyVarBinders :: [InvisTVBinder]
+ dcUserTyVarBinders :: [TyVarBinder]
where
type TyVarBinder = VarBndr TyVar ForAllTyFlag
type InvisTVBinder = VarBndr TyVar Specificity
and
data Specificity = InferredSpec | SpecifiedSpec
data ForAllTyFlag = Invisible Specificity | Required
This change necessitates some boring, mechanical changes scattered
throughout the diff:
... is now used in place of ...
-----------------+---------------
TyVarBinder | InvisTVBinder
IfaceForAllBndr | IfaceForAllSpecBndr
Specified | SpecifiedSpec
Inferred | InferredSpec
mkForAllTys | mkInvisForAllTys
additionally,
tyVarSpecToBinders -- added or removed calls
ifaceForAllSpecToBndrs -- removed calls
Visibility casts in mkDataConRep
--------------------------------
Type abstractions in Core (/\a. e) always have type (forall a. t)
because coreTyLamForAllTyFlag = Specified. This is also true of data
constructor workers. So we may be faced with the following:
data con worker: (forall a. blah)
data con wrapper: (forall a -> blah)
In this case the wrapper must use a visibility cast (e |> ForAllCo ...)
with appropriately set fco_vis{L,R}. Relevant functions:
mkDataConRep in compiler/GHC/Types/Id/Make.hs
dataConUserTyVarBindersNeedWrapper in compiler/GHC/Core/DataCon.hs
mkForAllVisCos in compiler/GHC/Core/Coercion.hs
mkCoreTyLams in compiler/GHC/Core/Make.hs
mkWpForAllCast in compiler/GHC/Tc/Types/Evidence.hs
More specifically:
- dataConUserTyVarBindersNeedWrapper has been updated to answer "yes"
if there are visible foralls in the type of the data constructor.
- mkDataConRep now uses mkCoreTyLams to generate the big lambda
abstractions (/\a b c. e) in the data con wrapper.
- mkCoreTyLams is a variant of mkCoreLams that applies visibility casts
as needed. It similar in purpose to the pre-existing mkWpForAllCast,
so the common bits have been factored out into mkForAllVisCos.
ConDecl in compiler/Language/Haskell/Syntax/Decls.hs
----------------------------------------------------
The surface syntax representation of a data constructor declaration is
ConDecl. In accordance with the proposal, only GADT syntax is extended
with support for visible forall, so we are interested in ConDeclGADT.
ConDeclGADT's field con_bndrs has been renamed to con_outer_bndrs
and is now accompanied by con_inner_bndrs:
con_outer_bndrs :: XRec pass (HsOuterSigTyVarBndrs pass)
con_inner_bndrs :: [HsForAllTelescope pass]
Visible foralls always end up in con_inner_bndrs. The outer binders are
stored and processed separately to support implicit quantification and
the forall-or-nothing rule, a design established by HsSigType.
A side effect of this change is that even in absence of visible foralls,
GHC now permits multiple invisible foralls, e.g.
data T a where { MkT :: forall a b. forall c d. ... -> T a }
But of course, this is done in service of making at least some of these
foralls visible. The entire compiler front-end has been updated to deal
with con_inner_bndrs. See the following modified or added functions:
Parser:
mkGadtDecl in compiler/GHC/Parser/PostProcess.hs
splitLHsGadtTy in compiler/GHC/Hs/Type.hs
Pretty-printer:
pprConDecl in compiler/GHC/Hs/Decls.hs
pprHsForAllTelescope in compiler/GHC/Hs/Type.hs
Renamer:
rnConDecl in compiler/GHC/Rename/Module.hs
bindHsForAllTelescopes in compiler/GHC/Rename/HsType.hs
extractHsForAllTelescopes in compiler/GHC/Rename/HsType.hs
Type checker:
tcConDecl in compiler/GHC/Tc/TyCl.hs
tcGadtConTyVarBndrs in compiler/GHC/Tc/Gen/HsType.hs
Template Haskell
----------------
The TH AST is left unchanged for the moment to avoid breakage. An
attempt to quote or reify a data constructor declaration with visible
forall in its type will result an error:
data ThRejectionReason -- in GHC/HsToCore/Errors/Types.hs
= ...
| ThDataConVisibleForall -- new error constructor
However, as noted in the previous section, GHC now permits multiple
invisible foralls, and TH was updated accordingly. Updated code:
repC in compiler/GHC/HsToCore/Quote.hs
reifyDataCon in compiler/GHC/Tc/Gen/Splice.hs
ppr @Con in libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs
Pattern matching
----------------
Everything described above concerns data constructor declarations, but
what about their use sites? Now it is trickier to type check a pattern
match fn(Con a b c)=... because we can no longer assume that a,b,c are
all value arguments. Indeed, some or all of them may very well turn out
to be required type arguments.
To that end, see the changes to:
tcDataConPat in compiler/GHC/Tc/Gen/Pat.hs
splitConTyArgs in compiler/GHC/Tc/Gen/Pat.hs
and the new helpers split_con_ty_args, zip_pats_bndrs.
This is also the reason the TcRnTooManyTyArgsInConPattern error
constructor has been removed. The new code emits TcRnArityMismatch
or TcRnIllegalInvisibleTypePattern.
Summary
-------
DataCon, ConDecl, as well as all related functions have been updated to
support required type arguments in data constructors.
Test cases:
HieGadtConSigs GadtConSigs_th_dump1 GadtConSigs_th_pprint1
T25127_data T25127_data_inst T25127_infix
T25127_newtype T25127_fail_th_quote T25127_fail_arity
TyAppPat_Tricky
Co-authored-by: mniip
jappie unkown input: jappie
we confirmed later this was due to lack of \n matching.
Anyway movnig on to more unexpected stuff:
```haskell
main :: IO ()
main = do
interact (concatMap interaction . lines)
get's stuck forever. actually `^D` (ctrl+d) unstucks it and runs all input as expected. for example you can get: ```
sdfkds fakdsf unkown input: sdfkdsunkown input: fakdsf
This program works!
```haskell
interaction :: String -> String
interaction "jappie" = "hi \n"
interaction "jakob" = "hello \n"
interaction x = "unkown input: " <> x <> "\n"
main :: IO ()
main = do
interact (concatMap interaction . lines)
the reason is that linebuffering is set for both in and output by default. so lines eats the input lines, and all the \n postfixes make sure the buffer is put out. - - - - - 9fa590a6 by Zubin Duggal at 2025-07-17T06:07:03-04:00 fetch_gitlab: Ensure we copy users_guide.pdf and Haddock.pdf to the release docs directory Fixes #24093 - - - - - cc650b4b by Andrew Lelechenko at 2025-07-17T12:30:24-04:00 Add Data.List.NonEmpty.mapMaybe As per https://github.com/haskell/core-libraries-committee/issues/337 - - - - - 360fa82c by Duncan Coutts at 2025-07-17T12:31:14-04:00 base: Deprecate GHC.Weak.Finalize.runFinalizerBatch https://github.com/haskell/core-libraries-committee/issues/342 - - - - - f4e8466c by Alan Zimmerman at 2025-07-17T12:31:55-04:00 EPA: Update exact printing based on GHC 9.14 tests As a result of migrating the GHC ghc-9.14 branch tests to ghc-exactprint in https://github.com/alanz/ghc-exactprint/tree/ghc-9.14, a couple of discrepancies were picked up - The opening paren for a DefaultDecl was printed in the wrong place - The import declaration level specifiers were not printed. This commit adds those fixes, and some tests for them. The tests brought to light that the ImportDecl ppr instance had not been updated for level specifiers, so it updates that too. - - - - - 8b731e3c by Matthew Pickering at 2025-07-21T13:36:43-04:00 level imports: Fix infinite loop with cyclic module imports I didn't anticipate that downsweep would run before we checked for cyclic imports. Therefore we need to use the reachability function which handles cyclic graphs. Fixes #26087 - - - - - d751a9f1 by Pierre Thierry at 2025-07-21T13:37:28-04:00 Fix documentation about deriving from generics - - - - - f8d9d016 by Andrew Lelechenko at 2025-07-22T21:13:28-04:00 Fix issues with toRational for types capable to represent infinite and not-a-number values This commit fixes all of the following pitfalls:
toRational (read "Infinity" :: Double) 179769313486231590772930519078902473361797697894230657273430081157732675805500963132708477322407536021120113879871393357658789768814416622492847430639474124377767893424865485276302219601246094119453082952085005768838150682342462881473913110540827237163350510684586298239947245938479716304835356329624224137216 % 1 toRational (read "NaN" :: Double) 269653970229347386159395778618353710042696546841345985910145121736599013708251444699062715983611304031680170819807090036488184653221624933739271145959211186566651840137298227914453329401869141179179624428127508653257226023513694322210869665811240855745025766026879447359920868907719574457253034494436336205824 % 1
realToFrac (read "NaN" :: Double) -- With -O0 Infinity realToFrac (read "NaN" :: Double) -- With -O1 NaN
realToFrac (read "NaN" :: Double) :: CDouble Infinity realToFrac (read "NaN" :: CDouble) :: Double Infinity
Implements https://github.com/haskell/core-libraries-committee/issues/338
- - - - -
5dabc718 by Zubin Duggal at 2025-07-22T21:14:10-04:00
haddock: Don't warn about missing link destinations for derived names.
Fixes #26114
- - - - -
9c3a0937 by Matthew Pickering at 2025-07-22T21:14:52-04:00
template haskell: use a precise condition when implicitly lifting
Implicit lifting corrects a level error by replacing references to `x`
with `$(lift x)`, therefore you can use a level `n` binding at level `n
+ 1`, if it can be lifted.
Therefore, we now have a precise check that the use level is 1 more than
the bind level.
Before this bug was not observable as you only had 0 and 1 contexts but
it is easily evident when using explicit level imports.
Fixes #26088
- - - - -
5144b22f by Andreas Klebinger at 2025-07-22T21:15:34-04:00
Add since tag and more docs for do-clever-arg-eta-expansion
Fixes #26113
- - - - -
c865623b by Andreas Klebinger at 2025-07-22T21:15:34-04:00
Add since tag for -fexpose-overloaded-unfoldings
Fixes #26112
- - - - -
49a44ab7 by Simon Hengel at 2025-07-23T17:59:55+07:00
Refactor GHC.Driver.Errors.printMessages
- - - - -
84711c39 by Simon Hengel at 2025-07-23T18:27:34+07:00
Respect `-fdiagnostics-as-json` for error messages from pre-processors
(fixes #25480)
- - - - -
d046b5ab by Simon Hengel at 2025-07-24T06:12:05-04:00
Include the rendered message in -fdiagnostics-as-json output
This implements #26173.
- - - - -
d2b89603 by Ben Gamari at 2025-07-24T06:12:47-04:00
rts/Interpreter: Factor out ctoi tuple info tables into data
Instead of a massive case let's put this into data which we can reuse
elsewhere.
- - - - -
4bc78496 by Sebastian Graf at 2025-07-24T16:19:34-04:00
CprAnal: Detect recursive newtypes (#25944)
While `cprTransformDataConWork` handles recursive data con workers, it
did not detect the case when a newtype is responsible for the recursion.
This is now detected in the `Cast` case of `cprAnal`.
The same reproducer made it clear that `isRecDataCon` lacked congruent
handling for `AppTy` and `CastTy`, now fixed.
Furthermore, the new repro case T25944 triggered this bug via an
infinite loop in `cprFix`, caused by the infelicity in `isRecDataCon`.
While it should be much less likely to trigger such an infinite loop now
that `isRecDataCon` has been fixed, I made sure to abort the loop after
10 iterations and emitting a warning instead.
Fixes #25944.
- - - - -
0a583689 by Sylvain Henry at 2025-07-24T16:20:26-04:00
STM: don't create a transaction in the rhs of catchRetry# (#26028)
We don't need to create a transaction for the rhs of (catchRetry#)
because contrary to the lhs we don't need to abort it on retry. Moreover
it is particularly harmful if we have code such as (#26028):
let cN = readTVar vN >> retry
tree = c1 `orElse` (c2 `orElse` (c3 `orElse` ...))
atomically tree
Because it will stack transactions for the rhss and the read-sets of all
the transactions will be iteratively merged in O(n^2) after the
execution of the most nested retry.
- - - - -
a49eca26 by Simon Peyton Jones at 2025-07-25T09:49:58+01:00
Renaming around predicate types
.. we were (as it turned out) abstracting over
type-class selectors in SPECIALISATION rules!
Wibble isEqPred
- - - - -
f80375dd by Simon Peyton Jones at 2025-07-25T09:49:58+01:00
Refactor of Specialise.hs
This patch just tidies up `specHeader` a bit, removing one
of its many results, and adding some comments.
No change in behaviour.
Also add a few more `HasDebugCallStack` contexts.
- - - - -
1bd12371 by Simon Peyton Jones at 2025-07-25T09:49:58+01:00
Improve treatment of SPECIALISE pragmas -- again!
This MR does another major refactor of the way that SPECIALISE
pragmas work, to fix #26115, #26116, #26117.
* We now /always/ solve forall-constraints in an all-or-nothing way.
See Note [Solving a Wanted forall-constraint] in GHC.Tc.Solver.Solve
This means we might have unsolved quantified constraints, which need
to be reported. See `inert_insts` in `getUnsolvedInerts`.
* I refactored the short-cut solver for type classes to work by
recursively calling the solver rather than by having a little baby
solver that kept being not clever enough.
See Note [Shortcut solving] in GHC.Tc.Solver.Dict
* I totally rewrote the desugaring of SPECIALISE pragmas, again.
The new story is in Note [Desugaring new-form SPECIALISE pragmas]
in GHC.HsToCore.Binds
Both old-form and new-form SPECIALISE pragmas now route through the same
function `dsSpec_help`. The tricky function `decomposeRuleLhs` is now used only
for user-written RULES, not for SPECIALISE pragmas.
* I improved `solveOneFromTheOther` to account for rewriter sets. Previously
it would solve a non-rewritten dict from a rewritten one. For equalities
we were already dealing with this, in
Some incidental refactoring
* A small refactor: `ebv_tcvs` in `EvBindsBar` now has a list of coercions, rather
than a set of tyvars. We just delay taking the free vars.
* GHC.Core.FVs.exprFVs now returns /all/ free vars.
Use `exprLocalFVs` for Local vars.
Reason: I wanted another variant for /evidence/ variables.
* Ues `EvId` in preference to `EvVar`. (Evidence variables are always Ids.)
Rename `isEvVar` to `isEvId`.
* I moved `inert_safehask` out of `InertCans` and into `InertSet` where it
more properly belongs.
Compiler-perf changes:
* There was a palpable bug (#26117) which this MR fixes in
newWantedEvVar, which bypassed all the subtle overlapping-Given
and shortcutting logic. (See the new `newWantedEvVar`.) Fixing this
but leads to extra dictionary bindings; they are optimised away quickly
but they made CoOpt_Read allocate 3.6% more.
* Hpapily T15164 improves.
* The net compiler-allocation change is 0.0%
Metric Decrease:
T15164
Metric Increase:
CoOpt_Read
T12425
- - - - -
953fd8f1 by Simon Peyton Jones at 2025-07-25T09:49:58+01:00
Solve forall-constraints immediately, or not at all
This MR refactors the constraint solver to solve forall-constraints immediately,
rather than emitting an implication constraint to be solved later.
The most immediate motivation was that when solving quantified constraints
in SPECIALISE pragmas, we really really don't want to leave behind half-
solved implications. Also it's in tune with the approach of the new
short-cut solver, which recursively invokes the solver.
It /also/ saves quite a bit of plumbing; e.g
- The `wl_implics` field of `WorkList` is gone,
- The types of `solveSimpleWanteds` and friends are simplified.
- An EvFun contains binding, rather than an EvBindsVar ref-cell that
will in the future contain bindings. That makes `evVarsOfTerm`
simpler. Much nicer.
It also improves error messages a bit.
All described in Note [Solving a Wanted forall-constraint] in
GHC.Tc.Solver.Solve.
One tiresome point: in the tricky case of `inferConstraintsCoerceBased`
we make a forall-constraint. This we /do/ want to partially solve, so
we can infer a suitable context. (I'd be quite happy to force the user to
write a context, bt I don't want to change behavior.) So we want to generate
an /implication/ constraint in `emitPredSpecConstraints` rather than a
/forall-constraint/ as we were doing before. Discussed in (WFA3) of
the above Note.
Incidental refactoring
* `GHC.Tc.Deriv.Infer.inferConstraints` was consulting the state monad for
the DerivEnv that the caller had just consulted. Nicer to pass it as an
argument I think, so I have done that. No change in behaviour.
- - - - -
6921ab42 by Simon Peyton Jones at 2025-07-25T09:49:58+01:00
Remove duplicated code in Ast.hs for evTermFreeVars
This is just a tidy up.
- - - - -
1165f587 by Simon Peyton Jones at 2025-07-25T09:49:58+01:00
Small tc-tracing changes only
- - - - -
0776ffe0 by Simon Hengel at 2025-07-26T04:54:20-04:00
Respect `-fdiagnostics-as-json` for core diagnostics (see #24113)
- - - - -
cc1116e0 by Andrew Lelechenko at 2025-07-26T04:55:01-04:00
docs: add since pragma to Data.List.NonEmpty.mapMaybe
- - - - -
ee2dc248 by Simon Hengel at 2025-07-31T06:25:35-04:00
Update comments on `OptKind` to reflect the code reality
- - - - -
b029633a by Wen Kokke at 2025-07-31T06:26:21-04:00
rts: Disable --eventlog-flush-interval unless compiled with -threaded.
This commit fixes issue #26222:
Using --eventlog-flush-interval with the non-threaded RTS leads to eventlog corruption.
https://gitlab.haskell.org/ghc/ghc/-/issues/26222
This commit makes three changes when code is compiled against the non-threaded RTS:
1. It disables the --eventlog-flush-interval flag.
2. It disables the documentation for the --eventlog-flush-interval flag.
3. It disables the relevant state from RtsConfig and code from Timer.
4. It updates the entry for --eventlog-flush-interval in the users guide.
- - - - -
31159f1d by Wen Kokke at 2025-07-31T06:26:21-04:00
rts: Split T20006 into tests with and without -threaded
- - - - -
618687ef by Simon Hengel at 2025-07-31T06:27:03-04:00
docs/users_guide/win32-dlls.rst: Remove references to `readline`
- - - - -
083e40f1 by Rodrigo Mesquita at 2025-08-01T04:38:23-04:00
debugger: Uniquely identify breakpoints by internal id
Since b85b11994e0130ff2401dd4bbdf52330e0bcf776 (support inlining
breakpoints), a breakpoint has been identified at runtime by *two* pairs
of
naturalAndNot ((2 ^ 65) .|. (2 ^ 3)) (2 ^ 3) 0
In contrast, `naturalAndNot` does not truncate when both arguments are larger than a `Word`, so this appears to be a bug.
Luckily, the fix is pretty easy: we just need to call `bigNatAndNotWord#` instead of truncating.
Fixes #26230
- - - - -
3506fa7d by Simon Hengel at 2025-08-13T21:05:18-04:00
Report -pgms as a deprecated flag
(instead of reporting an unspecific warning)
Before:
on the commandline: warning:
Object splitting was removed in GHC 8.8
After:
on the commandline: warning: [GHC-53692] [-Wdeprecated-flags]
-pgms is deprecated: Object splitting was removed in GHC 8.8
- - - - -
51c701fe by Zubin Duggal at 2025-08-13T21:06:00-04:00
testsuite: Be more permissive when filtering out GNU_PROPERTY_TYPE linker warnings
The warning text is slightly different with ld.bfd.
Fixes #26249
- - - - -
dfe6f464 by Simon Hengel at 2025-08-13T21:06:43-04:00
Refactoring: Don't misuse `MCDiagnostic` for lint messages
`MCDiagnostic` is meant to be used for compiler diagnostics.
Any code that creates `MCDiagnostic` directly, without going through
`GHC.Driver.Errors.printMessage`, side steps `-fdiagnostics-as-json`
(see e.g. !14475, !14492 !14548).
To avoid this in the future I want to control more narrowly who creates
`MCDiagnostic` (see #24113).
Some parts of the compiler use `MCDiagnostic` purely for formatting
purposes, without creating any real compiler diagnostics. This change
introduces a helper function, `formatDiagnostic`, that can be used in
such cases instead of constructing `MCDiagnostic`.
- - - - -
a8b2fbae by Teo Camarasu at 2025-08-13T21:07:24-04:00
rts: ensure MessageBlackHole.link is always a valid closure
We turn a MessageBlackHole into an StgInd in wakeBlockingQueue().
Therefore it's important that the link field, which becomes the
indirection field, always points to a valid closure.
It's unclear whether it's currently possible for the previous behaviour
to lead to a crash, but it's good to be consistent about this invariant nonetheless.
Co-authored-by: Andreas Klebinger <klebinger.andreas@gmx.at>
- - - - -
4021181e by Teo Camarasu at 2025-08-13T21:07:24-04:00
rts: spin if we see a WHITEHOLE in messageBlackHole
When a BLACKHOLE gets cancelled in raiseAsync, we indirect to a THUNK.
GC can then shortcut this, replacing our BLACKHOLE with a fresh THUNK.
This THUNK is not guaranteed to have a valid indirectee field.
If at the same time, a message intended for the previous BLACKHOLE is
processed and concurrently we BLACKHOLE the THUNK, thus temporarily
turning it into a WHITEHOLE, we can get a segfault, since we look at the
undefined indirectee field of the THUNK
The fix is simple: spin if we see a WHITEHOLE, and it will soon be
replaced with a valid BLACKHOLE.
Resolves #26205
- - - - -
1107af89 by Oleg Grenrus at 2025-08-13T21:08:06-04:00
Allow defining HasField instances for naughty fields
Resolves #26295
... as HasField solver doesn't solve for fields with "naughty"
selectors, we could as well allow defining HasField instances for these
fields.
- - - - -
020e7587 by Sylvain Henry at 2025-08-13T21:09:00-04:00
Fix Data.List unqualified import warning
- - - - -
fd811ded by Simon Peyton Jones at 2025-08-14T17:56:47-04:00
Make injecting implicit bindings into its own pass
Previously we were injecting "impliicit bindings" (data constructor
worker and wrappers etc)
- both at the end of CoreTidy,
- and at the start of CorePrep
This is unpleasant and confusing. This patch puts it it its own pass,
addImplicitBinds, which runs between the two.
The function `GHC.CoreToStg.AddImplicitBinds.addImplicitBinds` now takes /all/
TyCons, not just the ones for algebraic data types. That change ripples
through to
- corePrepPgm
- doCodeGen
- byteCodeGen
All take [TyCon] which includes all TyCons
- - - - -
9bd7fcc5 by Simon Peyton Jones at 2025-08-14T17:56:47-04:00
Implement unary classes
The big change is described exhaustively in
Note [Unary class magic] in GHC.Core.TyCon
Other changes
* We never unbox class dictionaries in worker/wrapper. This has been true for some
time now, but the logic is now centralised in functions in
GHC.Core.Opt.WorkWrap.Utils, namely `canUnboxTyCon`, and `canUnboxArg`
See Note [Do not unbox class dictionaries] in GHC.Core.Opt.WorkWrap.Utils.
* Refactored the `notWorthFloating` logic in GHc.Core.Opt.SetLevels.
I can't remember if I actually changed any behaviour here, but if so it's
only in a corner cases.
* Fixed a bug in `GHC.Core.TyCon.isEnumerationTyCon`, which was wrongly returning
True for (##).
* Remove redundant Role argument to `liftCoSubstWithEx`. It was always
Representational.
* I refactored evidence generation in the constraint solver:
* Made GHC.Tc.Types.Evidence contain better abstactions for evidence
generation.
* I deleted the file `GHC.Tc.Types.EvTerm` and merged its (small) contents
elsewhere. It wasn't paying its way.
* Made evidence for implicit parameters go via a proper abstraction.
* Fix inlineBoringOk; see (IB6) in Note [inlineBoringOk]
This fixes a slowdown in `countdownEffectfulDynLocal`
in the `effectful` library.
Smaller things
* Rename `isDataTyCon` to `isBoxedDataTyCon`.
* GHC.Core.Corecion.liftCoSubstWithEx was only called with Representational role,
so I baked that into the function and removed the argument.
* Get rid of `GHC.Core.TyCon.tyConSingleAlgDataCon_maybe` in favour of calling
`not isNewTyCon` at the call sites; more explicit.
* Refatored `GHC.Core.TyCon.isInjectiveTyCon`; but I don't think I changed its
behaviour
* Moved `decomposeIPPred` to GHC.Core.Predicate
Compile time performance changes:
geo. mean +0.1%
minimum -6.8%
maximum +14.4%
The +14% one is in T21839c, where it seems that a bit more inlining
is taking place. That seems acceptable; and the average change is small
Metric Decrease:
LargeRecord
T12227
T12707
T16577
T21839r
T5642
Metric Increase:
T15164
T21839c
T3294
T5321FD
T5321Fun
WWRec
- - - - -
b4075d71 by Simon Peyton Jones at 2025-08-14T17:56:47-04:00
Slight improvement to pre/postInlineUnconditionally
Avoids an extra simplifier iteration
- - - - -
9e443596 by Simon Peyton Jones at 2025-08-14T17:56:47-04:00
Fix a long-standing assertion error in normSplitTyConApp_maybe
- - - - -
91310ad0 by Simon Peyton Jones at 2025-08-14T17:56:47-04:00
Add comment to coercion optimiser
- - - - -
5b841d82 by Teo Camarasu at 2025-08-14T17:57:56-04:00
template-haskell: move some identifiers from ghc-internal to template-haskell
These identifiers are not used internally by the compiler. Therefore we
have no reason for them to be in ghc-internal.
By moving them to template-haskell, we benefit from it being easier to
change them and we avoid having to build them in stage0.
Resolves #26048
- - - - -
33e2c7e5 by Teo Camarasu at 2025-08-14T17:57:56-04:00
template-haskell: transfer $infix note to public module
This Haddock note should be in the public facing module
- - - - -
2a411fc4 by Sylvain Henry at 2025-08-14T17:59:09-04:00
JS: export HEAP8 symbol (#26290)
Newer Emscripten requires this.
- - - - -
248f78ca by Ben Gamari at 2025-08-14T17:59:51-04:00
users-guide: Drop the THREAD_RUNNABLE event
As of f361281c89fbce42865d8b8b27b0957205366186 it is no longer emitted.
- - - - -
706d33e3 by Recursion Ninja at 2025-08-15T04:12:12-04:00
Resolving issues #20645 and #26109
Correctly sign extending and casting smaller bit width types for LLVM operations:
- bitReverse8#
- bitReverse16#
- bitReverse32#
- byteSwap16#
- byteSwap32#
- pdep8#
- pdep16#
- pext8#
- pext16#
- - - - -
1cdc6f46 by Cheng Shao at 2025-08-15T04:12:56-04:00
hadrian: enforce have_llvm=False for wasm32/js
This patch fixes hadrian to always pass have_llvm=False to the
testsuite driver for wasm32/js targets. These targets don't really
support the LLVM backend, and the optllvm test way doesn't work. We
used to special-case wasm32/js to avoid auto-adding optllvm way in
testsuite/config/ghc, but this is still problematic if someone writes
a new LLVM-related test and uses something like when(have_llvm(),
extra_ways(["optllvm"])). So better just enforce have_llvm=False for
these targets here.
- - - - -
ca03226d by Ben Gamari at 2025-08-18T13:43:20+00:00
configure: Allow use of LLVM 20
- - - - -
783cd7d6 by Cheng Shao at 2025-08-18T20:13:14-04:00
compiler: use `UniqMap` instead of `Map` for `BCEnv` in bytecode compiler
The bytecode compiler maintains a `BCEnv` which was previously `Map Id
StackDepth`. Given `Id` is `Uniquable`, we might as well use `UniqMap`
here as a more efficient data structure, hence this patch.
Co-authored-by: Codex <codex@openai.com>
- - - - -
58e46da9 by fendor at 2025-08-18T20:13:56-04:00
rts: Strip lower three bits when hashing Word instead of lower eight bits
- - - - -
45dbfa23 by Cheng Shao at 2025-08-18T20:14:37-04:00
libffi: update to 3.5.2
Bumps libffi submodule.
- - - - -
54be78ef by Ben Gamari at 2025-08-19T16:28:05-04:00
testsuite: Fix T20006b
This test is supposed to fail for non-threaded ways yet it
was previously marked as only failing in `normal`.
Fix this.
- - - - -
f4bac607 by Simon Peyton Jones at 2025-08-19T16:28:47-04:00
Take yet more care with reporting redundant constraints
This small patch fixes #25992, which relates to reporting redundant
constraints on default-method declarations.
See (TRC5) in Note [Tracking redundant constraints]
- - - - -
ab130fec by fendor at 2025-08-19T16:29:29-04:00
Bump dependencies of hadrian-bootstrap-gen to use GHC 9.6.7
- - - - -
6d02ac6f by fendor at 2025-08-19T16:29:29-04:00
Bump required GHC version for test-bootstrap jobs to 9.10.1
Include test-bootstrap job for GHC 9.12.2.
Update hadrian bootstrap plans use GHC 9.10 and 9.12
Remove older GHC bootstrap configurations.
We require at least GHC 9.10.1 to build GHC.
Adds plans for:
* 9.10.1
* 9.10.2
* 9.12.1
* 9.12.2
- - - - -
9e857171 by Brandon Chinn at 2025-08-20T11:47:46-04:00
Don't warn unused-imports with used generated imports
Fixes #21730
* The old notion of "implicit" import has been renamed to "generated". See Note [Generated imports] in GHC.Hs.ImpExp.
* ImportMap now keeps track of generated and user-written imports separately. This avoids the fake SrcSpan we used to give the implicit Prelude import, and the hack that went with it.
* -ddump-minimal-imports now considers generated imports (but still only
warns on + prints user-written imports)
* bestImport considers generated imports to take priority over user-written imports.
- - - - -
9fb3bad4 by Ben Gamari at 2025-08-20T11:48:31-04:00
mailmap: Use ben@well-typed.com more liberally
Nearly all of this work was done while working for Well-Typed.
- - - - -
774fec37 by Ben Gamari at 2025-08-20T11:49:15-04:00
Add primop to annotate the call stack with arbitrary data
We introduce a new primop `annotateStack#` which allows us to push
arbitrary data onto the call-stack.
This allows us to extract the data later when decoding the stack, for
example when an exception is thrown, showing more information to the
user without having to annotate the full call-stack with `HasCallStack`
constraints.
A new stack frame value is introduced `AnnFrame`, which consists of
nothing but a generic payload.
The primop has a small wrapper API that allows users to annotate their
call-stack in programs.
There is a pure API and an IO-based one. The former is a little bit
dubious, as it affects the evaluation of a program, so use with care.
The latter is "safe", as it doesn't change the evaluation of the
program.
The stack annotation mechanism is similarly implemented to the
`ExceptionAnnotation` and `Exception`, there is a typeclass to indicate
something can be pushed onto the call-stack and all values are wrapped
in the existential `SomeStackAnnotation`, which recover the type of the
annotation payload.
There is currently no builtin way to show the stack annotations when
`Backtraces` are displayed (i.e., when showing stack traces to the user),
which we will address in a follow-up MR.
-------------------------
Metric Increase:
ghc_experimental_so
-------------------------
We increase the size of the package, so this is not unreasonable.
Co-Authored-By: fendor <fendor@posteo.de>
Co-Authored-By: Ben Gamari <bgamari.foss@gmail.com>
- - - - -
fdfa3892 by Ben Gamari at 2025-08-20T11:49:57-04:00
testsuite: Add regression test for #24606
- - - - -
39b2e382 by Cheng Shao at 2025-08-20T11:50:40-04:00
compiler: only use `Name` instead of `Id` in `SptEntry`
As a part of #26298, this patch refactors `SptEntry` to only carry a
`Name` instead of `Id`: we do not care about extra information like
caffyness or type at all in any static pointer related codegen logic.
This is necessary to make `SptEntry` serializable, as a part of the
grand plan of serializable bytecode.
Co-authored-by: Codex <codex@openai.com>
- - - - -
276f8ea8 by Vekhir -- at 2025-08-20T11:51:35-04:00
Bump Cabal dependency
- - - - -
0b9c7437 by Zubin Duggal at 2025-08-20T11:52:18-04:00
ci: Teach ci.sh to fetch FreeBSD artifacts from ghcup unofficial bindists and bootstrap compiler on FreeBSD to 9.10.1
Also refactor fetch_ghc logic in ci.sh, renaming the GHC_VERSION enviorment configuration variable to FETCH_GHC_VERSION,
making it clear that it is intended for use on platforms like Windows and FreeBSD where we don't want to use the GHC
excecutable from the platform environment and instead need to download and install GHC-$FETCH_GHC_VERSION from a release
bindist.
Fixes #26296
- - - - -
b2914797 by Cheng Shao at 2025-08-20T11:53:00-04:00
driver: use UniqSet for hiddenModules in DynFlags/FinderOpts
This patch replaces Set ModuleName with UniqSet ModuleName in
DynFlags.hiddenModules and FinderOpts.finder_hiddenModules for
improved efficiency.
Co-authored-by: Codex <codex@openai.com>
- - - - -
0335d899 by Cheng Shao at 2025-08-20T11:53:00-04:00
driver: use UniqMap ModuleName in the finder
This patch replaces Map ModuleName with UniqMap ModuleName in the
finder for improved efficiency.
Co-authored-by: Codex <codex@openai.com>
- - - - -
91f4faaa by Cheng Shao at 2025-08-20T11:53:43-04:00
configure: check python3 version and require minimal 3.7
Since !9515, the testsuite driver requires python3 version to be at
least 3.7, though this has never been checked by configure logic. This
patch implements the version check. Fixes #23234.
Co-authored-by: Codex <codex@openai.com>
- - - - -
df4ee9b4 by Cheng Shao at 2025-08-20T11:54:25-04:00
compiler: use zero cost coerce in GHC.CmmToAsm.CFG.loopInfo
This patch refactors GHC.CmmToAsm.CFG.loopInfo to use zero cost coerce
and thus addresses the TODO. For coerce to work, constructors of
Label/LabelMap/LabelSet from GHC.Cmm.Dataflow.Label are exposed,
though I believe it's a worthy tradeoff to avoid unnecessary runtime
cost without using unsafeCoerce, since the latter could be a landmine
for future refactoring.
Co-authored-by: Codex <codex@openai.com>
- - - - -
ccda188d by Simon Peyton Jones at 2025-08-20T11:55:07-04:00
Start with empty inerts in shortcut solving
When short-cut solving we were starting with an inert set that had
unsolved Wanteds. This caused an infinite loop (#26314), because a
typechecker plugin kept being given that unsolved Wanted.
It's better just to start with an empty inert set
- - - - -
c8882ed7 by Ben Gamari at 2025-08-20T11:55:49-04:00
configure: Bump minimal bootstrap GHC version to 9.8
- - - - -
f0a19d74 by fendor at 2025-08-20T19:55:00-04:00
Remove deprecated functions from the ghci package
- - - - -
ebeb991b by fendor at 2025-08-20T19:55:00-04:00
base: Remove unstable heap representation details from GHC.Exts
- - - - -
e368e247 by Rodrigo Mesquita at 2025-08-20T19:55:42-04:00
bytecode: Use 32bits for breakpoint index
Fixes #26325
- - - - -
42724462 by Simon Hengel at 2025-08-21T17:52:11-04:00
Serialize wired-in names as external names when creating HIE files
Note that the domain of de-serialized names stays the same.
Specifically, for known-key names, before `lookupKnownKeyName` was used,
while now this is handled by `lookupOrigNameCache` which captures the
same range provided that the OrigNameCache has been initialized with
`knownKeyNames` (which is the case by default).
(fixes #26238)
- - - - -
6a43f8ec by Cheng Shao at 2025-08-21T17:52:52-04:00
compiler: fix closure C type in SPT init code
This patch fixes the closure C type in SPT init code to StgClosure,
instead of the previously incorrect StgPtr. Having an incorrect C type
makes SPT init code not compatible with other foreign stub generation
logic, which may also emit their own extern declarations for the same
closure symbols and thus will clash with the incorrect prototypes in
SPT init code.
- - - - -
5b5d9d47 by Ben Gamari at 2025-08-25T14:29:35-04:00
Revert "STM: don't create a transaction in the rhs of catchRetry# (#26028)"
This reverts commit 0a5836891ca29836a24c306d2a364c2e4b5377fd
- - - - -
10f06163 by Cheng Shao at 2025-08-25T14:30:16-04:00
wasm: ensure setKeepCAFs() is called in ghci
This patch is a critical bugfix for #26106, see comment and linked
issue for details.
- - - - -
bedc1004 by Cheng Shao at 2025-08-26T09:31:18-04:00
compiler: use zero cost coerce in hoopl setElems/mapToList
This patch is a follow-up of !14680 and changes setElems/mapToList in
GHC/Cmm/Dataflow/Label to use coerce instead of mapping mkHooplLabel
over the keys.
- - - - -
13250d97 by Ryan Scott at 2025-08-26T09:31:59-04:00
Reject infix promoted data constructors without DataKinds
In the rename, make sure to apply the same `DataKinds` checks for both
`HsTyVar` (for prefix promoted data constructors) and `HsOpTy` (for infix
promoted data constructors) alike.
Fixes #26318.
- - - - -
37655c46 by Teo Camarasu at 2025-08-26T15:24:51-04:00
tests: disable T22859 under LLVM
This test was failing under the LLVM backend since the allocations
differ from the NCG.
Resolves #26282
- - - - -
2cbba9d6 by Teo Camarasu at 2025-08-26T15:25:33-04:00
base-exports: update version numbers
As the version of the compiler has been bumped, a lot of the embedded
version numbers will need to be updated if we ever run this test with
`--test-accept` so let's just update them now, and keep future diffs
clean.
- - - - -
f9f2ffcf by Alexandre Esteves at 2025-08-27T07:19:14-04:00
Import new name for 'utimbuf' on windows to fix #26337
Fixes an `-Wincompatible-pointer-types` instance that turns into an error on
recent toolchains and surfaced as such on nixpkgs when doing linux->ucrt cross.
This long-standing warning has been present at least since 9.4:
C:\GitLabRunner\builds\0\1709189\tmp\ghc16652_0\ghc_4.c:26:115: error:
warning: incompatible pointer types passing 'struct utimbuf *' to parameter of type 'struct _utimbuf *' [-Wincompatible-pointer-types]
|
26 | HsInt32 ghczuwrapperZC9ZCbaseZCSystemziPosixziInternalsZCzuutime(char* a1, struct utimbuf* a2) {return _utime(a1, a2);}
| ^
HsInt32 ghczuwrapperZC9ZCbaseZCSystemziPosixziInternalsZCzuutime(char* a1, struct utimbuf* a2) {return _utime(a1, a2);}
^~
C:\GitLabRunner\builds\0\1709189\_build\stage0\lib\..\..\mingw\x86_64-w64-mingw32\include\sys\utime.h:109:72: error:
note: passing argument to parameter '_Utimbuf' here
|
109 | __CRT_INLINE int __cdecl _utime(const char *_Filename,struct _utimbuf *_Utimbuf) {
| ^
__CRT_INLINE int __cdecl _utime(const char *_Filename,struct _utimbuf *_Utimbuf) {
```
- - - - -
ae89f000 by Hassan Al-Awwadi at 2025-08-27T07:19:56-04:00
Adds the fucnction addDependentDirectory to Q, resolving issue #26148.
This function adds a new directory to the list of things a module depends upon. That means that when the contents of the directory change, the recompilation checker will notice this and the module will be recompiled. Documentation has also been added for addDependentFunction and addDependentDirectory in the user guide.
- - - - -
00478944 by Simon Peyton Jones at 2025-08-27T16:48:30+01:00
Comments only
- - - - -
a7884589 by Simon Peyton Jones at 2025-08-28T11:08:23+01:00
Type-family occurs check in unification
The occurs check in `GHC.Core.Unify.uVarOrFam` was inadequate in dealing
with type families.
Better now. See Note [The occurs check in the Core unifier].
As I did this I realised that the whole apartness thing is trickier than I
thought: see the new Note [Shortcomings of the apartness test]
- - - - -
8adfc222 by sheaf at 2025-08-28T19:47:17-04:00
Fix orientation in HsWrapper composition (<.>)
This commit fixes the order in which WpCast HsWrappers are composed,
fixing a bug introduced in commit 56b32c5a2d5d7cad89a12f4d74dc940e086069d1.
Fixes #26350
- - - - -
eb2ab1e2 by Oleg Grenrus at 2025-08-29T11:00:53-04:00
Generalise thNameToGhcName by adding HasHscEnv
There were multiple single monad-specific `getHscEnv` across codebase.
HasHscEnv is modelled on HasDynFlags.
My first idea was to simply add thNameToGhcNameHsc and
thNameToGhcNameTc, but those would been exactly the same
as thNameToGhcName already.
Also add an usage example to thNameToGhcName and mention that it's
recommended way of looking up names in GHC plugins
- - - - -
2d575a7f by fendor at 2025-08-29T11:01:36-04:00
configure: Bump minimal bootstrap GHC version to 9.10
- - - - -
716274a5 by Simon Peyton Jones at 2025-08-29T17:27:12-04:00
Fix deep subsumption again
This commit fixed #26255:
commit 56b32c5a2d5d7cad89a12f4d74dc940e086069d1
Author: sheaf
2025-07-29 10:50:36.560949 UTC 160,161c160 < PUSH_L 0 < SLIDE 1 2
SLIDE 1 1
164,165d162 < PUSH_L 0 < SLIDE 1 1 175,176c172 < PUSH_L 0 < SLIDE 1 2 ---
SLIDE 1 1
179,180d174 < PUSH_L 0 < SLIDE 1 1 206,207d199 < PUSH_L 0 < SLIDE 1 1 210,211d201 < PUSH_L 0 < SLIDE 1 1 214,215d203 < PUSH_L 0 < SLIDE 1 1 218,219d205 < PUSH_L 0 < SLIDE 1 1 222,223d207 < PUSH_L 0 < SLIDE 1 1 ... 600,601c566 < PUSH_L 0 < SLIDE 1 2 ---
SLIDE 1 1
604,605d568 < PUSH_L 0 < SLIDE 1 1 632,633d594 < PUSH_L 0 < SLIDE 1 1 636,637d596 < PUSH_L 0 < SLIDE 1 1 640,641d598 < PUSH_L 0 < SLIDE 1 1 644,645d600 < PUSH_L 0 < SLIDE 1 1 648,649d602 < PUSH_L 0 < SLIDE 1 1 652,653d604 < PUSH_L 0 < SLIDE 1 1 656,657d606 < PUSH_L 0 < SLIDE 1 1 660,661d608 < PUSH_L 0 < SLIDE 1 1 664,665d610 < PUSH_L 0 < SLIDE 1 1 ``` I also compiled lib:Cabal to bytecode and counted the number of bytecode lines with `find dist-newstyle -name "*.dump-BCOs" -exec wc {} +`: with unoptimized core: 1190689 lines (before) - 1172891 lines (now) = 17798 less redundant instructions (-1.5% lines) with optimized core: 1924818 lines (before) - 1864836 lines (now) = 59982 less redundant instructions (-3.1% lines) - - - - - 8b2c72c0 by L0neGamer at 2025-09-04T06:32:03-04:00 Add Control.Monad.thenM and Control.Applicative.thenA - - - - - 39e1b7cb by Teo Camarasu at 2025-09-04T06:32:46-04:00 ghc-internal: invert dependency of GHC.Internal.TH.Syntax on Data.Data This means that Data.Data no longer blocks building TH.Syntax, which allows greater parallelism in our builds. We move the Data.Data.Data instances to Data.Data. Quasi depends on Data.Data for one of its methods, so, we split the Quasi/Q, etc definition out of GHC.Internal.TH.Syntax into its own module. This has the added benefit of splitting up this quite large module. Previously TH.Syntax was a bottleneck when compiling ghc-internal. Now it is less of a bottle-neck and is also slightly quicker to compile (since it no longer contains these instances) at the cost of making Data.Data slightly more expensive to compile. TH.Lift which depends on TH.Syntax can also compile quicker and no longer blocks ghc-internal finishing to compile. Resolves #26217 ------------------------- Metric Decrease: MultiLayerModulesTH_OneShot T13253 T21839c T24471 Metric Increase: T12227 ------------------------- - - - - - bdf82fd2 by Teo Camarasu at 2025-09-04T06:32:46-04:00 compiler: delete unused names in Builtins.Names.TH returnQ and bindQ are no longer used in the compiler. There was also a very old comment that referred to them that I have modernized - - - - - 41a448e5 by Ben Gamari at 2025-09-04T19:21:43-04:00 hadrian: Pass lib & include directories to ghc `Setup configure` - - - - - 46bb9a79 by Ben Gamari at 2025-09-04T19:21:44-04:00 rts/IPE: Fix compilation when zstd is enabled This was broken by the refactoring undertaken in c80dd91c0bf6ac034f0c592f16c548b9408a8481. Closes #26312. - - - - - 138a6e34 by sheaf at 2025-09-04T19:22:46-04:00 Make mkCast assertion a bit clearer This commit changes the assertion message that gets printed when one calls mkCast with a coercion whose kind does not match the type of the inner expression. I always found the assertion message a bit confusing, as it didn't clearly state what exactly was the error. - - - - - 9d626be1 by sheaf at 2025-09-04T19:22:46-04:00 Simplifier/rules: fix mistakes in Notes & comments - - - - - 94b62aa7 by Simon Peyton Jones at 2025-09-08T03:37:14-04:00 Refactor ForAllCo This is a pure refactor, addressing #26389. It arranges that the kind coercion in a ForAllCo is a MCoercion, rather than a plain Coercion, thus removing redundancy in the common case. See (FC8) in Note [ForAllCo] It's a nice cleanup. - - - - - 624afa4a by sheaf at 2025-09-08T03:38:05-04:00 Use tcMkScaledFunTys in matchExpectedFunTys We should use tcMkScaledFunTys rather than mkScaledFunTys in GHC.Tc.Utils.Unify.matchExpectedFunTys, as the latter crashes when the kind of the result type is a bare metavariable. We know the result is always Type-like, so we don't need scaledFunTys to try to rediscover that from the kind. Fixes #26277 - - - - - 0975d2b6 by sheaf at 2025-09-08T03:38:54-04:00 Revert "Remove hptAllFamInstances usage during upsweep" This reverts commit 3bf6720eff5e86e673568e756161e6d6150eb440. - - - - - 0cf34176 by soulomoon at 2025-09-08T03:38:54-04:00 Family consistency checks: add test for #26154 This commit adds the test T26154, to make sure that GHC doesn't crash when performing type family consistency checks. This test case was extracted from Agda. Fixes #26154 - - - - - ba210d98 by Simon Peyton Jones at 2025-09-08T16:26:36+01:00 Report solid equality errors before custom errors This MR fixes #26255 by * Reporting solid equality errors like Int ~ Bool before "custom type errors". See comments in `report1` in `reportWanteds` * Suppressing errors that arise from superclasses of Wanteds. See (SCE1) in Note [Suppressing confusing errors] More details in #26255. - - - - - b6249140 by Simon Peyton Jones at 2025-09-10T10:42:38-04:00 Fix a scoping error in Specialise This small patch fixes #26329, which triggered a scoping error. Test is in T21391, with -fpolymorphic-specialisation enabled - - - - - 45305ab8 by sheaf at 2025-09-10T10:43:29-04:00 Make rationalTo{Float,Double} inline in phase 0 We hold off on inlining these until phase 0 to allow constant-folding rules to fire. However, once we get to phase 0, we should inline them, e.g. to expose unboxing opportunities. See CLC proposal #356. - - - - - 0959d4bc by Andreas Klebinger at 2025-09-10T10:44:12-04:00 Add regression test for #26056 - - - - - dc79593d by sheaf at 2025-09-10T10:45:01-04:00 Deep subsumption: unify mults without tcEqMult As seen in #26332, we may well end up with a non-reflexive multiplicity coercion when doing deep subsumption. We should do the same thing that we do without deep subsumption: unify the multiplicities normally, without requiring that the coercion is reflexive (which is what 'tcEqMult' was doing). Fixes #26332 - - - - - 4bfe2269 by sheaf at 2025-09-10T10:45:50-04:00 lint-codes: fixup MSYS drive letter on Windows This change ensures that System.Directory.listDirectory doesn't trip up on an MSYS-style path like '/c/Foo' when trying to list all testsuite stdout/stderr files as required for testing coverage of GHC diagnostic codes in the testsuite. Fixes #25178 - - - - - 56540775 by Ben Gamari at 2025-09-10T10:46:32-04:00 gitlab-ci: Disable split sections on FreeBSD Due to #26303. - - - - - 1537784b by Moritz Angermann at 2025-09-10T10:47:13-04:00 Improve mach-o relocation information This change adds more information about the symbol and addresses we try to relocate in the linker. This significantly helps when deubbging relocation issues reported by users. - - - - - 4e67855b by Moritz Angermann at 2025-09-10T10:47:54-04:00 test.mk expect GhcLeadingUnderscore, not LeadingUnderscore (in line with the other Ghc prefixed variables. - - - - - c1cdd265 by Moritz Angermann at 2025-09-10T10:48:35-04:00 testsuite: Fix broken exec_signals_child.c There is no signal 0. The signal mask is 1-32. - - - - - 99ac335c by Moritz Angermann at 2025-09-10T10:49:15-04:00 testsuite: clarify Windows/Darwin locale rationale for skipping T6037 T2507 T8959a - - - - - 0e8fa77a by Moritz Angermann at 2025-09-10T10:49:56-04:00 Skip broken tests on macOS (due to leading underscore not handled properly in the expected output.) - - - - - 28570c59 by Zubin Duggal at 2025-09-10T10:50:37-04:00 docs(sphinx): fix links to reverse flags when using the :ghc-flag:`-fno-<flag>` syntax This solution is rather hacky and I suspect there is a better way to do this but I don't know enough about Sphinx to do better. Fixes #26352 - - - - - d17257ed by Cheng Shao at 2025-09-10T17:01:27+02:00 rel-eng: update alpine images to 3.22 This patch is a part of #25876 and updates alpine images to 3.22, while still retaining 3.12 for x86_64 fully_static bindists. ------------------------- Metric Decrease: MultiComponentModulesRecomp ------------------------- - - - - - db3276bb by Sylvain Henry at 2025-09-11T11:27:28-04:00 T16180: indicate that the stack isn't executable - - - - - 11eeeba7 by Sylvain Henry at 2025-09-11T11:27:28-04:00 Fix some tests (statically linked GHC vs libc) When GHC is linked statically, the stdout C global variable that GHC uses isn't shared with the stdout C global variable used by loaded code. As a consequence, the latter must be explicitly flushed because GHC won't flush it before exiting. - - - - - 80a07571 by Sylvain Henry at 2025-09-11T11:28:18-04:00 Testsuite: fix debug_rts detection Running the testsuite without Hadrian should set config.debug_rts correctly too. - - - - - c5abacfa by Cheng Shao at 2025-09-12T09:55:22+02:00 compiler: move Binary instance of Map to GHC.Utils.Binary This patch moves `Binary` instance of `Map` from `haddock-api` to `GHC.Utils.Binary`. This also allows us to remove a redundant instance defined for `NameEntityInfo`, which is a type synonym for `Map`. - - - - - 1017 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - .gitlab/common.sh - .gitlab/darwin/toolchain.nix - .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 - .mailmap - CODEOWNERS - README.md - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/PrimOps/Ids.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/Types/Prim.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - + compiler/GHC/ByteCode/Breakpoints.hs - compiler/GHC/ByteCode/InfoTable.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Linker.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm.hs - compiler/GHC/Cmm/CommonBlockElim.hs - compiler/GHC/Cmm/Dataflow/Label.hs - compiler/GHC/CmmToAsm/CFG.hs - compiler/GHC/CmmToAsm/LA64/CodeGen.hs - compiler/GHC/CmmToAsm/LA64/Instr.hs - compiler/GHC/CmmToAsm/LA64/Ppr.hs - compiler/GHC/CmmToAsm/PPC/Ppr.hs - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/CmmToLlvm/Data.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Class.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion.hs-boot - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/ConLike.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/DataCon.hs-boot - compiler/GHC/Core/FVs.hs - compiler/GHC/Core/FamInstEnv.hs - compiler/GHC/Core/LateCC/OverloadedCalls.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Map/Expr.hs - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Core/Opt/Monad.hs - compiler/GHC/Core/Opt/OccurAnal.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/Pipeline/Types.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/Simplify/Env.hs - compiler/GHC/Core/Opt/Simplify/Inline.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/Specialise.hs - compiler/GHC/Core/Opt/WorkWrap.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/PatSyn.hs - compiler/GHC/Core/Ppr.hs - compiler/GHC/Core/Predicate.hs - compiler/GHC/Core/Reduction.hs - compiler/GHC/Core/Rules.hs - compiler/GHC/Core/Subst.hs - compiler/GHC/Core/Tidy.hs - compiler/GHC/Core/TyCo/Compare.hs - compiler/GHC/Core/TyCo/FVs.hs - compiler/GHC/Core/TyCo/Ppr.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/TyCo/Subst.hs - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Unfold.hs - compiler/GHC/Core/Unfold/Make.hs - compiler/GHC/Core/Unify.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/CoreToIface.hs - compiler/GHC/CoreToStg.hs - + compiler/GHC/CoreToStg/AddImplicitBinds.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Data/IOEnv.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/CmdLine.hs - compiler/GHC/Driver/CodeOutput.hs - compiler/GHC/Driver/Config.hs - compiler/GHC/Driver/Config/Core/Lint.hs - compiler/GHC/Driver/Config/Core/Opt/Simplify.hs - compiler/GHC/Driver/Config/Finder.hs - compiler/GHC/Driver/Downsweep.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Env/Types.hs - compiler/GHC/Driver/Errors.hs - compiler/GHC/Driver/Errors/Ppr.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Driver/Session.hs - + compiler/GHC/Driver/Session/Inspect.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/ImpExp.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Breakpoints.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Errors/Ppr.hs - compiler/GHC/HsToCore/Errors/Types.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Pmc/Solver.hs - compiler/GHC/HsToCore/Pmc/Solver/Types.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/HsToCore/Usage.hs - compiler/GHC/Iface/Decl.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Ext/Binary.hs - compiler/GHC/Iface/Ext/Types.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Iface/Rename.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Tidy.hs - compiler/GHC/Iface/Tidy/StaticPtrTable.hs - compiler/GHC/Iface/Type.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Linker/Loader.hs - compiler/GHC/Linker/Types.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Header.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/PostProcess/Haddock.hs - compiler/GHC/Plugins.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Splice.hs - compiler/GHC/Runtime/Debugger/Breakpoints.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Eval/Types.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/Runtime/Interpreter/Types.hs - compiler/GHC/Stg/BcPrep.hs - compiler/GHC/Stg/FVs.hs - compiler/GHC/Stg/Lint.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/StgToCmm.hs - compiler/GHC/StgToCmm/InfoTableProv.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToJS/Prim.hs - compiler/GHC/StgToJS/StaticPtr.hs - compiler/GHC/SysTools/Process.hs - compiler/GHC/SysTools/Tasks.hs - compiler/GHC/Tc/Deriv.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Deriv/Infer.hs - compiler/GHC/Tc/Deriv/Utils.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Bind.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/Gen/Splice.hs - compiler/GHC/Tc/Gen/Splice.hs-boot - compiler/GHC/Tc/Instance/Class.hs - compiler/GHC/Tc/Instance/Family.hs - compiler/GHC/Tc/Module.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/InertSet.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/Solver/Types.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Build.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/TyCl/Utils.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Types/Constraint.hs - − compiler/GHC/Tc/Types/EvTerm.hs - compiler/GHC/Tc/Types/Evidence.hs - compiler/GHC/Tc/Types/Origin.hs - compiler/GHC/Tc/Types/TH.hs - compiler/GHC/Tc/Utils/Concrete.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/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Basic.hs - − compiler/GHC/Types/Breakpoint.hs - compiler/GHC/Types/Demand.hs - compiler/GHC/Types/Error.hs - compiler/GHC/Types/Error/Codes.hs - compiler/GHC/Types/Id.hs - compiler/GHC/Types/Id/Make.hs - compiler/GHC/Types/Name/Cache.hs - compiler/GHC/Types/Name/Reader.hs - compiler/GHC/Types/RepType.hs - compiler/GHC/Types/SptEntry.hs - compiler/GHC/Types/Tickish.hs - compiler/GHC/Types/TyThing.hs - compiler/GHC/Types/Var.hs - compiler/GHC/Types/Var.hs-boot - compiler/GHC/Unit/Env.hs - compiler/GHC/Unit/Finder.hs - compiler/GHC/Unit/Finder/Types.hs - compiler/GHC/Unit/Module/Deps.hs - compiler/GHC/Unit/Module/Graph.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Utils/Binary.hs - compiler/GHC/Utils/Error.hs - compiler/GHC/Utils/Logger.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Pat.hs - compiler/Setup.hs - compiler/ghc.cabal.in - configure.ac - distrib/configure.ac.in - docs/users_guide/9.14.1-notes.rst → docs/users_guide/9.16.1-notes.rst - docs/users_guide/conf.py - docs/users_guide/debug-info.rst - + docs/users_guide/diagnostics-as-json-schema-1_2.json - docs/users_guide/eventlog-formats.rst - docs/users_guide/expected-undocumented-flags.txt - docs/users_guide/exts/doandifthenelse.rst - docs/users_guide/exts/ffi.rst - docs/users_guide/exts/gadt_syntax.rst - docs/users_guide/exts/linear_types.rst - + docs/users_guide/exts/relaxed_poly_rec.rst - docs/users_guide/exts/required_type_arguments.rst - docs/users_guide/exts/strict.rst - docs/users_guide/exts/types.rst - docs/users_guide/flags.py - docs/users_guide/ghci.rst - docs/users_guide/profiling.rst - docs/users_guide/release-notes.rst - docs/users_guide/runtime_control.rst - docs/users_guide/separate_compilation.rst - docs/users_guide/using-optimisation.rst - docs/users_guide/using-warnings.rst - docs/users_guide/using.rst - docs/users_guide/win32-dlls.rst - ghc/GHCi/UI.hs - ghc/GHCi/UI/Exception.hs - ghc/GHCi/UI/Monad.hs - ghc/GHCi/UI/Print.hs - ghc/ghc-bin.cabal.in - hadrian/bootstrap/generate_bootstrap_plans - hadrian/bootstrap/hadrian-bootstrap-gen.cabal - hadrian/bootstrap/plan-9_10_1.json - hadrian/bootstrap/plan-9_6_5.json → hadrian/bootstrap/plan-9_10_2.json - hadrian/bootstrap/plan-9_6_6.json → hadrian/bootstrap/plan-9_12_1.json - hadrian/bootstrap/plan-9_6_4.json → hadrian/bootstrap/plan-9_12_2.json - − hadrian/bootstrap/plan-9_6_1.json - − hadrian/bootstrap/plan-9_6_2.json - − hadrian/bootstrap/plan-9_6_3.json - − hadrian/bootstrap/plan-9_8_1.json - − hadrian/bootstrap/plan-9_8_2.json - hadrian/bootstrap/plan-bootstrap-9_10_1.json - hadrian/bootstrap/plan-bootstrap-9_6_5.json → hadrian/bootstrap/plan-bootstrap-9_10_2.json - hadrian/bootstrap/plan-bootstrap-9_6_6.json → hadrian/bootstrap/plan-bootstrap-9_12_1.json - hadrian/bootstrap/plan-bootstrap-9_8_1.json → hadrian/bootstrap/plan-bootstrap-9_12_2.json - − hadrian/bootstrap/plan-bootstrap-9_6_1.json - − hadrian/bootstrap/plan-bootstrap-9_6_2.json - − hadrian/bootstrap/plan-bootstrap-9_6_3.json - − hadrian/bootstrap/plan-bootstrap-9_6_4.json - − hadrian/bootstrap/plan-bootstrap-9_8_2.json - hadrian/bootstrap/src/Main.hs - hadrian/cfg/default.host.target.in - hadrian/cfg/default.target.in - hadrian/cfg/system.config.in - hadrian/hadrian.cabal - hadrian/src/Builder.hs - hadrian/src/Oracles/Flag.hs - hadrian/src/Oracles/Setting.hs - hadrian/src/Oracles/TestSettings.hs - hadrian/src/Rules/Generate.hs - hadrian/src/Rules/ToolArgs.hs - hadrian/src/Settings/Builders/Cabal.hs - hadrian/src/Settings/Builders/RunTest.hs - hadrian/src/Settings/Default.hs - hadrian/src/Settings/Packages.hs - hadrian/src/Settings/Program.hs - hadrian/stack.yaml - hadrian/stack.yaml.lock - libffi-tarballs - libraries/Cabal - libraries/Win32 - libraries/array - libraries/base/base.cabal.in - libraries/base/changelog.md - libraries/base/src/Control/Applicative.hs - libraries/base/src/Control/Exception.hs - libraries/base/src/Control/Exception/Backtrace.hs - libraries/base/src/Control/Monad.hs - libraries/base/src/Data/Array/Byte.hs - libraries/base/src/Data/Bifunctor.hs - libraries/base/src/Data/Fixed.hs - libraries/base/src/Data/List/NonEmpty.hs - libraries/base/src/GHC/Exts.hs - libraries/base/src/GHC/Generics.hs - − libraries/base/src/GHC/IOPort.hs - libraries/base/src/GHC/Stack/CloneStack.hs - libraries/base/src/GHC/Weak/Finalize.hs - libraries/base/src/System/Console/GetOpt.hs - libraries/binary - libraries/deepseq - libraries/directory - libraries/exceptions - libraries/filepath - libraries/ghc-bignum/changelog.md - + libraries/ghc-boot-th/GHC/Boot/TH/Monad.hs - libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs - libraries/ghc-boot-th/ghc-boot-th.cabal.in - libraries/ghc-boot/ghc-boot.cabal.in - libraries/ghc-compact/GHC/Compact.hs - libraries/ghc-compact/GHC/Compact/Serialized.hs - libraries/ghc-compact/ghc-compact.cabal - libraries/ghc-experimental/ghc-experimental.cabal.in - + libraries/ghc-experimental/src/GHC/Exception/Backtrace/Experimental.hs - + libraries/ghc-experimental/src/GHC/Stack/Annotation/Experimental.hs - + libraries/ghc-experimental/src/System/Mem/Experimental.hs - libraries/ghc-heap/GHC/Exts/Heap/ClosureTypes.hs - libraries/ghc-heap/GHC/Exts/Heap/Closures.hs - + libraries/ghc-heap/GHC/Exts/Heap/Constants.hs - libraries/ghc-heap/GHC/Exts/Heap/FFIClosures_ProfilingDisabled.hsc - libraries/ghc-heap/GHC/Exts/Heap/FFIClosures_ProfilingEnabled.hsc - + libraries/ghc-heap/GHC/Exts/Heap/InfoTable.hs - + libraries/ghc-heap/GHC/Exts/Heap/InfoTable/Types.hs - + libraries/ghc-heap/GHC/Exts/Heap/InfoTableProf.hs - libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/Types.hs - libraries/ghc-heap/GHC/Exts/Heap/Utils.hsc - libraries/ghc-heap/GHC/Exts/Stack.hs - + libraries/ghc-heap/GHC/Exts/Stack/Constants.hs - libraries/ghc-heap/GHC/Exts/Stack/Decode.hs - libraries/ghc-heap/ghc-heap.cabal.in - libraries/ghc-heap/tests/parse_tso_flags.hs - libraries/ghc-heap/cbits/HeapPrim.cmm → libraries/ghc-internal/cbits/HeapPrim.cmm - libraries/ghc-heap/cbits/Stack.cmm → libraries/ghc-internal/cbits/Stack.cmm - libraries/ghc-internal/cbits/StackCloningDecoding.cmm - libraries/ghc-heap/cbits/Stack_c.c → libraries/ghc-internal/cbits/Stack_c.c - libraries/ghc-internal/cbits/pdep.c - libraries/ghc-internal/cbits/pext.c - libraries/ghc-internal/ghc-internal.cabal.in - libraries/ghc-internal/jsbits/base.js - + libraries/ghc-internal/src/GHC/Internal/AllocationLimitHandler.hs - libraries/ghc-internal/src/GHC/Internal/Base.hs - libraries/ghc-internal/src/GHC/Internal/Bignum/Natural.hs - libraries/ghc-internal/src/GHC/Internal/ClosureTypes.hs - libraries/ghc-internal/src/GHC/Internal/Control/Monad.hs - libraries/ghc-internal/src/GHC/Internal/Data/Data.hs - libraries/ghc-internal/src/GHC/Internal/Data/OldList.hs - libraries/ghc-internal/src/GHC/Internal/Event/Windows.hsc - libraries/ghc-internal/src/GHC/Internal/Event/Windows/Thread.hs - libraries/ghc-internal/src/GHC/Internal/Exception.hs - libraries/ghc-internal/src/GHC/Internal/Exception/Backtrace.hs - libraries/ghc-internal/src/GHC/Internal/Exception/Backtrace.hs-boot - libraries/ghc-internal/src/GHC/Internal/Exception/Type.hs - libraries/ghc-internal/src/GHC/Internal/Exts.hs - libraries/ghc-internal/src/GHC/Internal/Float.hs - + libraries/ghc-internal/src/GHC/Internal/Heap/Closures.hs - libraries/ghc-heap/GHC/Exts/Heap/Constants.hsc → libraries/ghc-internal/src/GHC/Internal/Heap/Constants.hsc - libraries/ghc-heap/GHC/Exts/Heap/InfoTable.hsc → libraries/ghc-internal/src/GHC/Internal/Heap/InfoTable.hsc - libraries/ghc-heap/GHC/Exts/Heap/InfoTable/Types.hsc → libraries/ghc-internal/src/GHC/Internal/Heap/InfoTable/Types.hsc - libraries/ghc-heap/GHC/Exts/Heap/InfoTableProf.hsc → libraries/ghc-internal/src/GHC/Internal/Heap/InfoTableProf.hsc - + libraries/ghc-internal/src/GHC/Internal/Heap/ProfInfo/Types.hs - libraries/ghc-internal/src/GHC/Internal/IO/Buffer.hs - libraries/ghc-internal/src/GHC/Internal/IO/Windows/Handle.hsc - − libraries/ghc-internal/src/GHC/Internal/IOPort.hs - libraries/ghc-internal/src/GHC/Internal/List.hs - libraries/ghc-internal/src/GHC/Internal/Prim/PtrEq.hs - libraries/ghc-internal/src/GHC/Internal/Real.hs - + libraries/ghc-internal/src/GHC/Internal/Stack/Annotation.hs - libraries/ghc-internal/src/GHC/Internal/Stack/CloneStack.hs - libraries/ghc-heap/GHC/Exts/Stack/Constants.hsc → libraries/ghc-internal/src/GHC/Internal/Stack/Constants.hsc - + libraries/ghc-internal/src/GHC/Internal/Stack/Decode.hs - libraries/ghc-internal/src/GHC/Internal/System/IO.hs - libraries/ghc-internal/src/GHC/Internal/System/Posix/Internals.hs - libraries/ghc-internal/src/GHC/Internal/TH/Lib.hs - libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs - + libraries/ghc-internal/src/GHC/Internal/TH/Monad.hs - libraries/ghc-internal/src/GHC/Internal/TH/Quote.hs - libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs - + libraries/ghc-internal/tests/Makefile - + libraries/ghc-internal/tests/all.T - + libraries/ghc-internal/tests/backtraces/Makefile - + libraries/ghc-internal/tests/backtraces/T14532a.hs - + libraries/ghc-internal/tests/backtraces/T14532a.stdout - + libraries/ghc-internal/tests/backtraces/T14532b.hs - + libraries/ghc-internal/tests/backtraces/T14532b.stdout - + libraries/ghc-internal/tests/backtraces/all.T - + libraries/ghc-internal/tests/stack-annotation/Makefile - + libraries/ghc-internal/tests/stack-annotation/TestUtils.hs - + libraries/ghc-internal/tests/stack-annotation/all.T - + libraries/ghc-internal/tests/stack-annotation/ann_frame001.hs - + libraries/ghc-internal/tests/stack-annotation/ann_frame001.stdout - + libraries/ghc-internal/tests/stack-annotation/ann_frame002.hs - + libraries/ghc-internal/tests/stack-annotation/ann_frame002.stdout - + libraries/ghc-internal/tests/stack-annotation/ann_frame003.hs - + libraries/ghc-internal/tests/stack-annotation/ann_frame003.stdout - + libraries/ghc-internal/tests/stack-annotation/ann_frame004.hs - + libraries/ghc-internal/tests/stack-annotation/ann_frame004.stdout - libraries/ghc-prim/changelog.md - libraries/ghc-prim/ghc-prim.cabal - libraries/ghci/GHCi/CreateBCO.hs - + libraries/ghci/GHCi/Debugger.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/Run.hs - libraries/ghci/GHCi/TH.hs - libraries/ghci/ghci.cabal.in - libraries/haskeline - libraries/hpc - libraries/os-string - libraries/parsec - libraries/process - libraries/semaphore-compat - libraries/stm - libraries/template-haskell/Language/Haskell/TH/Lib.hs - libraries/template-haskell/Language/Haskell/TH/Quote.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - libraries/template-haskell/changelog.md - libraries/template-haskell/template-haskell.cabal.in - libraries/template-haskell/tests/all.T - libraries/terminfo - libraries/text - libraries/time - libraries/unix - linters/lint-codes/LintCodes/Coverage.hs - linters/lint-whitespace/lint-whitespace.cabal - m4/find_ld.m4 - m4/find_python.m4 - m4/fp_settings.m4 - m4/ghc_toolchain.m4 - m4/prep_target_file.m4 - mk/get-win32-tarballs.py - + rts/AllocArray.c - + rts/AllocArray.h - rts/CloneStack.c - rts/CloneStack.h - rts/ClosureFlags.c - rts/Disassembler.c - rts/Exception.cmm - rts/Hash.c - rts/Heap.c - rts/IPE.c - rts/Interpreter.c - rts/Interpreter.h - rts/LdvProfile.c - rts/Messages.c - rts/Prelude.h - rts/PrimOps.cmm - rts/Printer.c - rts/ProfHeap.c - rts/Profiling.c - rts/RetainerProfile.c - rts/RetainerSet.c - rts/RtsFlags.c - rts/RtsMessages.c - rts/RtsStartup.c - rts/RtsSymbols.c - rts/RtsUtils.c - rts/Schedule.c - rts/StgMiscClosures.cmm - rts/ThreadLabels.c - rts/Threads.c - rts/Timer.c - rts/Trace.c - rts/Trace.h - rts/TraverseHeap.c - rts/Updates.h - rts/Weak.c - rts/eventlog/EventLog.c - rts/eventlog/EventLog.h - rts/external-symbols.list.in - rts/include/Rts.h - rts/include/rts/Constants.h - rts/include/rts/Flags.h - rts/include/rts/IPE.h - rts/include/rts/prof/CCS.h - rts/include/rts/storage/ClosureTypes.h - rts/include/rts/storage/Closures.h - rts/include/rts/storage/GC.h - rts/include/rts/storage/Heap.h - rts/include/rts/storage/TSO.h - rts/include/stg/MiscClosures.h - rts/include/stg/SMP.h - rts/js/mem.js - rts/js/profiling.js - rts/linker/LoadArchive.c - rts/linker/MachO.c - rts/linker/PEi386.c - rts/posix/ticker/Pthread.c - rts/posix/ticker/TimerFd.c - rts/rts.cabal - rts/sm/Compact.c - rts/sm/Evac.c - rts/sm/NonMoving.c - rts/sm/NonMoving.h - rts/sm/NonMovingAllocate.c - rts/sm/NonMovingMark.c - rts/sm/Sanity.c - rts/sm/Scav.c - rts/sm/Storage.c - rts/win32/AsyncWinIO.c - rts/win32/libHSghc-internal.def - testsuite/.gitignore - testsuite/config/ghc - testsuite/driver/testlib.py - testsuite/ghc-config/ghc-config.hs - testsuite/mk/test.mk - testsuite/tests/arrows/should_compile/T21301.stderr - testsuite/tests/backpack/cabal/bkpcabal08/bkpcabal08.stdout - testsuite/tests/core-to-stg/T24124.stderr - testsuite/tests/corelint/LintEtaExpand.stderr - testsuite/tests/corelint/T21115b.stderr - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - + testsuite/tests/cpranal/sigs/T25944.hs - + testsuite/tests/cpranal/sigs/T25944.stderr - testsuite/tests/cpranal/sigs/all.T - testsuite/tests/deSugar/should_compile/T2431.stderr - testsuite/tests/deSugar/should_fail/DsStrictFail.stderr - testsuite/tests/deSugar/should_run/T20024.stderr - testsuite/tests/deSugar/should_run/dsrun005.stderr - testsuite/tests/deSugar/should_run/dsrun007.stderr - testsuite/tests/deSugar/should_run/dsrun008.stderr - testsuite/tests/dependent/should_fail/T16326_Fail6.stderr - testsuite/tests/deriving/should_compile/T14682.stderr - testsuite/tests/deriving/should_compile/T20815.hs - testsuite/tests/deriving/should_compile/drv-empty-data.stderr - testsuite/tests/deriving/should_fail/T12768.stderr - testsuite/tests/deriving/should_fail/T1496.stderr - testsuite/tests/deriving/should_fail/T5498.stderr - testsuite/tests/deriving/should_fail/T7148.stderr - testsuite/tests/deriving/should_fail/T7148a.stderr - testsuite/tests/deriving/should_run/T9576.stderr - testsuite/tests/dmdanal/should_compile/T16029.stdout - testsuite/tests/dmdanal/should_compile/T23398.hs - testsuite/tests/dmdanal/should_compile/T23398.stderr - testsuite/tests/dmdanal/sigs/T21119.stderr - testsuite/tests/dmdanal/sigs/T21888.stderr - testsuite/tests/driver/all.T - testsuite/tests/driver/json.stderr - testsuite/tests/driver/json_warn.stderr - + testsuite/tests/driver/make-prim/GHC/Internal/Prim.hs - + testsuite/tests/driver/make-prim/Makefile - + testsuite/tests/driver/make-prim/Test.hs - + testsuite/tests/driver/make-prim/Test2.hs - + testsuite/tests/driver/make-prim/all.T - testsuite/tests/driver/recomp015/all.T - testsuite/tests/ffi/should_run/T1288_c.c - testsuite/tests/ffi/should_run/T1288_ghci_c.c - testsuite/tests/ffi/should_run/T2276_c.c - testsuite/tests/ffi/should_run/T2276_ghci_c.c - testsuite/tests/gadt/T12468.stderr - testsuite/tests/ghc-e/should_fail/T18441fail5.stderr - testsuite/tests/ghc-e/should_fail/T24172.stderr - + testsuite/tests/ghci.debugger/scripts/T26042b.hs - + testsuite/tests/ghci.debugger/scripts/T26042b.script - + testsuite/tests/ghci.debugger/scripts/T26042b.stdout - + testsuite/tests/ghci.debugger/scripts/T26042c.hs - + testsuite/tests/ghci.debugger/scripts/T26042c.script - + testsuite/tests/ghci.debugger/scripts/T26042c.stdout - + testsuite/tests/ghci.debugger/scripts/T26042d.hs - + testsuite/tests/ghci.debugger/scripts/T26042d.script - + testsuite/tests/ghci.debugger/scripts/T26042d.stdout - + testsuite/tests/ghci.debugger/scripts/T26042d2.hs - + testsuite/tests/ghci.debugger/scripts/T26042d2.script - + testsuite/tests/ghci.debugger/scripts/T26042d2.stdout - + testsuite/tests/ghci.debugger/scripts/T26042e.hs - + testsuite/tests/ghci.debugger/scripts/T26042e.script - + testsuite/tests/ghci.debugger/scripts/T26042e.stdout - + testsuite/tests/ghci.debugger/scripts/T26042f.hs - + testsuite/tests/ghci.debugger/scripts/T26042f.script - + testsuite/tests/ghci.debugger/scripts/T26042f1.stderr - + testsuite/tests/ghci.debugger/scripts/T26042f1.stdout - + testsuite/tests/ghci.debugger/scripts/T26042f2.stdout - + testsuite/tests/ghci.debugger/scripts/T26042g.hs - + testsuite/tests/ghci.debugger/scripts/T26042g.script - + testsuite/tests/ghci.debugger/scripts/T26042g.stdout - testsuite/tests/ghci.debugger/scripts/all.T - testsuite/tests/ghci.debugger/scripts/break011.stdout - testsuite/tests/ghci.debugger/scripts/break024.stdout - testsuite/tests/ghci/prog-mhu003/prog-mhu003.stderr - testsuite/tests/ghci/prog-mhu004/prog-mhu004a.stderr - + testsuite/tests/ghci/prog-mhu005/Makefile - + testsuite/tests/ghci/prog-mhu005/a/A.hs - + testsuite/tests/ghci/prog-mhu005/all.T - + testsuite/tests/ghci/prog-mhu005/b/B.hs - + testsuite/tests/ghci/prog-mhu005/prog-mhu005a.script - + testsuite/tests/ghci/prog-mhu005/prog-mhu005a.stderr - + testsuite/tests/ghci/prog-mhu005/prog-mhu005a.stdout - + testsuite/tests/ghci/prog-mhu005/unitA - + testsuite/tests/ghci/prog-mhu005/unitB - + testsuite/tests/ghci/prog021/A.hs - + testsuite/tests/ghci/prog021/B.hs - + testsuite/tests/ghci/prog021/Makefile - + testsuite/tests/ghci/prog021/all.T - + testsuite/tests/ghci/prog021/prog021a.script - + testsuite/tests/ghci/prog021/prog021a.stderr - + testsuite/tests/ghci/prog021/prog021a.stdout - + testsuite/tests/ghci/prog021/prog021b.script - + testsuite/tests/ghci/prog021/prog021b.stderr - + testsuite/tests/ghci/prog021/prog021b.stdout - + testsuite/tests/ghci/prog022/A.hs - + testsuite/tests/ghci/prog022/B.hs - + testsuite/tests/ghci/prog022/Makefile - + testsuite/tests/ghci/prog022/all.T - + testsuite/tests/ghci/prog022/ghci.prog022a.script - + testsuite/tests/ghci/prog022/ghci.prog022a.stderr - + testsuite/tests/ghci/prog022/ghci.prog022a.stdout - + testsuite/tests/ghci/prog022/ghci.prog022b.script - + testsuite/tests/ghci/prog022/ghci.prog022b.stderr - + testsuite/tests/ghci/prog022/ghci.prog022b.stdout - testsuite/tests/ghci/scripts/Defer02.stderr - testsuite/tests/ghci/scripts/T15325.stderr - testsuite/tests/ghci/scripts/T7388.hs - testsuite/tests/ghci/scripts/T7388.script - testsuite/tests/ghci/scripts/T8353.stderr - testsuite/tests/ghci/scripts/ghci021.stderr - testsuite/tests/ghci/scripts/ghci038.stdout - testsuite/tests/haddock/haddock_testsuite/Makefile - + testsuite/tests/haddock/haddock_testsuite/T26114.hs - + testsuite/tests/haddock/haddock_testsuite/T26114.stdout - testsuite/tests/haddock/haddock_testsuite/all.T - testsuite/tests/haddock/should_compile_flag_haddock/T17544.stderr - testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr - + testsuite/tests/hiefile/should_run/HieGadtConSigs.hs - + testsuite/tests/hiefile/should_run/HieGadtConSigs.stdout - testsuite/tests/hiefile/should_run/HieQueries.stdout - testsuite/tests/hiefile/should_run/TestUtils.hs - testsuite/tests/hiefile/should_run/all.T - + testsuite/tests/hpc/recsel/Makefile - + testsuite/tests/hpc/recsel/recsel.hs - + testsuite/tests/hpc/recsel/recsel.stdout - + testsuite/tests/hpc/recsel/test.T - testsuite/tests/impredicative/T17332.stderr - testsuite/tests/indexed-types/should_compile/T2238.hs - + testsuite/tests/indexed-types/should_fail/T26176.hs - + testsuite/tests/indexed-types/should_fail/T26176.stderr - testsuite/tests/indexed-types/should_fail/T5439.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/interface-stability/ghc-experimental-exports.stdout - testsuite/tests/interface-stability/ghc-experimental-exports.stdout-mingw32 - testsuite/tests/interface-stability/ghc-prim-exports.stdout - testsuite/tests/interface-stability/ghc-prim-exports.stdout-mingw32 - testsuite/tests/interface-stability/template-haskell-exports.stdout - + testsuite/tests/linear/should_compile/T26332.hs - testsuite/tests/linear/should_compile/all.T - + testsuite/tests/llvm/should_run/T20645.hs - + testsuite/tests/llvm/should_run/T20645.stdout - testsuite/tests/llvm/should_run/all.T - − testsuite/tests/module/T21752.stderr - testsuite/tests/module/mod150.stderr - testsuite/tests/module/mod151.stderr - testsuite/tests/module/mod152.stderr - testsuite/tests/module/mod153.stderr - testsuite/tests/numeric/should_compile/T15547.stderr - testsuite/tests/numeric/should_compile/T23907.stderr - + testsuite/tests/numeric/should_compile/T26229.hs - testsuite/tests/numeric/should_compile/all.T - + testsuite/tests/numeric/should_run/T18619.hs - + testsuite/tests/numeric/should_run/T18619.stderr - + testsuite/tests/numeric/should_run/T26230.hs - + testsuite/tests/numeric/should_run/T26230.stdout - testsuite/tests/numeric/should_run/T9810.stdout - testsuite/tests/numeric/should_run/all.T - testsuite/tests/numeric/should_run/foundation.hs - testsuite/tests/overloadedrecflds/should_fail/T18999_NoDisambiguateRecordFields.stderr - + testsuite/tests/overloadedrecflds/should_run/T26295.hs - + testsuite/tests/overloadedrecflds/should_run/T26295.stdout - testsuite/tests/overloadedrecflds/should_run/all.T - testsuite/tests/parser/should_compile/DumpParsedAst.stderr - testsuite/tests/parser/should_compile/DumpRenamedAst.stderr - testsuite/tests/parser/should_compile/T14189.stderr - testsuite/tests/parser/should_compile/T15323.stderr - testsuite/tests/parser/should_compile/T19082.stderr - testsuite/tests/partial-sigs/should_compile/T10403.stderr - + testsuite/tests/partial-sigs/should_compile/T26256.hs - + testsuite/tests/partial-sigs/should_compile/T26256.stderr - testsuite/tests/partial-sigs/should_compile/all.T - testsuite/tests/partial-sigs/should_fail/T10615.stderr - + testsuite/tests/patsyn/should_compile/T26331.hs - + testsuite/tests/patsyn/should_compile/T26331a.hs - testsuite/tests/patsyn/should_compile/all.T - testsuite/tests/patsyn/should_run/ghci.stderr - testsuite/tests/perf/compiler/T4007.stdout - testsuite/tests/perf/compiler/hard_hole_fits.stderr - + testsuite/tests/perf/should_run/SpecTyFamRun.hs - + testsuite/tests/perf/should_run/SpecTyFamRun.stdout - + testsuite/tests/perf/should_run/SpecTyFam_Import.hs - testsuite/tests/perf/should_run/all.T - testsuite/tests/plugins/Makefile - + testsuite/tests/plugins/T21730-plugin/Makefile - + testsuite/tests/plugins/T21730-plugin/Setup.hs - + testsuite/tests/plugins/T21730-plugin/T21730-plugin.cabal - + testsuite/tests/plugins/T21730-plugin/T21730_Plugin.hs - + testsuite/tests/plugins/T21730.hs - testsuite/tests/plugins/all.T - testsuite/tests/plugins/plugins10.stdout - testsuite/tests/primops/should_run/UnliftedIOPort.hs - testsuite/tests/primops/should_run/all.T - testsuite/tests/printer/Makefile - testsuite/tests/printer/T18791.stderr - + testsuite/tests/printer/TestLevelImports.hs - + testsuite/tests/printer/TestNamedDefaults.hs - testsuite/tests/printer/all.T - + testsuite/tests/profiling/should_compile/T26056.hs - testsuite/tests/profiling/should_compile/all.T - testsuite/tests/profiling/should_run/caller-cc/all.T - testsuite/tests/profiling/should_run/callstack001.stdout - testsuite/tests/quantified-constraints/T15290a.stderr - testsuite/tests/quantified-constraints/T19690.stderr - testsuite/tests/quantified-constraints/T19921.stderr - testsuite/tests/quantified-constraints/T21006.stderr - testsuite/tests/quasiquotation/T4491/test.T - testsuite/tests/quotes/LiftErrMsg.stderr - testsuite/tests/quotes/LiftErrMsgDefer.stderr - testsuite/tests/quotes/LiftErrMsgTyped.stderr - testsuite/tests/rename/should_compile/T22513d.stderr - testsuite/tests/rename/should_compile/T22513e.stderr - testsuite/tests/rename/should_compile/T22513f.stderr - testsuite/tests/rename/should_compile/T22513g.stderr - testsuite/tests/rename/should_compile/T22513h.stderr - testsuite/tests/rename/should_compile/T22513i.stderr - testsuite/tests/rename/should_compile/rn039.ghc.stderr - testsuite/tests/rename/should_fail/T15487.stderr - testsuite/tests/rename/should_fail/T18740a.stderr - testsuite/tests/rename/should_fail/rnfail044.stderr - + testsuite/tests/rep-poly/NoEtaRequired.hs - testsuite/tests/rep-poly/T21906.stderr - testsuite/tests/rep-poly/all.T - testsuite/tests/roles/should_compile/Roles14.stderr - testsuite/tests/roles/should_compile/Roles3.stderr - testsuite/tests/roles/should_compile/Roles4.stderr - testsuite/tests/roles/should_fail/RolesIArray.stderr - + testsuite/tests/rts/T22859.hs - + testsuite/tests/rts/T22859.stderr - testsuite/tests/rts/all.T - testsuite/tests/rts/exec_signals_child.c - testsuite/tests/rts/flags/all.T - testsuite/tests/rts/ipe/ipeMap.c - testsuite/tests/rts/ipe/ipe_lib.c - testsuite/tests/rts/linker/T11223/T11223_link_order_a_b_2_fail.stderr-ws-32-mingw32 - testsuite/tests/rts/linker/T11223/T11223_link_order_a_b_2_fail.stderr-ws-64-mingw32 - testsuite/tests/rts/linker/T11223/all.T - testsuite/tests/safeHaskell/flags/SafeFlags17.stderr - testsuite/tests/safeHaskell/safeLanguage/SafeLang15.stderr - testsuite/tests/simd/should_run/all.T - + testsuite/tests/simd/should_run/doublex2_shuffle.hs - + testsuite/tests/simd/should_run/doublex2_shuffle.stdout - + testsuite/tests/simd/should_run/doublex2_shuffle_baseline.hs - + testsuite/tests/simd/should_run/doublex2_shuffle_baseline.stdout - + testsuite/tests/simd/should_run/floatx4_shuffle.hs - + testsuite/tests/simd/should_run/floatx4_shuffle.stdout - + testsuite/tests/simd/should_run/floatx4_shuffle_baseline.hs - + testsuite/tests/simd/should_run/floatx4_shuffle_baseline.stdout - testsuite/tests/simplCore/should_compile/DataToTagFamilyScrut.stderr - testsuite/tests/simplCore/should_compile/OpaqueNoCastWW.stderr - testsuite/tests/simplCore/should_compile/T15056.stderr - testsuite/tests/simplCore/should_compile/T15205.stderr - testsuite/tests/simplCore/should_compile/T15445.stderr - testsuite/tests/simplCore/should_compile/T17366.stderr - testsuite/tests/simplCore/should_compile/T17966.stderr - testsuite/tests/simplCore/should_compile/T22309.stderr - testsuite/tests/simplCore/should_compile/T22375DataFamily.stderr - testsuite/tests/simplCore/should_compile/T23307.stderr - testsuite/tests/simplCore/should_compile/T23307a.stderr - + testsuite/tests/simplCore/should_compile/T24606.hs - testsuite/tests/simplCore/should_compile/T25389.stderr - testsuite/tests/simplCore/should_compile/T25713.stderr - + testsuite/tests/simplCore/should_compile/T26051.hs - + testsuite/tests/simplCore/should_compile/T26051.stderr - + testsuite/tests/simplCore/should_compile/T26051_Import.hs - + testsuite/tests/simplCore/should_compile/T26115.hs - + testsuite/tests/simplCore/should_compile/T26115.stderr - + testsuite/tests/simplCore/should_compile/T26116.hs - + testsuite/tests/simplCore/should_compile/T26116.stderr - + testsuite/tests/simplCore/should_compile/T26117.hs - + testsuite/tests/simplCore/should_compile/T26117.stderr - + testsuite/tests/simplCore/should_compile/T26323b.hs - testsuite/tests/simplCore/should_compile/T7360.stderr - testsuite/tests/simplCore/should_compile/all.T - + testsuite/tests/simplCore/should_run/T26323.hs - + testsuite/tests/simplCore/should_run/T26323.stdout - testsuite/tests/simplCore/should_run/all.T - testsuite/tests/simplStg/should_compile/T15226b.stderr - + testsuite/tests/splice-imports/DodgyLevelExport.hs - + testsuite/tests/splice-imports/DodgyLevelExport.stderr - + testsuite/tests/splice-imports/DodgyLevelExportA.hs - + testsuite/tests/splice-imports/LevelImportExports.hs - + testsuite/tests/splice-imports/LevelImportExports.stdout - + testsuite/tests/splice-imports/LevelImportExportsA.hs - testsuite/tests/splice-imports/Makefile - + testsuite/tests/splice-imports/ModuleExport.hs - + testsuite/tests/splice-imports/ModuleExport.stderr - + testsuite/tests/splice-imports/ModuleExportA.hs - + testsuite/tests/splice-imports/ModuleExportB.hs - testsuite/tests/splice-imports/SI29.stderr - + testsuite/tests/splice-imports/T26087.stderr - + testsuite/tests/splice-imports/T26087A.hs - + testsuite/tests/splice-imports/T26087B.hs - + testsuite/tests/splice-imports/T26088.stderr - + testsuite/tests/splice-imports/T26088A.hs - + testsuite/tests/splice-imports/T26088B.hs - + testsuite/tests/splice-imports/T26090.hs - + testsuite/tests/splice-imports/T26090.stderr - + testsuite/tests/splice-imports/T26090A.hs - testsuite/tests/splice-imports/all.T - testsuite/tests/tcplugins/CtIdPlugin.hs - + testsuite/tests/th/GadtConSigs_th_dump1.hs - + testsuite/tests/th/GadtConSigs_th_dump1.stderr - + testsuite/tests/th/GadtConSigs_th_pprint1.hs - + testsuite/tests/th/GadtConSigs_th_pprint1.stderr - testsuite/tests/th/Makefile - testsuite/tests/th/T10267.stderr - testsuite/tests/th/T11452.stderr - testsuite/tests/th/T14627.stderr - testsuite/tests/th/T15321.stderr - testsuite/tests/th/T16180.hs - testsuite/tests/th/T20868.stdout - testsuite/tests/th/T7276.stderr - + testsuite/tests/th/TH_Depends_Dir.hs - + testsuite/tests/th/TH_Depends_Dir.stdout - + testsuite/tests/th/TH_Depends_Dir_External.hs - testsuite/tests/th/TH_NestedSplicesFail3.stderr - testsuite/tests/th/TH_NestedSplicesFail4.stderr - testsuite/tests/th/all.T - testsuite/tests/type-data/should_run/T22332a.stderr - testsuite/tests/typecheck/should_compile/Makefile - testsuite/tests/typecheck/should_compile/T12427a.stderr - testsuite/tests/typecheck/should_compile/T12763.stderr - testsuite/tests/typecheck/should_compile/T13050.stderr - + testsuite/tests/typecheck/should_compile/T14010.hs - testsuite/tests/typecheck/should_compile/T14273.stderr - testsuite/tests/typecheck/should_compile/T14590.stderr - testsuite/tests/typecheck/should_compile/T14774.stdout - testsuite/tests/typecheck/should_compile/T18406b.stderr - testsuite/tests/typecheck/should_compile/T18529.stderr - + testsuite/tests/typecheck/should_compile/T20873c.hs - − testsuite/tests/typecheck/should_compile/T22141a.stderr - − testsuite/tests/typecheck/should_compile/T22141b.stderr - − testsuite/tests/typecheck/should_compile/T22141c.stderr - − testsuite/tests/typecheck/should_compile/T22141d.stderr - − testsuite/tests/typecheck/should_compile/T22141e.stderr - testsuite/tests/typecheck/should_compile/T23171.hs - testsuite/tests/typecheck/should_compile/T23739a.hs - testsuite/tests/typecheck/should_compile/T25180.stderr - + testsuite/tests/typecheck/should_compile/T25992a.hs - + testsuite/tests/typecheck/should_compile/T26154.hs - + testsuite/tests/typecheck/should_compile/T26154_A.hs - + testsuite/tests/typecheck/should_compile/T26154_B.hs - + testsuite/tests/typecheck/should_compile/T26154_B.hs-boot - + testsuite/tests/typecheck/should_compile/T26154_Other.hs - + testsuite/tests/typecheck/should_compile/T26225.hs - + testsuite/tests/typecheck/should_compile/T26225b.hs - + testsuite/tests/typecheck/should_compile/T26256a.hs - + testsuite/tests/typecheck/should_compile/T26277.hs - + testsuite/tests/typecheck/should_compile/T26345.hs - + testsuite/tests/typecheck/should_compile/T26346.hs - + testsuite/tests/typecheck/should_compile/T26350.hs - + testsuite/tests/typecheck/should_compile/T26358.hs - testsuite/tests/typecheck/should_compile/T9497a.stderr - testsuite/tests/typecheck/should_compile/TcSpecPragmas.stderr - + testsuite/tests/typecheck/should_compile/TyAppPat_Tricky.hs - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_compile/refinement_hole_fits.stderr - testsuite/tests/typecheck/should_compile/subsumption_sort_hole_fits.stderr - − testsuite/tests/typecheck/should_fail/T12563.stderr - testsuite/tests/typecheck/should_fail/T14605.hs - testsuite/tests/typecheck/should_fail/T14605.stderr - testsuite/tests/typecheck/should_fail/T14618.stderr - testsuite/tests/typecheck/should_fail/T14884.stderr - testsuite/tests/typecheck/should_fail/T15801.stderr - testsuite/tests/typecheck/should_fail/T18640a.stderr - testsuite/tests/typecheck/should_fail/T18640b.stderr - testsuite/tests/typecheck/should_fail/T18851.hs - testsuite/tests/typecheck/should_fail/T19627.stderr - testsuite/tests/typecheck/should_fail/T20443b.stderr - − testsuite/tests/typecheck/should_fail/T20873c.hs - − testsuite/tests/typecheck/should_fail/T20873c.stderr - testsuite/tests/typecheck/should_fail/T21130.stderr - testsuite/tests/typecheck/should_fail/T21530b.stderr - testsuite/tests/typecheck/should_compile/T22141a.hs → testsuite/tests/typecheck/should_fail/T22141a.hs - testsuite/tests/typecheck/should_fail/T22141a.stderr - testsuite/tests/typecheck/should_compile/T22141b.hs → testsuite/tests/typecheck/should_fail/T22141b.hs - testsuite/tests/typecheck/should_fail/T22141b.stderr - testsuite/tests/typecheck/should_compile/T22141c.hs → testsuite/tests/typecheck/should_fail/T22141c.hs - testsuite/tests/typecheck/should_fail/T22141c.stderr - testsuite/tests/typecheck/should_compile/T22141d.hs → testsuite/tests/typecheck/should_fail/T22141d.hs - testsuite/tests/typecheck/should_fail/T22141d.stderr - testsuite/tests/typecheck/should_compile/T22141e.hs → testsuite/tests/typecheck/should_fail/T22141e.hs - testsuite/tests/typecheck/should_fail/T22141e.stderr - testsuite/tests/typecheck/should_compile/T22141e_Aux.hs → testsuite/tests/typecheck/should_fail/T22141e_Aux.hs - testsuite/tests/typecheck/should_fail/T22912.stderr - testsuite/tests/typecheck/should_fail/T23739b.stderr - testsuite/tests/typecheck/should_fail/T23739c.stderr - + testsuite/tests/typecheck/should_fail/T26255a.hs - + testsuite/tests/typecheck/should_fail/T26255a.stderr - + testsuite/tests/typecheck/should_fail/T26255b.hs - + testsuite/tests/typecheck/should_fail/T26255b.stderr - + testsuite/tests/typecheck/should_fail/T26255c.hs - + testsuite/tests/typecheck/should_fail/T26255c.stderr - + testsuite/tests/typecheck/should_fail/T26318.hs - + testsuite/tests/typecheck/should_fail/T26318.stderr - testsuite/tests/typecheck/should_fail/T6022.stderr - testsuite/tests/typecheck/should_fail/T8883.stderr - testsuite/tests/typecheck/should_fail/T9497d.stderr - testsuite/tests/typecheck/should_fail/TyAppPat_TooMany.stderr - testsuite/tests/typecheck/should_fail/UnliftedNewtypesFamilyKindFail2.stderr - testsuite/tests/typecheck/should_fail/all.T - testsuite/tests/typecheck/should_fail/tcfail037.stderr - testsuite/tests/typecheck/should_fail/tcfail140.stderr - testsuite/tests/typecheck/should_fail/tcfail174.stderr - testsuite/tests/typecheck/should_run/T10284.stderr - testsuite/tests/typecheck/should_run/T13838.stderr - testsuite/tests/typecheck/should_run/T9497a-run.stderr - testsuite/tests/typecheck/should_run/T9497b-run.stderr - testsuite/tests/typecheck/should_run/T9497c-run.stderr - testsuite/tests/unboxedsums/unpack_sums_7.stdout - testsuite/tests/unsatisfiable/T23816.stderr - testsuite/tests/unsatisfiable/UnsatDefer.stderr - + testsuite/tests/vdq-rta/should_compile/T25127_data.hs - + testsuite/tests/vdq-rta/should_compile/T25127_data_inst.hs - + testsuite/tests/vdq-rta/should_compile/T25127_infix.hs - + testsuite/tests/vdq-rta/should_compile/T25127_newtype.hs - testsuite/tests/vdq-rta/should_compile/all.T - testsuite/tests/vdq-rta/should_fail/T23738_fail_pun.stderr - testsuite/tests/vdq-rta/should_fail/T23739_fail_case.hs - testsuite/tests/vdq-rta/should_fail/T23739_fail_case.stderr - testsuite/tests/vdq-rta/should_fail/T24159_type_syntax_th_fail.script - + testsuite/tests/vdq-rta/should_fail/T25127_fail_arity.hs - + testsuite/tests/vdq-rta/should_fail/T25127_fail_arity.stderr - + testsuite/tests/vdq-rta/should_fail/T25127_fail_th_quote.hs - + testsuite/tests/vdq-rta/should_fail/T25127_fail_th_quote.stderr - testsuite/tests/vdq-rta/should_fail/all.T - testsuite/tests/wasm/should_run/control-flow/LoadCmmGroup.hs - testsuite/tests/wasm/should_run/control-flow/RunWasm.hs - utils/check-exact/ExactPrint.hs - utils/deriveConstants/Main.hs - utils/genprimopcode/Lexer.x - utils/genprimopcode/Main.hs - utils/genprimopcode/Parser.y - utils/genprimopcode/ParserM.hs - utils/genprimopcode/Syntax.hs - utils/ghc-toolchain/exe/Main.hs - utils/ghc-toolchain/src/GHC/Toolchain/Target.hs - utils/ghc-toolchain/src/GHC/Toolchain/Tools/Link.hs - utils/haddock/CHANGES.md - utils/haddock/doc/cheatsheet/haddocks.md - utils/haddock/doc/markup.rst - utils/haddock/haddock-api/haddock-api.cabal - utils/haddock/haddock-api/src/Haddock/Backends/Hoogle.hs - utils/haddock/haddock-api/src/Haddock/Backends/LaTeX.hs - utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs - utils/haddock/haddock-api/src/Haddock/Convert.hs - utils/haddock/haddock-api/src/Haddock/GhcUtils.hs - utils/haddock/haddock-api/src/Haddock/Interface.hs - utils/haddock/haddock-api/src/Haddock/Interface/AttachInstances.hs - utils/haddock/haddock-api/src/Haddock/Interface/Create.hs - utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs - utils/haddock/haddock-api/src/Haddock/InterfaceFile.hs - utils/haddock/haddock-api/src/Haddock/Types.hs - utils/haddock/haddock-library/haddock-library.cabal - utils/haddock/haddock-test/haddock-test.cabal - utils/haddock/haddock-test/src/Test/Haddock/Config.hs - utils/haddock/haddock.cabal - utils/haddock/html-test/ref/Bug1004.html - + utils/haddock/html-test/ref/Bug25739.html - + utils/haddock/html-test/ref/RedactTypeSynonyms.html - + utils/haddock/html-test/src/Bug25739.hs - + utils/haddock/html-test/src/RedactTypeSynonyms.hs - + utils/haddock/latex-test/ref/RedactTypeSynonyms/RedactTypeSynonyms.tex - + utils/haddock/latex-test/src/RedactTypeSynonyms/RedactTypeSynonyms.hs - utils/hsc2hs - 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/0523deffe6e002bad869caa9458c60c... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0523deffe6e002bad869caa9458c60c... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Cheng Shao (@TerrorJack)