[Git][ghc/ghc][wip/sand-witch/modern-STV-extension-shuffling] 53 commits: NCG: remove useless .align directive (#20758)

Andrei Borzenkov (@sand-witch) gitlab at gitlab.haskell.org
Mon May 29 05:25:22 UTC 2023



Andrei Borzenkov pushed to branch wip/sand-witch/modern-STV-extension-shuffling at Glasgow Haskell Compiler / GHC


Commits:
b56d7379 by Sylvain Henry at 2023-05-22T14:21:22-04:00
NCG: remove useless .align directive (#20758)

- - - - -
15b93d2f by Simon Peyton Jones at 2023-05-22T14:21:58-04:00
Add test for #23156

This program had exponential typechecking time in GHC 9.4 and 9.6

- - - - -
2b53f206 by Greg Steuck at 2023-05-22T20:23:11-04:00
Revert "Change hostSupportsRPaths to report False on OpenBSD"

This reverts commit 1e0d8fdb55a38ece34fa6cf214e1d2d46f5f5bf2.

- - - - -
882e43b7 by Greg Steuck at 2023-05-22T20:23:11-04:00
Disable T17414 on OpenBSD

Like on other systems it's not guaranteed that there's sufficient
space in /tmp to write 2G out.

- - - - -
9d531f9a by Greg Steuck at 2023-05-22T20:23:11-04:00
Bring back getExecutablePath to getBaseDir on OpenBSD

Fix #18173

- - - - -
9db0eadd by Krzysztof Gogolewski at 2023-05-22T20:23:47-04:00
Add an error origin for impedance matching (#23427)

- - - - -
33cf4659 by Ben Gamari at 2023-05-23T03:46:20-04:00
testsuite: Add tests for #23146

Both lifted and unlifted variants.

- - - - -
76727617 by Ben Gamari at 2023-05-23T03:46:21-04:00
codeGen: Fix some Haddocks

- - - - -
33a8c348 by Ben Gamari at 2023-05-23T03:46:21-04:00
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.

- - - - -
2fc18e9e by Rodrigo Mesquita at 2023-05-23T03:46:21-04:00
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)

- - - - -
0598f7f0 by Rodrigo Mesquita at 2023-05-23T03:46:21-04:00
Make LFInfos for DataCons on construction

As a result of the discussion in !10165, we decided to amend the
previous commit which fixed the logic of `mkLFImported` with regard to
datacon workers and wrappers.

Instead of having the logic for the LFInfo of datacons be in
`mkLFImported`, we now construct an LFInfo for all data constructors on
GHC.Types.Id.Make and store it in the `lfInfo` field.

See the new Note [LFInfo of DataCon workers and wrappers] and
ammendments to Note [The LFInfo of Imported Ids]

- - - - -
12294b22 by Rodrigo Mesquita at 2023-05-23T03:46:21-04:00
Update Note [Core letrec invariant]

Authored by @simonpj

- - - - -
e93ab972 by Rodrigo Mesquita at 2023-05-23T03:46:21-04:00
Rename mkLFImported to importedIdLFInfo

The `mkLFImported` sounded too much like a constructor of sorts, when
really it got the `LFInfo` of an imported Id from its `lf_info` field
when this existed, and otherwise returned a conservative estimate of
that imported Id's LFInfo. This in contrast to functions such as
`mkLFReEntrant` which really are about constructing an `LFInfo`.

- - - - -
e54d9259 by Rodrigo Mesquita at 2023-05-23T03:46:21-04:00
Enforce invariant on typePrimRepArgs in the types

As part of the documentation effort in !10165 I came across this
invariant on 'typePrimRepArgs' which is easily expressed at the
type-level through a NonEmpty list.

It allowed us to remove one panic.

- - - - -
b8fe6a0c by Rodrigo Mesquita at 2023-05-23T03:46:21-04:00
Merge outdated Note [Data con representation] into Note [Data constructor representation]

Introduce new Note [Constructor applications in STG] to better support
the merge, and reference it from the relevant bits in the STG syntax.

- - - - -
e1590ddc by Simon Peyton Jones at 2023-05-23T03:46:57-04:00
Add the SolverStage monad

This refactoring makes a substantial improvement in the
structure of the type-checker's constraint solver: #23070.

Specifically:

* Introduced the SolverStage monad.   See GHC.Tc.Solver.Monad
  Note [The SolverStage monad]

* Make each solver pipeline (equalities, dictionaries, irreds etc)
  deal with updating the inert set, as a separate SolverStage.  There
  is sometimes special stuff to do, and it means that each full
  pipeline can have type SolverStage Void, indicating that they never
  return anything.

* Made GHC.Tc.Solver.Equality.zonkEqTypes into a SolverStage.  Much nicer.

* Combined the remnants of GHC.Tc.Solver.Canonical and
  GHC.Tc.Solver.Interact into a new module GHC.Tc.Solver.Solve.
  (Interact and Canonical are removed.)

* Gave the same treatment to dictionary and irred constraints
  as I have already done for equality constraints:
    * New types (akin to EqCt): IrredCt and DictCt
    * Ct is now just a simple sum type
          data Ct
            = CDictCan      DictCt
            | CIrredCan     IrredCt
            | CEqCan        EqCt
            | CQuantCan     QCInst
            | CNonCanonical CtEvidence
    * inert_dicts can now have the better type DictMap DictCt, instead of
      DictMap Ct; and similarly inert_irreds.

* Significantly simplified the treatment of implicit parameters.
  Previously we had a number of special cases
    * interactGivenIP, an entire function
    * special case in maybeKickOut
    * special case in findDict, when looking up dictionaries
  But actually it's simpler than that. When adding a new Given, implicit
  parameter constraint to the InertSet, we just need to kick out any
  existing inert constraints that mention that implicit parameter.

  The main work is done in GHC.Tc.Solver.InertSet.delIPDict, along with
  its auxiliary GHC.Core.Predicate.mentionsIP.

  See Note [Shadowing of implicit parameters] in GHC.Tc.Solver.Dict.

* Add a new fast-path in GHC.Tc.Errors.Hole.tcCheckHoleFit.
  See Note [Fast path for tcCheckHoleFit].  This is a big win in some cases:
  test hard_hole_fits gets nearly 40% faster (at compile time).

* Add a new fast-path for solving /boxed/ equality constraints
  (t1 ~ t2).  See Note [Solving equality classes] in GHC.Tc.Solver.Dict.
  This makes a big difference too: test T17836 compiles 40% faster.

* Implement the PermissivePlan of #23413, which concerns what happens with
  insoluble Givens.   Our previous treatment was wildly inconsistent as that
  ticket pointed out.

  A part of this, I simplified GHC.Tc.Validity.checkAmbiguity: now we simply
  don't run the ambiguity check at all if -XAllowAmbiguousTypes is on.

Smaller points:

* In `GHC.Tc.Errors.misMatchOrCND` instead of having a special case for
  insoluble /occurs/ checks, broaden in to all insouluble constraints.
  Just generally better. See Note [Insoluble mis-match] in that module.

As noted above, compile time perf gets better.  Here are the changes
over 0.5% on Fedora.  (The figures are slightly larger on Windows for
some reason.)

Metrics: compile_time/bytes allocated
-------------------------------------
                LargeRecord(normal)   -0.9%
MultiLayerModulesTH_OneShot(normal)   +0.5%
                     T11822(normal)   -0.6%
                     T12227(normal)   -1.8% GOOD
                     T12545(normal)   -0.5%
                     T13035(normal)   -0.6%
                     T15703(normal)   -1.4% GOOD
                     T16875(normal)   -0.5%
                     T17836(normal)  -40.7% GOOD
                    T17836b(normal)  -12.3% GOOD
                    T17977b(normal)   -0.5%
                      T5837(normal)   -1.1%
                      T8095(normal)   -2.7% GOOD
                      T9020(optasm)   -1.1%
             hard_hole_fits(normal)  -37.0% GOOD

                          geo. mean   -1.3%
                          minimum    -40.7%
                          maximum     +0.5%

Metric Decrease:
    T12227
    T15703
    T17836
    T17836b
    T8095
    hard_hole_fits
    LargeRecord
    T9198
    T13035

- - - - -
6abf3648 by Simon Peyton Jones at 2023-05-23T03:46:57-04:00
Avoid an assertion failure in abstractFloats

The function GHC.Core.Opt.Simplify.Utils.abstractFloats
was carelessly calling lookupIdSubst_maybe on a CoVar;
but a precondition of the latter is being given an Id.

In fact it's harmless to call it on a CoVar, but still, the
precondition on lookupIdSubst_maybe makes sense, so I added
a test for CoVars.

This avoids a crash in a DEBUG compiler, but otherwise has
no effect. Fixes #23426.

- - - - -
838aaf4b by hainq at 2023-05-24T12:41:19-04:00
Migrate errors in GHC.Tc.Validity

This patch migrates the error messages in GHC.Tc.Validity to use
the new diagnostic infrastructure.

It adds the constructors:

  - TcRnSimplifiableConstraint
  - TcRnArityMismatch
  - TcRnIllegalInstanceDecl, with sub-datatypes for HasField errors
    and fundep coverage condition errors.

- - - - -
8539764b by Krzysztof Gogolewski at 2023-05-24T12:41:56-04:00
linear lint: Add missing processing of DEFAULT

In this correct program

f :: a %1 -> a
f x = case x of x { _DEFAULT -> x }

after checking the alternative we weren't popping the case binder 'x'
from the usage environment, which meant that the lambda-bound 'x'
was counted twice: in the scrutinee and (incorrectly) in the alternative.
In fact, we weren't checking the usage of 'x' at all.
Now the code for handling _DEFAULT is similar to the one handling
data constructors.

Fixes #23025.

- - - - -
ae683454 by Matthew Pickering at 2023-05-24T12:42:32-04:00
Remove outdated "Don't check hs-boot type family instances too early" note

This note was introduced in 25b70a29f623 which delayed performing some
consistency checks for type families. However, the change was reverted
later in 6998772043a7f0b0360116eb5ffcbaa5630b21fb but the note was not
removed.

I found it confusing when reading to code to try and work out what
special behaviour there was for hs-boot files (when in-fact there isn't
any).

- - - - -
44af57de by Matthew Pickering at 2023-05-24T12:43:08-04:00
rts: Define ticky macro stubs

These macros have long been undefined which has meant we were missing
reporting these allocations in ticky profiles.

The most critical missing definition was TICK_ALLOC_HEAP_NOCTR which was
missing all the RTS calls to allocate, this leads to a the overall
ALLOC_RTS_tot number to be severaly underreported.

Of particular interest though is the ALLOC_STACK_ctr and ALLOC_STACK_tot
counters which are useful to tracking stack allocations.

Fixes #23421

- - - - -
b2dabe3a by Matthew Pickering at 2023-05-24T12:43:08-04:00
rts: ticky: Rename TICK_ALLOC_HEAP_NOCTR to TICK_ALLOC_RTS

This macro increments the ALLOC_HEAP_tot and ALLOC_HEAP_ctr so it makes
more sense to name it after that rather than the suffix NOCTR, whose
meaning has been lost to the mists of time.

- - - - -
eac4420a by Ben Gamari at 2023-05-24T12:43:45-04:00
users guide: A few small mark-up fixes

- - - - -
a320ca76 by Rodrigo Mesquita at 2023-05-24T12:44:20-04:00
configure: Fix support check for response files.

In failing to escape the '-o' in '-o\nconftest\nconftest.o\n' argument
to printf, the writing of the arguments response file always failed.

The fix is to pass the arguments after `--` so that they are treated
positional arguments rather than flags to printf.

Closes #23435

- - - - -
f21ce0e4 by mangoiv at 2023-05-24T12:45:00-04:00
[feat] add .direnv to the .gitignore file

- - - - -
36d5944d by Bodigrim at 2023-05-24T20:58:34-04:00
Add Data.List.unsnoc

See https://github.com/haskell/core-libraries-committee/issues/165 for discussion

- - - - -
c0f2f9e3 by Bartłomiej Cieślar at 2023-05-24T20:59:14-04:00
Fix crash in backpack signature merging with -ddump-rn-trace

In some cases, backpack signature merging could crash in addUsedGRE
when -ddump-rn-trace was enabled, as pretty-printing the GREInfo would cause
unavailable interfaces to be loaded.
This commit fixes that issue by not pretty-printing the GREInfo in addUsedGRE
when -ddump-rn-trace is enabled.

Fixes #23424

Signed-off-by: Bartłomiej Cieślar <bcieslar2001 at gmail.com>

- - - - -
5a07d94a by Krzysztof Gogolewski at 2023-05-25T03:30:20-04:00
Add a regression test for #13981

The panic was fixed by 6998772043a7f0b. Fixes #13981.

- - - - -
182df90e by Krzysztof Gogolewski at 2023-05-25T03:30:57-04:00
Add a test for #23355

It was fixed by !10061, so I'm adding it in the same group.

- - - - -
1b31b039 by uhbif19 at 2023-05-25T12:08:28+02:00
Migrate errors in GHC.Rename.Splice GHC.Rename.Pat

This commit migrates the errors in GHC.Rename.Splice and GHC.Rename.Pat
to use the new diagnostic infrastructure.

- - - - -
56abe494 by sheaf at 2023-05-25T12:09:55+02:00
Common up Template Haskell errors in TcRnMessage

This commit commons up the various Template Haskell errors into a
single constructor, TcRnTHError, of TcRnMessage.

- - - - -
a487ba9e by Krzysztof Gogolewski at 2023-05-25T14:35:56-04:00
Enable ghci tests for unboxed tuples

The tests were originally skipped because ghci used not to support
unboxed tuples/sums.

- - - - -
dc3422d4 by Matthew Pickering at 2023-05-25T18:57:19-04:00
rts: Build ticky GHC with single-threaded RTS

The threaded RTS allows you to use ticky profiling but only for the
counters in the generated code. The counters used in the C portion of
the RTS are disabled. Updating the counters is also racy using the
threaded RTS which can lead to misleading or incorrect ticky results.

Therefore we change the hadrian flavour to build using the
single-threaded RTS (mainly in order to get accurate C code counter
increments)

Fixes #23430

- - - - -
fbc8e04e by sheaf at 2023-05-25T18:58:00-04:00
Propagate long-distance info in generated code

When desugaring generated pattern matches, we skip pattern match checks.
However, this ended up also discarding long-distance information, which
might be needed for user-written sub-expressions.

Example:

```haskell
okay (GADT di) cd =
  let sr_field :: ()
      sr_field = case getFooBar di of { Foo -> () }
  in case cd of { SomeRec _ -> SomeRec sr_field }
```

With sr_field a generated FunBind, we still want to propagate the outer
long-distance information from the GADT pattern match into the checks
for the user-written RHS of sr_field.

Fixes #23445

- - - - -
f8ced241 by Matthew Pickering at 2023-05-26T15:26:21-04:00
Introduce GHCiMessage to wrap GhcMessage

By introducing a wrapped message type we can control how certain
messages are printed in GHCi (to add extra information for example)

- - - - -
58e554c1 by Matthew Pickering at 2023-05-26T15:26:22-04:00
Generalise UnknownDiagnostic to allow embedded diagnostics to access
parent diagnostic options.

* Split default diagnostic options from Diagnostic class into
  HasDefaultDiagnosticOpts class.
* Generalise UnknownDiagnostic to allow embedded diagnostics to access
  options.

The principle idea here is that when wrapping an error message (such as
GHCMessage to make GHCiMessage) then we need to also be able to lift the
configuration when overriding how messages are printed (see load' for an
example).

- - - - -
b112546a by Matthew Pickering at 2023-05-26T15:26:22-04:00
Allow API users to wrap error messages created during 'load'

This allows API users to configure how messages are rendered when they
are emitted from the load function. For an example see how
'loadWithCache' is used in GHCi.

- - - - -
2e4cf0ee by Matthew Pickering at 2023-05-26T15:26:22-04:00
Abstract cantFindError and turn Opt_BuildingCabal into a print-time option

* cantFindError is abstracted so that the parts which mention specific
  things about ghc/ghci are parameters. The intention being that
  GHC/GHCi can specify the right values to put here but otherwise
  display the same error message.
* The BuildingCabalPackage argument from GenericMissing is removed and
  turned into a print-time option. The reason for the error is not
  dependent on whether `-fbuilding-cabal-package` is passed, so we don't
  want to store that in the error message.

- - - - -
34b44f7d by Matthew Pickering at 2023-05-26T15:26:22-04:00
error messages: Don't display ghci specific hints for missing packages

Tickets like #22884 suggest that it is confusing that GHC used on the
command line can suggest options which only work in GHCi.

This ticket uses the error message infrastructure to override certain
error messages which displayed GHCi specific information so that this
information is only showed when using GHCi.

The main annoyance is that we mostly want to display errors in the same
way as before, but with some additional information. This means that the
error rendering code has to be exported from the Iface/Errors/Ppr.hs
module.

I am unsure about whether the approach taken here is the best or most
maintainable solution.

Fixes #22884

- - - - -
05a1b626 by Matthew Pickering at 2023-05-26T15:26:58-04:00
ghcup-metadata: Don't override existing metadata if version already exists.

If a nightly pipeline runs twice for some reason for the same version
then we really don't want to override an existing entry with new
bindists. This could cause ABI compatability issues for users or break
ghcup's caching logic.

- - - - -
fcbcb3cc by Matthew Pickering at 2023-05-26T15:26:58-04:00
ghcup-metadata: Use proper API url for bindist download

Previously we were using links from the web interface, but it's more
robust and future-proof to use the documented links to the artifacts.

https://docs.gitlab.com/ee/api/job_artifacts.html

- - - - -
5b59c8fe by Matthew Pickering at 2023-05-26T15:26:58-04:00
ghcup-metadata: Set Nightly and LatestNightly tags

The latest nightly release needs the LatestNightly tag, and all other
nightly releases need the Nightly tag. Therefore when the metadata is
updated we need to replace all LatestNightly with Nightly.`

- - - - -
914e1468 by Matthew Pickering at 2023-05-26T15:26:58-04:00
ghcup-metadata: Download nightly metadata for correct date

The metadata now lives in https://gitlab.haskell.org/ghc/ghcup-metadata
with one metadata file per year. When we update the metadata we download
and update the right file for the current year.

- - - - -
16cf7d2e by Matthew Pickering at 2023-05-26T15:26:58-04:00
ghcup-metadata: Download metadata and update for correct year

something about pipeline date

- - - - -
14792c4b by Matthew Pickering at 2023-05-26T15:26:58-04:00
ghcup-metadata: Don't skip CI

On a push we now have a CI job which updates gitlab pages with the
metadata files.

- - - - -
1121bdd8 by Matthew Pickering at 2023-05-26T15:26:59-04:00
ghcup-metadata: Add --date flag to specify the release date

The ghcup-metadata now has a viReleaseDay field which needs to be
populated with the day of the release.

- - - - -
bc478bee by Matthew Pickering at 2023-05-26T15:26:59-04:00
ghcup-metadata: Add dlOutput field

ghcup now requires us to add this field which specifies where it should
download the bindist to. See
https://gitlab.haskell.org/ghc/ghcup-metadata/-/issues/1 for some more
discussion.

- - - - -
2bdbd9da by Josh Meredith at 2023-05-26T15:27:35-04:00
JS: Convert rendering to use HLine instead of SDoc (#22455)

- - - - -
abd9e37c by Norman Ramsey at 2023-05-26T15:28:12-04:00
testsuite: add WasmControlFlow test

This patch adds the WasmControlFlow test to test the wasm backend's
relooper component.

- - - - -
07f858eb by Sylvain Henry at 2023-05-26T15:28:53-04:00
Factorize getLinkDeps

Prepare reuse of getLinkDeps for TH implementation in the JS backend
(cf #22261 and review of !9779).

- - - - -
fad9d092 by Oleg Grenrus at 2023-05-27T13:38:08-04:00
Change GHC.Driver.Session import to .DynFlags

Also move targetPlatform selector

Plenty of GHC needs just DynFlags.
Even more can be made to use .DynFlags if more selectors is migrated.
This is a low hanging fruit.

- - - - -
69fdbece by Alan Zimmerman at 2023-05-27T13:38:45-04:00
EPA: Better fix for #22919

The original fix for #22919 simply removed the ability to match up
prior comments with the first declaration in the file.

Restore it, but add a check that the comment is on a single line, by
ensuring that it comes immediately prior to the next thing (comment or
start of declaration), and that the token preceding it is not on the
same line.

closes #22919

- - - - -
8331bf94 by Ben Gamari at 2023-05-29T09:24:22+04:00
Extension shuffling (#23291)

Where introduced 4 new extensions:
  - PatternSignatures
  - ExtendedForAllScope
  - MethodTypeVariables
  - ImplicitForAll

Tasks of ScopedTypeVariables extension were distributed between
PatternSignatures, ExtendedForAllScope and MethodTypeVariables according
to the proposal. Now ScopedTypeVaribles only implies these three exntesions.

Extension ImplicitForAll saves current behavior. NoImplicitForAll
disables implicit bounding of type variables in many contexts.

Was introduced one new warning option: -Wpattern-signature-binds
It warns when pattern signature binds into scope new type variable. For
example:

  f (a :: t) = ...

- - - - -


30 changed files:

- .gitignore
- .gitlab-ci.yml
- .gitlab/rel_eng/mk-ghcup-metadata/README.mkd
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- compiler/GHC/Builtin/Types/Prim.hs
- compiler/GHC/Cmm/CLabel.hs
- compiler/GHC/CmmToAsm.hs
- compiler/GHC/CmmToAsm/AArch64/Ppr.hs
- compiler/GHC/CmmToAsm/X86/Ppr.hs
- compiler/GHC/CmmToLlvm.hs
- compiler/GHC/CmmToLlvm/Base.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/InstEnv.hs
- compiler/GHC/Core/LateCC.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/Pipeline.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Core/Opt/Specialise.hs
- compiler/GHC/Core/Predicate.hs
- compiler/GHC/Core/Tidy.hs
- compiler/GHC/Core/TyCo/Compare.hs
- compiler/GHC/Core/TyCon.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Unify.hs
- compiler/GHC/Core/UsageEnv.hs
- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Driver/CmdLine.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d89cfd2d61a8517116b4d050a2894230fd5cab3e...8331bf9473b123f499f95620dca239aee8da9895

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d89cfd2d61a8517116b4d050a2894230fd5cab3e...8331bf9473b123f499f95620dca239aee8da9895
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/20230529/7fef748d/attachment-0001.html>


More information about the ghc-commits mailing list