[Git][ghc/ghc][wip/simplifier-tweaks] 40 commits: Refactoring in preparation for lazy skolemisation

Simon Peyton Jones (@simonpj) gitlab at gitlab.haskell.org
Thu Feb 8 14:48:03 UTC 2024



Simon Peyton Jones pushed to branch wip/simplifier-tweaks at Glasgow Haskell Compiler / GHC


Commits:
e2ea933f by Simon Peyton Jones at 2024-02-06T10:12:04-05:00
Refactoring in preparation for lazy skolemisation

* Make HsMatchContext and HsStmtContext be parameterised over the
  function name itself, rather than over the pass.
  See [mc_fun field of FunRhs] in Language.Haskell.Syntax.Expr
    - Replace types
        HsMatchContext GhcPs --> HsMatchContextPs
        HsMatchContext GhcRn --> HsMatchContextRn
        HsMatchContext GhcTc --> HsMatchContextRn  (sic! not Tc)
        HsStmtContext  GhcRn --> HsStmtContextRn
    - Kill off convertHsMatchCtxt

* Split GHC.Tc.Type.BasicTypes.TcSigInfo so that TcCompleteSig (describing
  a complete user-supplied signature) is its own data type.
    - Split TcIdSigInfo(CompleteSig, PartialSig) into
        TcCompleteSig(CSig)
        TcPartialSig(PSig)
    - Use TcCompleteSig in tcPolyCheck, CheckGen
    - Rename types and data constructors:
        TcIdSigInfo         --> TcIdSig
        TcPatSynInfo(TPSI)  --> TcPatSynSig(PatSig)
    - Shuffle around helper functions:
        tcSigInfoName           (moved to GHC.Tc.Types.BasicTypes)
        completeSigPolyId_maybe (moved to GHC.Tc.Types.BasicTypes)
        tcIdSigName             (inlined and removed)
        tcIdSigLoc              (introduced)
    - Rearrange the pattern match in chooseInferredQuantifiers

* Rename functions and types:
    tcMatchesCase         --> tcCaseMatches
    tcMatchesFun          --> tcFunBindMatches
    tcMatchLambda         --> tcLambdaMatches
    tcPats                --> tcMatchPats
    matchActualFunTysRho  --> matchActualFunTys
    matchActualFunTySigma --> matchActualFunTy

* Add HasDebugCallStack constraints to:
    mkBigCoreVarTupTy, mkBigCoreTupTy, boxTy,
    mkPiTy, mkPiTys, splitAppTys, splitTyConAppNoView_maybe

* Use `penv` from the outer context in the inner loop of
  GHC.Tc.Gen.Pat.tcMultiple

* Move tcMkVisFunTy, tcMkInvisFunTy, tcMkScaledFunTys down the file,
  factor out and export tcMkScaledFunTy.

* Move isPatSigCtxt down the file.

* Formatting and comments

Co-authored-by: Vladislav Zavialov <vlad.z.4096 at gmail.com>

