[Git][ghc/ghc][wip/romes/step-out-11] 57 commits: Specialise: Improve specialisation by refactoring interestingDict
by Rodrigo Mesquita (@alt-romes) 30 Jul '25
by Rodrigo Mesquita (@alt-romes) 30 Jul '25
30 Jul '25
Rodrigo Mesquita pushed to branch wip/romes/step-out-11 at Glasgow Haskell Compiler / GHC
Commits:
f707bab4 by Andreas Klebinger at 2025-07-12T14:56:16+01:00
Specialise: Improve specialisation by refactoring interestingDict
This MR addresses #26051, which concerns missed type-class specialisation.
The main payload of the MR is to completely refactor the key function
`interestingDict` in GHC.Core.Opt.Specialise
The main change is that we now also look at the structure of the
dictionary we consider specializing on, rather than only the type.
See the big `Note [Interesting dictionary arguments]`
- - - - -
ca7a9d42 by Simon Peyton Jones at 2025-07-12T14:56:16+01:00
Treat tuple dictionaries uniformly; don't unbox them
See `Note [Do not unbox class dictionaries]` in DmdAnal.hs,
sep (DNB1).
This MR reverses the plan in #23398, which suggested a special case to
unbox tuple dictionaries in worker/wrapper. But:
- This was the cause of a pile of complexity in the specialiser (#26158)
- Even with that complexity, specialision was still bad, very bad
See https://gitlab.haskell.org/ghc/ghc/-/issues/19747#note_626297
And it's entirely unnecessary! Specialision works fine without
unboxing tuple dictionaries.
- - - - -
be7296c9 by Andreas Klebinger at 2025-07-12T14:56:16+01:00
Remove complex special case from the type-class specialiser
There was a pretty tricky special case in Specialise which is no
longer necessary.
* Historical Note [Floating dictionaries out of cases]
* #26158
* #19747 https://gitlab.haskell.org/ghc/ghc/-/issues/19747#note_626297
This MR removes it. Hooray.
- - - - -
4acf3a86 by Ben Gamari at 2025-07-15T05:46:32-04:00
configure: bump version to 9.15
- - - - -
45efaf71 by Teo Camarasu at 2025-07-15T05:47:13-04:00
rts/nonmovingGC: remove n_free
We remove the nonmovingHeap.n_free variable.
We wanted this to track the length of nonmovingHeap.free.
But this isn't possible to do atomically.
When this isn't accurate we can get a segfault by going past the end of
the list.
Instead, we just count the length of the list when we grab it in
nonmovingPruneFreeSegment.
Resolves #26186
- - - - -
c635f164 by Ben Gamari at 2025-07-15T14:05:54-04:00
configure: Drop probing of ld.gold
As noted in #25716, `gold` has been dropped from binutils-2.44.
Fixes #25716.
Metric Increase:
size_hello_artifact_gzip
size_hello_unicode_gzip
ghc_prim_so
- - - - -
637bb538 by Ben Gamari at 2025-07-15T14:05:55-04:00
testsuite/recomp015: Ignore stderr
This is necessary since ld.bfd complains
that we don't have a .note.GNU-stack section,
potentially resulting in an executable stack.
- - - - -
d3cd4ec8 by Wen Kokke at 2025-07-15T14:06:39-04:00
Fix documentation for heap profile ID
- - - - -
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/bfb686bb5ba503e9386dc899e1ebbe248…
- - - - -
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 <sam.derbyshire(a)gmail.com>
- - - - -
c6cd2da1 by Jappie Klooster at 2025-07-17T06:06:20-04:00
Update interact docs to explain about buffering
We need to tell the user to set to the
appropriate buffer format.
Otherwise, this function may get randomly stuck,
or just behave confusingly.
issue: https://gitlab.haskell.org/ghc/ghc/-/issues/26131
NB, I'm running this with cabal *NOT* ghci. ghci messes with buffering anyway.
```haskell
interaction :: String -> String
interaction "jappie" = "hi"
interaction "jakob" = "hello"
interaction x = "unkown input: " <> x
main :: IO ()
main = interact interaction
```
so in my input (prefixed by `>`) I get:
```
> 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
- - - - -
9620cae0 by Rodrigo Mesquita at 2025-07-30T11:11:39+01:00
debugger: Uniquely identify breakpoints by internal id
Since b85b11994e0130ff2401dd4bbdf52330e0bcf776 (support inlining
breakpoints), a breakpoint has been identified at runtime by *two* pairs
of <module,index>.
- The first, aka a 'BreakpointId', uniquely identifies a breakpoint in
the source of a module by using the Tick index. A Tick index can index
into ModBreaks.modBreaks_xxx to fetch source-level information about
where that tick originated.
- When a user specifies e.g. a line breakpoint using :break, we'll reverse
engineer what a Tick index for that line
- We update the `BreakArray` of that module (got from the
LoaderState) at that tick index to `breakOn`.
- A BCO we can stop at is headed by a BRK_FUN instruction. This
instruction stores in an operand the `tick index` it is associated
to. We look it up in the associated `BreakArray` (also an operand)
and check wheter it was set to `breakOn`.
- The second, aka the `ibi_info_mod` + `ibi_info_ix` of the
`InternalBreakpointId`, uniquely index into the `imodBreaks_breakInfo`
-- the information we gathered during code generation about the
existing breakpoint *ocurrences*.
- Note that with optimisation there may be many occurrences of the
same source-tick-breakpoint across different modules. The
`ibi_info_ix` is unique per occurrence, but the `bi_tick_ix` may be
shared. See Note [Breakpoint identifiers] about this.
- Note that besides the tick ids, info ids are also stored in
`BRK_FUN` so the break handler can refer to the associated
`CgBreakInfo`.
In light of that, the driving changes come from the desire to have the
info_id uniquely identify the breakpoint at runtime, and the source tick
id being derived from it:
- An InternalBreakpointId should uniquely identify a breakpoint just
from the code-generation identifiers of `ibi_info_ix` and `ibi_info_mod`.
So we drop `ibi_tick_mod` and `ibi_tick_ix`.
- A BRK_FUN instruction need only record the "internal breakpoint id",
not the tick-level id.
So we drop the tick mod and tick index operands.
- A BreakArray should be indexed by InternalBreakpointId rather than
BreakpointId
That means we need to do some more work when setting a breakpoint.
Specifically, we need to figure out the internal ids (occurrences of a
breakpoint) from the source-level BreakpointId we want to set the
breakpoint at (recall :break refers to breaks at the source level).
Besides this change being an improvement to the handling of breakpoints
(it's clearer to have a single unique identifier than two competing
ones), it unlocks the possibility of generating "internal" breakpoints
during Cg (needed for #26042).
It should also be easier to introduce multi-threaded-aware `BreakArrays`
following this change (needed for #26064).
Se also the new Note [ModBreaks vs InternalModBreaks]
- - - - -
586e7ea0 by Rodrigo Mesquita at 2025-07-30T11:11:39+01:00
cleanup: Move dehydrateCgBreakInfo to Stg2Bc
This no longer has anything to do with Core.
- - - - -
09f39496 by Rodrigo Mesquita at 2025-07-30T11:11:39+01:00
rts/Disassembler: Fix spacing of BRK_FUN
- - - - -
519b71e2 by Rodrigo Mesquita at 2025-07-30T11:11:40+01:00
debugger: Fix bciPtr in Step-out
We need to use `BCO_NEXT` to move bciPtr to ix=1, because ix=0 points to
the instruction itself!
I do not understand how this didn't crash before.
- - - - -
b8ed860a by Rodrigo Mesquita at 2025-07-30T11:11:40+01:00
debugger: Allow BRK_FUNs to head case continuation BCOs
When we start executing a BCO, we may want to yield to the scheduler:
this may be triggered by a heap/stack check, context switch, or a
breakpoint. To yield, we need to put the stack in a state such that
when execution is resumed we are back to where we yielded from.
Previously, a BKR_FUN could only head a function BCO because we only
knew how to construct a valid stack for yielding from one -- simply add
`apply_interp_info` + the BCO to resume executing. This is valid because
the stack at the start of run_BCO is headed by that BCO's arguments.
However, in case continuation BCOs (as per Note [Case continuation BCOs]),
we couldn't easily reconstruct a valid stack that could be resumed
because we dropped too soon the stack frames regarding the value
returned (stg_ret) and received (stg_ctoi) by that continuation.
This is especially tricky because of the variable type and size return
frames (e.g. pointer ret_p/ctoi_R1p vs a tuple ret_t/ctoi_t2).
The trick to being able to yield from a BRK_FUN at the start of a case
cont BCO is to stop removing the ret frame headers eagerly and instead
keep them until the BCO starts executing. The new layout at the start of
a case cont. BCO is described by the new Note [Stack layout when entering run_BCO].
Now, we keep the ret_* and ctoi_* frames when entering run_BCO.
A BRK_FUN is then executed if found, and the stack is yielded as-is with
the preserved ret and ctoi frames.
Then, a case cont BCO's instructions always SLIDE off the headers of the
ret and ctoi frames, in StgToByteCode.doCase, turning a stack like
| .... |
+---------------+
| fv2 |
+---------------+
| fv1 |
+---------------+
| BCO |
+---------------+
| stg_ctoi_ret_ |
+---------------+
| retval |
+---------------+
| stg_ret_..... |
+---------------+
into
| .... |
+---------------+
| fv2 |
+---------------+
| fv1 |
+---------------+
| retval |
+---------------+
for the remainder of the BCO.
Moreover, this more uniform approach of keeping the ret and ctoi frames
means we need less ad-hoc logic concerning the variable size of
ret_tuple vs ret_p/np frames in the code generator and interpreter:
Always keep the return to cont. stack intact at the start of run_BCO,
and the statically generated instructions will take care of adjusting
it.
Unlocks BRK_FUNs at the start of case cont. BCOs which will enable a
better user-facing step-out (#26042) which is free of the bugs the
current BRK_ALTS implementation suffers from (namely, using BRK_FUN
rather than BRK_ALTS in a case cont. means we'll never accidentally end
up in a breakpoint "deeper" than the continuation, because we stop at
the case cont itself rather than on the first breakpoint we evaluate
after it).
- - - - -
bed90fb6 by Rodrigo Mesquita at 2025-07-30T11:11:40+01:00
BRK_FUN with InternalBreakLocs for code-generation time breakpoints
At the start of a case continuation BCO, place a BRK_FUN.
This BRK_FUN uses the new "internal breakpoint location" -- allowing us
to come up with a valid source location for this breakpoint that is not associated with a source-level tick.
For case continuation BCOs, we use the last tick seen before it as the
source location. The reasoning is described in Note [Debugger: Stepout internal break locs].
Note how T26042c, which was broken because it displayed the incorrect
behavior of the previous step out when we'd end up at a deeper level
than the one from which we initiated step-out, is now fixed.
As of this commit, BRK_ALTS is now dead code and is thus dropped.
Note [Debugger: Stepout internal break locs]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Step-out tells the interpreter to run until the current function
returns to where it was called from, and stop there.
This is achieved by enabling the BRK_FUN found on the first RET_BCO
frame on the stack (See [Note Debugger: Step-out]).
Case continuation BCOs (which select an alternative branch) must
therefore be headed by a BRK_FUN. An example:
f x = case g x of <--- end up here
1 -> ...
2 -> ...
g y = ... <--- step out from here
- `g` will return a value to the case continuation BCO in `f`
- The case continuation BCO will receive the value returned from g
- Match on it and push the alternative continuation for that branch
- And then enter that alternative.
If we step-out of `g`, the first RET_BCO on the stack is the case
continuation of `f` -- execution should stop at its start, before
selecting an alternative. (One might ask, "why not enable the breakpoint
in the alternative instead?", because the alternative continuation is
only pushed to the stack *after* it is selected by the case cont. BCO)
However, the case cont. BCO is not associated with any source-level
tick, it is merely the glue code which selects alternatives which do
have source level ticks. Therefore, we have to come up at code
generation time with a breakpoint location ('InternalBreakLoc') to
display to the user when it is stopped there.
Our solution is to use the last tick seen just before reaching the case
continuation. This is robust because a case continuation will thus
always have a relevant breakpoint location:
- The source location will be the last source-relevant expression
executed before the continuation is pushed
- So the source location will point to the thing you've just stepped
out of
- Doing :step-local from there will put you on the selected
alternative (which at the source level may also be the e.g. next
line in a do-block)
Examples, using angle brackets (<<...>>) to denote the breakpoint span:
f x = case <<g x>> {- step in here -} of
1 -> ...
2 -> ...>
g y = <<...>> <--- step out from here
...
f x = <<case g x of <--- end up here, whole case highlighted
1 -> ...
2 -> ...>>
doing :step-local ...
f x = case g x of
1 -> <<...>> <--- stop in the alternative
2 -> ...
A second example based on T26042d2, where the source is a do-block IO
action, optimised to a chain of `case expressions`.
main = do
putStrLn "hello1"
<<f>> <--- step-in here
putStrLn "hello3"
putStrLn "hello4"
f = do
<<putStrLn "hello2.1">> <--- step-out from here
putStrLn "hello2.2"
...
main = do
putStrLn "hello1"
<<f>> <--- end up here again, the previously executed expression
putStrLn "hello3"
putStrLn "hello4"
doing step/step-local ...
main = do
putStrLn "hello1"
f
<<putStrLn "hello3">> <--- straight to the next line
putStrLn "hello4"
Finishes #26042
- - - - -
78f06878 by Rodrigo Mesquita at 2025-07-30T11:11:40+01:00
bytecode: Don't PUSH_L 0; SLIDE 1 1
While looking through bytecode I noticed a quite common unfortunate
pattern:
...
PUSH_L 0
SLIDE 1 1
We do this often by generically constructing a tail call from a function
atom that may be somewhere arbitrary on the stack.
However, for the special case that the function can be found directly on
top of the stack, as part of the arguments, it's plain redundant to push
then slide it.
In this commit we add a small optimisation to the generation of
tailcalls in bytecode. Simply: lookahead for the function in the stack.
If it is the first thing on the stack and it is part of the arguments
which would be dropped as we entered the tail call, then don't push then
slide it.
In a simple example (T26042b), this already produced a drastic
improvement in generated code (left is old, right is with this patch):
```diff
3c3
< 2025-07-29 10:14:02.081277 UTC
---
> 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%)
with optimized core:
1924818 lines (before) - 1864836 lines (now)
= 59982 less redundant instructions (-3.1%)
- - - - -
217 changed files:
- .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py
- compiler/GHC/ByteCode/Asm.hs
- compiler/GHC/ByteCode/Breakpoints.hs
- compiler/GHC/ByteCode/Instr.hs
- compiler/GHC/ByteCode/Linker.hs
- compiler/GHC/ByteCode/Types.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/FVs.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/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/Unfold/Make.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/Driver/Errors.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Breakpoints.hs
- compiler/GHC/HsToCore/Errors/Ppr.hs
- compiler/GHC/HsToCore/Pmc/Solver/Types.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Parser.y
- compiler/GHC/Rename/Splice.hs
- compiler/GHC/Runtime/Debugger/Breakpoints.hs
- compiler/GHC/Runtime/Eval.hs
- compiler/GHC/Runtime/Interpreter.hs
- compiler/GHC/StgToByteCode.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/Expr.hs
- compiler/GHC/Tc/Gen/Pat.hs
- compiler/GHC/Tc/Gen/Sig.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/PatSyn.hs
- compiler/GHC/Tc/Types/Constraint.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/Error.hs
- compiler/GHC/Types/Var.hs
- compiler/GHC/Unit/Module/Graph.hs
- compiler/GHC/Utils/Logger.hs
- configure.ac
- docs/users_guide/9.14.1-notes.rst
- + docs/users_guide/diagnostics-as-json-schema-1_2.json
- docs/users_guide/eventlog-formats.rst
- docs/users_guide/profiling.rst
- docs/users_guide/using-optimisation.rst
- docs/users_guide/using.rst
- ghc/GHCi/UI.hs
- ghc/GHCi/UI/Monad.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
- libraries/ghci/GHCi/Debugger.hs
- libraries/ghci/GHCi/Message.hs
- libraries/ghci/GHCi/Run.hs
- m4/find_ld.m4
- mk/get-win32-tarballs.py
- rts/Disassembler.c
- rts/Exception.cmm
- rts/Interpreter.c
- rts/PrimOps.cmm
- rts/ProfHeap.c
- rts/Profiling.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/include/rts/Bytecodes.h
- rts/linker/LoadArchive.c
- rts/linker/PEi386.c
- rts/sm/NonMoving.c
- rts/sm/NonMoving.h
- rts/sm/NonMovingAllocate.c
- rts/sm/Sanity.c
- 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/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/T23398.hs
- testsuite/tests/dmdanal/should_compile/T23398.stderr
- testsuite/tests/driver/json.stderr
- testsuite/tests/driver/json_warn.stderr
- testsuite/tests/driver/recomp015/all.T
- testsuite/tests/ghci.debugger/scripts/T26042b.stdout
- testsuite/tests/ghci.debugger/scripts/T26042c.script
- testsuite/tests/ghci.debugger/scripts/T26042c.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.stdout
- testsuite/tests/ghci.debugger/scripts/T26042f2.stdout
- testsuite/tests/ghci.debugger/scripts/T26042g.stdout
- testsuite/tests/ghci.debugger/scripts/all.T
- 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/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_run/T9810.stdout
- + 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/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_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/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/all.T
- + 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/typecheck/should_compile/T12427a.stderr
- testsuite/tests/typecheck/should_compile/T23171.hs
- testsuite/tests/typecheck/should_compile/TcSpecPragmas.stderr
- 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
- utils/check-exact/ExactPrint.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Link.hs
- utils/haddock/haddock-api/haddock-api.cabal
- 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/8084c422f331ab5bbd3617fbce6e70…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8084c422f331ab5bbd3617fbce6e70…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/romes/step-out-11] 2 commits: BRK_FUN with InternalBreakLocs for code-generation time breakpoints
by Rodrigo Mesquita (@alt-romes) 30 Jul '25
by Rodrigo Mesquita (@alt-romes) 30 Jul '25
30 Jul '25
Rodrigo Mesquita pushed to branch wip/romes/step-out-11 at Glasgow Haskell Compiler / GHC
Commits:
4fcfaae8 by Rodrigo Mesquita at 2025-07-30T11:00:49+01:00
BRK_FUN with InternalBreakLocs for code-generation time breakpoints
At the start of a case continuation BCO, place a BRK_FUN.
This BRK_FUN uses the new "internal breakpoint location" -- allowing us
to come up with a valid source location for this breakpoint that is not associated with a source-level tick.
For case continuation BCOs, we use the last tick seen before it as the
source location. The reasoning is described in Note [Debugger: Stepout internal break locs].
Note how T26042c, which was broken because it displayed the incorrect
behavior of the previous step out when we'd end up at a deeper level
than the one from which we initiated step-out, is now fixed.
As of this commit, BRK_ALTS is now dead code and is thus dropped.
Note [Debugger: Stepout internal break locs]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Step-out tells the interpreter to run until the current function
returns to where it was called from, and stop there.
This is achieved by enabling the BRK_FUN found on the first RET_BCO
frame on the stack (See [Note Debugger: Step-out]).
Case continuation BCOs (which select an alternative branch) must
therefore be headed by a BRK_FUN. An example:
f x = case g x of <--- end up here
1 -> ...
2 -> ...
g y = ... <--- step out from here
- `g` will return a value to the case continuation BCO in `f`
- The case continuation BCO will receive the value returned from g
- Match on it and push the alternative continuation for that branch
- And then enter that alternative.
If we step-out of `g`, the first RET_BCO on the stack is the case
continuation of `f` -- execution should stop at its start, before
selecting an alternative. (One might ask, "why not enable the breakpoint
in the alternative instead?", because the alternative continuation is
only pushed to the stack *after* it is selected by the case cont. BCO)
However, the case cont. BCO is not associated with any source-level
tick, it is merely the glue code which selects alternatives which do
have source level ticks. Therefore, we have to come up at code
generation time with a breakpoint location ('InternalBreakLoc') to
display to the user when it is stopped there.
Our solution is to use the last tick seen just before reaching the case
continuation. This is robust because a case continuation will thus
always have a relevant breakpoint location:
- The source location will be the last source-relevant expression
executed before the continuation is pushed
- So the source location will point to the thing you've just stepped
out of
- Doing :step-local from there will put you on the selected
alternative (which at the source level may also be the e.g. next
line in a do-block)
Examples, using angle brackets (<<...>>) to denote the breakpoint span:
f x = case <<g x>> {- step in here -} of
1 -> ...
2 -> ...>
g y = <<...>> <--- step out from here
...
f x = <<case g x of <--- end up here, whole case highlighted
1 -> ...
2 -> ...>>
doing :step-local ...
f x = case g x of
1 -> <<...>> <--- stop in the alternative
2 -> ...
A second example based on T26042d2, where the source is a do-block IO
action, optimised to a chain of `case expressions`.
main = do
putStrLn "hello1"
<<f>> <--- step-in here
putStrLn "hello3"
putStrLn "hello4"
f = do
<<putStrLn "hello2.1">> <--- step-out from here
putStrLn "hello2.2"
...
main = do
putStrLn "hello1"
<<f>> <--- end up here again, the previously executed expression
putStrLn "hello3"
putStrLn "hello4"
doing step/step-local ...
main = do
putStrLn "hello1"
f
<<putStrLn "hello3">> <--- straight to the next line
putStrLn "hello4"
Finishes #26042
- - - - -
8084c422 by Rodrigo Mesquita at 2025-07-30T11:01:03+01:00
bytecode: Don't PUSH_L 0; SLIDE 1 1
While looking through bytecode I noticed a quite common unfortunate
pattern:
...
PUSH_L 0
SLIDE 1 1
We do this often by generically constructing a tail call from a function
atom that may be somewhere arbitrary on the stack.
However, for the special case that the function can be found directly on
top of the stack, as part of the arguments, it's plain redundant to push
then slide it.
In this commit we add a small optimisation to the generation of
tailcalls in bytecode. Simply: lookahead for the function in the stack.
If it is the first thing on the stack and it is part of the arguments
which would be dropped as we entered the tail call, then don't push then
slide it.
In a simple example (T26042b), this already produced a drastic
improvement in generated code (left is old, right is with this patch):
```diff
3c3
< 2025-07-29 10:14:02.081277 UTC
---
> 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%)
with optimized core:
1924818 lines (before) - 1864836 lines (now)
= 59982 less redundant instructions (-3.1%)
- - - - -
21 changed files:
- compiler/GHC/ByteCode/Asm.hs
- compiler/GHC/ByteCode/Breakpoints.hs
- compiler/GHC/ByteCode/Instr.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Runtime/Debugger/Breakpoints.hs
- compiler/GHC/Runtime/Eval.hs
- compiler/GHC/StgToByteCode.hs
- ghc/GHCi/UI.hs
- rts/Disassembler.c
- rts/Interpreter.c
- rts/include/rts/Bytecodes.h
- testsuite/tests/ghci.debugger/scripts/T26042b.stdout
- testsuite/tests/ghci.debugger/scripts/T26042c.script
- testsuite/tests/ghci.debugger/scripts/T26042c.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.stdout
- testsuite/tests/ghci.debugger/scripts/T26042f2.stdout
- testsuite/tests/ghci.debugger/scripts/T26042g.stdout
- testsuite/tests/ghci.debugger/scripts/all.T
Changes:
=====================================
compiler/GHC/ByteCode/Asm.hs
=====================================
@@ -854,8 +854,6 @@ assembleI platform i = case i of
emit_ bci_BRK_FUN [ Op p1, Op info_addr, Op info_unitid_addr
, SmallOp (toW16 infox), Op np ]
- BRK_ALTS active -> emit_ bci_BRK_ALTS [SmallOp (if active then 1 else 0)]
-
#if MIN_VERSION_rts(1,0,3)
BCO_NAME name -> do np <- lit1 (BCONPtrStr name)
emit_ bci_BCO_NAME [Op np]
=====================================
compiler/GHC/ByteCode/Breakpoints.hs
=====================================
@@ -1,4 +1,5 @@
{-# LANGUAGE RecordWildCards #-}
+{-# LANGUAGE DerivingStrategies #-}
-- | Breakpoint information constructed during ByteCode generation.
--
@@ -15,6 +16,7 @@ module GHC.ByteCode.Breakpoints
-- ** Internal breakpoint identifier
, InternalBreakpointId(..), BreakInfoIndex
+ , InternalBreakLoc(..)
-- * Operations
@@ -23,7 +25,7 @@ module GHC.ByteCode.Breakpoints
-- ** Source-level information operations
, getBreakLoc, getBreakVars, getBreakDecls, getBreakCCS
- , getBreakSourceId
+ , getBreakSourceId, getBreakSourceMod
-- * Utils
, seqInternalModBreaks
@@ -165,7 +167,7 @@ data CgBreakInfo
{ cgb_tyvars :: ![IfaceTvBndr] -- ^ Type variables in scope at the breakpoint
, cgb_vars :: ![Maybe (IfaceIdBndr, Word)]
, cgb_resty :: !IfaceType
- , cgb_tick_id :: !BreakpointId
+ , cgb_tick_id :: !(Either InternalBreakLoc BreakpointId)
-- ^ This field records the original breakpoint tick identifier for this
-- internal breakpoint info. It is used to convert a breakpoint
-- *occurrence* index ('InternalBreakpointId') into a *definition* index
@@ -173,9 +175,18 @@ data CgBreakInfo
--
-- The modules of breakpoint occurrence and breakpoint definition are not
-- necessarily the same: See Note [Breakpoint identifiers].
+ --
+ -- If there is no original tick identifier (that is, the breakpoint was
+ -- created during code generation), instead refer directly to the SrcSpan
+ -- we want to use for it.
}
-- See Note [Syncing breakpoint info] in GHC.Runtime.Eval
+-- | Breakpoints created during code generation don't have a source-level tick
+-- location. Instead, we come up with one ourselves.
+newtype InternalBreakLoc = InternalBreakLoc SrcSpan
+ deriving newtype (Eq, Show, NFData, Outputable)
+
-- | Get an internal breakpoint info by 'InternalBreakpointId'
getInternalBreak :: InternalBreakpointId -> InternalModBreaks -> CgBreakInfo
getInternalBreak (InternalBreakpointId mod ix) imbs =
@@ -196,27 +207,36 @@ assert_modules_match ibi_mod imbs_mod =
-- | Get the source module and tick index for this breakpoint
-- (as opposed to the module where this breakpoint occurs, which is in 'InternalBreakpointId')
-getBreakSourceId :: InternalBreakpointId -> InternalModBreaks -> BreakpointId
+getBreakSourceId :: InternalBreakpointId -> InternalModBreaks -> Either InternalBreakLoc BreakpointId
getBreakSourceId (InternalBreakpointId ibi_mod ibi_ix) imbs =
assert_modules_match ibi_mod (imodBreaks_module imbs) $
let cgb = imodBreaks_breakInfo imbs IM.! ibi_ix
in cgb_tick_id cgb
+-- | Get the source module for this breakpoint (where the breakpoint is defined)
+getBreakSourceMod :: InternalBreakpointId -> InternalModBreaks -> Module
+getBreakSourceMod (InternalBreakpointId ibi_mod ibi_ix) imbs =
+ assert_modules_match ibi_mod (imodBreaks_module imbs) $
+ let cgb = imodBreaks_breakInfo imbs IM.! ibi_ix
+ in case cgb_tick_id cgb of
+ Left InternalBreakLoc{} -> imodBreaks_module imbs
+ Right BreakpointId{bi_tick_mod} -> bi_tick_mod
+
-- | Get the source span for this breakpoint
getBreakLoc :: (Module -> IO ModBreaks) -> InternalBreakpointId -> InternalModBreaks -> IO SrcSpan
-getBreakLoc = getBreakXXX modBreaks_locs
+getBreakLoc = getBreakXXX modBreaks_locs (\(InternalBreakLoc x) -> x)
-- | Get the vars for this breakpoint
getBreakVars :: (Module -> IO ModBreaks) -> InternalBreakpointId -> InternalModBreaks -> IO [OccName]
-getBreakVars = getBreakXXX modBreaks_vars
+getBreakVars = getBreakXXX modBreaks_vars (const [])
-- | Get the decls for this breakpoint
getBreakDecls :: (Module -> IO ModBreaks) -> InternalBreakpointId -> InternalModBreaks -> IO [String]
-getBreakDecls = getBreakXXX modBreaks_decls
+getBreakDecls = getBreakXXX modBreaks_decls (const [])
-- | Get the decls for this breakpoint
-getBreakCCS :: (Module -> IO ModBreaks) -> InternalBreakpointId -> InternalModBreaks -> IO (String, String)
-getBreakCCS = getBreakXXX modBreaks_ccs
+getBreakCCS :: (Module -> IO ModBreaks) -> InternalBreakpointId -> InternalModBreaks -> IO (Maybe (String, String))
+getBreakCCS = getBreakXXX (fmap Just . modBreaks_ccs) (const Nothing)
-- | Internal utility to access a ModBreaks field at a particular breakpoint index
--
@@ -228,14 +248,17 @@ getBreakCCS = getBreakXXX modBreaks_ccs
-- 'ModBreaks'. When the tick module is different, we need to look up the
-- 'ModBreaks' in the HUG for that other module.
--
+-- When there is no tick module (the breakpoint was generated at codegen), use
+-- the function on internal mod breaks.
+--
-- To avoid cyclic dependencies, we instead receive a function that looks up
-- the 'ModBreaks' given a 'Module'
-getBreakXXX :: (ModBreaks -> Array BreakTickIndex a) -> (Module -> IO ModBreaks) -> InternalBreakpointId -> InternalModBreaks -> IO a
-getBreakXXX view lookupModule (InternalBreakpointId ibi_mod ibi_ix) imbs =
+getBreakXXX :: (ModBreaks -> Array BreakTickIndex a) -> (InternalBreakLoc -> a) -> (Module -> IO ModBreaks) -> InternalBreakpointId -> InternalModBreaks -> IO a
+getBreakXXX view viewInternal lookupModule (InternalBreakpointId ibi_mod ibi_ix) imbs =
assert_modules_match ibi_mod (imodBreaks_module imbs) $ do
let cgb = imodBreaks_breakInfo imbs IM.! ibi_ix
case cgb_tick_id cgb of
- BreakpointId{bi_tick_mod, bi_tick_index}
+ Right BreakpointId{bi_tick_mod, bi_tick_index}
| bi_tick_mod == ibi_mod
-> do
let these_mbs = imodBreaks_modBreaks imbs
@@ -244,6 +267,8 @@ getBreakXXX view lookupModule (InternalBreakpointId ibi_mod ibi_ix) imbs =
-> do
other_mbs <- lookupModule bi_tick_mod
return $ view other_mbs ! bi_tick_index
+ Left l ->
+ return $ viewInternal l
--------------------------------------------------------------------------------
-- Instances
=====================================
compiler/GHC/ByteCode/Instr.hs
=====================================
@@ -260,10 +260,6 @@ data BCInstr
-- Breakpoints
| BRK_FUN !InternalBreakpointId
- -- An internal breakpoint for triggering a break on any case alternative
- -- See Note [Debugger: BRK_ALTS]
- | BRK_ALTS !Bool {- enabled? -}
-
#if MIN_VERSION_rts(1,0,3)
-- | A "meta"-instruction for recording the name of a BCO for debugging purposes.
-- These are ignored by the interpreter but helpfully printed by the disassmbler.
@@ -458,7 +454,6 @@ instance Outputable BCInstr where
= text "BRK_FUN" <+> text "<breakarray>"
<+> ppr info_mod <+> ppr infox
<+> text "<cc>"
- ppr (BRK_ALTS active) = text "BRK_ALTS" <+> ppr active
#if MIN_VERSION_rts(1,0,3)
ppr (BCO_NAME nm) = text "BCO_NAME" <+> text (show nm)
#endif
@@ -584,7 +579,6 @@ bciStackUse OP_INDEX_ADDR{} = 0
bciStackUse SWIZZLE{} = 0
bciStackUse BRK_FUN{} = 0
-bciStackUse BRK_ALTS{} = 0
-- These insns actually reduce stack use, but we need the high-tide level,
-- so can't use this info. Not that it matters much.
=====================================
compiler/GHC/Linker/Loader.hs
=====================================
@@ -58,6 +58,7 @@ import GHCi.RemoteTypes
import GHC.Iface.Load
import GHCi.Message (ConInfoTable(..), LoadedDLL)
+import GHC.ByteCode.Breakpoints
import GHC.ByteCode.Linker
import GHC.ByteCode.Asm
import GHC.ByteCode.Types
@@ -1711,8 +1712,10 @@ allocateCCS interp ce mbss
let count = 1 + (maybe 0 fst $ IM.lookupMax imodBreaks_breakInfo)
let ccs = IM.map
(\info ->
- fromMaybe (toRemotePtr nullPtr)
- (M.lookup (cgb_tick_id info) ccss)
+ case cgb_tick_id info of
+ Right bi -> fromMaybe (toRemotePtr nullPtr)
+ (M.lookup bi ccss)
+ Left InternalBreakLoc{} -> toRemotePtr nullPtr
)
imodBreaks_breakInfo
assertPpr (count == length ccs)
=====================================
compiler/GHC/Runtime/Debugger/Breakpoints.hs
=====================================
@@ -253,8 +253,11 @@ mkBreakpointOccurrences = do
let imod = modBreaks_module $ imodBreaks_modBreaks ibrks
IntMap.foldrWithKey (\info_ix cgi bmp -> do
let ibi = InternalBreakpointId imod info_ix
- let BreakpointId tick_mod tick_ix = cgb_tick_id cgi
- extendModuleEnvWith (IntMap.unionWith (S.<>)) bmp tick_mod (IntMap.singleton tick_ix [ibi])
+ case cgb_tick_id cgi of
+ Right (BreakpointId tick_mod tick_ix)
+ -> extendModuleEnvWith (IntMap.unionWith (S.<>)) bmp tick_mod (IntMap.singleton tick_ix [ibi])
+ Left _
+ -> bmp
) bmp0 (imodBreaks_breakInfo ibrks)
--------------------------------------------------------------------------------
@@ -287,7 +290,7 @@ getCurrentBreakModule = do
Nothing -> pure Nothing
Just ibi -> do
brks <- readIModBreaks hug ibi
- return $ Just $ bi_tick_mod $ getBreakSourceId ibi brks
+ return $ Just $ getBreakSourceMod ibi brks
ix ->
Just <$> getHistoryModule hug (resumeHistory r !! (ix-1))
=====================================
compiler/GHC/Runtime/Eval.hs
=====================================
@@ -151,7 +151,7 @@ getHistoryModule :: HUG.HomeUnitGraph -> History -> IO Module
getHistoryModule hug hist = do
let ibi = historyBreakpointId hist
brks <- readIModBreaks hug ibi
- return $ bi_tick_mod $ getBreakSourceId ibi brks
+ return $ getBreakSourceMod ibi brks
getHistorySpan :: HUG.HomeUnitGraph -> History -> IO SrcSpan
getHistorySpan hug hist = do
=====================================
compiler/GHC/StgToByteCode.hs
=====================================
@@ -63,7 +63,7 @@ import GHC.StgToCmm.Closure ( NonVoid(..), fromNonVoid, idPrimRepU,
assertNonVoidIds, assertNonVoidStgArgs )
import GHC.StgToCmm.Layout
import GHC.Runtime.Heap.Layout hiding (WordOff, ByteOff, wordsToBytes)
-import GHC.Runtime.Interpreter ( interpreterProfiled )
+import GHC.Runtime.Interpreter ( interpreterProfiled, readIModModBreaks )
import GHC.Data.Bitmap
import GHC.Data.FlatBag as FlatBag
import GHC.Data.OrdList
@@ -99,6 +99,7 @@ import GHC.CoreToIface
import Control.Monad.IO.Class
import Control.Monad.Trans.Reader (ReaderT(..))
import Control.Monad.Trans.State (StateT(..))
+import Data.Array ((!))
-- -----------------------------------------------------------------------------
-- Generating byte code for a complete module
@@ -393,26 +394,26 @@ schemeR_wrk fvs nm original_body (args, body)
-- | Introduce break instructions for ticked expressions.
-- If no breakpoint information is available, the instruction is omitted.
schemeER_wrk :: StackDepth -> BCEnv -> CgStgExpr -> BcM BCInstrList
-schemeER_wrk d p (StgTick (Breakpoint tick_ty tick_id fvs) rhs) = do
- code <- schemeE d 0 p rhs
- mb_current_mod_breaks <- getCurrentModBreaks
- case mb_current_mod_breaks of
- -- if we're not generating ModBreaks for this module for some reason, we
- -- can't store breakpoint occurrence information.
- Nothing -> pure code
- Just current_mod_breaks -> do
- platform <- profilePlatform <$> getProfile
- let idOffSets = getVarOffSets platform d p fvs
- ty_vars = tyCoVarsOfTypesWellScoped (tick_ty:map idType fvs)
- toWord :: Maybe (Id, WordOff) -> Maybe (Id, Word)
- toWord = fmap (\(i, wo) -> (i, fromIntegral wo))
- breakInfo = dehydrateCgBreakInfo ty_vars (map toWord idOffSets) tick_ty tick_id
+schemeER_wrk d p (StgTick bp@(Breakpoint tick_ty tick_id fvs) rhs) = do
+ platform <- profilePlatform <$> getProfile
+
+ -- When we find a tick we update the "last breakpoint location".
+ -- We use it when constructing step-out BRK_FUNs in doCase
+ -- See Note [Stepout breakpoint locations]
+ code <- withBreakTick bp $ schemeE d 0 p rhs
+
+ let idOffSets = getVarOffSets platform d p fvs
+ ty_vars = tyCoVarsOfTypesWellScoped (tick_ty:map idType fvs)
+ toWord :: Maybe (Id, WordOff) -> Maybe (Id, Word)
+ toWord = fmap (\(i, wo) -> (i, fromIntegral wo))
+ breakInfo = dehydrateCgBreakInfo ty_vars (map toWord idOffSets) tick_ty (Right tick_id)
- let info_mod = modBreaks_module current_mod_breaks
- infox <- newBreakInfo breakInfo
+ mibi <- newBreakInfo breakInfo
+
+ return $ case mibi of
+ Nothing -> code
+ Just ibi -> BRK_FUN ibi `consOL` code
- let breakInstr = BRK_FUN (InternalBreakpointId info_mod infox)
- return $ breakInstr `consOL` code
schemeER_wrk d p rhs = schemeE d 0 p rhs
getVarOffSets :: Platform -> StackDepth -> BCEnv -> [Id] -> [Maybe (Id, WordOff)]
@@ -748,12 +749,21 @@ doTailCall init_d s p fn args = do
where
do_pushes !d [] reps = do
- assert (null reps) return ()
- (push_fn, sz) <- pushAtom d p (StgVarArg fn)
platform <- profilePlatform <$> getProfile
- assert (sz == wordSize platform) return ()
- let slide = mkSlideB platform (d - init_d + wordSize platform) (init_d - s)
- return (push_fn `appOL` (slide `appOL` unitOL ENTER))
+ assert (null reps) return ()
+ case lookupBCEnv_maybe fn p of
+ Just d_v
+ | d - d_v == 0 -- shortcut; the first thing on the stack is what we want to enter,
+ , d_v <= init_d -- and it is between init_d and sequel (which would be dropped)
+ -> do
+ let slide = mkSlideB platform (d - init_d + wordSize platform)
+ (init_d - s - wordSize platform)
+ return (slide `appOL` unitOL ENTER)
+ _ -> do
+ (push_fn, sz) <- pushAtom d p (StgVarArg fn)
+ assert (sz == wordSize platform) return ()
+ let slide = mkSlideB platform (d - init_d + wordSize platform) (init_d - s)
+ return (push_fn `appOL` (slide `appOL` unitOL ENTER))
do_pushes !d args reps = do
let (push_apply, n, rest_of_reps) = findPushSeq reps
(these_args, rest_of_args) = splitAt n args
@@ -1325,19 +1335,35 @@ doCase d s p scrut bndr alts
| ubx_tuple_frame = SLIDE 0 3 `consOL` alt_final1
| otherwise = SLIDE 0 1 `consOL` alt_final1
- -- When entering a case continuation BCO, the stack is always headed
- -- by the stg_ret frame and the stg_ctoi frame that returned to it.
- -- See Note [Stack layout when entering run_BCO]
- --
- -- Right after the breakpoint instruction, a case continuation BCO
- -- drops the stg_ret and stg_ctoi frame headers (see alt_final1,
- -- alt_final2), leaving the stack with the scrutinee followed by the
- -- free variables (with depth==d_bndr)
- alt_final
- | gopt Opt_InsertBreakpoints (hsc_dflags hsc_env)
- -- See Note [Debugger: BRK_ALTS]
- = BRK_ALTS False `consOL` alt_final2
- | otherwise = alt_final2
+ -- When entering a case continuation BCO, the stack is always headed
+ -- by the stg_ret frame and the stg_ctoi frame that returned to it.
+ -- See Note [Stack layout when entering run_BCO]
+ --
+ -- Right after the breakpoint instruction, a case continuation BCO
+ -- drops the stg_ret and stg_ctoi frame headers (see alt_final1,
+ -- alt_final2), leaving the stack with the scrutinee followed by the
+ -- free variables (with depth==d_bndr)
+ alt_final <- getLastBreakTick >>= \case
+ Just (Breakpoint tick_ty tick_id fvs)
+ | gopt Opt_InsertBreakpoints (hsc_dflags hsc_env)
+ -- Construct an internal breakpoint to put at the start of this case
+ -- continuation BCO, for step-out.
+ -- See Note [Debugger: Stepout internal break locs]
+ -> do
+ internal_tick_loc <- makeCaseInternalBreakLoc tick_id
+
+ -- same fvs available in the case expression are available in the case continuation
+ let idOffSets = getVarOffSets platform d p fvs
+ ty_vars = tyCoVarsOfTypesWellScoped (tick_ty:map idType fvs)
+ toWord :: Maybe (Id, WordOff) -> Maybe (Id, Word)
+ toWord = fmap (\(i, wo) -> (i, fromIntegral wo))
+ breakInfo = dehydrateCgBreakInfo ty_vars (map toWord idOffSets) tick_ty (Left internal_tick_loc)
+
+ mibi <- newBreakInfo breakInfo
+ return $ case mibi of
+ Nothing -> alt_final2
+ Just ibi -> BRK_FUN ibi `consOL` alt_final2
+ _ -> pure alt_final2
add_bco_name <- shouldAddBcoName
let
@@ -1357,72 +1383,122 @@ doCase d s p scrut bndr alts
_ -> panic "schemeE(StgCase).push_alts"
in return (PUSH_ALTS alt_bco scrut_rep `consOL` scrut_code)
+-- | Come up with an 'InternalBreakLoc' from the location of the given 'BreakpointId'.
+-- See also Note [Debugger: Stepout internal break locs]
+makeCaseInternalBreakLoc :: BreakpointId -> BcM InternalBreakLoc
+makeCaseInternalBreakLoc bid = do
+ hug <- hsc_HUG <$> getHscEnv
+ curr_mod <- getCurrentModule
+ mb_mod_brks <- getCurrentModBreaks
+
+ InternalBreakLoc <$> case bid of
+ BreakpointId{bi_tick_mod, bi_tick_index}
+ | bi_tick_mod == curr_mod
+ , Just these_mbs <- mb_mod_brks
+ -> do
+ return $ modBreaks_locs these_mbs ! bi_tick_index
+ | otherwise
+ -> do
+ other_mbs <- liftIO $ readIModModBreaks hug bi_tick_mod
+ return $ modBreaks_locs other_mbs ! bi_tick_index
+
{-
-Note [Debugger: BRK_ALTS]
-~~~~~~~~~~~~~~~~~~~~~~~~~
-As described in Note [Debugger: Step-out] in rts/Interpreter.c, to implement
-the stepping-out debugger feature we traverse the stack at runtime, identify
-the first continuation BCO, and explicitly enable that BCO's breakpoint thus
-ensuring that we stop exactly when we return to the continuation.
-
-However, case continuation BCOs (produced by PUSH_ALTS and which merely compute
-which case alternative BCO to enter next) contain no user-facing breakpoint
-ticks (BRK_FUN). While we could in principle add breakpoints in case continuation
-BCOs, there are a few reasons why this is not an attractive option:
-
- 1) It's not useful to a user stepping through the program to always have a
- breakpoint after the scrutinee is evaluated but before the case alternative
- is selected. The source span associated with such a breakpoint would also be
- slightly awkward to choose.
-
- 2) It's not easy to add a breakpoint tick before the case alternatives because in
- essentially all internal representations they are given as a list of Alts
- rather than an expression.
-
-To provide the debugger a way to break in a case continuation
-despite the BCOs' lack of BRK_FUNs, we introduce an alternative
-type of breakpoint, represented by the BRK_ALTS instruction,
-at the start of every case continuation BCO. For instance,
-
- case x of
- 0# -> ...
- _ -> ...
-
-will produce a continuation of the form (N.B. the below bytecode
-is simplified):
-
- PUSH_ALTS P
- BRK_ALTS 0
- TESTEQ_I 0 lblA
- PUSH_BCO
- BRK_FUN 0
- -- body of 0# alternative
- ENTER
-
- lblA:
- PUSH_BCO
- BRK_FUN 1
- -- body of wildcard alternative
- ENTER
-
-When enabled (by its single boolean operand), the BRK_ALTS instruction causes
-the program to break at the next encountered breakpoint (implemented
-by setting the TSO's TSO_STOP_NEXT_BREAKPOINT flag). Since the case
-continuation BCO will ultimately jump to one of the alternatives (each of
-which having its own BRK_FUN) we are guaranteed to stop in the taken alternative.
-
-It's important that BRK_ALTS (just like BRK_FUN) is the first instruction of
-the BCO, since that's where the debugger will look to enable it at runtime.
-
-KNOWN ISSUES:
--------------
-This implementation of BRK_ALTS that modifies the first argument of the
-bytecode to enable it does not allow multi-threaded debugging because the BCO
-object is shared across threads and enabling the breakpoint in one will enable
-it in all other threads too. This will have to change to support multi-threads
-debugging.
-
-The progress towards multi-threaded debugging is tracked by #26064
+Note [Debugger: Stepout internal break locs]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+Step-out tells the interpreter to run until the current function
+returns to where it was called from, and stop there.
+
+This is achieved by enabling the BRK_FUN found on the first RET_BCO
+frame on the stack (See [Note Debugger: Step-out]).
+
+Case continuation BCOs (which select an alternative branch) must
+therefore be headed by a BRK_FUN. An example:
+
+ f x = case g x of <--- end up here
+ 1 -> ...
+ 2 -> ...
+
+ g y = ... <--- step out from here
+
+- `g` will return a value to the case continuation BCO in `f`
+- The case continuation BCO will receive the value returned from g
+- Match on it and push the alternative continuation for that branch
+- And then enter that alternative.
+
+If we step-out of `g`, the first RET_BCO on the stack is the case
+continuation of `f` -- execution should stop at its start, before
+selecting an alternative. (One might ask, "why not enable the breakpoint
+in the alternative instead?", because the alternative continuation is
+only pushed to the stack *after* it is selected by the case cont. BCO)
+
+However, the case cont. BCO is not associated with any source-level
+tick, it is merely the glue code which selects alternatives which do
+have source level ticks. Therefore, we have to come up at code
+generation time with a breakpoint location ('InternalBreakLoc') to
+display to the user when it is stopped there.
+
+Our solution is to use the last tick seen just before reaching the case
+continuation. This is robust because a case continuation will thus
+always have a relevant breakpoint location:
+
+ - The source location will be the last source-relevant expression
+ executed before the continuation is pushed
+
+ - So the source location will point to the thing you've just stepped
+ out of
+
+ - Doing :step-local from there will put you on the selected
+ alternative (which at the source level may also be the e.g. next
+ line in a do-block)
+
+Examples, using angle brackets (<<...>>) to denote the breakpoint span:
+
+ f x = case <<g x>> {- step in here -} of
+ 1 -> ...
+ 2 -> ...>
+
+ g y = <<...>> <--- step out from here
+
+ ...
+
+ f x = <<case g x of <--- end up here, whole case highlighted
+ 1 -> ...
+ 2 -> ...>>
+
+ doing :step-local ...
+
+ f x = case g x of
+ 1 -> <<...>> <--- stop in the alternative
+ 2 -> ...
+
+A second example based on T26042d2, where the source is a do-block IO
+action, optimised to a chain of `case expressions`.
+
+ main = do
+ putStrLn "hello1"
+ <<f>> <--- step-in here
+ putStrLn "hello3"
+ putStrLn "hello4"
+
+ f = do
+ <<putStrLn "hello2.1">> <--- step-out from here
+ putStrLn "hello2.2"
+
+ ...
+
+ main = do
+ putStrLn "hello1"
+ <<f>> <--- end up here again, the previously executed expression
+ putStrLn "hello3"
+ putStrLn "hello4"
+
+ doing step/step-local ...
+
+ main = do
+ putStrLn "hello1"
+ f
+ <<putStrLn "hello3">> <--- straight to the next line
+ putStrLn "hello4"
-}
-- -----------------------------------------------------------------------------
@@ -2625,6 +2701,7 @@ data BcM_Env
{ bcm_hsc_env :: !HscEnv
, bcm_module :: !Module -- current module (for breakpoints)
, modBreaks :: !(Maybe ModBreaks)
+ , last_bp_tick :: !(Maybe StgTickish)
}
data BcM_State
@@ -2643,7 +2720,7 @@ newtype BcM r = BcM (BcM_Env -> BcM_State -> IO (r, BcM_State))
runBc :: HscEnv -> Module -> Maybe ModBreaks -> BcM r -> IO (r, BcM_State)
runBc hsc_env this_mod mbs (BcM m)
- = m (BcM_Env hsc_env this_mod mbs) (BcM_State 0 0 IntMap.empty)
+ = m (BcM_Env hsc_env this_mod mbs Nothing) (BcM_State 0 0 IntMap.empty)
instance HasDynFlags BcM where
getDynFlags = hsc_dflags <$> getHscEnv
@@ -2673,14 +2750,19 @@ getLabelsBc n = BcM $ \_ st ->
let ctr = nextlabel st
in return (coerce [ctr .. ctr+n-1], st{nextlabel = ctr+n})
-newBreakInfo :: CgBreakInfo -> BcM Int
-newBreakInfo info = BcM $ \_ st ->
- let ix = breakInfoIdx st
- st' = st
- { breakInfo = IntMap.insert ix info (breakInfo st)
- , breakInfoIdx = ix + 1
- }
- in return (ix, st')
+newBreakInfo :: CgBreakInfo -> BcM (Maybe InternalBreakpointId)
+newBreakInfo info = BcM $ \env st -> do
+ -- if we're not generating ModBreaks for this module for some reason, we
+ -- can't store breakpoint occurrence information.
+ case modBreaks env of
+ Nothing -> pure (Nothing, st)
+ Just modBreaks -> do
+ let ix = breakInfoIdx st
+ st' = st
+ { breakInfo = IntMap.insert ix info (breakInfo st)
+ , breakInfoIdx = ix + 1
+ }
+ return (Just $ InternalBreakpointId (modBreaks_module modBreaks) ix, st')
getCurrentModule :: BcM Module
getCurrentModule = BcM $ \env st -> return (bcm_module env, st)
@@ -2688,12 +2770,20 @@ getCurrentModule = BcM $ \env st -> return (bcm_module env, st)
getCurrentModBreaks :: BcM (Maybe ModBreaks)
getCurrentModBreaks = BcM $ \env st -> return (modBreaks env, st)
+withBreakTick :: StgTickish -> BcM a -> BcM a
+withBreakTick bp (BcM act) = BcM $ \env st ->
+ act env{last_bp_tick=Just bp} st
+
+getLastBreakTick :: BcM (Maybe StgTickish)
+getLastBreakTick = BcM $ \env st ->
+ pure (last_bp_tick env, st)
+
tickFS :: FastString
tickFS = fsLit "ticked"
-- Dehydrating CgBreakInfo
-dehydrateCgBreakInfo :: [TyVar] -> [Maybe (Id, Word)] -> Type -> BreakpointId -> CgBreakInfo
+dehydrateCgBreakInfo :: [TyVar] -> [Maybe (Id, Word)] -> Type -> Either InternalBreakLoc BreakpointId -> CgBreakInfo
dehydrateCgBreakInfo ty_vars idOffSets tick_ty bid =
CgBreakInfo
{ cgb_tyvars = map toIfaceTvBndr ty_vars
=====================================
ghc/GHCi/UI.hs
=====================================
@@ -45,7 +45,7 @@ import GHC.Runtime.Eval (mkTopLevEnv)
import GHC.Runtime.Eval.Utils
-- The GHC interface
-import GHC.ByteCode.Breakpoints (imodBreaks_modBreaks, InternalBreakpointId(..), getBreakSourceId)
+import GHC.ByteCode.Breakpoints (imodBreaks_modBreaks, InternalBreakpointId(..), getBreakSourceId, getBreakSourceMod)
import GHC.Runtime.Interpreter
import GHCi.RemoteTypes
import GHCi.BreakArray( breakOn, breakOff )
@@ -1621,7 +1621,7 @@ toBreakIdAndLocation (Just inf) = do
brks <- liftIO $ readIModBreaks hug inf
let bi = getBreakSourceId inf brks
return $ listToMaybe [ id_loc | id_loc@(_,loc) <- IntMap.assocs (breaks st),
- breakId loc == bi ]
+ Right (breakId loc) == bi ]
printStoppedAtBreakInfo :: GHC.GhcMonad m => Resume -> [Name] -> m ()
printStoppedAtBreakInfo res names = do
@@ -3825,7 +3825,7 @@ pprStopped res = do
hug <- hsc_HUG <$> GHC.getSession
brks <- liftIO $ readIModBreaks hug ibi
return $ Just $ moduleName $
- bi_tick_mod $ getBreakSourceId ibi brks
+ getBreakSourceMod ibi brks
return $
text "Stopped in"
<+> ((case mb_mod_name of
=====================================
rts/Disassembler.c
=====================================
@@ -101,9 +101,6 @@ disInstr ( StgBCO *bco, int pc )
}
debugBelch("\n");
break; }
- case bci_BRK_ALTS:
- debugBelch ("BRK_ALTS %d\n", BCO_NEXT);
- break;
case bci_SWIZZLE: {
W_ stkoff = BCO_GET_LARGE_ARG;
StgInt by = BCO_GET_LARGE_ARG;
=====================================
rts/Interpreter.c
=====================================
@@ -370,16 +370,11 @@ to the continuation.
To achieve this, when the flag is set as the interpreter is re-entered:
(1) Traverse the stack until a RET_BCO frame is found or we otherwise hit the
bottom (STOP_FRAME).
- (2) Look for a breakpoint instruction heading the BCO instructions (a
+ (2) Look for a BRK_FUN instruction heading the BCO instructions (a
breakpoint, when present, is always the first instruction in a BCO)
- (2a) For PUSH_ALT BCOs, the breakpoint instruction will be BRK_ALTS
- (as explained in Note [Debugger: BRK_ALTS]) and it can be enabled by
- setting its first operand to 1.
-
- (2b) Otherwise, the instruction will be BRK_FUN and the breakpoint can be
- enabled by setting the associated BreakArray at the associated tick
- index to 0.
+ The breakpoint can be enabled by setting the associated BreakArray at the
+ associated internal breakpoint index to 0.
By simply enabling the breakpoint heading the continuation we can ensure that
when it is returned to we will stop there without additional work -- it
@@ -740,8 +735,8 @@ interpretBCO (Capability* cap)
int bciPtr = 0;
StgWord16 bci = BCO_NEXT;
- /* A breakpoint instruction (BRK_FUN or BRK_ALTS) is always the first
- * instruction in a BCO */
+ /* A breakpoint instruction (BRK_FUN) can only be the first instruction
+ * in a BCO */
if ((bci & 0xFF) == bci_BRK_FUN) {
W_ arg1_brk_array, arg4_info_index;
@@ -756,10 +751,6 @@ interpretBCO (Capability* cap)
// ACTIVATE the breakpoint by tick index
((StgInt*)breakPoints->payload)[arg4_info_index] = 0;
}
- else if ((bci & 0xFF) == bci_BRK_ALTS) {
- // ACTIVATE BRK_ALTS by setting its only argument to ON
- instrs[1] = 1;
- }
// else: if there is no BRK instruction perhaps we should keep
// traversing; that said, the continuation should always have a BRK
}
@@ -1804,17 +1795,6 @@ run_BCO:
goto nextInsn;
}
- /* See Note [Debugger: BRK_ALTS] */
- case bci_BRK_ALTS:
- {
- StgWord16 active = BCO_NEXT;
- if (active) {
- cap->r.rCurrentTSO->flags |= TSO_STOP_NEXT_BREAKPOINT;
- }
-
- goto nextInsn;
- }
-
case bci_STKCHECK: {
// Explicit stack check at the beginning of a function
// *only* (stack checks in case alternatives are
=====================================
rts/include/rts/Bytecodes.h
=====================================
@@ -214,8 +214,6 @@
#define bci_OP_INDEX_ADDR_32 242
#define bci_OP_INDEX_ADDR_64 243
-#define bci_BRK_ALTS 244
-
/* If you need to go past 255 then you will run into the flags */
=====================================
testsuite/tests/ghci.debugger/scripts/T26042b.stdout
=====================================
@@ -8,35 +8,32 @@ _result ::
10 foo True i = return i
^^^^^^^^
11 foo False _ = do
-Stopped in Main.bar, T26042b.hs:21:3-10
+Stopped in Main., T26042b.hs:20:3-17
_result ::
GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld
-> (# GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld,
Int #) = _
-y :: Int = _
+19 let t = z * 2
20 y <- foo True t
+ ^^^^^^^^^^^^^^^
21 return y
- ^^^^^^^^
-22
-Stopped in Main.foo, T26042b.hs:15:3-10
+Stopped in Main., T26042b.hs:14:3-18
_result ::
GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld
-> (# GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld,
Int #) = _
-n :: Int = _
+13 y = 4
14 n <- bar (x + y)
+ ^^^^^^^^^^^^^^^^
15 return n
- ^^^^^^^^
-16
-Stopped in Main.main, T26042b.hs:6:3-9
+Stopped in Main., T26042b.hs:5:3-26
_result ::
GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld
-> (# GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld,
() #) = _
-a :: Int = _
+4 main = do
5 a <- foo False undefined
+ ^^^^^^^^^^^^^^^^^^^^^^^^
6 print a
- ^^^^^^^
-7 print a
14
14
=====================================
testsuite/tests/ghci.debugger/scripts/T26042c.script
=====================================
@@ -14,15 +14,7 @@ main
-- we go straight to `main`.
:stepout
:list
--- stepping out from here will stop in the thunk (TODO: WHY?)
-:stepout
-:list
-
--- bring us back to main from the thunk (why were we stopped there?...)
-:stepout
-:list
-
--- and finally out
+-- stepping out from here will exit main
:stepout
-- this test is also run with optimisation to make sure the IO bindings inline and we can stop at them
=====================================
testsuite/tests/ghci.debugger/scripts/T26042c.stdout
=====================================
@@ -8,17 +8,14 @@ _result ::
10 foo True i = return i
^^^^^^^^
11 foo False _ = do
-Stopped in Main.main, T26042c.hs:6:3-9
+Stopped in Main., T26042c.hs:5:3-26
_result ::
GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld
-> (# GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld,
() #) = _
-a :: Int = _
+4 main = do
5 a <- foo False undefined
+ ^^^^^^^^^^^^^^^^^^^^^^^^
6 print a
- ^^^^^^^
-7 print a
14
14
-not stopped at a breakpoint
-not stopped at a breakpoint
=====================================
testsuite/tests/ghci.debugger/scripts/T26042d2.hs
=====================================
@@ -0,0 +1,13 @@
+
+module Main where
+
+main = do
+ putStrLn "hello1"
+ f
+ putStrLn "hello3"
+ putStrLn "hello4"
+
+f = do
+ putStrLn "hello2.1"
+ putStrLn "hello2.2"
+{-# NOINLINE f #-}
=====================================
testsuite/tests/ghci.debugger/scripts/T26042d2.script
=====================================
@@ -0,0 +1,12 @@
+:load T26042d2.hs
+
+:break 11
+main
+:list
+:stepout
+:list
+:stepout
+
+-- should exit! we compile this test case with -O1 to make sure the monad >> are inlined
+-- and thus the test relies on the filtering behavior based on SrcSpans for stepout
+
=====================================
testsuite/tests/ghci.debugger/scripts/T26042d2.stdout
=====================================
@@ -0,0 +1,24 @@
+Breakpoint 0 activated at T26042d2.hs:11:3-21
+hello1
+Stopped in Main.f, T26042d2.hs:11:3-21
+_result ::
+ GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld
+ -> (# GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld,
+ () #) = _
+10 f = do
+11 putStrLn "hello2.1"
+ ^^^^^^^^^^^^^^^^^^^
+12 putStrLn "hello2.2"
+hello2.1
+hello2.2
+Stopped in Main., T26042d2.hs:6:3
+_result ::
+ GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld
+ -> (# GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld,
+ () #) = _
+5 putStrLn "hello1"
+6 f
+ ^
+7 putStrLn "hello3"
+hello3
+hello4
=====================================
testsuite/tests/ghci.debugger/scripts/T26042e.stdout
=====================================
@@ -7,14 +7,12 @@ y :: [a1] -> Int = _
11 let !z = y x
^^^^^^^^^^^^
12 let !t = y ['b']
-Stopped in T7.main, T26042e.hs:19:3-11
+Stopped in T7., T26042e.hs:18:3-17
_result :: IO () = _
-x :: Int = _
-y :: Int = _
+17 main = do
18 let !(x, y) = a
+ ^^^^^^^^^^^^^^^
19 print '1'
- ^^^^^^^^^
-20 print '2'
'1'
'2'
'3'
=====================================
testsuite/tests/ghci.debugger/scripts/T26042f2.stdout
=====================================
@@ -8,18 +8,16 @@ x :: Int = 450
21 pure (x + 3)
^^
22 {-# OPAQUE t #-}
-Stopped in T8.g, T26042f.hs:15:3-17
+Stopped in T8., T26042f.hs:14:3-14
_result :: Identity Int = _
-a :: Int = 453
+13 g x = do
14 a <- t (x*2)
+ ^^^^^^^^^^^^
15 n <- pure (a+a)
- ^^^^^^^^^^^^^^^
-16 return (n+n)
-Stopped in T8.f, T26042f.hs:9:3-17
+Stopped in T8., T26042f.hs:8:3-14
_result :: Identity Int = _
-b :: Int = 1812
+7 f x = do
8 b <- g (x*x)
+ ^^^^^^^^^^^^
9 y <- pure (b+b)
- ^^^^^^^^^^^^^^^
-10 return (y+y)
7248
=====================================
testsuite/tests/ghci.debugger/scripts/T26042g.stdout
=====================================
@@ -6,10 +6,13 @@ x :: Int = 14
11 succ x = (-) (x - 2) (x + 1)
^^^^^^^^^^^^^^^^^^^
12
-Stopped in T9.top, T26042g.hs:8:10-21
+Stopped in T9., T26042g.hs:(6,3)-(8,21)
_result :: Int = _
+5 top = do
+ vv
+6 case succ 14 of
7 5 -> 5
8 _ -> 6 + other 55
- ^^^^^^^^^^^^
+ ^^
9
171
=====================================
testsuite/tests/ghci.debugger/scripts/all.T
=====================================
@@ -147,8 +147,9 @@ test('T25932', extra_files(['T25932.hs']), ghci_script, ['T25932.script'])
# Step out tests
test('T26042b', [extra_hc_opts('-O -fno-unoptimized-core-for-interpreter'), extra_files(['T26042b.hs'])], ghci_script, ['T26042b.script'])
-test('T26042c', [expect_broken(26042),extra_hc_opts('-O -fno-unoptimized-core-for-interpreter'), extra_files(['T26042c.hs'])], ghci_script, ['T26042c.script'])
+test('T26042c', [extra_hc_opts('-O -fno-unoptimized-core-for-interpreter'), extra_files(['T26042c.hs'])], ghci_script, ['T26042c.script'])
test('T26042d', [extra_hc_opts('-O -fno-unoptimized-core-for-interpreter'), extra_files(['T26042d.hs'])], ghci_script, ['T26042d.script'])
+test('T26042d2', [extra_hc_opts('-O -fno-unoptimized-core-for-interpreter'), extra_files(['T26042d2.hs'])], ghci_script, ['T26042d2.script'])
test('T26042e', extra_files(['T26042e.hs']), ghci_script, ['T26042e.script'])
test('T26042f1', extra_files(['T26042f.hs', 'T26042f.script']), ghci_script, ['T26042f.script']) # >> is not inlined, so stepout has nowhere to stop
test('T26042f2', [extra_hc_opts('-O -fno-unoptimized-core-for-interpreter'), extra_files(['T26042f.hs', 'T26042f.script'])], ghci_script, ['T26042f.script'])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/062cc2b1156b5760958d883b09ce07…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/062cc2b1156b5760958d883b09ce07…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 4 commits: Update comments on `OptKind` to reflect the code reality
by Marge Bot (@marge-bot) 30 Jul '25
by Marge Bot (@marge-bot) 30 Jul '25
30 Jul '25
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
b7d541c5 by Simon Hengel at 2025-07-30T04:20:49-04:00
Update comments on `OptKind` to reflect the code reality
- - - - -
686f7e2a by Wen Kokke at 2025-07-30T04:20:52-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.
- - - - -
5db4eade by Wen Kokke at 2025-07-30T04:20:52-04:00
rts: Split T20006 into tests with and without -threaded
- - - - -
aeb9536c by Simon Hengel at 2025-07-30T04:20:53-04:00
docs/users_guide/win32-dlls.rst: Remove references to `readline`
- - - - -
7 changed files:
- compiler/GHC/Driver/CmdLine.hs
- docs/users_guide/runtime_control.rst
- docs/users_guide/win32-dlls.rst
- rts/RtsFlags.c
- rts/Timer.c
- rts/include/rts/Flags.h
- testsuite/tests/rts/flags/all.T
Changes:
=====================================
compiler/GHC/Driver/CmdLine.hs
=====================================
@@ -92,14 +92,14 @@ data GhcFlagMode
data OptKind m -- Suppose the flag is -f
= NoArg (EwM m ()) -- -f all by itself
- | HasArg (String -> EwM m ()) -- -farg or -f arg
+ | HasArg (String -> EwM m ()) -- -farg or -f=arg or -f arg
| SepArg (String -> EwM m ()) -- -f arg
- | Prefix (String -> EwM m ()) -- -farg
- | OptPrefix (String -> EwM m ()) -- -f or -farg (i.e. the arg is optional)
- | OptIntSuffix (Maybe Int -> EwM m ()) -- -f or -f=n; pass n to fn
- | IntSuffix (Int -> EwM m ()) -- -f or -f=n; pass n to fn
- | Word64Suffix (Word64 -> EwM m ()) -- -f or -f=n; pass n to fn
- | FloatSuffix (Float -> EwM m ()) -- -f or -f=n; pass n to fn
+ | Prefix (String -> EwM m ()) -- -farg or -f=arg
+ | OptPrefix (String -> EwM m ()) -- -f or -farg or -f=arg (i.e. the arg is optional)
+ | OptIntSuffix (Maybe Int -> EwM m ()) -- -f or -fn or -f=n; pass n to fn
+ | IntSuffix (Int -> EwM m ()) -- -fn or -f=n; pass n to fn
+ | Word64Suffix (Word64 -> EwM m ()) -- -fn or -f=n; pass n to fn
+ | FloatSuffix (Float -> EwM m ()) -- -fn or -f=n; pass n to fn
| PassFlag (String -> EwM m ()) -- -f; pass "-f" fn
| AnySuffix (String -> EwM m ()) -- -f or -farg; pass entire "-farg" to fn
=====================================
docs/users_guide/runtime_control.rst
=====================================
@@ -1361,7 +1361,8 @@ When the program is linked with the :ghc-flag:`-eventlog` option
:since: 9.2
When enabled, the eventlog will be flushed periodically every
- ⟨seconds⟩. This can be useful in live-monitoring situations where the
+ ⟨seconds⟩ (only available with :ghc-flag:`-threaded`).
+ This can be useful in live-monitoring situations where the
eventlog is consumed in real-time by another process.
.. rts-flag:: -v [⟨flags⟩]
=====================================
docs/users_guide/win32-dlls.rst
=====================================
@@ -76,11 +76,6 @@ window, use the flag ``-optl-mwindows`` in the link step.
However using Debug.Trace.trace is alright because it uses Windows
debugging output support rather than ``stderr``.
-For some reason, Mingw ships with the ``readline`` library, but not with
-the ``readline`` headers. As a result, GHC (like Hugs) does not use
-``readline`` for interactive input on Windows. You can get a close
-simulation by using an emacs shell buffer!
-
.. _library-differences:
Differences in library behaviour
=====================================
rts/RtsFlags.c
=====================================
@@ -248,7 +248,9 @@ void initRtsFlagsDefaults(void)
RtsFlags.TraceFlags.user = false;
RtsFlags.TraceFlags.ticky = false;
RtsFlags.TraceFlags.trace_output = NULL;
+# if defined(THREADED_RTS)
RtsFlags.TraceFlags.eventlogFlushTime = 0;
+# endif
RtsFlags.TraceFlags.nullWriter = false;
#endif
@@ -448,8 +450,10 @@ usage_text[] = {
# endif
" -x disable an event class, for any flag above",
" the initial enabled event classes are 'sgpu'",
+# if defined(THREADED_RTS)
" --eventlog-flush-interval=<secs>",
" Periodically flush the eventlog at the specified interval.",
+# endif
#endif
"",
@@ -1052,12 +1056,14 @@ error = true;
else if (!strncmp("eventlog-flush-interval=",
&rts_argv[arg][2], 24)) {
OPTION_SAFE;
+ THREADED_BUILD_ONLY(
double intervalSeconds = parseDouble(rts_argv[arg]+26, &error);
if (error) {
errorBelch("bad value for --eventlog-flush-interval");
}
RtsFlags.TraceFlags.eventlogFlushTime =
fsecondsToTime(intervalSeconds);
+ ) break;
}
else if (strequal("copying-gc",
&rts_argv[arg][2])) {
@@ -1963,6 +1969,7 @@ static void normaliseRtsOpts (void)
RtsFlags.ProfFlags.heapProfileIntervalTicks = 0;
}
+#if defined(THREADED_RTS)
if (RtsFlags.TraceFlags.eventlogFlushTime > 0 && RtsFlags.MiscFlags.tickInterval != 0) {
RtsFlags.TraceFlags.eventlogFlushTicks =
RtsFlags.TraceFlags.eventlogFlushTime /
@@ -1970,6 +1977,7 @@ static void normaliseRtsOpts (void)
} else {
RtsFlags.TraceFlags.eventlogFlushTicks = 0;
}
+#endif
if (RtsFlags.GcFlags.stkChunkBufferSize >
RtsFlags.GcFlags.stkChunkSize / 2) {
=====================================
rts/Timer.c
=====================================
@@ -43,8 +43,10 @@ static StgWord timer_disabled;
/* ticks left before next pre-emptive context switch */
static int ticks_to_ctxt_switch = 0;
+#if defined(THREADED_RTS)
/* ticks left before next next forced eventlog flush */
static int ticks_to_eventlog_flush = 0;
+#endif
/*
@@ -118,7 +120,7 @@ handle_tick(int unused STG_UNUSED)
contextSwitchAllCapabilities(); /* schedule a context switch */
}
}
-
+#if defined(THREADED_RTS)
if (eventLogStatus() == EVENTLOG_RUNNING
&& RtsFlags.TraceFlags.eventlogFlushTicks > 0) {
ticks_to_eventlog_flush--;
@@ -127,6 +129,7 @@ handle_tick(int unused STG_UNUSED)
flushEventLog(NULL);
}
}
+#endif
/*
* If we've been inactive for idleGCDelayTime (set by +RTS
=====================================
rts/include/rts/Flags.h
=====================================
@@ -188,8 +188,11 @@ typedef struct _TRACE_FLAGS {
bool sparks_full; /* trace spark events 100% accurately */
bool ticky; /* trace ticky-ticky samples */
bool user; /* trace user events (emitted from Haskell code) */
- Time eventlogFlushTime; /* Time between force eventlog flushes (or 0 if disabled) */
+#if defined(THREADED_RTS)
+ /* Time between force eventlog flushes (or 0 if disabled) */
+ Time eventlogFlushTime;
int eventlogFlushTicks;
+#endif
char *trace_output; /* output filename for eventlog */
bool nullWriter; /* use null writer instead of file writer */
} TRACE_FLAGS;
=====================================
testsuite/tests/rts/flags/all.T
=====================================
@@ -57,6 +57,14 @@ test('T12870h',
multimod_compile_and_run,
['T12870g', '-rtsopts=ignoreAll -with-rtsopts="-G3"'])
-test('T20006', [extra_run_opts('+RTS --eventlog-flush-interval=1')],
- compile_and_run,
- [''])
+test('T20006a',
+ [extra_files(['T20006.hs']), extra_run_opts('+RTS --eventlog-flush-interval=1'),
+ only_ways(['threaded1', 'threaded2'])],
+ multimod_compile_and_run,
+ ['T20006', ''])
+
+test('T20006b',
+ [extra_files(['T20006.hs']), extra_run_opts('+RTS --eventlog-flush-interval=1'),
+ expect_fail_for(['normal'])],
+ multimod_compile_and_run,
+ ['T20006', ''])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6eb97252bf802cf05180463226bb5e…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6eb97252bf802cf05180463226bb5e…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 4 commits: Update comments on `OptKind` to reflect the code reality
by Marge Bot (@marge-bot) 30 Jul '25
by Marge Bot (@marge-bot) 30 Jul '25
30 Jul '25
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
fe29dbc7 by Simon Hengel at 2025-07-30T01:49:42-04:00
Update comments on `OptKind` to reflect the code reality
- - - - -
de45c5e6 by Wen Kokke at 2025-07-30T01:49:45-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.
- - - - -
ed3c6809 by Wen Kokke at 2025-07-30T01:49:45-04:00
rts: Split T20006 into tests with and without -threaded
- - - - -
6eb97252 by Simon Hengel at 2025-07-30T01:49:46-04:00
docs/users_guide/win32-dlls.rst: Remove references to `readline`
- - - - -
7 changed files:
- compiler/GHC/Driver/CmdLine.hs
- docs/users_guide/runtime_control.rst
- docs/users_guide/win32-dlls.rst
- rts/RtsFlags.c
- rts/Timer.c
- rts/include/rts/Flags.h
- testsuite/tests/rts/flags/all.T
Changes:
=====================================
compiler/GHC/Driver/CmdLine.hs
=====================================
@@ -92,14 +92,14 @@ data GhcFlagMode
data OptKind m -- Suppose the flag is -f
= NoArg (EwM m ()) -- -f all by itself
- | HasArg (String -> EwM m ()) -- -farg or -f arg
+ | HasArg (String -> EwM m ()) -- -farg or -f=arg or -f arg
| SepArg (String -> EwM m ()) -- -f arg
- | Prefix (String -> EwM m ()) -- -farg
- | OptPrefix (String -> EwM m ()) -- -f or -farg (i.e. the arg is optional)
- | OptIntSuffix (Maybe Int -> EwM m ()) -- -f or -f=n; pass n to fn
- | IntSuffix (Int -> EwM m ()) -- -f or -f=n; pass n to fn
- | Word64Suffix (Word64 -> EwM m ()) -- -f or -f=n; pass n to fn
- | FloatSuffix (Float -> EwM m ()) -- -f or -f=n; pass n to fn
+ | Prefix (String -> EwM m ()) -- -farg or -f=arg
+ | OptPrefix (String -> EwM m ()) -- -f or -farg or -f=arg (i.e. the arg is optional)
+ | OptIntSuffix (Maybe Int -> EwM m ()) -- -f or -fn or -f=n; pass n to fn
+ | IntSuffix (Int -> EwM m ()) -- -fn or -f=n; pass n to fn
+ | Word64Suffix (Word64 -> EwM m ()) -- -fn or -f=n; pass n to fn
+ | FloatSuffix (Float -> EwM m ()) -- -fn or -f=n; pass n to fn
| PassFlag (String -> EwM m ()) -- -f; pass "-f" fn
| AnySuffix (String -> EwM m ()) -- -f or -farg; pass entire "-farg" to fn
=====================================
docs/users_guide/runtime_control.rst
=====================================
@@ -1361,7 +1361,8 @@ When the program is linked with the :ghc-flag:`-eventlog` option
:since: 9.2
When enabled, the eventlog will be flushed periodically every
- ⟨seconds⟩. This can be useful in live-monitoring situations where the
+ ⟨seconds⟩ (only available with :ghc-flag:`-threaded`).
+ This can be useful in live-monitoring situations where the
eventlog is consumed in real-time by another process.
.. rts-flag:: -v [⟨flags⟩]
=====================================
docs/users_guide/win32-dlls.rst
=====================================
@@ -76,11 +76,6 @@ window, use the flag ``-optl-mwindows`` in the link step.
However using Debug.Trace.trace is alright because it uses Windows
debugging output support rather than ``stderr``.
-For some reason, Mingw ships with the ``readline`` library, but not with
-the ``readline`` headers. As a result, GHC (like Hugs) does not use
-``readline`` for interactive input on Windows. You can get a close
-simulation by using an emacs shell buffer!
-
.. _library-differences:
Differences in library behaviour
=====================================
rts/RtsFlags.c
=====================================
@@ -248,7 +248,9 @@ void initRtsFlagsDefaults(void)
RtsFlags.TraceFlags.user = false;
RtsFlags.TraceFlags.ticky = false;
RtsFlags.TraceFlags.trace_output = NULL;
+# if defined(THREADED_RTS)
RtsFlags.TraceFlags.eventlogFlushTime = 0;
+# endif
RtsFlags.TraceFlags.nullWriter = false;
#endif
@@ -448,8 +450,10 @@ usage_text[] = {
# endif
" -x disable an event class, for any flag above",
" the initial enabled event classes are 'sgpu'",
+# if defined(THREADED_RTS)
" --eventlog-flush-interval=<secs>",
" Periodically flush the eventlog at the specified interval.",
+# endif
#endif
"",
@@ -1052,12 +1056,14 @@ error = true;
else if (!strncmp("eventlog-flush-interval=",
&rts_argv[arg][2], 24)) {
OPTION_SAFE;
+ THREADED_BUILD_ONLY(
double intervalSeconds = parseDouble(rts_argv[arg]+26, &error);
if (error) {
errorBelch("bad value for --eventlog-flush-interval");
}
RtsFlags.TraceFlags.eventlogFlushTime =
fsecondsToTime(intervalSeconds);
+ ) break;
}
else if (strequal("copying-gc",
&rts_argv[arg][2])) {
@@ -1963,6 +1969,7 @@ static void normaliseRtsOpts (void)
RtsFlags.ProfFlags.heapProfileIntervalTicks = 0;
}
+#if defined(THREADED_RTS)
if (RtsFlags.TraceFlags.eventlogFlushTime > 0 && RtsFlags.MiscFlags.tickInterval != 0) {
RtsFlags.TraceFlags.eventlogFlushTicks =
RtsFlags.TraceFlags.eventlogFlushTime /
@@ -1970,6 +1977,7 @@ static void normaliseRtsOpts (void)
} else {
RtsFlags.TraceFlags.eventlogFlushTicks = 0;
}
+#endif
if (RtsFlags.GcFlags.stkChunkBufferSize >
RtsFlags.GcFlags.stkChunkSize / 2) {
=====================================
rts/Timer.c
=====================================
@@ -43,8 +43,10 @@ static StgWord timer_disabled;
/* ticks left before next pre-emptive context switch */
static int ticks_to_ctxt_switch = 0;
+#if defined(THREADED_RTS)
/* ticks left before next next forced eventlog flush */
static int ticks_to_eventlog_flush = 0;
+#endif
/*
@@ -118,7 +120,7 @@ handle_tick(int unused STG_UNUSED)
contextSwitchAllCapabilities(); /* schedule a context switch */
}
}
-
+#if defined(THREADED_RTS)
if (eventLogStatus() == EVENTLOG_RUNNING
&& RtsFlags.TraceFlags.eventlogFlushTicks > 0) {
ticks_to_eventlog_flush--;
@@ -127,6 +129,7 @@ handle_tick(int unused STG_UNUSED)
flushEventLog(NULL);
}
}
+#endif
/*
* If we've been inactive for idleGCDelayTime (set by +RTS
=====================================
rts/include/rts/Flags.h
=====================================
@@ -188,8 +188,11 @@ typedef struct _TRACE_FLAGS {
bool sparks_full; /* trace spark events 100% accurately */
bool ticky; /* trace ticky-ticky samples */
bool user; /* trace user events (emitted from Haskell code) */
- Time eventlogFlushTime; /* Time between force eventlog flushes (or 0 if disabled) */
+#if defined(THREADED_RTS)
+ /* Time between force eventlog flushes (or 0 if disabled) */
+ Time eventlogFlushTime;
int eventlogFlushTicks;
+#endif
char *trace_output; /* output filename for eventlog */
bool nullWriter; /* use null writer instead of file writer */
} TRACE_FLAGS;
=====================================
testsuite/tests/rts/flags/all.T
=====================================
@@ -57,6 +57,14 @@ test('T12870h',
multimod_compile_and_run,
['T12870g', '-rtsopts=ignoreAll -with-rtsopts="-G3"'])
-test('T20006', [extra_run_opts('+RTS --eventlog-flush-interval=1')],
- compile_and_run,
- [''])
+test('T20006a',
+ [extra_files(['T20006.hs']), extra_run_opts('+RTS --eventlog-flush-interval=1'),
+ only_ways(['threaded1', 'threaded2'])],
+ multimod_compile_and_run,
+ ['T20006', ''])
+
+test('T20006b',
+ [extra_files(['T20006.hs']), extra_run_opts('+RTS --eventlog-flush-interval=1'),
+ expect_fail_for(['normal'])],
+ multimod_compile_and_run,
+ ['T20006', ''])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d0f7737e3bbeda9273d4f3dc834494…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d0f7737e3bbeda9273d4f3dc834494…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/sol/hie-wierd-in-as-external] 2 commits: Use isKnownOrigName_maybe to reconstruct wired-in names
by Simon Hengel (@sol) 30 Jul '25
by Simon Hengel (@sol) 30 Jul '25
30 Jul '25
Simon Hengel pushed to branch wip/sol/hie-wierd-in-as-external at Glasgow Haskell Compiler / GHC
Commits:
9815908e by Simon Hengel at 2025-07-30T11:43:53+07:00
Use isKnownOrigName_maybe to reconstruct wired-in names
- - - - -
9909605a by Simon Hengel at 2025-07-30T11:43:53+07:00
Rely on knownKeysOrigNameCache
- - - - -
2 changed files:
- compiler/GHC/Types/Name/Cache.hs
- testsuite/tests/hiefile/should_run/TestUtils.hs
Changes:
=====================================
compiler/GHC/Types/Name/Cache.hs
=====================================
@@ -100,9 +100,14 @@ OrigNameCache at all? Good question; after all,
3) Loading of interface files encodes names via Uniques, as detailed in
Note [Symbol table representation of names] in GHC.Iface.Binary
-It turns out that we end up looking up built-in syntax in the cache when we
-generate Haddock documentation. E.g. if we don't find tuple data constructors
-there, hyperlinks won't work as expected. Test case: haddockHtmlTest (Bug923.hs)
+
+However note that:
+ 1) It turns out that we end up looking up built-in syntax in the cache when
+ we generate Haddock documentation. E.g. if we don't find tuple data
+ constructors there, hyperlinks won't work as expected. Test case:
+ haddockHtmlTest (Bug923.hs)
+ 2) HIE de-serialization relies on built-in names being present in the
+ knownKeysOrigNameCache.
-}
-- | The NameCache makes sure that there is just one Unique assigned for
=====================================
testsuite/tests/hiefile/should_run/TestUtils.hs
=====================================
@@ -25,9 +25,6 @@ import GHC.Iface.Ext.Utils
import GHC.Driver.Session
import GHC.SysTools
-makeNc :: IO NameCache
-makeNc = initNameCache 'z' []
-
dynFlagsForPrinting :: String -> IO DynFlags
dynFlagsForPrinting libdir = do
systemSettings <- initSysTools libdir
@@ -37,7 +34,7 @@ readTestHie :: FilePath -> IO (DynFlags, HieFile)
readTestHie fp = do
libdir:_ <- getArgs
df <- dynFlagsForPrinting libdir
- nc <- makeNc
+ nc <- newNameCache 'r' knownKeysOrigNameCache
hfr <- readHieFile nc fp
pure (df, hie_file_result hfr)
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/330d46a1e9414c37cc0460c4de123c…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/330d46a1e9414c37cc0460c4de123c…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 4 commits: Update comments on `OptKind` to reflect the code reality
by Marge Bot (@marge-bot) 30 Jul '25
by Marge Bot (@marge-bot) 30 Jul '25
30 Jul '25
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
6cbd9c99 by Simon Hengel at 2025-07-29T23:17:01-04:00
Update comments on `OptKind` to reflect the code reality
- - - - -
abcdb794 by Wen Kokke at 2025-07-29T23:17:03-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.
- - - - -
89f56de1 by Wen Kokke at 2025-07-29T23:17:03-04:00
rts: Split T20006 into tests with and without -threaded
- - - - -
d0f7737e by Simon Hengel at 2025-07-29T23:17:04-04:00
docs/users_guide/win32-dlls.rst: Remove references to `readline`
- - - - -
7 changed files:
- compiler/GHC/Driver/CmdLine.hs
- docs/users_guide/runtime_control.rst
- docs/users_guide/win32-dlls.rst
- rts/RtsFlags.c
- rts/Timer.c
- rts/include/rts/Flags.h
- testsuite/tests/rts/flags/all.T
Changes:
=====================================
compiler/GHC/Driver/CmdLine.hs
=====================================
@@ -92,14 +92,14 @@ data GhcFlagMode
data OptKind m -- Suppose the flag is -f
= NoArg (EwM m ()) -- -f all by itself
- | HasArg (String -> EwM m ()) -- -farg or -f arg
+ | HasArg (String -> EwM m ()) -- -farg or -f=arg or -f arg
| SepArg (String -> EwM m ()) -- -f arg
- | Prefix (String -> EwM m ()) -- -farg
- | OptPrefix (String -> EwM m ()) -- -f or -farg (i.e. the arg is optional)
- | OptIntSuffix (Maybe Int -> EwM m ()) -- -f or -f=n; pass n to fn
- | IntSuffix (Int -> EwM m ()) -- -f or -f=n; pass n to fn
- | Word64Suffix (Word64 -> EwM m ()) -- -f or -f=n; pass n to fn
- | FloatSuffix (Float -> EwM m ()) -- -f or -f=n; pass n to fn
+ | Prefix (String -> EwM m ()) -- -farg or -f=arg
+ | OptPrefix (String -> EwM m ()) -- -f or -farg or -f=arg (i.e. the arg is optional)
+ | OptIntSuffix (Maybe Int -> EwM m ()) -- -f or -fn or -f=n; pass n to fn
+ | IntSuffix (Int -> EwM m ()) -- -fn or -f=n; pass n to fn
+ | Word64Suffix (Word64 -> EwM m ()) -- -fn or -f=n; pass n to fn
+ | FloatSuffix (Float -> EwM m ()) -- -fn or -f=n; pass n to fn
| PassFlag (String -> EwM m ()) -- -f; pass "-f" fn
| AnySuffix (String -> EwM m ()) -- -f or -farg; pass entire "-farg" to fn
=====================================
docs/users_guide/runtime_control.rst
=====================================
@@ -1361,7 +1361,8 @@ When the program is linked with the :ghc-flag:`-eventlog` option
:since: 9.2
When enabled, the eventlog will be flushed periodically every
- ⟨seconds⟩. This can be useful in live-monitoring situations where the
+ ⟨seconds⟩ (only available with :ghc-flag:`-threaded`).
+ This can be useful in live-monitoring situations where the
eventlog is consumed in real-time by another process.
.. rts-flag:: -v [⟨flags⟩]
=====================================
docs/users_guide/win32-dlls.rst
=====================================
@@ -76,11 +76,6 @@ window, use the flag ``-optl-mwindows`` in the link step.
However using Debug.Trace.trace is alright because it uses Windows
debugging output support rather than ``stderr``.
-For some reason, Mingw ships with the ``readline`` library, but not with
-the ``readline`` headers. As a result, GHC (like Hugs) does not use
-``readline`` for interactive input on Windows. You can get a close
-simulation by using an emacs shell buffer!
-
.. _library-differences:
Differences in library behaviour
=====================================
rts/RtsFlags.c
=====================================
@@ -248,7 +248,9 @@ void initRtsFlagsDefaults(void)
RtsFlags.TraceFlags.user = false;
RtsFlags.TraceFlags.ticky = false;
RtsFlags.TraceFlags.trace_output = NULL;
+# if defined(THREADED_RTS)
RtsFlags.TraceFlags.eventlogFlushTime = 0;
+# endif
RtsFlags.TraceFlags.nullWriter = false;
#endif
@@ -448,8 +450,10 @@ usage_text[] = {
# endif
" -x disable an event class, for any flag above",
" the initial enabled event classes are 'sgpu'",
+# if defined(THREADED_RTS)
" --eventlog-flush-interval=<secs>",
" Periodically flush the eventlog at the specified interval.",
+# endif
#endif
"",
@@ -1052,12 +1056,14 @@ error = true;
else if (!strncmp("eventlog-flush-interval=",
&rts_argv[arg][2], 24)) {
OPTION_SAFE;
+ THREADED_BUILD_ONLY(
double intervalSeconds = parseDouble(rts_argv[arg]+26, &error);
if (error) {
errorBelch("bad value for --eventlog-flush-interval");
}
RtsFlags.TraceFlags.eventlogFlushTime =
fsecondsToTime(intervalSeconds);
+ ) break;
}
else if (strequal("copying-gc",
&rts_argv[arg][2])) {
@@ -1963,6 +1969,7 @@ static void normaliseRtsOpts (void)
RtsFlags.ProfFlags.heapProfileIntervalTicks = 0;
}
+#if defined(THREADED_RTS)
if (RtsFlags.TraceFlags.eventlogFlushTime > 0 && RtsFlags.MiscFlags.tickInterval != 0) {
RtsFlags.TraceFlags.eventlogFlushTicks =
RtsFlags.TraceFlags.eventlogFlushTime /
@@ -1970,6 +1977,7 @@ static void normaliseRtsOpts (void)
} else {
RtsFlags.TraceFlags.eventlogFlushTicks = 0;
}
+#endif
if (RtsFlags.GcFlags.stkChunkBufferSize >
RtsFlags.GcFlags.stkChunkSize / 2) {
=====================================
rts/Timer.c
=====================================
@@ -43,8 +43,10 @@ static StgWord timer_disabled;
/* ticks left before next pre-emptive context switch */
static int ticks_to_ctxt_switch = 0;
+#if defined(THREADED_RTS)
/* ticks left before next next forced eventlog flush */
static int ticks_to_eventlog_flush = 0;
+#endif
/*
@@ -118,7 +120,7 @@ handle_tick(int unused STG_UNUSED)
contextSwitchAllCapabilities(); /* schedule a context switch */
}
}
-
+#if defined(THREADED_RTS)
if (eventLogStatus() == EVENTLOG_RUNNING
&& RtsFlags.TraceFlags.eventlogFlushTicks > 0) {
ticks_to_eventlog_flush--;
@@ -127,6 +129,7 @@ handle_tick(int unused STG_UNUSED)
flushEventLog(NULL);
}
}
+#endif
/*
* If we've been inactive for idleGCDelayTime (set by +RTS
=====================================
rts/include/rts/Flags.h
=====================================
@@ -188,8 +188,11 @@ typedef struct _TRACE_FLAGS {
bool sparks_full; /* trace spark events 100% accurately */
bool ticky; /* trace ticky-ticky samples */
bool user; /* trace user events (emitted from Haskell code) */
- Time eventlogFlushTime; /* Time between force eventlog flushes (or 0 if disabled) */
+#if defined(THREADED_RTS)
+ /* Time between force eventlog flushes (or 0 if disabled) */
+ Time eventlogFlushTime;
int eventlogFlushTicks;
+#endif
char *trace_output; /* output filename for eventlog */
bool nullWriter; /* use null writer instead of file writer */
} TRACE_FLAGS;
=====================================
testsuite/tests/rts/flags/all.T
=====================================
@@ -57,6 +57,14 @@ test('T12870h',
multimod_compile_and_run,
['T12870g', '-rtsopts=ignoreAll -with-rtsopts="-G3"'])
-test('T20006', [extra_run_opts('+RTS --eventlog-flush-interval=1')],
- compile_and_run,
- [''])
+test('T20006a',
+ [extra_files(['T20006.hs']), extra_run_opts('+RTS --eventlog-flush-interval=1'),
+ only_ways(['threaded1', 'threaded2'])],
+ multimod_compile_and_run,
+ ['T20006', ''])
+
+test('T20006b',
+ [extra_files(['T20006.hs']), extra_run_opts('+RTS --eventlog-flush-interval=1'),
+ expect_fail_for(['normal'])],
+ multimod_compile_and_run,
+ ['T20006', ''])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/dc19c1e6dca210faa48ec0cec2401d…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/dc19c1e6dca210faa48ec0cec2401d…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 4 commits: Update comments on `OptKind` to reflect the code reality
by Marge Bot (@marge-bot) 30 Jul '25
by Marge Bot (@marge-bot) 30 Jul '25
30 Jul '25
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
86cb8ae4 by Simon Hengel at 2025-07-29T20:45:54-04:00
Update comments on `OptKind` to reflect the code reality
- - - - -
805271a2 by Wen Kokke at 2025-07-29T20:45:57-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.
- - - - -
46ce31d6 by Wen Kokke at 2025-07-29T20:45:57-04:00
rts: Split T20006 into tests with and without -threaded
- - - - -
dc19c1e6 by Simon Hengel at 2025-07-29T20:45:58-04:00
docs/users_guide/win32-dlls.rst: Remove references to `readline`
- - - - -
7 changed files:
- compiler/GHC/Driver/CmdLine.hs
- docs/users_guide/runtime_control.rst
- docs/users_guide/win32-dlls.rst
- rts/RtsFlags.c
- rts/Timer.c
- rts/include/rts/Flags.h
- testsuite/tests/rts/flags/all.T
Changes:
=====================================
compiler/GHC/Driver/CmdLine.hs
=====================================
@@ -92,14 +92,14 @@ data GhcFlagMode
data OptKind m -- Suppose the flag is -f
= NoArg (EwM m ()) -- -f all by itself
- | HasArg (String -> EwM m ()) -- -farg or -f arg
+ | HasArg (String -> EwM m ()) -- -farg or -f=arg or -f arg
| SepArg (String -> EwM m ()) -- -f arg
- | Prefix (String -> EwM m ()) -- -farg
- | OptPrefix (String -> EwM m ()) -- -f or -farg (i.e. the arg is optional)
- | OptIntSuffix (Maybe Int -> EwM m ()) -- -f or -f=n; pass n to fn
- | IntSuffix (Int -> EwM m ()) -- -f or -f=n; pass n to fn
- | Word64Suffix (Word64 -> EwM m ()) -- -f or -f=n; pass n to fn
- | FloatSuffix (Float -> EwM m ()) -- -f or -f=n; pass n to fn
+ | Prefix (String -> EwM m ()) -- -farg or -f=arg
+ | OptPrefix (String -> EwM m ()) -- -f or -farg or -f=arg (i.e. the arg is optional)
+ | OptIntSuffix (Maybe Int -> EwM m ()) -- -f or -fn or -f=n; pass n to fn
+ | IntSuffix (Int -> EwM m ()) -- -fn or -f=n; pass n to fn
+ | Word64Suffix (Word64 -> EwM m ()) -- -fn or -f=n; pass n to fn
+ | FloatSuffix (Float -> EwM m ()) -- -fn or -f=n; pass n to fn
| PassFlag (String -> EwM m ()) -- -f; pass "-f" fn
| AnySuffix (String -> EwM m ()) -- -f or -farg; pass entire "-farg" to fn
=====================================
docs/users_guide/runtime_control.rst
=====================================
@@ -1361,7 +1361,8 @@ When the program is linked with the :ghc-flag:`-eventlog` option
:since: 9.2
When enabled, the eventlog will be flushed periodically every
- ⟨seconds⟩. This can be useful in live-monitoring situations where the
+ ⟨seconds⟩ (only available with :ghc-flag:`-threaded`).
+ This can be useful in live-monitoring situations where the
eventlog is consumed in real-time by another process.
.. rts-flag:: -v [⟨flags⟩]
=====================================
docs/users_guide/win32-dlls.rst
=====================================
@@ -76,11 +76,6 @@ window, use the flag ``-optl-mwindows`` in the link step.
However using Debug.Trace.trace is alright because it uses Windows
debugging output support rather than ``stderr``.
-For some reason, Mingw ships with the ``readline`` library, but not with
-the ``readline`` headers. As a result, GHC (like Hugs) does not use
-``readline`` for interactive input on Windows. You can get a close
-simulation by using an emacs shell buffer!
-
.. _library-differences:
Differences in library behaviour
=====================================
rts/RtsFlags.c
=====================================
@@ -248,7 +248,9 @@ void initRtsFlagsDefaults(void)
RtsFlags.TraceFlags.user = false;
RtsFlags.TraceFlags.ticky = false;
RtsFlags.TraceFlags.trace_output = NULL;
+# if defined(THREADED_RTS)
RtsFlags.TraceFlags.eventlogFlushTime = 0;
+# endif
RtsFlags.TraceFlags.nullWriter = false;
#endif
@@ -448,8 +450,10 @@ usage_text[] = {
# endif
" -x disable an event class, for any flag above",
" the initial enabled event classes are 'sgpu'",
+# if defined(THREADED_RTS)
" --eventlog-flush-interval=<secs>",
" Periodically flush the eventlog at the specified interval.",
+# endif
#endif
"",
@@ -1052,12 +1056,14 @@ error = true;
else if (!strncmp("eventlog-flush-interval=",
&rts_argv[arg][2], 24)) {
OPTION_SAFE;
+ THREADED_BUILD_ONLY(
double intervalSeconds = parseDouble(rts_argv[arg]+26, &error);
if (error) {
errorBelch("bad value for --eventlog-flush-interval");
}
RtsFlags.TraceFlags.eventlogFlushTime =
fsecondsToTime(intervalSeconds);
+ ) break;
}
else if (strequal("copying-gc",
&rts_argv[arg][2])) {
@@ -1963,6 +1969,7 @@ static void normaliseRtsOpts (void)
RtsFlags.ProfFlags.heapProfileIntervalTicks = 0;
}
+#if defined(THREADED_RTS)
if (RtsFlags.TraceFlags.eventlogFlushTime > 0 && RtsFlags.MiscFlags.tickInterval != 0) {
RtsFlags.TraceFlags.eventlogFlushTicks =
RtsFlags.TraceFlags.eventlogFlushTime /
@@ -1970,6 +1977,7 @@ static void normaliseRtsOpts (void)
} else {
RtsFlags.TraceFlags.eventlogFlushTicks = 0;
}
+#endif
if (RtsFlags.GcFlags.stkChunkBufferSize >
RtsFlags.GcFlags.stkChunkSize / 2) {
=====================================
rts/Timer.c
=====================================
@@ -43,8 +43,10 @@ static StgWord timer_disabled;
/* ticks left before next pre-emptive context switch */
static int ticks_to_ctxt_switch = 0;
+#if defined(THREADED_RTS)
/* ticks left before next next forced eventlog flush */
static int ticks_to_eventlog_flush = 0;
+#endif
/*
@@ -118,7 +120,7 @@ handle_tick(int unused STG_UNUSED)
contextSwitchAllCapabilities(); /* schedule a context switch */
}
}
-
+#if defined(THREADED_RTS)
if (eventLogStatus() == EVENTLOG_RUNNING
&& RtsFlags.TraceFlags.eventlogFlushTicks > 0) {
ticks_to_eventlog_flush--;
@@ -127,6 +129,7 @@ handle_tick(int unused STG_UNUSED)
flushEventLog(NULL);
}
}
+#endif
/*
* If we've been inactive for idleGCDelayTime (set by +RTS
=====================================
rts/include/rts/Flags.h
=====================================
@@ -188,8 +188,11 @@ typedef struct _TRACE_FLAGS {
bool sparks_full; /* trace spark events 100% accurately */
bool ticky; /* trace ticky-ticky samples */
bool user; /* trace user events (emitted from Haskell code) */
- Time eventlogFlushTime; /* Time between force eventlog flushes (or 0 if disabled) */
+#if defined(THREADED_RTS)
+ /* Time between force eventlog flushes (or 0 if disabled) */
+ Time eventlogFlushTime;
int eventlogFlushTicks;
+#endif
char *trace_output; /* output filename for eventlog */
bool nullWriter; /* use null writer instead of file writer */
} TRACE_FLAGS;
=====================================
testsuite/tests/rts/flags/all.T
=====================================
@@ -57,6 +57,14 @@ test('T12870h',
multimod_compile_and_run,
['T12870g', '-rtsopts=ignoreAll -with-rtsopts="-G3"'])
-test('T20006', [extra_run_opts('+RTS --eventlog-flush-interval=1')],
- compile_and_run,
- [''])
+test('T20006a',
+ [extra_files(['T20006.hs']), extra_run_opts('+RTS --eventlog-flush-interval=1'),
+ only_ways(['threaded1', 'threaded2'])],
+ multimod_compile_and_run,
+ ['T20006', ''])
+
+test('T20006b',
+ [extra_files(['T20006.hs']), extra_run_opts('+RTS --eventlog-flush-interval=1'),
+ expect_fail_for(['normal'])],
+ multimod_compile_and_run,
+ ['T20006', ''])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/93032e00c78dd3f9d45dd90d88d78a…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/93032e00c78dd3f9d45dd90d88d78a…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/T23109] 50 commits: Bump win32-tarballs to v0.9
by Simon Peyton Jones (@simonpj) 29 Jul '25
by Simon Peyton Jones (@simonpj) 29 Jul '25
29 Jul '25
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/bfb686bb5ba503e9386dc899e1ebbe248…
- - - - -
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 <sam.derbyshire(a)gmail.com>
- - - - -
c6cd2da1 by Jappie Klooster at 2025-07-17T06:06:20-04:00
Update interact docs to explain about buffering
We need to tell the user to set to the
appropriate buffer format.
Otherwise, this function may get randomly stuck,
or just behave confusingly.
issue: https://gitlab.haskell.org/ghc/ghc/-/issues/26131
NB, I'm running this with cabal *NOT* ghci. ghci messes with buffering anyway.
```haskell
interaction :: String -> String
interaction "jappie" = "hi"
interaction "jakob" = "hello"
interaction x = "unkown input: " <> x
main :: IO ()
main = interact interaction
```
so in my input (prefixed by `>`) I get:
```
> 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/586cd1f482e465fe6ab70a828a1f39…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/586cd1f482e465fe6ab70a828a1f39…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 4 commits: Update comments on `OptKind` to reflect the code reality
by Marge Bot (@marge-bot) 29 Jul '25
by Marge Bot (@marge-bot) 29 Jul '25
29 Jul '25
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
f7740ba5 by Simon Hengel at 2025-07-29T18:15:00-04:00
Update comments on `OptKind` to reflect the code reality
- - - - -
87f8ffb5 by Wen Kokke at 2025-07-29T18:15:02-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.
- - - - -
8c7a33d8 by Wen Kokke at 2025-07-29T18:15:02-04:00
rts: Split T20006 into tests with and without -threaded
- - - - -
93032e00 by Simon Hengel at 2025-07-29T18:15:03-04:00
docs/users_guide/win32-dlls.rst: Remove references to `readline`
- - - - -
7 changed files:
- compiler/GHC/Driver/CmdLine.hs
- docs/users_guide/runtime_control.rst
- docs/users_guide/win32-dlls.rst
- rts/RtsFlags.c
- rts/Timer.c
- rts/include/rts/Flags.h
- testsuite/tests/rts/flags/all.T
Changes:
=====================================
compiler/GHC/Driver/CmdLine.hs
=====================================
@@ -92,14 +92,14 @@ data GhcFlagMode
data OptKind m -- Suppose the flag is -f
= NoArg (EwM m ()) -- -f all by itself
- | HasArg (String -> EwM m ()) -- -farg or -f arg
+ | HasArg (String -> EwM m ()) -- -farg or -f=arg or -f arg
| SepArg (String -> EwM m ()) -- -f arg
- | Prefix (String -> EwM m ()) -- -farg
- | OptPrefix (String -> EwM m ()) -- -f or -farg (i.e. the arg is optional)
- | OptIntSuffix (Maybe Int -> EwM m ()) -- -f or -f=n; pass n to fn
- | IntSuffix (Int -> EwM m ()) -- -f or -f=n; pass n to fn
- | Word64Suffix (Word64 -> EwM m ()) -- -f or -f=n; pass n to fn
- | FloatSuffix (Float -> EwM m ()) -- -f or -f=n; pass n to fn
+ | Prefix (String -> EwM m ()) -- -farg or -f=arg
+ | OptPrefix (String -> EwM m ()) -- -f or -farg or -f=arg (i.e. the arg is optional)
+ | OptIntSuffix (Maybe Int -> EwM m ()) -- -f or -fn or -f=n; pass n to fn
+ | IntSuffix (Int -> EwM m ()) -- -fn or -f=n; pass n to fn
+ | Word64Suffix (Word64 -> EwM m ()) -- -fn or -f=n; pass n to fn
+ | FloatSuffix (Float -> EwM m ()) -- -fn or -f=n; pass n to fn
| PassFlag (String -> EwM m ()) -- -f; pass "-f" fn
| AnySuffix (String -> EwM m ()) -- -f or -farg; pass entire "-farg" to fn
=====================================
docs/users_guide/runtime_control.rst
=====================================
@@ -1361,7 +1361,8 @@ When the program is linked with the :ghc-flag:`-eventlog` option
:since: 9.2
When enabled, the eventlog will be flushed periodically every
- ⟨seconds⟩. This can be useful in live-monitoring situations where the
+ ⟨seconds⟩ (only available with :ghc-flag:`-threaded`).
+ This can be useful in live-monitoring situations where the
eventlog is consumed in real-time by another process.
.. rts-flag:: -v [⟨flags⟩]
=====================================
docs/users_guide/win32-dlls.rst
=====================================
@@ -76,11 +76,6 @@ window, use the flag ``-optl-mwindows`` in the link step.
However using Debug.Trace.trace is alright because it uses Windows
debugging output support rather than ``stderr``.
-For some reason, Mingw ships with the ``readline`` library, but not with
-the ``readline`` headers. As a result, GHC (like Hugs) does not use
-``readline`` for interactive input on Windows. You can get a close
-simulation by using an emacs shell buffer!
-
.. _library-differences:
Differences in library behaviour
=====================================
rts/RtsFlags.c
=====================================
@@ -248,7 +248,9 @@ void initRtsFlagsDefaults(void)
RtsFlags.TraceFlags.user = false;
RtsFlags.TraceFlags.ticky = false;
RtsFlags.TraceFlags.trace_output = NULL;
+# if defined(THREADED_RTS)
RtsFlags.TraceFlags.eventlogFlushTime = 0;
+# endif
RtsFlags.TraceFlags.nullWriter = false;
#endif
@@ -448,8 +450,10 @@ usage_text[] = {
# endif
" -x disable an event class, for any flag above",
" the initial enabled event classes are 'sgpu'",
+# if defined(THREADED_RTS)
" --eventlog-flush-interval=<secs>",
" Periodically flush the eventlog at the specified interval.",
+# endif
#endif
"",
@@ -1052,12 +1056,14 @@ error = true;
else if (!strncmp("eventlog-flush-interval=",
&rts_argv[arg][2], 24)) {
OPTION_SAFE;
+ THREADED_BUILD_ONLY(
double intervalSeconds = parseDouble(rts_argv[arg]+26, &error);
if (error) {
errorBelch("bad value for --eventlog-flush-interval");
}
RtsFlags.TraceFlags.eventlogFlushTime =
fsecondsToTime(intervalSeconds);
+ ) break;
}
else if (strequal("copying-gc",
&rts_argv[arg][2])) {
@@ -1963,6 +1969,7 @@ static void normaliseRtsOpts (void)
RtsFlags.ProfFlags.heapProfileIntervalTicks = 0;
}
+#if defined(THREADED_RTS)
if (RtsFlags.TraceFlags.eventlogFlushTime > 0 && RtsFlags.MiscFlags.tickInterval != 0) {
RtsFlags.TraceFlags.eventlogFlushTicks =
RtsFlags.TraceFlags.eventlogFlushTime /
@@ -1970,6 +1977,7 @@ static void normaliseRtsOpts (void)
} else {
RtsFlags.TraceFlags.eventlogFlushTicks = 0;
}
+#endif
if (RtsFlags.GcFlags.stkChunkBufferSize >
RtsFlags.GcFlags.stkChunkSize / 2) {
=====================================
rts/Timer.c
=====================================
@@ -43,8 +43,10 @@ static StgWord timer_disabled;
/* ticks left before next pre-emptive context switch */
static int ticks_to_ctxt_switch = 0;
+#if defined(THREADED_RTS)
/* ticks left before next next forced eventlog flush */
static int ticks_to_eventlog_flush = 0;
+#endif
/*
@@ -118,7 +120,7 @@ handle_tick(int unused STG_UNUSED)
contextSwitchAllCapabilities(); /* schedule a context switch */
}
}
-
+#if defined(THREADED_RTS)
if (eventLogStatus() == EVENTLOG_RUNNING
&& RtsFlags.TraceFlags.eventlogFlushTicks > 0) {
ticks_to_eventlog_flush--;
@@ -127,6 +129,7 @@ handle_tick(int unused STG_UNUSED)
flushEventLog(NULL);
}
}
+#endif
/*
* If we've been inactive for idleGCDelayTime (set by +RTS
=====================================
rts/include/rts/Flags.h
=====================================
@@ -188,8 +188,11 @@ typedef struct _TRACE_FLAGS {
bool sparks_full; /* trace spark events 100% accurately */
bool ticky; /* trace ticky-ticky samples */
bool user; /* trace user events (emitted from Haskell code) */
- Time eventlogFlushTime; /* Time between force eventlog flushes (or 0 if disabled) */
+#if defined(THREADED_RTS)
+ /* Time between force eventlog flushes (or 0 if disabled) */
+ Time eventlogFlushTime;
int eventlogFlushTicks;
+#endif
char *trace_output; /* output filename for eventlog */
bool nullWriter; /* use null writer instead of file writer */
} TRACE_FLAGS;
=====================================
testsuite/tests/rts/flags/all.T
=====================================
@@ -57,6 +57,14 @@ test('T12870h',
multimod_compile_and_run,
['T12870g', '-rtsopts=ignoreAll -with-rtsopts="-G3"'])
-test('T20006', [extra_run_opts('+RTS --eventlog-flush-interval=1')],
- compile_and_run,
- [''])
+test('T20006a',
+ [extra_files(['T20006.hs']), extra_run_opts('+RTS --eventlog-flush-interval=1'),
+ only_ways(['threaded1', 'threaded2'])],
+ multimod_compile_and_run,
+ ['T20006', ''])
+
+test('T20006b',
+ [extra_files(['T20006.hs']), extra_run_opts('+RTS --eventlog-flush-interval=1'),
+ expect_fail_for(['normal'])],
+ multimod_compile_and_run,
+ ['T20006', ''])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ac89057bdca8386552c4295e72c6bd…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ac89057bdca8386552c4295e72c6bd…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 4 commits: Update comments on `OptKind` to reflect the code reality
by Marge Bot (@marge-bot) 29 Jul '25
by Marge Bot (@marge-bot) 29 Jul '25
29 Jul '25
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
c8a99ce0 by Simon Hengel at 2025-07-29T15:42:26-04:00
Update comments on `OptKind` to reflect the code reality
- - - - -
66d50826 by Wen Kokke at 2025-07-29T15:42:31-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.
- - - - -
995b995b by Wen Kokke at 2025-07-29T15:42:31-04:00
rts: Split T20006 into tests with and without -threaded
- - - - -
ac89057b by Simon Hengel at 2025-07-29T15:42:32-04:00
docs/users_guide/win32-dlls.rst: Remove references to `readline`
- - - - -
7 changed files:
- compiler/GHC/Driver/CmdLine.hs
- docs/users_guide/runtime_control.rst
- docs/users_guide/win32-dlls.rst
- rts/RtsFlags.c
- rts/Timer.c
- rts/include/rts/Flags.h
- testsuite/tests/rts/flags/all.T
Changes:
=====================================
compiler/GHC/Driver/CmdLine.hs
=====================================
@@ -92,14 +92,14 @@ data GhcFlagMode
data OptKind m -- Suppose the flag is -f
= NoArg (EwM m ()) -- -f all by itself
- | HasArg (String -> EwM m ()) -- -farg or -f arg
+ | HasArg (String -> EwM m ()) -- -farg or -f=arg or -f arg
| SepArg (String -> EwM m ()) -- -f arg
- | Prefix (String -> EwM m ()) -- -farg
- | OptPrefix (String -> EwM m ()) -- -f or -farg (i.e. the arg is optional)
- | OptIntSuffix (Maybe Int -> EwM m ()) -- -f or -f=n; pass n to fn
- | IntSuffix (Int -> EwM m ()) -- -f or -f=n; pass n to fn
- | Word64Suffix (Word64 -> EwM m ()) -- -f or -f=n; pass n to fn
- | FloatSuffix (Float -> EwM m ()) -- -f or -f=n; pass n to fn
+ | Prefix (String -> EwM m ()) -- -farg or -f=arg
+ | OptPrefix (String -> EwM m ()) -- -f or -farg or -f=arg (i.e. the arg is optional)
+ | OptIntSuffix (Maybe Int -> EwM m ()) -- -f or -fn or -f=n; pass n to fn
+ | IntSuffix (Int -> EwM m ()) -- -fn or -f=n; pass n to fn
+ | Word64Suffix (Word64 -> EwM m ()) -- -fn or -f=n; pass n to fn
+ | FloatSuffix (Float -> EwM m ()) -- -fn or -f=n; pass n to fn
| PassFlag (String -> EwM m ()) -- -f; pass "-f" fn
| AnySuffix (String -> EwM m ()) -- -f or -farg; pass entire "-farg" to fn
=====================================
docs/users_guide/runtime_control.rst
=====================================
@@ -1361,7 +1361,8 @@ When the program is linked with the :ghc-flag:`-eventlog` option
:since: 9.2
When enabled, the eventlog will be flushed periodically every
- ⟨seconds⟩. This can be useful in live-monitoring situations where the
+ ⟨seconds⟩ (only available with :ghc-flag:`-threaded`).
+ This can be useful in live-monitoring situations where the
eventlog is consumed in real-time by another process.
.. rts-flag:: -v [⟨flags⟩]
=====================================
docs/users_guide/win32-dlls.rst
=====================================
@@ -76,11 +76,6 @@ window, use the flag ``-optl-mwindows`` in the link step.
However using Debug.Trace.trace is alright because it uses Windows
debugging output support rather than ``stderr``.
-For some reason, Mingw ships with the ``readline`` library, but not with
-the ``readline`` headers. As a result, GHC (like Hugs) does not use
-``readline`` for interactive input on Windows. You can get a close
-simulation by using an emacs shell buffer!
-
.. _library-differences:
Differences in library behaviour
=====================================
rts/RtsFlags.c
=====================================
@@ -248,7 +248,9 @@ void initRtsFlagsDefaults(void)
RtsFlags.TraceFlags.user = false;
RtsFlags.TraceFlags.ticky = false;
RtsFlags.TraceFlags.trace_output = NULL;
+# if defined(THREADED_RTS)
RtsFlags.TraceFlags.eventlogFlushTime = 0;
+# endif
RtsFlags.TraceFlags.nullWriter = false;
#endif
@@ -448,8 +450,10 @@ usage_text[] = {
# endif
" -x disable an event class, for any flag above",
" the initial enabled event classes are 'sgpu'",
+# if defined(THREADED_RTS)
" --eventlog-flush-interval=<secs>",
" Periodically flush the eventlog at the specified interval.",
+# endif
#endif
"",
@@ -1052,12 +1056,14 @@ error = true;
else if (!strncmp("eventlog-flush-interval=",
&rts_argv[arg][2], 24)) {
OPTION_SAFE;
+ THREADED_BUILD_ONLY(
double intervalSeconds = parseDouble(rts_argv[arg]+26, &error);
if (error) {
errorBelch("bad value for --eventlog-flush-interval");
}
RtsFlags.TraceFlags.eventlogFlushTime =
fsecondsToTime(intervalSeconds);
+ ) break;
}
else if (strequal("copying-gc",
&rts_argv[arg][2])) {
@@ -1963,6 +1969,7 @@ static void normaliseRtsOpts (void)
RtsFlags.ProfFlags.heapProfileIntervalTicks = 0;
}
+#if defined(THREADED_RTS)
if (RtsFlags.TraceFlags.eventlogFlushTime > 0 && RtsFlags.MiscFlags.tickInterval != 0) {
RtsFlags.TraceFlags.eventlogFlushTicks =
RtsFlags.TraceFlags.eventlogFlushTime /
@@ -1970,6 +1977,7 @@ static void normaliseRtsOpts (void)
} else {
RtsFlags.TraceFlags.eventlogFlushTicks = 0;
}
+#endif
if (RtsFlags.GcFlags.stkChunkBufferSize >
RtsFlags.GcFlags.stkChunkSize / 2) {
=====================================
rts/Timer.c
=====================================
@@ -43,8 +43,10 @@ static StgWord timer_disabled;
/* ticks left before next pre-emptive context switch */
static int ticks_to_ctxt_switch = 0;
+#if defined(THREADED_RTS)
/* ticks left before next next forced eventlog flush */
static int ticks_to_eventlog_flush = 0;
+#endif
/*
@@ -118,7 +120,7 @@ handle_tick(int unused STG_UNUSED)
contextSwitchAllCapabilities(); /* schedule a context switch */
}
}
-
+#if defined(THREADED_RTS)
if (eventLogStatus() == EVENTLOG_RUNNING
&& RtsFlags.TraceFlags.eventlogFlushTicks > 0) {
ticks_to_eventlog_flush--;
@@ -127,6 +129,7 @@ handle_tick(int unused STG_UNUSED)
flushEventLog(NULL);
}
}
+#endif
/*
* If we've been inactive for idleGCDelayTime (set by +RTS
=====================================
rts/include/rts/Flags.h
=====================================
@@ -188,8 +188,11 @@ typedef struct _TRACE_FLAGS {
bool sparks_full; /* trace spark events 100% accurately */
bool ticky; /* trace ticky-ticky samples */
bool user; /* trace user events (emitted from Haskell code) */
- Time eventlogFlushTime; /* Time between force eventlog flushes (or 0 if disabled) */
+#if defined(THREADED_RTS)
+ /* Time between force eventlog flushes (or 0 if disabled) */
+ Time eventlogFlushTime;
int eventlogFlushTicks;
+#endif
char *trace_output; /* output filename for eventlog */
bool nullWriter; /* use null writer instead of file writer */
} TRACE_FLAGS;
=====================================
testsuite/tests/rts/flags/all.T
=====================================
@@ -57,6 +57,14 @@ test('T12870h',
multimod_compile_and_run,
['T12870g', '-rtsopts=ignoreAll -with-rtsopts="-G3"'])
-test('T20006', [extra_run_opts('+RTS --eventlog-flush-interval=1')],
- compile_and_run,
- [''])
+test('T20006a',
+ [extra_files(['T20006.hs']), extra_run_opts('+RTS --eventlog-flush-interval=1'),
+ only_ways(['threaded1', 'threaded2'])],
+ multimod_compile_and_run,
+ ['T20006', ''])
+
+test('T20006b',
+ [extra_files(['T20006.hs']), extra_run_opts('+RTS --eventlog-flush-interval=1'),
+ expect_fail_for(['normal'])],
+ multimod_compile_and_run,
+ ['T20006', ''])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1f3d422fb5393548ac7d8d098a005c…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1f3d422fb5393548ac7d8d098a005c…
You're receiving this email because of your account on gitlab.haskell.org.
1
0