Simon Hengel pushed to branch wip/sol/remove-ddump-json at Glasgow Haskell Compiler / GHC
Commits:
8d33d048 by Berk Özkütük at 2025-07-07T20:42:20-04:00
Consider `PromotedDataCon` in `tyConStupidTheta`
Haddock checks data declarations for the stupid theta so as not to
pretty-print them as empty contexts. Type data declarations end up as
`PromotedDataCon`s by the time Haddock performs this check, causing a
panic. This commit extends `tyConStupidTheta` so that it returns an
empty list for `PromotedDataCon`s. This decision was guided by the fact
that type data declarations never have data type contexts (see (R1) in
Note [Type data declarations]).
Fixes #25739.
- - - - -
a26243fd by Ryan Hendrickson at 2025-07-07T20:43:07-04:00
haddock: Document instances from other packages
When attaching instances to `Interface`s, it isn't enough just to look
for instances in the list of `Interface`s being processed. We also need
to look in the modules on which they depend, including those outside of
this package.
Fixes #25147.
Fixes #26079.
- - - - -
0fb24420 by Rodrigo Mesquita at 2025-07-07T20:43:49-04:00
hadrian: Fallback logic for internal interpreter
When determining whether to build the internal interpreter, the `make`
build system had a fallback case for platforms not in the list of
explicitly-supported operating systems and architectures.
This fallback says we should try to build the internal interpreter if
building dynamic GHC programs (if the architecture is unknown).
Fixes #24098
- - - - -
fe925bd4 by Ben Gamari at 2025-07-07T20:44:30-04:00
users-guide: Reference Wasm FFI section
- - - - -
5856284b by Ben Gamari at 2025-07-07T20:44:30-04:00
users-guide: Fix too-short heading warning
- - - - -
a48dcdf3 by Duncan Coutts at 2025-07-07T20:45:18-04:00
Reorganise documentation for allocate* functions
Consolodate interface information into the .h file, keeping just
implementation details in the .c file.
Use Notes stlye in the .h file and refer to notes from the .c file.
- - - - -
de5b528c by Duncan Coutts at 2025-07-07T20:45:18-04:00
Introduce common utilities for allocating arrays
The intention is to share code among the several places that do this
already.
- - - - -
b321319d by Duncan Coutts at 2025-07-07T20:45:18-04:00
Use new array alloc utils in Heap.c
The CMM primop can now report heap overflow.
- - - - -
1d557ffb by Duncan Coutts at 2025-07-07T20:45:18-04:00
Use new array alloc utils in ThreadLabels.c
Replacing a local utility.
- - - - -
e59a1430 by Duncan Coutts at 2025-07-07T20:45:18-04:00
Use new array alloc utils in Threads.c
Replacing local open coded version.
- - - - -
482df1c9 by Duncan Coutts at 2025-07-07T20:45:18-04:00
Add exitHeapOverflow helper utility
This will be useful with the array alloc functions, since unlike
allocate/allocateMaybeFail, they do not come in two versions. So if it's
not convenient to propagate failure, then one can use this.
- - - - -
4d3ec8f9 by Duncan Coutts at 2025-07-07T20:45:18-04:00
Use new array alloc utils in Weak.c
Also add a cpp macro CCS_SYSTEM_OR_NULL which does what it says. The
benefit of this is that it allows us to referece CCS_SYSTEM even when
we're not in PROFILING mode. That makes abstracting over profiling vs
normal mode a lot easier.
- - - - -
0c4f2fde by Duncan Coutts at 2025-07-07T20:45:18-04:00
Convert the array alloc primops to use the new array alloc utils
- - - - -
a3354ad9 by Duncan Coutts at 2025-07-07T20:45:18-04:00
While we're at it, add one missing 'likely' hint
To a cmm primops that raises an exception, like the others now do.
- - - - -
33b546bd by meooow25 at 2025-07-07T20:46:09-04:00
Keep scanl' strict in the head on rewrite
`scanl'` forces elements to WHNF when the corresponding `(:)`s are
forced. The rewrite rule for `scanl'` missed forcing the first element,
which is fixed here with a `seq`.
- - - - -
8a69196e by Rodrigo Mesquita at 2025-07-08T07:39:47-04:00
debugger/rts: Allow toggling step-in per thread
The RTS global flag `rts_stop_next_breakpoint` globally sets the
interpreter to stop at the immediate next breakpoint.
With this commit, single step mode can additionally be set per thread in
the TSO flag (TSO_STOP_NEXT_BREAKPOINT).
Being able to toggle "stop at next breakpoint" per thread is an
important requirement for implementing "stepping out" of a function in a
multi-threaded context.
And, more generally, having a per-thread flag for single-stepping paves the
way for multi-threaded debugging.
That said, when we want to enable "single step" mode for the whole
interpreted program we still want to stop at the immediate next
breakpoint, whichever thread it belongs to.
That's why we also keep the global `rts_stop_next_breakpoint` flag, with
`rts_enableStopNextBreakpointAll` and `rts_disableStopNextBreakpointAll` helpers.
Preparation for #26042
- - - - -
73d3f864 by Rodrigo Mesquita at 2025-07-08T07:39:47-04:00
docs: Case continuation BCOs
This commit documents a subtle interaction between frames for case BCOs
and their parents frames. Namely, case continuation BCOs may refer to
(non-local) variables that are part of the parent's frame.
The note expanding a bit on these details is called [Case continuation BCOs]
- - - - -
d7aeddcf by Rodrigo Mesquita at 2025-07-08T07:39:47-04:00
debugger: Implement step-out feature
Implements support for stepping-out of a function (aka breaking right after
returning from a function) in the interactive debugger.
It also introduces a GHCi command :stepout to step-out of a function
being debugged in the interpreter. The feature is described as:
Stop at the first breakpoint immediately after returning from the current
function scope.
Known limitations: because a function tail-call does not push a stack
frame, if step-out is used inside of a function that was tail-called,
execution will not be returned to its caller, but rather its caller's
first non-tail caller. On the other hand, it means the debugger
follows the more realistic execution of the program.
In the following example:
.. code-block:: none
f = do
a
b <--- (1) set breakpoint then step in here
c
b = do
...
d <--- (2) step-into this tail call
d = do
...
something <--- (3) step-out here
...
Stepping-out will stop execution at the `c` invokation in `f`, rather than
stopping at `b`.
The key idea is simple: When step-out is enabled, traverse the runtime
stack until a continuation BCO is found -- and enable the breakpoint
heading that BCO explicitly using its tick-index.
The details are specified in `Note [Debugger: Step-out]` in `rts/Interpreter.c`.
Since PUSH_ALTS BCOs (representing case continuations) were never headed
by a breakpoint (unlike the case alternatives they push), we introduced
the BRK_ALTS instruction to allow the debugger to set a case
continuation to stop at the breakpoint heading the alternative that is
taken. This is further described in `Note [Debugger: BRK_ALTS]`.
Fixes #26042
- - - - -
5d9adf51 by Rodrigo Mesquita at 2025-07-08T07:39:47-04:00
debugger: Filter step-out stops by SrcSpan
To implement step-out, the RTS looks for the first continuation frame on
the stack and explicitly enables its entry breakpoint. However, some
continuations will be contained in the function from which step-out was
initiated (trivial example is a case expression).
Similarly to steplocal, we will filter the breakpoints at which the RTS
yields to the debugger based on the SrcSpan. When doing step-out, only
stop if the breakpoint is /not/ contained in the function from which we
initiated it.
This is especially relevant in monadic statements such as IO which is
compiled to a long chain of case expressions.
See Note [Debugger: Filtering step-out stops]
- - - - -
7677adcc by Cheng Shao at 2025-07-08T07:40:29-04:00
compiler: make ModBreaks serializable
- - - - -
14f67c6d by Rodrigo Mesquita at 2025-07-08T07:40:29-04:00
refactor: "Inspecting the session" moved from GHC
Moved utilities for inspecting the session from the GHC module to
GHC.Driver.Session.Inspect
Purely a clean up
- - - - -
9d3f484a by Rodrigo Mesquita at 2025-07-08T07:40:30-04:00
cleanup: Pass the HUG to readModBreaks, not HscEnv
A minor cleanup. The associated history and setupBreakpoint functions
are changed accordingly.
- - - - -
b595f713 by Rodrigo Mesquita at 2025-07-08T07:40:30-04:00
cleanup: Move readModBreaks to GHC.Runtime.Interpreter
With some small docs changes
- - - - -
d223227a by Rodrigo Mesquita at 2025-07-08T07:40:30-04:00
cleanup: Move interpreterProfiled to Interp.Types
Moves interpreterProfiled and interpreterDynamic to
GHC.Runtime.Interpreter.Types from GHC.Runtime.Interpreter.
- - - - -
7fdd0a3d by Rodrigo Mesquita at 2025-07-08T07:40:30-04:00
cleanup: Don't import GHC in Debugger.Breakpoints
Remove the top-level
import GHC
from GHC.Runtime.Debugger.Breakpoints
This makes the module dependencies more granular and cleans up the
qualified imports from the code.
- - - - -
5e4da31b by Rodrigo Mesquita at 2025-07-08T07:40:30-04:00
refactor: Use BreakpointId in Core and Ifaces
- - - - -
741ac3a8 by Rodrigo Mesquita at 2025-07-08T07:40:30-04:00
stg2bc: Derive BcM via ReaderT StateT
A small refactor that simplifies GHC.StgToByteCode by deriving-via the
Monad instances for BcM. This is done along the lines of previous
similar refactors like 72b54c0760bbf85be1f73c1a364d4701e5720465.
- - - - -
0414fcc9 by Rodrigo Mesquita at 2025-07-08T07:40:30-04:00
refact: Split InternalModBreaks out of ModBreaks
There are currently two competing ways of referring to a Breakpoint:
1. Using the Tick module + Tick index
2. Using the Info module + Info index
1. The Tick index is allocated during desugaring in `mkModBreaks`. It is
used to refer to a breakpoint associated to a Core Tick. For a given
Tick module, there are N Ticks indexed by Tick index.
2. The Info index is allocated during code generation (in StgToByteCode)
and uniquely identifies the breakpoints at runtime (and is indeed used
to determine which breakpoint was hit at runtime).
Why we need both is described by Note [Breakpoint identifiers].
For every info index we used to keep a `CgBreakInfo`, a datatype containing
information relevant to ByteCode Generation, in `ModBreaks`.
This commit splits out the `IntMap CgBreakInfo` out of `ModBreaks` into
a new datatype `InternalModBreaks`.
- The purpose is to separate the `ModBreaks` datatype, which stores
data associated from tick-level information which is fixed after
desugaring, from the unrelated `IntMap CgBreakInfo` information
accumulated during bytecode generation.
- We move `ModBreaks` to GHC.HsToCore.Breakpoints
The new `InternalModBreaks` simply combines the `IntMap CgBreakInfo`
with `ModBreaks`. After code generation we construct an
`InternalModBreaks` with the `CgBreakInfo`s we accumulated and the
existing `ModBreaks` and store that in the compiled BCO in `bc_breaks`.
- Note that we previously only updated the `modBreaks_breakInfo`
field of `ModBreaks` at this exact location, and then stored the
updated `ModBreaks` in the same `bc_breaks`.
- We put this new datatype in GHC.ByteCode.Breakpoints
The rest of the pipeline for which CgBreakInfo is relevant is
accordingly updated to also use `InternalModBreaks`
- - - - -
2a097955 by Rodrigo Mesquita at 2025-07-08T07:40:30-04:00
cleanup: Use BreakpointIds in bytecode gen
Small clean up to use BreakpointId and InternalBreakpointId more
uniformly in bytecode generation rather than using Module + Ix pairs
- - - - -
0515cc2f by Rodrigo Mesquita at 2025-07-08T07:40:30-04:00
ghci: Allocate BreakArrays at link time only
Previously, a BreakArray would be allocated with a slot for every tick
in a module at `mkModBreaks`, in HsToCore. However, this approach has
a few downsides:
- It interleaves interpreter behaviour (allocating arrays for
breakpoints) within the desugarer
- It is inflexible in the sense it is impossible for the bytecode
generator to add "internal" breakpoints that can be triggered at
runtime, because those wouldn't have a source tick. (This is relevant
for our intended implementation plan of step-out in #26042)
- It ties the BreakArray indices to the *tick* indexes, while at runtime
we would rather just have the *info* indexes (currently we have both
because BreakArrays are indexed by the *tick* one).
Paving the way for #26042 and #26064, this commit moves the allocation
of BreakArrays to bytecode-loading time -- akin to what is done for CCS
arrays.
Since a BreakArray is allocated only when bytecode is linked, if a
breakpoint is set (e.g. `:break 10`) before the bytecode is linked,
there will exist no BreakArray to trigger the breakpoint in.
Therefore, the function to allocate break arrays (`allocateBreakArrays`)
is exposed and also used in GHC.Runtime.Eval to allocate a break array
when a breakpoint is set, if it doesn't exist yet (in the linker env).
- - - - -
8016561f by Simon Peyton Jones at 2025-07-08T07:41:13-04:00
Add a test for T26176
- - - - -
454cd682 by Simon Peyton Jones at 2025-07-08T07:41:13-04:00
Add test for #14010
This test started to work in GHC 9.6 and has worked since.
This MR just adds a regression test
- - - - -
ea2c6673 by Teo Camarasu at 2025-07-08T13:24:43-04:00
Implement user-defined allocation limit handlers
Allocation Limits allow killing a thread if they allocate more than a
user-specified limit.
We extend this feature to allow more versatile behaviour.
- We allow not killing the thread if the limit is exceeded.
- We allow setting a custom handler to be called when the limit is exceeded.
User-specified allocation limit handlers run in a fresh thread and are passed
the ThreadId of the thread that exceeded its limit.
We introduce utility functions for getting and setting the allocation
limits of other threads, so that users can reset the limit of a thread
from a handler. Both of these are somewhat coarse-grained as we are
unaware of the allocations in the current nursery chunk.
We provide several examples of usages in testsuite/tests/rts/T22859.hs
Resolves #22859
- - - - -
03e047f9 by Simon Hengel at 2025-07-08T13:25:25-04:00
Fix typo in using.rst
- - - - -
67957854 by Ben Gamari at 2025-07-09T09:44:44-04:00
compiler: Import AnnotationWrapper from ghc-internal
Since `GHC.Desugar` exported from `base` has been deprecated.
- - - - -
813d99d6 by Ben Gamari at 2025-07-09T09:44:44-04:00
ghc-compact: Eliminate dependency on ghc-prim
- - - - -
0ec952a1 by Ben Gamari at 2025-07-09T09:44:44-04:00
ghc-heap: Eliminate dependency on ghc-prim
- - - - -
480074c3 by Ben Gamari at 2025-07-09T09:44:44-04:00
ghc-heap: Drop redundant import
- - - - -
03455829 by Ben Gamari at 2025-07-09T09:44:45-04:00
ghc-prim: Bump version to 0.13.1
There are no interface changes from 0.13.0 but the implementation now
lives in `ghc-internal`.
- - - - -
d315345a by Ben Gamari at 2025-07-09T09:44:45-04:00
template-haskell: Bump version number to 2.24.0.0
Bumps exceptions submodule.
- - - - -
004c800e by Ben Gamari at 2025-07-09T09:44:45-04:00
Bump GHC version number to 9.14
- - - - -
eb1a3816 by Ben Gamari at 2025-07-09T09:44:45-04:00
Bump parsec to 3.1.18.0
Bumps parsec submodule.
- - - - -
86f83296 by Ben Gamari at 2025-07-09T09:44:45-04:00
unix: Bump to 2.8.7.0
Bumps unix submodule.
- - - - -
89e13998 by Ben Gamari at 2025-07-09T09:44:45-04:00
binary: Bump to 0.8.9.3
Bumps binary submodule.
- - - - -
55fff191 by Ben Gamari at 2025-07-09T09:44:45-04:00
Win32: Bump to 2.14.2.0
Bumps Win32 submodule.
- - - - -
7dafa40c by Ben Gamari at 2025-07-09T09:44:45-04:00
base: Bump version to 4.22.0
Bumps various submodules.
- - - - -
ef03d8b8 by Rodrigo Mesquita at 2025-07-09T09:45:28-04:00
base: Export displayExceptionWithInfo
This function should be exposed from base following CLC#285
Approved change in CLC#344
Fixes #26058
- - - - -
01d3154e by Wen Kokke at 2025-07-10T17:06:36+01:00
Fix documentation for HEAP_PROF_SAMPLE_STRING
- - - - -
ac259c48 by Wen Kokke at 2025-07-10T17:06:38+01:00
Fix documentation for HEAP_PROF_SAMPLE_COST_CENTRE
- - - - -
2b4db9ba by Pi Delport at 2025-07-11T16:40:52-04:00
(Applicative docs typo: missing "one")
- - - - -
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/bfb686bb5ba503e9386dc899e1ebbe2488...
- - - - -
9cbb3ef5 by Ben Gamari at 2025-07-15T16:56:39-04:00
testsuite: Mark T12497 as fixed
Thanks to the LLVM toolchain update.
Closes #22694.
- - - - -
2854407e by Ben Gamari at 2025-07-15T16:56:39-04:00
testsuite: Accept new output of T11223_link_order_a_b_2_fail on Windows
The archive member number changed due to the fact that llvm-ar now uses a
string table.
- - - - -
28439593 by Ben Gamari at 2025-07-15T16:56:39-04:00
rts/linker/PEi386: Implement IMAGE_REL_AMD64_SECREL
This appears to now be used by libc++ as distributed by msys2.
- - - - -
2b053755 by Tamar Christina at 2025-07-15T16:56:39-04:00
rts: Cleanup merge resolution residue in lookupSymbolInDLL_PEi386 and make safe without dependent
- - - - -
e8acd2e7 by Wen Kokke at 2025-07-16T08:37:04-04:00
Remove the `profile_id` parameter from various RTS functions.
Various RTS functions took a `profile_id` parameter, intended to be used to
distinguish parallel heap profile breakdowns (e.g., `-hT` and `-hi`). However,
this feature was never implemented and the `profile_id` parameter was set to 0
throughout the RTS. This commit removes the parameter but leaves the hardcoded
profile ID in the functions that emit the encoded eventlog events as to not
change the protocol.
The affected functions are `traceHeapProfBegin`, `postHeapProfBegin`,
`traceHeapProfSampleString`, `postHeapProfSampleString`,
`traceHeapProfSampleCostCentre`, and `postHeapProfSampleCostCentre`.
- - - - -
76d392a2 by Wen Kokke at 2025-07-16T08:37:04-04:00
Make `traceHeapProfBegin` an init event.
- - - - -
bbaa44a7 by Peng Fan at 2025-07-16T16:50:42-04:00
NCG/LA64: Support finer-grained DBAR hints
For LA664 and newer uarchs, they have made finer granularity hints
available:
Bit4: ordering or completion (0: completion, 1: ordering)
Bit3: barrier for previous read (0: true, 1: false)
Bit2: barrier for previous write (0: true, 1: false)
Bit1: barrier for succeeding read (0: true, 1: false)
Bit0: barrier for succeeding write (0: true, 1: false)
And not affect the existing models because other hints are treated
as 'dbar 0' there.
- - - - -
7da86e16 by Andreas Klebinger at 2025-07-16T16:51:25-04:00
Disable -fprof-late-overloaded-calls for join points.
Currently GHC considers cost centres as destructive to
join contexts. Or in other words this is not considered valid:
join f x = ...
in
... -> scc<tick> jmp
This makes the functionality of `-fprof-late-overloaded-calls` not feasible
for join points in general. We used to try to work around this by putting the
ticks on the rhs of the join point rather than around the jump. However beyond
the loss of accuracy this was broken for recursive join points as we ended up
with something like:
rec-join f x = scc<tick> ... jmp f x
Which similarly is not valid as the tick once again destroys the tail call.
One might think we could limit ourselves to non-recursive tail calls and do
something clever like:
join f x = scc<tick> ...
in ... jmp f x
And sometimes this works! But sometimes the full rhs would look something like:
join g x = ....
join f x = scc<tick> ... -> jmp g x
Which, would again no longer be valid. I believe in the long run we can make
cost centre ticks non-destructive to join points. Or we could keep track of
where we are/are not allowed to insert a cost centre. But in the short term I will
simply disable the annotation of join calls under this flag.
- - - - -
7ee22fd5 by ARATA Mizuki at 2025-07-17T06:05:30-04:00
x86 NCG: Better lowering for shuffleFloatX4# and shuffleDoubleX2#
The new implementation
* make use of specialized instructions like (V)UNPCK{L,H}{PS,PD}, and
* do not require -mavx.
Close #26096
Co-authored-by: sheaf
jappie unkown input: jappie
we confirmed later this was due to lack of \n matching.
Anyway movnig on to more unexpected stuff:
```haskell
main :: IO ()
main = do
interact (concatMap interaction . lines)
get's stuck forever. actually `^D` (ctrl+d) unstucks it and runs all input as expected. for example you can get: ```
sdfkds fakdsf unkown input: sdfkdsunkown input: fakdsf
This program works!
```haskell
interaction :: String -> String
interaction "jappie" = "hi \n"
interaction "jakob" = "hello \n"
interaction x = "unkown input: " <> x <> "\n"
main :: IO ()
main = do
interact (concatMap interaction . lines)
the reason is that linebuffering is set for both in and output by default. so lines eats the input lines, and all the \n postfixes make sure the buffer is put out. - - - - - 9fa590a6 by Zubin Duggal at 2025-07-17T06:07:03-04:00 fetch_gitlab: Ensure we copy users_guide.pdf and Haddock.pdf to the release docs directory Fixes #24093 - - - - - cc650b4b by Andrew Lelechenko at 2025-07-17T12:30:24-04:00 Add Data.List.NonEmpty.mapMaybe As per https://github.com/haskell/core-libraries-committee/issues/337 - - - - - 360fa82c by Duncan Coutts at 2025-07-17T12:31:14-04:00 base: Deprecate GHC.Weak.Finalize.runFinalizerBatch https://github.com/haskell/core-libraries-committee/issues/342 - - - - - f4e8466c by Alan Zimmerman at 2025-07-17T12:31:55-04:00 EPA: Update exact printing based on GHC 9.14 tests As a result of migrating the GHC ghc-9.14 branch tests to ghc-exactprint in https://github.com/alanz/ghc-exactprint/tree/ghc-9.14, a couple of discrepancies were picked up - The opening paren for a DefaultDecl was printed in the wrong place - The import declaration level specifiers were not printed. This commit adds those fixes, and some tests for them. The tests brought to light that the ImportDecl ppr instance had not been updated for level specifiers, so it updates that too. - - - - - 8b731e3c by Matthew Pickering at 2025-07-21T13:36:43-04:00 level imports: Fix infinite loop with cyclic module imports I didn't anticipate that downsweep would run before we checked for cyclic imports. Therefore we need to use the reachability function which handles cyclic graphs. Fixes #26087 - - - - - d751a9f1 by Pierre Thierry at 2025-07-21T13:37:28-04:00 Fix documentation about deriving from generics - - - - - f8d9d016 by Andrew Lelechenko at 2025-07-22T21:13:28-04:00 Fix issues with toRational for types capable to represent infinite and not-a-number values This commit fixes all of the following pitfalls:
toRational (read "Infinity" :: Double) 179769313486231590772930519078902473361797697894230657273430081157732675805500963132708477322407536021120113879871393357658789768814416622492847430639474124377767893424865485276302219601246094119453082952085005768838150682342462881473913110540827237163350510684586298239947245938479716304835356329624224137216 % 1 toRational (read "NaN" :: Double) 269653970229347386159395778618353710042696546841345985910145121736599013708251444699062715983611304031680170819807090036488184653221624933739271145959211186566651840137298227914453329401869141179179624428127508653257226023513694322210869665811240855745025766026879447359920868907719574457253034494436336205824 % 1
realToFrac (read "NaN" :: Double) -- With -O0 Infinity realToFrac (read "NaN" :: Double) -- With -O1 NaN
realToFrac (read "NaN" :: Double) :: CDouble Infinity realToFrac (read "NaN" :: CDouble) :: Double Infinity
Implements https://github.com/haskell/core-libraries-committee/issues/338 - - - - - 5dabc718 by Zubin Duggal at 2025-07-22T21:14:10-04:00 haddock: Don't warn about missing link destinations for derived names. Fixes #26114 - - - - - 9c3a0937 by Matthew Pickering at 2025-07-22T21:14:52-04:00 template haskell: use a precise condition when implicitly lifting Implicit lifting corrects a level error by replacing references to `x` with `$(lift x)`, therefore you can use a level `n` binding at level `n + 1`, if it can be lifted. Therefore, we now have a precise check that the use level is 1 more than the bind level. Before this bug was not observable as you only had 0 and 1 contexts but it is easily evident when using explicit level imports. Fixes #26088 - - - - - 5144b22f by Andreas Klebinger at 2025-07-22T21:15:34-04:00 Add since tag and more docs for do-clever-arg-eta-expansion Fixes #26113 - - - - - c865623b by Andreas Klebinger at 2025-07-22T21:15:34-04:00 Add since tag for -fexpose-overloaded-unfoldings Fixes #26112 - - - - - 49a44ab7 by Simon Hengel at 2025-07-23T17:59:55+07:00 Refactor GHC.Driver.Errors.printMessages - - - - - 84711c39 by Simon Hengel at 2025-07-23T18:27:34+07:00 Respect `-fdiagnostics-as-json` for error messages from pre-processors (fixes #25480) - - - - - d046b5ab by Simon Hengel at 2025-07-24T06:12:05-04:00 Include the rendered message in -fdiagnostics-as-json output This implements #26173. - - - - - d2b89603 by Ben Gamari at 2025-07-24T06:12:47-04:00 rts/Interpreter: Factor out ctoi tuple info tables into data Instead of a massive case let's put this into data which we can reuse elsewhere. - - - - - 4bc78496 by Sebastian Graf at 2025-07-24T16:19:34-04:00 CprAnal: Detect recursive newtypes (#25944) While `cprTransformDataConWork` handles recursive data con workers, it did not detect the case when a newtype is responsible for the recursion. This is now detected in the `Cast` case of `cprAnal`. The same reproducer made it clear that `isRecDataCon` lacked congruent handling for `AppTy` and `CastTy`, now fixed. Furthermore, the new repro case T25944 triggered this bug via an infinite loop in `cprFix`, caused by the infelicity in `isRecDataCon`. While it should be much less likely to trigger such an infinite loop now that `isRecDataCon` has been fixed, I made sure to abort the loop after 10 iterations and emitting a warning instead. Fixes #25944. - - - - - 0a583689 by Sylvain Henry at 2025-07-24T16:20:26-04:00 STM: don't create a transaction in the rhs of catchRetry# (#26028) We don't need to create a transaction for the rhs of (catchRetry#) because contrary to the lhs we don't need to abort it on retry. Moreover it is particularly harmful if we have code such as (#26028): let cN = readTVar vN >> retry tree = c1 `orElse` (c2 `orElse` (c3 `orElse` ...)) atomically tree Because it will stack transactions for the rhss and the read-sets of all the transactions will be iteratively merged in O(n^2) after the execution of the most nested retry. - - - - - a49eca26 by Simon Peyton Jones at 2025-07-25T09:49:58+01:00 Renaming around predicate types .. we were (as it turned out) abstracting over type-class selectors in SPECIALISATION rules! Wibble isEqPred - - - - - f80375dd by Simon Peyton Jones at 2025-07-25T09:49:58+01:00 Refactor of Specialise.hs This patch just tidies up `specHeader` a bit, removing one of its many results, and adding some comments. No change in behaviour. Also add a few more `HasDebugCallStack` contexts. - - - - - 1bd12371 by Simon Peyton Jones at 2025-07-25T09:49:58+01:00 Improve treatment of SPECIALISE pragmas -- again! This MR does another major refactor of the way that SPECIALISE pragmas work, to fix #26115, #26116, #26117. * We now /always/ solve forall-constraints in an all-or-nothing way. See Note [Solving a Wanted forall-constraint] in GHC.Tc.Solver.Solve This means we might have unsolved quantified constraints, which need to be reported. See `inert_insts` in `getUnsolvedInerts`. * I refactored the short-cut solver for type classes to work by recursively calling the solver rather than by having a little baby solver that kept being not clever enough. See Note [Shortcut solving] in GHC.Tc.Solver.Dict * I totally rewrote the desugaring of SPECIALISE pragmas, again. The new story is in Note [Desugaring new-form SPECIALISE pragmas] in GHC.HsToCore.Binds Both old-form and new-form SPECIALISE pragmas now route through the same function `dsSpec_help`. The tricky function `decomposeRuleLhs` is now used only for user-written RULES, not for SPECIALISE pragmas. * I improved `solveOneFromTheOther` to account for rewriter sets. Previously it would solve a non-rewritten dict from a rewritten one. For equalities we were already dealing with this, in Some incidental refactoring * A small refactor: `ebv_tcvs` in `EvBindsBar` now has a list of coercions, rather than a set of tyvars. We just delay taking the free vars. * GHC.Core.FVs.exprFVs now returns /all/ free vars. Use `exprLocalFVs` for Local vars. Reason: I wanted another variant for /evidence/ variables. * Ues `EvId` in preference to `EvVar`. (Evidence variables are always Ids.) Rename `isEvVar` to `isEvId`. * I moved `inert_safehask` out of `InertCans` and into `InertSet` where it more properly belongs. Compiler-perf changes: * There was a palpable bug (#26117) which this MR fixes in newWantedEvVar, which bypassed all the subtle overlapping-Given and shortcutting logic. (See the new `newWantedEvVar`.) Fixing this but leads to extra dictionary bindings; they are optimised away quickly but they made CoOpt_Read allocate 3.6% more. * Hpapily T15164 improves. * The net compiler-allocation change is 0.0% Metric Decrease: T15164 Metric Increase: CoOpt_Read T12425 - - - - - 953fd8f1 by Simon Peyton Jones at 2025-07-25T09:49:58+01:00 Solve forall-constraints immediately, or not at all This MR refactors the constraint solver to solve forall-constraints immediately, rather than emitting an implication constraint to be solved later. The most immediate motivation was that when solving quantified constraints in SPECIALISE pragmas, we really really don't want to leave behind half- solved implications. Also it's in tune with the approach of the new short-cut solver, which recursively invokes the solver. It /also/ saves quite a bit of plumbing; e.g - The `wl_implics` field of `WorkList` is gone, - The types of `solveSimpleWanteds` and friends are simplified. - An EvFun contains binding, rather than an EvBindsVar ref-cell that will in the future contain bindings. That makes `evVarsOfTerm` simpler. Much nicer. It also improves error messages a bit. All described in Note [Solving a Wanted forall-constraint] in GHC.Tc.Solver.Solve. One tiresome point: in the tricky case of `inferConstraintsCoerceBased` we make a forall-constraint. This we /do/ want to partially solve, so we can infer a suitable context. (I'd be quite happy to force the user to write a context, bt I don't want to change behavior.) So we want to generate an /implication/ constraint in `emitPredSpecConstraints` rather than a /forall-constraint/ as we were doing before. Discussed in (WFA3) of the above Note. Incidental refactoring * `GHC.Tc.Deriv.Infer.inferConstraints` was consulting the state monad for the DerivEnv that the caller had just consulted. Nicer to pass it as an argument I think, so I have done that. No change in behaviour. - - - - - 6921ab42 by Simon Peyton Jones at 2025-07-25T09:49:58+01:00 Remove duplicated code in Ast.hs for evTermFreeVars This is just a tidy up. - - - - - 1165f587 by Simon Peyton Jones at 2025-07-25T09:49:58+01:00 Small tc-tracing changes only - - - - - 0776ffe0 by Simon Hengel at 2025-07-26T04:54:20-04:00 Respect `-fdiagnostics-as-json` for core diagnostics (see #24113) - - - - - cc1116e0 by Andrew Lelechenko at 2025-07-26T04:55:01-04:00 docs: add since pragma to Data.List.NonEmpty.mapMaybe - - - - - 9a98ce6e by Simon Hengel at 2025-07-27T15:12:07+07:00 Don't use MCDiagnostic for `ghcExit` This changes the error message of `ghcExit` from ``` <no location info>: error: Compilation had errors ``` to ``` Compilation had errors ``` - - - - - a800b480 by Simon Hengel at 2025-07-27T15:12:07+07:00 Respect `-fdiagnostics-as-json` for driver diagnostics (see #24113) - - - - - 74b8e7d5 by Simon Hengel at 2025-07-27T15:12:11+07:00 Remove -ddump-json (fixes #24113) - - - - - 366 changed files: - .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py - compiler/GHC.hs - compiler/GHC/Builtin/primops.txt.pp - 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/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Map/Expr.hs - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Core/Opt/Monad.hs - compiler/GHC/Core/Opt/OccurAnal.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/Specialise.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/Ppr.hs - compiler/GHC/Core/Predicate.hs - compiler/GHC/Core/Rules.hs - compiler/GHC/Core/Subst.hs - compiler/GHC/Core/Tidy.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Core/Unfold/Make.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/CoreToIface.hs - compiler/GHC/CoreToStg.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Driver/Config.hs - compiler/GHC/Driver/Errors.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Session.hs - + compiler/GHC/Driver/Session/Inspect.hs - compiler/GHC/Hs/ImpExp.hs - compiler/GHC/HsToCore.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/HsToCore/Ticks.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Tidy.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Linker/Loader.hs - compiler/GHC/Linker/Types.hs - compiler/GHC/Parser.y - compiler/GHC/Rename/Splice.hs - compiler/GHC/Runtime/Debugger/Breakpoints.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Eval/Types.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/Runtime/Interpreter/Types.hs - compiler/GHC/Stg/BcPrep.hs - compiler/GHC/Stg/FVs.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToJS/Prim.hs - compiler/GHC/SysTools/Process.hs - compiler/GHC/SysTools/Tasks.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/Gen/Splice.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/Breakpoint.hs - compiler/GHC/Types/Error.hs - compiler/GHC/Types/Tickish.hs - compiler/GHC/Types/Var.hs - compiler/GHC/Unit/Module/Graph.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Utils/Error.hs - compiler/GHC/Utils/Logger.hs - compiler/ghc.cabal.in - configure.ac - docs/users_guide/9.14.1-notes.rst - docs/users_guide/debugging.rst - + docs/users_guide/diagnostics-as-json-schema-1_2.json - docs/users_guide/eventlog-formats.rst - docs/users_guide/exts/doandifthenelse.rst - docs/users_guide/exts/ffi.rst - docs/users_guide/ghci.rst - docs/users_guide/profiling.rst - docs/users_guide/using-optimisation.rst - docs/users_guide/using.rst - ghc/GHCi/UI.hs - hadrian/src/Oracles/Flag.hs - hadrian/src/Rules/Generate.hs - hadrian/src/Settings/Builders/Cabal.hs - hadrian/src/Settings/Packages.hs - hadrian/src/Settings/Program.hs - libraries/Win32 - libraries/array - libraries/base/base.cabal.in - libraries/base/changelog.md - libraries/base/src/Control/Exception.hs - libraries/base/src/Data/List/NonEmpty.hs - libraries/base/src/GHC/Generics.hs - libraries/base/src/GHC/Weak/Finalize.hs - libraries/binary - libraries/deepseq - libraries/directory - libraries/exceptions - libraries/filepath - libraries/ghc-boot-th/ghc-boot-th.cabal.in - libraries/ghc-boot/ghc-boot.cabal.in - libraries/ghc-compact/GHC/Compact.hs - libraries/ghc-compact/GHC/Compact/Serialized.hs - libraries/ghc-compact/ghc-compact.cabal - libraries/ghc-experimental/ghc-experimental.cabal.in - + libraries/ghc-experimental/src/System/Mem/Experimental.hs - libraries/ghc-heap/GHC/Exts/Heap/Closures.hs - libraries/ghc-heap/GHC/Exts/Heap/FFIClosures_ProfilingDisabled.hsc - libraries/ghc-heap/GHC/Exts/Heap/FFIClosures_ProfilingEnabled.hsc - libraries/ghc-heap/GHC/Exts/Heap/Utils.hsc - libraries/ghc-heap/ghc-heap.cabal.in - libraries/ghc-heap/tests/parse_tso_flags.hs - libraries/ghc-internal/ghc-internal.cabal.in - + libraries/ghc-internal/src/GHC/Internal/AllocationLimitHandler.hs - libraries/ghc-internal/src/GHC/Internal/Base.hs - libraries/ghc-internal/src/GHC/Internal/Exception/Type.hs - libraries/ghc-internal/src/GHC/Internal/Float.hs - libraries/ghc-internal/src/GHC/Internal/List.hs - libraries/ghc-internal/src/GHC/Internal/Real.hs - libraries/ghc-internal/src/GHC/Internal/System/IO.hs - libraries/ghc-prim/changelog.md - libraries/ghc-prim/ghc-prim.cabal - + libraries/ghci/GHCi/Debugger.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/Run.hs - libraries/ghci/ghci.cabal.in - libraries/haskeline - libraries/hpc - libraries/os-string - libraries/parsec - libraries/process - libraries/semaphore-compat - libraries/stm - libraries/template-haskell/template-haskell.cabal.in - libraries/terminfo - libraries/text - libraries/unix - m4/find_ld.m4 - mk/get-win32-tarballs.py - + rts/AllocArray.c - + rts/AllocArray.h - rts/Disassembler.c - rts/Heap.c - rts/Interpreter.c - rts/Interpreter.h - rts/Prelude.h - rts/PrimOps.cmm - rts/ProfHeap.c - rts/RaiseAsync.c - rts/RetainerSet.c - rts/RtsStartup.c - rts/RtsSymbols.c - rts/RtsUtils.c - rts/STM.c - rts/Schedule.c - rts/StgMiscClosures.cmm - rts/ThreadLabels.c - rts/Threads.c - rts/Trace.c - rts/Trace.h - rts/Weak.c - rts/eventlog/EventLog.c - rts/eventlog/EventLog.h - rts/external-symbols.list.in - rts/include/Rts.h - rts/include/rts/Bytecodes.h - rts/include/rts/Constants.h - rts/include/rts/prof/CCS.h - rts/include/rts/storage/Closures.h - rts/include/rts/storage/GC.h - rts/include/rts/storage/Heap.h - rts/include/rts/storage/TSO.h - rts/include/stg/MiscClosures.h - rts/linker/LoadArchive.c - rts/linker/PEi386.c - rts/rts.cabal - rts/sm/NonMoving.c - rts/sm/NonMoving.h - rts/sm/NonMovingAllocate.c - rts/sm/Sanity.c - rts/sm/Storage.c - testsuite/tests/backpack/cabal/bkpcabal08/bkpcabal08.stdout - testsuite/tests/corelint/T21115b.stderr - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - + testsuite/tests/cpranal/sigs/T25944.hs - + testsuite/tests/cpranal/sigs/T25944.stderr - testsuite/tests/cpranal/sigs/all.T - testsuite/tests/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/T16167.stderr - − testsuite/tests/driver/T16167.stdout - testsuite/tests/driver/all.T - testsuite/tests/driver/json.stderr - testsuite/tests/driver/json2.stderr - − testsuite/tests/driver/json_dump.hs - − testsuite/tests/driver/json_dump.stderr - testsuite/tests/driver/json_warn.stderr - testsuite/tests/driver/recomp015/all.T - + testsuite/tests/ghci.debugger/scripts/T26042b.hs - + testsuite/tests/ghci.debugger/scripts/T26042b.script - + testsuite/tests/ghci.debugger/scripts/T26042b.stdout - + testsuite/tests/ghci.debugger/scripts/T26042c.hs - + testsuite/tests/ghci.debugger/scripts/T26042c.script - + testsuite/tests/ghci.debugger/scripts/T26042c.stdout - + testsuite/tests/ghci.debugger/scripts/T26042d.hs - + testsuite/tests/ghci.debugger/scripts/T26042d.script - + testsuite/tests/ghci.debugger/scripts/T26042d.stdout - + testsuite/tests/ghci.debugger/scripts/T26042e.hs - + testsuite/tests/ghci.debugger/scripts/T26042e.script - + testsuite/tests/ghci.debugger/scripts/T26042e.stdout - + testsuite/tests/ghci.debugger/scripts/T26042f.hs - + testsuite/tests/ghci.debugger/scripts/T26042f.script - + testsuite/tests/ghci.debugger/scripts/T26042f1.stderr - + testsuite/tests/ghci.debugger/scripts/T26042f1.stdout - + testsuite/tests/ghci.debugger/scripts/T26042f2.stdout - + testsuite/tests/ghci.debugger/scripts/T26042g.hs - + testsuite/tests/ghci.debugger/scripts/T26042g.script - + testsuite/tests/ghci.debugger/scripts/T26042g.stdout - testsuite/tests/ghci.debugger/scripts/all.T - testsuite/tests/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_fail/T26176.hs - + testsuite/tests/indexed-types/should_fail/T26176.stderr - testsuite/tests/indexed-types/should_fail/all.T - testsuite/tests/interface-stability/base-exports.stdout - testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs - testsuite/tests/interface-stability/base-exports.stdout-mingw32 - testsuite/tests/interface-stability/base-exports.stdout-ws-32 - testsuite/tests/interface-stability/ghc-experimental-exports.stdout - testsuite/tests/interface-stability/ghc-experimental-exports.stdout-mingw32 - testsuite/tests/interface-stability/ghc-prim-exports.stdout - testsuite/tests/interface-stability/ghc-prim-exports.stdout-mingw32 - + testsuite/tests/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/T22859.hs - + testsuite/tests/rts/T22859.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/T14010.hs - 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 - utils/check-exact/ExactPrint.hs - utils/ghc-toolchain/src/GHC/Toolchain/Tools/Link.hs - utils/haddock/CHANGES.md - utils/haddock/haddock-api/haddock-api.cabal - utils/haddock/haddock-api/src/Haddock/Interface/AttachInstances.hs - utils/haddock/haddock-api/src/Haddock/Interface/Create.hs - utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs - utils/haddock/haddock-api/src/Haddock/InterfaceFile.hs - utils/haddock/haddock-api/src/Haddock/Types.hs - utils/haddock/haddock-library/haddock-library.cabal - utils/haddock/haddock-test/haddock-test.cabal - utils/haddock/haddock-test/src/Test/Haddock/Config.hs - utils/haddock/haddock.cabal - utils/haddock/html-test/ref/Bug1004.html - + utils/haddock/html-test/ref/Bug25739.html - + utils/haddock/html-test/src/Bug25739.hs - utils/hsc2hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/49aaf5ad6781e91e717d07c95118dda... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/49aaf5ad6781e91e717d07c95118dda... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Simon Hengel (@sol)