- - - - -
f5d3e03c by Andrei Borzenkov at 2024-02-06T10:12:04-05:00
Lazy skolemisation for @a-binders (#17594)

This patch is a preparation for @a-binders implementation.  The main changes are:

* Skolemisation is now prepared to deal with @binders.
  See Note [Skolemisation overview] in GHC.Tc.Utils.Unify.
  Most of the action is in
    - Utils.Unify.matchExpectedFunTys
    - Gen.Pat.tcMatchPats
    - Gen.Expr.tcPolyExprCheck
    - Gen.Binds.tcPolyCheck

Some accompanying refactoring:

* I found that funTyConAppTy_maybe was doing a lot of allocation, and
  rejigged userTypeError_maybe to avoid calling it.

- - - - -
532993c8 by Zubin Duggal at 2024-02-06T10:12:41-05:00
driver: Really don't lose track of nodes when we fail to resolve cycles

This fixes a bug in 8db8d2fd1c881032b1b360c032b6d9d072c11723, where we could lose
track of acyclic components at the start of an unresolved cycle. We now ensure we
never loose track of any of these components.

As T24275 demonstrates, a "cyclic" SCC might not really be a true SCC:

When viewed without boot files, we have a single SCC

```
[REC main:T24275B [main:T24275B {-# SOURCE #-},
                   main:T24275A {-# SOURCE #-}]
     main:T24275A [main:T24275A {-# SOURCE #-}]]
```

But with boot files this turns into

```
[NONREC main:T24275B {-# SOURCE #-} [],
 REC main:T24275B [main:T24275B {-# SOURCE #-},
                   main:T24275A {-# SOURCE #-}]
    main:T24275A {-# SOURCE #-} [main:T24275B],
 NONREC main:T24275A [main:T24275A {-# SOURCE #-}]]
```

Note that this is truly not an SCC, as no nodes are reachable from T24275B.hs-boot.
However, we treat this entire group as a single "SCC" because it seems so when we
analyse the graph without taking boot files into account.

Indeed, we must return a single ResolvedCycle element in the BuildPlan for this
as described in Note [Upsweep].

However, since after resolving this is not a true SCC anymore, `findCycle` fails
to find a cycle and we have a sub-optimal error message as a result.

To handle this, I extended `findCycle` to not assume its input is an SCC, and to
try harder to find cycles in its input.

Fixes #24275

- - - - -
b35dd613 by Zubin Duggal at 2024-02-06T10:13:17-05:00
GHCi: Lookup breakpoint CCs in the correct module

We need to look up breakpoint CCs in the module that the breakpoint
points to, and not the current module.

Fixes #24327

- - - - -
b09e6958 by Zubin Duggal at 2024-02-06T10:13:17-05:00
testsuite: Add test for #24327

- - - - -
569b4c10 by doyougnu at 2024-02-07T03:06:26-05:00
ts: add compile_artifact, ignore_extension flag

In b521354216f2821e00d75f088d74081d8b236810 the testsuite gained the
capability to collect generic metrics. But this assumed that the test
was not linking and producing artifacts and we only wanted to track
object files, interface files, or build artifacts from the compiler
build. However, some backends, such as the JS backend, produce artifacts when
compiling, such as the jsexe directory which we want to track.

This patch:

- tweaks the testsuite to collect generic metrics on any build artifact
in the test directory.

- expands the exe_extension function to consider windows and adds the
ignore_extension flag.

- Modifies certain tests to add the ignore_extension flag. Tests such as
heaprof002 expect a .ps file, but on windows without ignore_extensions
the testsuite will look for foo.exe.ps. Hence the flag.

- adds the size_hello_artifact test

- - - - -
75a31379 by doyougnu at 2024-02-07T03:06:26-05:00
ts: add wasm_arch, heapprof002 wasm extension

- - - - -
c9731d6d by Rodrigo Mesquita at 2024-02-07T03:07:03-05:00
Synchronize bindist configure for #24324

In cdddeb0f1280b40cc194028bbaef36e127175c4c, we set up a
workaround for #24324 in the in-tree configure script, but forgot to
update the bindist configure script accordingly. This updates it.

- - - - -
d309f4e7 by Matthew Pickering at 2024-02-07T03:07:38-05:00
distrib/configure: Fix typo in CONF_GCC_LINKER_OPTS_STAGE2 variable

Instead we were setting CONF_GCC_LINK_OPTS_STAGE2 which meant that we
were missing passing `--target` when invoking the linker.

Fixes #24414

- - - - -
77db84ab by Ben Gamari at 2024-02-08T00:35:22-05:00
llvmGen: Adapt to allow use of new pass manager.

We now must use `-passes` in place of `-O<n>` due to #21936.

Closes #21936.

- - - - -
3c9ddf97 by Matthew Pickering at 2024-02-08T00:35:59-05:00
testsuite: Mark length001 as fragile on javascript

Modifying the timeout multiplier is not a robust way to get this test to
reliably fail. Therefore we mark it as fragile until/if javascript ever
supports the stack limit.

- - - - -
20b702b5 by Matthew Pickering at 2024-02-08T00:35:59-05:00
Javascript: Don't filter out rtsDeps list

This logic appears to be incorrect as it would drop any dependency which
was not in a direct dependency of the package being linked.

In the ghc-internals split this started to cause errors because
`ghc-internal` is not a direct dependency of most packages, and hence
important symbols to keep which are hard coded into the js runtime were
getting dropped.

- - - - -
2df96366 by Ben Gamari at 2024-02-08T00:35:59-05:00
base: Cleanup whitespace in cbits

- - - - -
44f6557a by Ben Gamari at 2024-02-08T00:35:59-05:00
Move `base` to `ghc-internal`

Here we move a good deal of the implementation of `base` into a new
package, `ghc-internal` such that it can be evolved independently
from the user-visible interfaces of `base`.

While we want to isolate implementation from interfaces, naturally, we
would like to avoid turning `base` into a mere set of module re-exports.
However, this is a non-trivial undertaking for a variety of reasons:

 * `base` contains numerous known-key and wired-in things, requiring
   corresponding changes in the compiler

 * `base` contains a significant amount of C code and corresponding
   autoconf logic, which is very fragile and difficult to break apart

 * `base` has numerous import cycles, which are currently dealt with via
   carefully balanced `hs-boot` files

 * We must not break existing users

To accomplish this migration, I tried the following approaches:

* [Split-GHC.Base]: Break apart the GHC.Base knot to allow incremental
  migration of modules into ghc-internal: this knot is simply too
  intertwined to be easily pulled apart, especially given the rather
  tricky import cycles that it contains)

