[Git][ghc/ghc][wip/9.4.6-backports] 40 commits: Handle top-level Addr# literals in the bytecode compiler

Zubin (@wz1000) gitlab at gitlab.haskell.org
Thu Aug 3 20:45:37 UTC 2023



Zubin pushed to branch wip/9.4.6-backports at Glasgow Haskell Compiler / GHC


Commits:
09dde710 by Alexis King at 2023-08-04T01:57:14+05:30
Handle top-level Addr# literals in the bytecode compiler

Fixes #22376.

(cherry picked from commit 26243de1e3716886161d79918af9359f7639314b)

- - - - -
cfab991e by Andreas Klebinger at 2023-08-04T02:01:36+05:30
Fix some correctness issues around tag inference when targeting the bytecode generator.

* Let binders are now always assumed untagged for bytecode.
* Imported referenced are now always assumed to be untagged for bytecode.

Fixes #22840

(cherry picked from commit d6411d6cddb8c94c74e5834f0199370d189d31a2)

- - - - -
88b7bb66 by Ryan Scott at 2023-08-04T02:01:36+05:30
Restore mingwex dependency on Windows

This partially reverts some of the changes in !9475 to make `base` and
`ghc-prim` depend on the `mingwex` library on Windows. It also restores the
RTS's stubs for `mingwex`-specific symbols such as `_lock_file`.

This is done because the C runtime provides `libmingwex` nowadays, and
moreoever, not linking against `mingwex` requires downstream users to link
against it explicitly in difficult-to-predict circumstances. Better to always
link against `mingwex` and prevent users from having to do the guesswork
themselves.

See https://gitlab.haskell.org/ghc/ghc/-/merge_requests/10360#note_495873 for
the discussion that led to this.

(cherry picked from commit 2b1a4abe3f5935ca58c84c6073e6bdfa5160832f)
(cherry picked from commit ff73fc3fc40399795bd0625f437e201d8d30280a)

- - - - -
4382d8d1 by Ryan Scott at 2023-08-04T02:01:36+05:30
RtsSymbols.c: Remove mingwex symbol stubs

As of !9475, the RTS now links against `ucrt` instead of `msvcrt` on Windows,
which means that the RTS no longer needs to declare stubs for the `__mingw_*`
family of symbols. Let's remove these stubs to avoid confusion.

Fixes #23309.

(cherry picked from commit 289547580b6f2808ee123f106c3118b716486d5b)
(cherry picked from commit e41704b2c27ccc2f0b028c9569a654ff21da8548)

- - - - -
29b069c3 by Ben Gamari at 2023-08-04T02:01:36+05:30
nonmoving: Account for mutator allocations in bytes_allocated

