Simon Peyton Jones pushed to branch wip/T23109 at Glasgow Haskell Compiler / GHC
Commits:
73082769 by Ben Gamari at 2025-07-15T16:56:38-04:00
Bump win32-tarballs to v0.9
- - - - -
3b63b254 by Ben Gamari at 2025-07-15T16:56:39-04:00
rts/LoadArchive: Handle null terminated string tables
As of `llvm-ar` now emits filename tables terminated with null
characters instead of the usual POSIX `/\n` sequence.
Fixes #26150.
- - - - -
195f6527 by Tamar Christina at 2025-07-15T16:56:39-04:00
rts: rename label so name doesn't conflict with param
- - - - -
63373b95 by Tamar Christina at 2025-07-15T16:56:39-04:00
rts: Handle API set symbol versioning conflicts
- - - - -
48e9aa3e by Tamar Christina at 2025-07-15T16:56:39-04:00
rts: Mark API set symbols as HIDDEN and correct symbol type
- - - - -
959e827a by Tamar Christina at 2025-07-15T16:56:39-04:00
rts: Implement WEAK EXTERNAL undef redirection by target symbol name
- - - - -
65f19293 by Ben Gamari at 2025-07-15T16:56:39-04:00
rts/LoadArchive: Handle string table entries terminated with /
llvm-ar appears to terminate string table entries with `/\n` [1]. This
matters in the case of thin archives, since the filename is used. In the
past this worked since `llvm-ar` would produce archives with "small"
filenames when possible. However, now it appears to always use the
string table.
[1] https://github.com/llvm/llvm-project/blob/bfb686bb5ba503e9386dc899e1ebbe2488...
- - - - -
9cbb3ef5 by Ben Gamari at 2025-07-15T16:56:39-04:00
testsuite: Mark T12497 as fixed
Thanks to the LLVM toolchain update.
Closes #22694.
- - - - -
2854407e by Ben Gamari at 2025-07-15T16:56:39-04:00
testsuite: Accept new output of T11223_link_order_a_b_2_fail on Windows
The archive member number changed due to the fact that llvm-ar now uses a
string table.
- - - - -
28439593 by Ben Gamari at 2025-07-15T16:56:39-04:00
rts/linker/PEi386: Implement IMAGE_REL_AMD64_SECREL
This appears to now be used by libc++ as distributed by msys2.
- - - - -
2b053755 by Tamar Christina at 2025-07-15T16:56:39-04:00
rts: Cleanup merge resolution residue in lookupSymbolInDLL_PEi386 and make safe without dependent
- - - - -
e8acd2e7 by Wen Kokke at 2025-07-16T08:37:04-04:00
Remove the `profile_id` parameter from various RTS functions.
Various RTS functions took a `profile_id` parameter, intended to be used to
distinguish parallel heap profile breakdowns (e.g., `-hT` and `-hi`). However,
this feature was never implemented and the `profile_id` parameter was set to 0
throughout the RTS. This commit removes the parameter but leaves the hardcoded
profile ID in the functions that emit the encoded eventlog events as to not
change the protocol.
The affected functions are `traceHeapProfBegin`, `postHeapProfBegin`,
`traceHeapProfSampleString`, `postHeapProfSampleString`,
`traceHeapProfSampleCostCentre`, and `postHeapProfSampleCostCentre`.
- - - - -
76d392a2 by Wen Kokke at 2025-07-16T08:37:04-04:00
Make `traceHeapProfBegin` an init event.
- - - - -
bbaa44a7 by Peng Fan at 2025-07-16T16:50:42-04:00
NCG/LA64: Support finer-grained DBAR hints
For LA664 and newer uarchs, they have made finer granularity hints
available:
Bit4: ordering or completion (0: completion, 1: ordering)
Bit3: barrier for previous read (0: true, 1: false)
Bit2: barrier for previous write (0: true, 1: false)
Bit1: barrier for succeeding read (0: true, 1: false)
Bit0: barrier for succeeding write (0: true, 1: false)
And not affect the existing models because other hints are treated
as 'dbar 0' there.
- - - - -
7da86e16 by Andreas Klebinger at 2025-07-16T16:51:25-04:00
Disable -fprof-late-overloaded-calls for join points.
Currently GHC considers cost centres as destructive to
join contexts. Or in other words this is not considered valid:
join f x = ...
in
... -> scc<tick> jmp
This makes the functionality of `-fprof-late-overloaded-calls` not feasible
for join points in general. We used to try to work around this by putting the
ticks on the rhs of the join point rather than around the jump. However beyond
the loss of accuracy this was broken for recursive join points as we ended up
with something like:
rec-join f x = scc<tick> ... jmp f x
Which similarly is not valid as the tick once again destroys the tail call.
One might think we could limit ourselves to non-recursive tail calls and do
something clever like:
join f x = scc<tick> ...
in ... jmp f x
And sometimes this works! But sometimes the full rhs would look something like:
join g x = ....
join f x = scc<tick> ... -> jmp g x
Which, would again no longer be valid. I believe in the long run we can make
cost centre ticks non-destructive to join points. Or we could keep track of
where we are/are not allowed to insert a cost centre. But in the short term I will
simply disable the annotation of join calls under this flag.
- - - - -
7ee22fd5 by ARATA Mizuki at 2025-07-17T06:05:30-04:00
x86 NCG: Better lowering for shuffleFloatX4# and shuffleDoubleX2#
The new implementation
* make use of specialized instructions like (V)UNPCK{L,H}{PS,PD}, and
* do not require -mavx.
Close #26096
Co-authored-by: sheaf
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 - - - - - a73abc33 by Simon Peyton Jones at 2025-07-29T18:26:44+01: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 - - - - - b742dbec by Simon Peyton Jones at 2025-07-29T18:32:36+01: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 T16577 T21839r T5642 Metric Increase: T15164 T21839c T3294 T5321FD T5321Fun WWRec - - - - - 50f45b52 by Simon Peyton Jones at 2025-07-29T18:32:43+01:00 Accept GHCi debugger output change @alt-romes says this is fine - - - - - 00351f51 by Simon Peyton Jones at 2025-07-29T18:33:42+01:00 Small hacky fix to specUnfolding ...just using mkApps instead of mkCoreApps (This part is likely to change again in a future commit.) - - - - - e106d8ae by Simon Peyton Jones at 2025-07-29T18:33:47+01:00 Slight improvement to pre/postInlineUnconditionally Avoids an extra simplifier iteration - - - - - 63b0bf89 by Simon Peyton Jones at 2025-07-29T18:33:47+01:00 Fix a long-standing assertion error in normSplitTyConApp_maybe - - - - - 0b448d1a by Simon Peyton Jones at 2025-07-29T18:33:47+01:00 Add comment to coercion optimiser - - - - - a90f83d4 by Simon Peyton Jones at 2025-07-29T23:30:04+01:00 Fix mergo bugs - - - - - 241 changed files: - .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py - compiler/GHC/Builtin/Types.hs - compiler/GHC/ByteCode/InfoTable.hs - compiler/GHC/CmmToAsm/LA64/CodeGen.hs - compiler/GHC/CmmToAsm/LA64/Instr.hs - compiler/GHC/CmmToAsm/LA64/Ppr.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Class.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/FVs.hs - compiler/GHC/Core/FamInstEnv.hs - compiler/GHC/Core/LateCC/OverloadedCalls.hs - compiler/GHC/Core/Make.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/SetLevels.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/Utils.hs - compiler/GHC/Core/Predicate.hs - compiler/GHC/Core/Rules.hs - compiler/GHC/Core/Subst.hs - compiler/GHC/Core/TyCo/Rep.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/Utils.hs - compiler/GHC/CoreToStg.hs - + compiler/GHC/CoreToStg/AddImplicitBinds.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Driver/Errors.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Hs/ImpExp.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Errors/Ppr.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Pmc/Solver/Types.hs - compiler/GHC/Iface/Decl.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Tidy.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Parser.y - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Splice.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/StgToCmm.hs - compiler/GHC/SysTools/Process.hs - compiler/GHC/Tc/Deriv.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/Gen/App.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Gen/Sig.hs - compiler/GHC/Tc/Instance/Class.hs - compiler/GHC/Tc/Instance/Family.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/Constraint.hs - − compiler/GHC/Tc/Types/EvTerm.hs - compiler/GHC/Tc/Types/Evidence.hs - compiler/GHC/Tc/Types/Origin.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/Types/Demand.hs - compiler/GHC/Types/Error.hs - compiler/GHC/Types/Id.hs - compiler/GHC/Types/Id/Make.hs - compiler/GHC/Types/RepType.hs - compiler/GHC/Types/TyThing.hs - compiler/GHC/Types/Var.hs - compiler/GHC/Unit/Module/Graph.hs - compiler/GHC/Utils/Logger.hs - compiler/ghc.cabal.in - docs/users_guide/9.14.1-notes.rst - + docs/users_guide/diagnostics-as-json-schema-1_2.json - docs/users_guide/profiling.rst - docs/users_guide/using-optimisation.rst - docs/users_guide/using.rst - ghc/GHCi/UI.hs - libraries/base/changelog.md - libraries/base/src/Data/List/NonEmpty.hs - libraries/base/src/GHC/Generics.hs - libraries/base/src/GHC/Weak/Finalize.hs - libraries/ghc-internal/src/GHC/Internal/Float.hs - libraries/ghc-internal/src/GHC/Internal/Real.hs - libraries/ghc-internal/src/GHC/Internal/System/IO.hs - mk/get-win32-tarballs.py - rts/Interpreter.c - rts/PrimOps.cmm - rts/ProfHeap.c - rts/RaiseAsync.c - rts/RetainerSet.c - rts/STM.c - rts/Trace.c - rts/Trace.h - rts/eventlog/EventLog.c - rts/eventlog/EventLog.h - rts/linker/LoadArchive.c - rts/linker/PEi386.c - testsuite/tests/core-to-stg/T24124.stderr - + 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/deriving/should_compile/T20815.hs - 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/dmdanal/should_compile/T16029.stdout - testsuite/tests/dmdanal/sigs/T21119.stderr - testsuite/tests/dmdanal/sigs/T21888.stderr - testsuite/tests/driver/json.stderr - testsuite/tests/driver/json_warn.stderr - testsuite/tests/ghci.debugger/scripts/break011.stdout - testsuite/tests/ghci.debugger/scripts/break024.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/hiefile/should_run/HieQueries.stdout - testsuite/tests/impredicative/T17332.stderr - testsuite/tests/indexed-types/should_compile/T2238.hs - 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/lib/stm/T26028.hs - + testsuite/tests/lib/stm/T26028.stdout - + testsuite/tests/lib/stm/all.T - testsuite/tests/numeric/should_compile/T15547.stderr - testsuite/tests/numeric/should_compile/T23907.stderr - testsuite/tests/numeric/should_run/T9810.stdout - testsuite/tests/printer/Makefile - + testsuite/tests/printer/TestLevelImports.hs - + testsuite/tests/printer/TestNamedDefaults.hs - testsuite/tests/printer/all.T - 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/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/all.T - 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/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/T15205.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/T25389.stderr - testsuite/tests/simplCore/should_compile/T25713.stderr - + 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/T7360.stderr - testsuite/tests/simplCore/should_compile/all.T - testsuite/tests/simplStg/should_compile/T15226b.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/all.T - testsuite/tests/tcplugins/CtIdPlugin.hs - 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/T14774.stdout - testsuite/tests/typecheck/should_compile/T18406b.stderr - testsuite/tests/typecheck/should_compile/T18529.stderr - testsuite/tests/typecheck/should_compile/T23171.hs - testsuite/tests/typecheck/should_compile/TcSpecPragmas.stderr - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_fail/T14605.hs - testsuite/tests/typecheck/should_fail/T14605.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/T19627.stderr - testsuite/tests/typecheck/should_fail/T21530b.stderr - testsuite/tests/typecheck/should_fail/T22912.stderr - testsuite/tests/typecheck/should_fail/tcfail174.stderr - testsuite/tests/unboxedsums/unpack_sums_7.stdout - testsuite/tests/wasm/should_run/control-flow/LoadCmmGroup.hs - testsuite/tests/wasm/should_run/control-flow/RunWasm.hs - utils/check-exact/ExactPrint.hs - utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/586cd1f482e465fe6ab70a828a1f395... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/586cd1f482e465fe6ab70a828a1f395... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Simon Peyton Jones (@simonpj)