* [Move-Core]: Moving the "core" connected component of base (roughly
  150 modules) into ghc-internal. While the Haskell side of this seems
  tractable, the C dependencies are very subtle to break apart.

* [Move-Incrementally]:

  1. Move all of base into ghc-internal
  2. Examine the module structure and begin moving obvious modules (e.g.
     leaves of the import graph) back into base
  3. Examine the modules remaining in ghc-internal, refactor as necessary
     to facilitate further moves
  4. Go to (2) iterate until the cost/benefit of further moves is
     insufficient to justify continuing
  5. Rename the modules moved into ghc-internal to ensure that they don't
     overlap with those in base
  6. For each module moved into ghc-internal, add a shim module to base
     with the declarations which should be exposed and any requisite
     Haddocks (thus guaranteeing that base will be insulated from changes
     in the export lists of modules in ghc-internal

Here I am using the [Move-Incrementally] approach, which is empirically
the least painful of the unpleasant options above

Bumps haddock submodule.

Metric Decrease:
    haddock.Cabal
    haddock.base
Metric Increase:
    MultiComponentModulesRecomp
    T16875
    size_hello_artifact

- - - - -
e8fb2451 by Vladislav Zavialov at 2024-02-08T00:36:36-05:00
Haddock comments on infix constructors (#24221)

Rewrite the `HasHaddock` instance for `ConDecl GhcPs` to account for
infix constructors.

This change fixes a Haddock regression (introduced in 19e80b9af252)
that affected leading comments on infix data constructor declarations:

	-- | Docs for infix constructor
	| Int :* Bool

The comment should be associated with the data constructor (:*), not
with its left-hand side Int.

- - - - -
9060d55b by Ben Gamari at 2024-02-08T00:37:13-05:00
Add os-string as a boot package

Introduces `os-string` submodule. This will be necessary for
`filepath-1.5`.

- - - - -
9d65235a by Ben Gamari at 2024-02-08T00:37:13-05:00
gitignore: Ignore .hadrian_ghci_multi/

- - - - -
d7ee12ea by Ben Gamari at 2024-02-08T00:37:13-05:00
hadrian: Set -this-package-name

When constructing the GHC flags for a package Hadrian must take care to
set `-this-package-name` in addition to `-this-unit-id`. This hasn't
broken until now as we have not had any uses of qualified package
imports. However, this will change with `filepath-1.5` and the
corresponding `unix` bump, breaking `hadrian/multi-ghci`.

- - - - -
f2dffd2e by Ben Gamari at 2024-02-08T00:37:13-05:00
Bump filepath to 1.5.0.0

Required bumps of the following submodules:

 * `directory`
 * `filepath`
 * `haskeline`
 * `process`
 * `unix`
 * `hsc2hs`
 * `Win32`
 * `semaphore-compat`

and the addition of `os-string` as a boot package.

- - - - -
ab533e71 by Matthew Pickering at 2024-02-08T00:37:50-05:00
Use specific clang assembler when compiling with -fllvm

There are situations where LLVM will produce assembly which older gcc
toolchains can't handle. For example on Deb10, it seems that LLVM >= 13
produces assembly which the default gcc doesn't support.

A more robust solution in the long term is to require a specific LLVM
compatible assembler when using -fllvm.

Fixes #16354

- - - - -
c32b6426 by Matthew Pickering at 2024-02-08T00:37:50-05:00
Update CI images with LLVM 15, ghc-9.6.4 and cabal-install-3.10.2.0

- - - - -
5fcd58be by Matthew Pickering at 2024-02-08T00:37:50-05:00
Update bootstrap plans for 9.4.8 and 9.6.4

- - - - -
707a32f5 by Matthew Pickering at 2024-02-08T00:37:50-05:00
Add alpine 3_18 release job

This is mainly experimental and future proofing to enable a smooth
transition to newer alpine releases once 3_12 is too old.

- - - - -
c37931b3 by John Ericson at 2024-02-08T06:39:05-05:00
Generate LLVM min/max bound policy via Hadrian

Per #23966, I want the top-level configure to only generate
configuration data for Hadrian, not do any "real" tasks on its own.
This is part of that effort --- one less file generated by it.

(It is still done with a `.in` file, so in a future world non-Hadrian
also can easily create this file.)

Split modules:

- GHC.CmmToLlvm.Config
- GHC.CmmToLlvm.Version
- GHC.CmmToLlvm.Version.Bounds
- GHC.CmmToLlvm.Version.Type

This also means we can get rid of the silly `unused.h` introduced in
!6803 / 7dfcab2f4bcb7206174ea48857df1883d05e97a2 as temporary kludge.

Part of #23966

- - - - -
9f987235 by Apoorv Ingle at 2024-02-08T06:39:42-05:00
Enable mdo statements to use HsExpansions
Fixes: #24411
Added test T24411 for regression

- - - - -
00151098 by Simon Peyton Jones at 2024-02-08T14:47:54+00:00
Several improvements to the handling of coercions

* Make `mkSymCo` and `mkInstCo` smarter
  Fixes #23642

* Fix return role of `SelCo` in the coercion optimiser.
  Fixes #23617

* Make the coercion optimiser `opt_trans_rule` work better for newtypes
  Fixes #23619

- - - - -
d58539fb by Simon Peyton Jones at 2024-02-08T14:47:54+00:00
Simplifier improvements

This MR started as: allow the simplifer to do more in one pass,
arising from places I could see the simplifier taking two iterations
where one would do.  But it turned into a larger project, because
these changes unexpectedly made inlining blow up, especially join
points in deeply-nested cases.

The net result is good: a 1.5% improvement in compile time.  The table
below shows changes over 1%.

The main changes are:

* The SimplEnv now has a seInlineDepth field, which says how deep
  in unfoldings we are.  See Note [Inline depth] in Simplify.Env

* Avoid repeatedly simplifying coercions.
  see Note [Avoid re-simplifying coercions] in Simplify.Iteration
  As you'll see from the Note, this makes use of the seInlineDepth.

* Allow Simplify.Utils.postInlineUnconditionally to inline variables
  that are used exactly once. See Note [Post-inline for single-use things].

* Allow Simplify.Iteration.simplAuxBind to inline used-once things.
  This is another part of Note [Post-inline for single-use things], and
  is really good for reducing simplifier iterations in situations like
      case K e of { K x -> blah }
  wher x is used once in blah.

* Make GHC.Core.SimpleOpt.exprIsConApp_maybe do some simple case
  elimination.  Note [Case elim in exprIsConApp_maybe]

* Many new or rewritten Notes.  E.g. Note [Avoiding simplifying repeatedly]

Join points
~~~~~~~~~~~
* Be very careful about inlining join points. See
  Note [Duplicating join points] in GHC.Core.Opt.Simplify.Iteration

* When making join points, don't do so if the join point is so small
  it will immediately be inlined; check uncondInlineJoin.

* When considering inlining a join point, never do so unless
  there is a positive gain: see (DJ5) in Note [Duplicating join points].

* Do not float join points at all, except to top level.
  See GHC.Core.Opt.SetLevels.dontFloatNonRec

* Do not add an unfolding to a join point at birth.  This is a tricky one
  and has a long Note [Do not add unfoldings to join points at birth]
  It shows up in two places
  - In `mkDupableAlt` do not add an inlining
  - (trickier) In `simplLetUnfolding` don't add an unfolding for a
    fresh join point
  I am not fully satisifed with this, but it works and is well documented.

* In GHC.Core.Unfold.sizeExpr, make jumps small, so that we don't penalise
  having a non-inlined join point.

* Use plan A for dataToTag and tagToEnum

I discovered that GHC.HsToCore.Pmc.Solver.Types.trvVarInfo was very
delicately balanced.  It's a small, heavily used, overloaded function
and it's important that it inlines. By a fluke it was before, but at
various times in my journey it stopped doing so.  So I added an INLINE
pragma to it.

    Metrics: compile_time/bytes allocated
    ------------------------------------------------
           CoOpt_Singletons(normal)   -8.2% GOOD
                LargeRecord(normal)  -22.7% GOOD
                  PmSeriesS(normal)   -4.1%
                  PmSeriesT(normal)   -3.1%
                  PmSeriesV(normal)   -1.6%
                     T11195(normal)   -1.9%
                     T12227(normal)  -19.9% GOOD
                     T12545(normal)   -5.4%
                     T12707(normal)   -2.1% GOOD
                 T13253-spj(normal)  -13.1% GOOD
                     T13386(normal)   -1.6%
                     T14766(normal)   -2.2% GOOD
                    T15630a(normal)          NEW
                     T15703(normal)  -13.5% GOOD
                     T16577(normal)   -4.3% GOOD
                     T17096(normal)   -4.4%
                     T17516(normal)   -0.2%
                     T18223(normal)  -16.3% GOOD
                     T18282(normal)   -5.3% GOOD
                     T18730(optasm)          NEW
                     T18923(normal)   -3.7% GOOD
                    T21839c(normal)   -2.3% GOOD
                      T3064(normal)   -1.3%
                      T5030(normal)  -16.1% GOOD
                   T5321Fun(normal)   -1.5%
                      T6048(optasm)  -11.8% GOOD
                       T783(normal)   -1.4%
                      T8095(normal)   -5.9% GOOD
                      T9630(normal)   -5.1% GOOD

                      T9020(optasm)   +1.5%
                    T18698a(normal)   +1.5%  BAD
                     T14683(normal)   +1.2%
        DsIncompleteRecSel3(normal)   +1.2%
MultiComponentModulesRecomp(normal)   +1.0%
    MultiLayerModulesRecomp(normal)   +1.9%
   MultiLayerModulesTH_Make(normal)   +1.4%
                     T10421(normal)   +1.9%  BAD
                    T10421a(normal)   +3.0%
                     T13056(optasm)   +1.1%
                     T13253(normal)   +1.0%
                      T1969(normal)   +1.1%  BAD
                     T15304(normal)   +1.7%
                      T9675(optasm)   +1.2%
                      T9961(normal)   +2.4%  BAD

                          geo. mean   -1.5%
                          minimum    -22.7%
                          maximum     +3.0%
Metric Decrease:
    CoOpt_Singletons
    LargeRecord
    T12227
    T12707
    T12990
    T13253-spj
    T13536a
    T14766
    T15703
    T16577
    T18223
    T18282
    T18923
    T21839c
    T5030
    T6048
    T8095
    T9630
Metric Increase:
    T10421
    T18698a
    T1969
    T9961

- - - - -
cb00fe38 by Simon Peyton Jones at 2024-02-08T14:47:54+00:00
Improve postInlineUnconditionally

This commit adds two things to postInlineUnconditionally:

1. Do not postInlineUnconditionally join point, ever.
   Doing so does not reduce allocation, which is the main point,
   and with join points that are used a lot it can bloat code.
   See point (1) of Note [Duplicating join points] in
   GHC.Core.Opt.Simplify.Iteration.

2. Do not postInlineUnconditionally a strict (demanded) binding.
   It will not allocate a thunk (it'll turn into a case instead)
   so again the main point of inlining it doesn't hold.  Better
   to check per-call-site.

- - - - -
d52624c2 by Simon Peyton Jones at 2024-02-08T14:47:54+00:00
More wibbles

* Inline join points whose RHS just calls another join point
* Don't float join points at all (SetLevels)
* Ensure that WorkWrap preserves lambda binders, in case of join points

- - - - -
d713408f by Simon Peyton Jones at 2024-02-08T14:47:54+00:00
Unused variable wibbles

- - - - -
d6631617 by Simon Peyton Jones at 2024-02-08T14:47:54+00:00
More import wibbles

- - - - -
05d0fb8b by Simon Peyton Jones at 2024-02-08T14:47:54+00:00
More imports

- - - - -
52ebfe2a by Simon Peyton Jones at 2024-02-08T14:47:54+00:00
More wibbles

- - - - -
a59d053d by Simon Peyton Jones at 2024-02-08T14:47:54+00:00
More on floating join points

* Get rid of the "join ceiling" which I have always hated
* Float joins to top level in final pass only
    (needs documenting--see my GHC log)
* Refactor wantToFloat so that it applies to Rec and NonRec uniformly

- - - - -
1bc12d79 by Simon Peyton Jones at 2024-02-08T14:47:54+00:00
Comments about floating joins

- - - - -
6da317d1 by Simon Peyton Jones at 2024-02-08T14:47:54+00:00
Improve occurrence analyis for bottoming function calls

See Note [Bottoming function calls]

- - - - -
a1f1493a by Simon Peyton Jones at 2024-02-08T14:47:54+00:00
Test output wibbles

- - - - -
65e5a27f by Simon Peyton Jones at 2024-02-08T14:47:54+00:00
More testsuite wibbles

- - - - -
fe74fb57 by Simon Peyton Jones at 2024-02-08T14:47:54+00:00
Float recursive joins to top level

This seems be be a net win.   Example
    joinrec { f x = ..f x'... } in f v
Despite Note [Floating join point bindings]

- - - - -
040c60a1 by Simon Peyton Jones at 2024-02-08T14:47:54+00:00
Inline join points that have evaluated things at the use site.

This helps quite a bit with wheel-sieve1.  Example

   let x = <small thunk> in
   join $j = (x,y) in
   case z of
     A -> case x of
            P -> $j
            Q -> blah
     B -> x
     C -> True

Here `x` can't be duplicated into the branches becuase it is used
in both the join point and the A branch.  But if we inline $j we get

   let x = <small thunk> in
   join $j = (x,y) in
   case z of
     A -> case x of x'
            P -> (x', y)
            Q -> blah
     B -> x
     C -> True

and now we /can/ duplicate x into the branches.

- - - - -


27 changed files:

- .gitignore
- .gitlab-ci.yml
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py
- .gitmodules
- compiler/GHC/Builtin/Names.hs
- compiler/GHC/CmmToLlvm.hs
- compiler/GHC/CmmToLlvm/Base.hs
- compiler/GHC/CmmToLlvm/Config.hs
- + compiler/GHC/CmmToLlvm/Version.hs
- + compiler/GHC/CmmToLlvm/Version/Bounds.hs.in
- + compiler/GHC/CmmToLlvm/Version/Type.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/Coercion/Opt.hs
- compiler/GHC/Core/Make.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/FloatOut.hs
- compiler/GHC/Core/Opt/Monad.hs
- compiler/GHC/Core/Opt/OccurAnal.hs
- compiler/GHC/Core/Opt/Pipeline.hs
- compiler/GHC/Core/Opt/SetLevels.hs
- compiler/GHC/Core/Opt/Simplify.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Inline.hs
- compiler/GHC/Core/Opt/Simplify/Iteration.hs
- compiler/GHC/Core/Opt/Simplify/Monad.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/47be08e0835754f64f74c0fb0778edb451481459...040c60a14705c2f5a318a7502a350eb483c4132b

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/47be08e0835754f64f74c0fb0778edb451481459...040c60a14705c2f5a318a7502a350eb483c4132b
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/20240208/4a516014/attachment-0001.html>


More information about the ghc-commits mailing list