Previously we failed to account direct mutator allocations into the
nonmoving heap against the mutator's allocation limit and
`cap->total_allocated`. This only manifests during CAF evaluation (since
we allocate the CAF's blackhole directly into the nonmoving heap).

Fixes #23312.

(cherry picked from commit b2cdb7dacc095142e29c0f28a956b7fa97cdb4b1)

- - - - -
aa5ee238 by Moisés Ackerman at 2023-08-04T02:01:36+05:30
Add failing test case for #23492

(cherry picked from commit 6074cc3cda9b9836c784942a1aa7f766fb142787)

- - - - -
da6bb236 by Moisés Ackerman at 2023-08-04T02:01:36+05:30
Use generated src span for catch-all case of record selector functions

This fixes #23492. The problem was that we used the real source span
of the field declaration for the generated catch-all case in the
selector function, in particular in the generated call to
`recSelError`, which meant it was included in the HIE output. Using
`generatedSrcSpan` instead means that it is not included.

(cherry picked from commit 356a269258a50bf67811fe0edb193fc9f82dfad1)

- - - - -
f4f14d4b by Simon Peyton Jones at 2023-08-04T02:01:36+05:30
Transfer DFunId_ness onto specialised bindings

Whether a binding is a DFunId or not has consequences for the `-fdicts-strict`
flag, essentially if we are doing demand analysis for a DFunId then `-fdicts-strict` does
not apply because the constraint solver can create recursive groups of dictionaries.

In #22549 this was fixed for the "normal" case, see
Note [Do not strictify the argument dictionaries of a dfun].
However the loop still existed if the DFunId was being specialised.

The problem was that the specialiser would specialise a DFunId and
turn it into a VanillaId and so the demand analyser didn't know to
apply special treatment to the binding anymore and the whole recursive
group was optimised to bottom.

The solution is to transfer over the DFunId-ness of the binding in the specialiser so
that the demand analyser knows not to apply the `-fstrict-dicts`.

Fixes #22549

(cherry picked from commit 3b0ea4809d92581a10e0e501a6fbd7339e8922bf)
(cherry picked from commit 6cd0f8079525fac92bbd6e0c1dbabc3180f8887b)

- - - - -
3587ead2 by Ryan Scott at 2023-08-04T02:01:37+05:30
Fix type variable substitution in gen_Newtype_fam_insts

Previously, `gen_Newtype_fam_insts` was substituting the type variable binders
of a type family instance using `substTyVars`, which failed to take type
variable dependencies into account. There is similar code in
`GHC.Tc.TyCl.Class.tcATDefault` that _does_ perform this substitution properly,
so this patch:

1. Factors out this code into a top-level `substATBndrs` function, and
2. Uses `substATBndrs` in `gen_Newtype_fam_insts`.

Fixes #23329.

(cherry picked from commit e8b72ff6e4aee1f889a9168df57bb1b00168fd21)
(cherry picked from commit eaadcaa7ca2b7bb1d4d214339092dd9e6df12a96)

- - - - -
d8c5cf93 by Ben Gamari at 2023-08-04T02:01:37+05:30
base: Fix incorrect CPP guard

This was guarded on `darwin_HOST_OS` instead of `defined(darwin_HOST_OS)`.

(cherry picked from commit d7ef1704aeba451bd3e0efbdaaab2638ee1f0bc8)

- - - - -
bfa2b5dd by Matthew Pickering at 2023-08-04T02:01:37+05:30
driver: Fix -S with .cmm files

There was an oversight in the driver which assumed that you would always
produce a `.o` file when compiling a .cmm file.

Fixes #23610

(cherry picked from commit 76983a0dca64dfb7e94aea0c4f494921f8513b41)

- - - - -
5b0c6178 by Sebastian Graf at 2023-08-04T02:01:37+05:30
DmdAnal: Unleash demand signatures of free RULE and unfolding binders (#23208)

In #23208 we observed that the demand signature of a binder occuring in a RULE
wasn't unleashed, leading to a transitively used binder being discarded as
absent. The solution was to use the same code path that we already use for
handling exported bindings.

See the changes to `Note [Absence analysis for stable unfoldings and RULES]`
for more details.

I took the chance to factor out the old notion of a `PlusDmdArg` (a pair of a
`VarEnv Demand` and a `Divergence`) into `DmdEnv`, which fits nicely into our
existing framework. As a result, I had to touch quite a few places in the code.

This refactoring exposed a few small bugs around correct handling of bottoming
demand environments. As a result, some strictness signatures now mention uniques
that weren't there before which caused test output changes to T13143, T19969 and
T22112. But these tests compared whole -ddump-simpl listings which is a very
fragile thing to begin with. I changed what exactly they test for based on the
symptoms in the corresponding issues.

There is a single regression in T18894 because we are more conservative around
stable unfoldings now. Unfortunately it is not easily fixed; let's wait until
there is a concrete motivation before invest more time.

Fixes #23208.

(cherry picked from commit c30ac25f7dfaded58bb2ff85d4bffe662e4af8b1)

- - - - -
b287b62b by Gergő Érdi at 2023-08-04T02:01:37+05:30
Fix loop in the interface representation of some `Unfolding` fields

As discovered in #22272, dehydration of the unfolding info of a
recursive definition used to involve a traversal of the definition
itself, which in turn involves traversing the unfolding info. Hence,
a loop.

Instead, we now store enough data in the interface that we can produce
the unfolding info without this traversal. See Note [Tying the 'CoreUnfolding' knot]
for details.

Fixes #22272

Co-authored-by: Simon Peyton Jones <simon.peytonjones at gmail.com>
(cherry picked from commit 3318a340bc2c52a50d155cadd2450883825a7768)

- - - - -
6f0071a0 by Simon Peyton Jones at 2023-08-04T02:01:37+05:30
Refactor the simplifier a bit to fix #22761

The core change in this commit, which fixes #22761, is that

* In a Core rule, ru_rhs is always occ-analysed.

This means adding a couple of calls to occurAnalyseExpr when
building a Rule, in
* GHC.Core.Rules.mkRule
* GHC.Core.Opt.Simplify.Iteration.simplRules

But diagosing the bug made me stare carefully at the code of the
Simplifier, and I ended up doing some only-loosely-related refactoring.

* I think that RULES could be lost because not every code path
  did addBndrRules

* The code around lambdas was very convoluted

It's mainly moving deck chairs around, but I like it more now.

(cherry picked from commit e45eb82830d6de4d09abb548e190be980dd001b4)
(cherry picked from commit e0f3aec8f4537fb75f2b38db0da6b7b52d8d29d6)

- - - - -
8c8d84a2 by Ben Gamari at 2023-08-04T02:01:37+05:30
hadrian: Fix mention of non-existent removeFiles function

Previously Hadrian's bindist Makefile referred to a `removeFiles`
function that was previously defined by the `make` build system. Since
the `make` build system is no longer around, this function is now
undefined. Naturally, make being make, this appears to be silently
ignored instead of producing an error.

Fix this by rewriting it to `rm -f`.

Closes #23373.

(cherry picked from commit c6cf9433e3d41e239265eaeff0fd02e6b45d5427)

- - - - -
a6b9cc2e by Krzysztof Gogolewski at 2023-08-04T02:01:37+05:30
Show an error when we cannot default a concrete tyvar

Fixes #23153

(cherry picked from commit 0da18eb79540181ae9835e73d52ba47ec79fff6b)

- - - - -
86a1d5d8 by Simon Peyton Jones at 2023-08-04T02:01:37+05:30
Look both ways when looking for quantified equalities

When looking up (t1 ~# t2) in the quantified constraints,
check both orientations.  Forgetting this led to #23333.

(cherry picked from commit 40c7daed0c971e58e86a8189f82f72e9213af8b6)

- - - - -
523da196 by Luite Stegeman at 2023-08-04T02:01:37+05:30
Add PrimCallConv support to GHCi

This adds support for calling Cmm code from bytecode using the native
calling convention, allowing modules that use `foreign import prim`
to be loaded and debugged in GHCi.

This patch introduces a new `PRIMCALL` bytecode instruction and
a helper stack frame `stg_primcall`. The code is based on the
existing functionality for dealing with unboxed tuples in bytecode,
which has been generalised to handle arbitrary calls.

Fixes #22051

(cherry picked from commit b4c14c4ba17b3abf3e7b88e1201ac7ba89fd56c9)

- - - - -
851f5a22 by Luite Stegeman at 2023-08-04T02:01:37+05:30
Add support for sized literals in the bytecode interpreter.

The bytecode interpreter only has branching instructions for
word-sized values. These are used for pattern matching.
Branching instructions for other types (e.g. Int16# or Word8#)
weren't needed, since unoptimized Core or STG never requires
branching on types like this.

It's now possible for optimized STG to reach the bytecode
generator (e.g. fat interface files or certain compiler flag
combinations), which requires dealing with various sized
literals in branches.

This patch improves support for generating bytecode from
optimized STG by adding the following new bytecode
instructions:

    TESTLT_I64
    TESTEQ_I64
    TESTLT_I32
    TESTEQ_I32
    TESTLT_I16
    TESTEQ_I16
    TESTLT_I8
    TESTEQ_I8
    TESTLT_W64
    TESTEQ_W64
    TESTLT_W32
    TESTEQ_W32
    TESTLT_W16
    TESTEQ_W16
    TESTLT_W8
    TESTEQ_W8

Fixes #21945

(cherry picked from commit 28f8c0ebbfe623784988745af75dcf3fdbdd3ca5)

- - - - -
6cec9cc6 by Alexis King at 2023-08-04T02:01:37+05:30
bytecode: Fix bitmaps for BCOs used to tag tuples and prim call args

fixes #23068

(cherry picked from commit bed3a292df532935426987e1f0c5eaa4f605407e)

- - - - -
c39a4602 by Alexis King at 2023-08-04T02:01:37+05:30
Use a uniform return convention in bytecode for unary results

fixes #22958

(cherry picked from commit d85ed900b271109185251cb0494d51048a4cf213)
(cherry picked from commit 74b8e5bd79957786b869183a19f747f2b73294a0)

- - - - -
96742732 by Ben Gamari at 2023-08-04T02:01:37+05:30
testsuite: Add tests for #23146

Both lifted and unlifted variants.

(cherry picked from commit 33cf4659f209ef8e97be188279216a2f4fe0cf51)

- - - - -
a3807678 by Ben Gamari at 2023-08-04T02:01:37+05:30
codeGen: Fix some Haddocks

(cherry picked from commit 76727617bccc88d1466ad6dc1442ab8ebb34f79a)

- - - - -
3f728ba8 by Ben Gamari at 2023-08-04T02:01:37+05:30
codeGen: Give proper LFInfo to datacon wrappers

As noted in `Note [Conveying CAF-info and LFInfo between modules]`,
when importing a binding from another module we must ensure that it gets
the appropriate `LambdaFormInfo` if it is in WHNF to ensure that
references to it are tagged correctly.

However, the implementation responsible for doing this,
`GHC.StgToCmm.Closure.mkLFImported`, only dealt with datacon workers and
not wrappers. This lead to the crash of this program in #23146:

    module B where

    type NP :: [UnliftedType] -> UnliftedType
    data NP xs where
      UNil :: NP '[]

    module A where
    import B

    fieldsSam :: NP xs -> NP xs -> Bool
    fieldsSam UNil UNil = True

    x = fieldsSam UNil UNil

Due to its GADT nature, `UNil` produces a trivial wrapper

    $WUNil :: NP '[]
    $WUNil = UNil @'[] @~(<co:1>)

which is referenced in the RHS of `A.x`. Due to the above-mentioned bug
in `mkLFImported`, the references to `$WUNil` passed to `fieldsSam` were
not tagged. This is problematic as `fieldsSam` expected its arguments to
be tagged as they are unlifted.

The fix is straightforward: extend the logic in `mkLFImported` to cover
(nullary) datacon wrappers as well as workers. This is safe because we
know that the wrapper of a nullary datacon will be in WHNF, even if it
includes equalities evidence (since such equalities are not runtime
relevant).

Thanks to @MangoIV for the great ticket and @alt-romes for his
minimization and help debugging.

Fixes #23146.

(cherry picked from commit 33a8c348cae5fd800c015fd8c2230b8066c7c0a4)

- - - - -
e643f817 by Rodrigo Mesquita at 2023-08-04T02:01:37+05:30
codeGen: Fix LFInfo of imported datacon wrappers

As noted in #23231 and in the previous commit, we were failing to give a
an LFInfo of LFCon to a nullary datacon wrapper from another module,
failing to properly tag pointers which ultimately led to the
segmentation fault in #23146.

On top of the previous commit which now considers wrappers where we
previously only considered workers, we change the order of the guards so
that we check for the arity of the binding before we check whether it is
a constructor. This allows us to
(1) Correctly assign `LFReEntrant` to imported wrappers whose worker was
nullary, which we previously would fail to do
(2) Remove the `isNullaryRepDataCon` predicate:
    (a) which was previously wrong, since it considered wrappers whose
    workers had zero-width arguments to be non-nullary and would fail to
    give `LFCon` to them
    (b) is now unnecessary, since arity == 0 guarantees
        - that the worker takes no arguments at all
        - and the wrapper takes no arguments and its RHS must be an
          application of the worker to zero-width-args only.
        - we lint these two items with an assertion that the datacon
          `hasNoNonZeroWidthArgs`

We also update `isTagged` to use the new logic in determining the
LFInfos of imported Ids.

The creation of LFInfos for imported Ids and this detail are explained
in Note [The LFInfo of Imported Ids].

Note that before the patch to those issues we would already consider these
nullary wrappers to have `LFCon` lambda form info; but failed to re-construct
that information in `mkLFImported`

Closes #23231, #23146

(I've additionally batched some fixes to documentation I found while
investigating this issue)

(cherry picked from commit 2fc18e9e784ccc775db8b06a5d10986588cce74a)

- - - - -
63fcecfb by Ben Gamari at 2023-08-04T02:01:37+05:30
rts: Ensure that pinned allocations respect block size

Previously, it was possible for pinned, aligned allocation requests to
allocate beyond the end of the pinned accumulator block. Specifically,
we failed to account for the padding needed to achieve the requested
alignment in the "large object" check. With large alignment requests,
this can result in the allocator using the capability's pinned object
accumulator block to service a request which is larger than
`PINNED_EMPTY_SIZE`.

To fix this we reorganize `allocatePinned` to consistently account for
the alignment padding in all large object checks. This is a bit subtle
as we must handle the case of a small allocation request filling the
accumulator block, as well as large requests.

Fixes #23400.

(cherry picked from commit fd8c57694a00f6359bd66365f1284388c869ac60)

- - - - -
e250bb23 by Ben Gamari at 2023-08-04T02:01:38+05:30
testsuite: Add test for #23400

(cherry picked from commit 98185d5212fb0464dcbcca0ca2c33326a7a002e8)

- - - - -
51e96e2e by Bryan Richter at 2023-08-04T02:01:38+05:30
Add missing void prototypes to rts functions

See #23561.

(cherry picked from commit 82ac6bf113526f61913943b911089534705984fb)

- - - - -
d4dcaea1 by Ben Gamari at 2023-08-04T02:01:38+05:30
Define FFI_GO_CLOSURES

The libffi shipped with Apple's XCode toolchain does not contain a
definition of the FFI_GO_CLOSURES macro, despite containing references
to said macro. Work around this by defining the macro, following the
model of a similar workaround in OpenJDK [1].

[1] https://github.com/openjdk/jdk17u-dev/pull/741/files

(cherry picked from commit 8b35e8caafeeccbf06b7faa70e807028a3f0ff43)

- - - - -
c57f41bd by Ben Gamari at 2023-08-04T02:01:38+05:30
rts/Trace: Ensure that debugTrace arguments are used

As debugTrace is a macro we must take care to ensure that
the fact is clear to the compiler lest we see warnings.

(cherry picked from commit 7c7d1f66d35f73a2faa898a33aa80cd276159dc2)

- - - - -
cf831d01 by Ben Gamari at 2023-08-04T02:01:38+05:30
rts: Various warnings fixes

(cherry picked from commit cb92051e3d85575ff6abd753c9b135930cc50cf8)

- - - - -
4a7cd6df by Matthew Craven at 2023-08-04T02:01:38+05:30
StgToCmm: Upgrade -fcheck-prim-bounds behavior

Fixes #21054. Additionally, we can now check for range overlap
when generating Cmm for primops that use memcpy internally.

(cherry picked from commit 65a442fccd081d9370ae4ee4e74f116139b5c2c8)

- - - - -
96327cf1 by Ben Gamari at 2023-08-04T02:01:38+05:30
hadrian: Ensure that way-flags are passed to CC

Previously the way-specific compilation flags (e.g. `-DDEBUG`,
`-DTHREADED_RTS`) would not be passed to the CC invocations. This meant
that C dependency files would not correctly reflect
dependencies predicated on the way, resulting in the rather
painful #23554.

Closes #23554.

(cherry picked from commit cca74dab6809f8cf7ffc2ec9df689e06aa425110)

- - - - -
04be0b92 by Ben Gamari at 2023-08-04T02:01:38+05:30
codeGen: Ensure that array reads have necessary barriers

This was the cause of #23541.

(cherry picked from commit 453c0531f2edf49b75c73bc45944600d8d7bf767)

- - - - -
2808d6d3 by Ben Gamari at 2023-08-04T02:01:38+05:30
codeGen: Ensure that TSAN is aware of writeArray# write barriers

By using a proper release store instead of a fence.

(cherry picked from commit aca20a5d4fde1c6429c887624bb95c9b54b7af73)

- - - - -
83ac30a0 by Ben Gamari at 2023-08-04T02:01:38+05:30
rts/win32: Ensure reliability of IO manager shutdown

When the Win32 threaded IO manager shuts down, `ioManagerDie` sends an
`IO_MANAGER_DIE` event to the IO manager thread using the
`io_manager_event` event object. Finally, it will closes the event object,
and invalidate `io_manager_event`.

Previously, `readIOManagerEvent` would see that `io_manager_event` is
invalid and return `0`, suggesting that everything is right with the
world. This meant that if `ioManagerDie` invalidated the handle before
the event manager was blocked on the event we would end up in a
situation where the event manager would never realize it was asked to
shut down.

Fix this by ensuring that `readIOManagerEvent` instead returns
`IO_MANAGER_DIE` when we detect that the event object has been
invalidated by `ioManagerDie`.

Fixes #23691.

(cherry picked from commit 6448f0c0b42e482ae514088c1c15ad6110be231f)

- - - - -
b5f9b045 by Ben Gamari at 2023-08-04T02:01:38+05:30
linker/PEi386: Don't sign-extend symbol section number

Previously we incorrectly interpreted PE section numbers as signed
values. However, this isn't the case; rather, it's an unsigned 16-bit number
with a few special bit-patterns (0xffff and 0xfffe). This resulted in #22941
as the linker would conclude that the sections were invalid.

Fixing this required quite a bit of refactoring.

Closes #22941.

(cherry picked from commit 9a284cd594715d9c6a4d7f43548215f1663691fa)

- - - - -
4c008f3c by Zubin Duggal at 2023-08-04T02:01:38+05:30
Bump submodule: process 1.6.17.0 (#23760)

- - - - -
4c77b98a by Zubin Duggal at 2023-08-04T02:01:38+05:30
testsuite: accept new notes output

- - - - -
ab72659a by sheaf at 2023-08-04T02:05:36+05:30
Typecheck remaining ValArgs in rebuildHsApps

This patch refactors hasFixedRuntimeRep_remainingValArgs, renaming it
to tcRemainingValArgs. The logic is moved to rebuildHsApps, which
ensures consistent behaviour across tcApp and quickLookArg1/tcEValArg.

This patch also refactors the treatment of stupid theta for data
constructors, changing the place we drop stupid theta arguments
from dsConLike to mkDataConRep (now the datacon wrapper drops these
arguments).

We decided not to implement PHASE 2 of the FixedRuntimeRep plan for
these remaining ValArgs. Future directions are outlined on the wiki:
  https://gitlab.haskell.org/ghc/ghc/-/wikis/Remaining-ValArgs

Fixes #21544 and #21650

(cherry picked from commit 28880828182a32bcb39ce8230965a8bc17aeb218)

- - - - -


30 changed files:

- compiler/GHC/ByteCode/Asm.hs
- compiler/GHC/ByteCode/Instr.hs
- compiler/GHC/ByteCode/Linker.hs
- compiler/GHC/ByteCode/Types.hs
- compiler/GHC/Cmm/CLabel.hs
- compiler/GHC/Cmm/CallConv.hs
- compiler/GHC/Cmm/Parser.y
- compiler/GHC/Core.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Simplify.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Core/Opt/Specialise.hs
- compiler/GHC/Core/Ppr.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/Seq.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/Tidy.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Unfold.hs
- compiler/GHC/Core/Unfold/Make.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/CoreToStg/Prep.hs
- compiler/GHC/Driver/CodeOutput.hs
- compiler/GHC/Driver/Config/Stg/Pipeline.hs
- compiler/GHC/Driver/Pipeline.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/288100967210c563ca4d93d21a70dc5f27b6b6ba...ab72659a5c96ce84e87b08d2af9c43564c87e285

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/288100967210c563ca4d93d21a70dc5f27b6b6ba...ab72659a5c96ce84e87b08d2af9c43564c87e285
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20230803/e32e0b46/attachment-0001.html>


More information about the ghc-commits mailing list