<!DOCTYPE html PUBLIC "-//W3C//DTD HTML 4.0 Transitional//EN" "http://www.w3.org/TR/REC-html40/loose.dtd">
<html lang="en">
<head>
<meta content="text/html; charset=US-ASCII" http-equiv="Content-Type">
<title>
GitLab
</title>



<style>img {
max-width: 100%; height: auto;
}
</style>
</head>
<body>
<div class="content">

<h3>
Simon Peyton Jones pushed to branch wip/T18282
at <a href="https://gitlab.haskell.org/ghc/ghc">Glasgow Haskell Compiler / GHC</a>
</h3>
<h4>
Commits:
</h4>
<ul>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9ee58f8d900884ac8b721b6b95dbfa6500f39431">9ee58f8d</a></strong>
<div>
<span>by Matthias Pall Gissurarson</span>
<i>at 2020-06-26T17:12:45+00:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Implement the proposed -XQualifiedDo extension

Co-authored-by: Facundo Domínguez <facundo.dominguez@tweag.io>

QualifiedDo is implemented using the same placeholders for operation names in
the AST that were devised for RebindableSyntax. Whenever the renamer checks
which names to use for do syntax, it first checks if the do block is qualified
(e.g. M.do { stmts }), in which case it searches for qualified names in
the module M.

This allows users to write

    {-# LANGUAGE QualifiedDo #-}
    import qualified SomeModule as M

    f x = M.do           -- desugars to:
      y <- M.return x    -- M.return x M.>>= \y ->
      M.return y         -- M.return y M.>>
      M.return y         -- M.return y

See Note [QualifiedDo] and the users' guide for more details.

Issue #18214

Proposal:
https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0216-qualified-do.rst

Since we change the constructors `ITdo` and `ITmdo` to carry the new module
name, we need to bump the haddock submodule to account or the new shape of
these constructors.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ce987865d7594ecbcb3d27435eef773e95b2db85">ce987865</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-06-27T11:55:21-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Revamp the treatment of auxiliary bindings for derived instances

This started as a simple fix for #18321 that organically grew into a
much more sweeping refactor of how auxiliary bindings for derived
instances are handled. I have rewritten `Note [Auxiliary binders]`
in `GHC.Tc.Deriv.Generate` to explain all of the moving parts, but
the highlights are:

* Previously, the OccName of each auxiliary binding would be given
  a suffix containing a hash of its package name, module name, and
  parent data type to avoid name clashes. This was needlessly
  complicated, so we take the more direct approach of generating
  `Exact` `RdrName`s for each auxiliary binding with the same
  `OccName`, but using an underlying `System` `Name` with a fresh
  `Unique` for each binding. Unlike hashes, allocating new `Unique`s
  does not require any cleverness and avoid name clashes all the
  same...
* ...speaking of which, in order to convince the renamer that multiple
  auxiliary bindings with the same `OccName` (but different
  `Unique`s) are kosher, we now use `rnLocalValBindsLHS` instead of
  `rnTopBindsLHS` to rename auxiliary bindings. Again, see
  `Note [Auxiliary binders]` for the full story.
* I have removed the `DerivHsBind` constructor for
  `DerivStuff`—which was only used for `Data.Data`-related
  auxiliary bindings—and refactored `gen_Data_binds` to use
  `DerivAuxBind` instead. This brings the treatment of
  `Data.Data`-related auxiliary bindings in line with every other
  form of auxiliary binding.

Fixes #18321.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a403eb917bd26caf96c29d67bfe91163b593b2c9">a403eb91</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-27T11:55:59-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">ghc-bignum: fix division by zero (#18359)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/1b3d13b68c95ef9bbeca4437028531d184abcbea">1b3d13b6</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-27T11:55:59-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix ghc-bignum exceptions

We must ensure that exceptions are not simplified. Previously we used:

   case raiseDivZero of
      _ -> 0## -- dummyValue

But it was wrong because the evaluation of `raiseDivZero` was removed and
the dummy value was directly returned. See new Note [ghc-bignum exceptions].

I've also removed the exception triggering primops which were fragile.
We don't need them to be primops, we can have them exported by ghc-prim.

I've also added a test for #18359 which triggered this patch.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a74ec37c9d7679a5563ab86a8759c79c3c5de6f0">a74ec37c</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-06-27T11:56:34-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Better loop detection in findTypeShape

Andreas pointed out, in !3466, that my fix for #18304 was not
quite right.  This patch fixes it properly, by having just one
RecTcChecker rather than (implicitly) two nested ones, in
findTypeShape.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a04020b88d4935d675f989806aff251f459561e9">a04020b8</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-27T11:57:11-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">DynFlags: don't store buildTag

`DynFlags.buildTag` was a field created from the set of Ways in
`DynFlags.ways`. It had to be kept in sync with `DynFlags.ways` which
was fragile. We want to avoid global state like this (#17957).

Moreover in #14335 we also want to support loading units with different
ways: target units would still use `DynFlags.ways` but plugins would use
`GHC.Driver.Ways.hostFullWays`. To avoid having to deal both with build
tag and with ways, we recompute the buildTag on-the-fly (should be
pretty cheap) and we remove `DynFlags.buildTag` field.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/0e83efa24636c72811e4c79fe1c7e4f7cf3170cd">0e83efa2</a></strong>
<div>
<span>by Krzysztof Gogolewski</span>
<i>at 2020-06-27T11:57:49-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Don't generalize when typechecking a tuple section

The code is simpler and cleaner.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d8ba9e6f951a2f8c6e2429a8b2dcb035c392908f">d8ba9e6f</a></strong>
<div>
<span>by Peter Trommler</span>
<i>at 2020-06-28T09:19:11-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">RTS: Refactor Haskell-C glue for PPC 64-bit

Make sure the stack is 16 byte aligned even when reserved stack
bytes are not a multiple of 16 bytes.

Avoid saving r2 (TOC). On ELF v1 the function descriptor of StgReturn
has the same TOC as StgRun, on ELF v2 the TOC is recomputed in the
function prologue.

Use the ABI provided functions to save clobbered GPRs and FPRs.

Improve comments. Describe what the stack looks like and how it relates
to the respective ABIs.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/42f797b0ad034a92389e7081aa50ef4ab3434d01">42f797b0</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-06-28T09:19:46-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Use NHsCoreTy to embed types into GND-generated code

`GeneralizedNewtypeDeriving` is in the unique situation where it must
produce an `LHsType GhcPs` from a Core `Type`. Historically, this was
done with the `typeToLHsType` function, which walked over the entire
`Type` and attempted to construct an `LHsType` with the same overall
structure. `typeToLHsType` is quite complicated, however, and has
been the subject of numerous bugs over the years (e.g., #14579).

Luckily, there is an easier way to accomplish the same thing: the
`XHsType` constructor of `HsType`. `XHsType` bundles an `NHsCoreTy`,
which allows embedding a Core `Type` directly into an `HsType`,
avoiding the need to laboriously convert from one to another (as
`typeToLHsType` did). Moreover, renaming and typechecking an
`XHsType` is simple, since one doesn't need to do anything to a
Core `Type`...

...well, almost. For the reasons described in
`Note [Typechecking NHsCoreTys]` in `GHC.Tc.Gen.HsType`, we must
apply a substitution that we build from the local `tcl_env` type
environment. But that's a relatively modest price to pay.

Now that `GeneralizedNewtypeDeriving` uses `NHsCoreTy`, the
`typeToLHsType` function no longer has any uses in GHC, so this patch
rips it out. Some additional tweaks to `hsTypeNeedsParens` were
necessary to make the new `-ddump-deriv` output correctly
parenthesized, but other than that, this patch is quite
straightforward.

This is a mostly internal refactoring, although it is likely that
`GeneralizedNewtypeDeriving`-generated code will now need fewer
language extensions in certain situations than it did before.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/68530b1cd45629e5a353a37df80195ac54d26ade">68530b1c</a></strong>
<div>
<span>by Jan Hrček</span>
<i>at 2020-06-28T09:20:22-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix duplicated words and typos in comments and user guide
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/15b79befc246aa9c63dd084012dc7843ea93daaa">15b79bef</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-06-28T09:20:57-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add integer-gmp's ghc.mk and GNUmakefile to .gitignore
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/bfa5698b1ab0190820a2df19487d3d72d3a7924d">bfa5698b</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-06-28T09:21:32-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix a typo in Lint

This simple error in GHC.Core.Litn.lintJoinLams meant that
Lint reported bogus errors.

Fixes #18399
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/fe9cb1e7645949c12fc3a780d10e7b4074be2719">fe9cb1e7</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-06-29T14:10:26+01:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Define multiShotIO and use it in mkSplitUniqueSupply

This patch is part of the ongoing eta-expansion saga;
see #18238.

It implements a neat trick (suggested by Sebastian Graf)
that allows the programmer to disable the default one-shot behaviour
of IO (the "state hack").  The trick is to use a new multiShotIO
function; see Note [multiShotIO].  For now, multiShotIO is defined
here in Unique.Supply; but it should ultimately be moved to the IO
library.

The change is necessary to get good code for GHC's unique supply;
see Note [Optimising the unique supply].

However it makes no difference to GHC as-is.  Rather, it makes
a difference when a subsequent commit

   Improve eta-expansion using ArityType

lands.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/cf0dde29f734643f22b48ff685bd684fe8d2c3b6">cf0dde29</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-06-29T14:12:21+01:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Make arityType deal with join points

As Note [Eta-expansion and join points] describes,
this patch makes arityType deal correctly with join points.
What was there before was not wrong, but yielded lower
arities than it could.

Fixes #18328

In base GHC this makes no difference to nofib.

        Program           Size    Allocs   Runtime   Elapsed  TotalMem
--------------------------------------------------------------------------------
         n-body          -0.1%     -0.1%     -1.2%     -1.1%      0.0%
--------------------------------------------------------------------------------
            Min          -0.1%     -0.1%    -55.0%    -56.5%      0.0%
            Max          -0.0%      0.0%    +16.1%    +13.4%      0.0%
 Geometric Mean          -0.0%     -0.0%    -30.1%    -31.0%     -0.0%

But it starts to make real difference when we land the change to the
way mkDupableAlts handles StrictArg, in fixing #13253 and friends.
I think this is because we then get more non-inlined join points.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6dadf97d32e71ec22534ff1c87466d68e86b5a32">6dadf97d</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-06-29T14:22:32+01:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Improve eta-expansion using ArityType

As #18355 shows, we were failing to preserve one-shot info when
eta-expanding.  It's rather easy to fix, by using ArityType more,
rather than just Arity.

This patch is important to suport the one-shot monad trick;
see #18202.  But the extra tracking of one-shot-ness requires
the patch

   Define multiShotIO and use it in mkSplitUniqueSupply

If that patch is missing, ths patch makes things worse in
GHC.Types.Uniq.Supply.  With it, however, we see these improvements

    T3064     compiler bytes allocated -2.2%
    T3294     compiler bytes allocated -1.3%
    T12707    compiler bytes allocated -2.2%
    T13056    compiler bytes allocated -2.2%
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c22490049a40a6a3baadf9323eaa975ae26d7c60">c2249004</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-06-29T14:22:51+01:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Use dumpStyle when printing inlinings

This just makes debug-printing consistent,
and more informative.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/5585c72bd9ca1419e49c524ab6a6d08726626a7d">5585c72b</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-06-29T14:22:51+01:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Comments only
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/5eae4b2d5883ee27dc6df4fba86fcd6936335cd7">5eae4b2d</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-06-29T14:26:34+01:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Reduce result discount in conSize

Ticket #18282 showed that the result discount given by conSize
was massively too large.  This patch reduces that discount to
a constant 10, which just balances the cost of the constructor
application itself.

Note [Constructor size and result discount] elaborates, as
does the ticket #18282.

Reducing result discount reduces inlining, which affects perf.  I
found that I could increase the unfoldingUseThrehold from 80 to 90 in
compensation; in combination with the result discount change I get
these overall nofib numbers:

        Program           Size    Allocs   Runtime   Elapsed  TotalMem
--------------------------------------------------------------------------------
          boyer          -0.2%     +5.4%     -3.2%     -3.4%      0.0%
       cichelli          -0.1%     +5.9%    -11.2%    -11.7%      0.0%
      compress2          -0.2%     +9.6%     -6.0%     -6.8%      0.0%
   cryptarithm2          -0.1%     -3.9%     -6.0%     -5.7%      0.0%
         gamteb          -0.2%     +2.6%    -13.8%    -14.4%      0.0%
         genfft          -0.1%     -1.6%    -29.5%    -29.9%      0.0%
             gg          -0.0%     -2.2%    -17.2%    -17.8%    -20.0%
           life          -0.1%     -2.2%    -62.3%    -63.4%      0.0%
           mate          +0.0%     +1.4%     -5.1%     -5.1%    -14.3%
         parser          -0.2%     -2.1%     +7.4%     +6.7%      0.0%
      primetest          -0.2%    -12.8%    -14.3%    -14.2%      0.0%
         puzzle          -0.2%     +2.1%    -10.0%    -10.4%      0.0%
            rsa          -0.2%    -11.7%     -3.7%     -3.8%      0.0%
         simple          -0.2%     +2.8%    -36.7%    -38.3%     -2.2%
   wheel-sieve2          -0.1%    -19.2%    -48.8%    -49.2%    -42.9%
--------------------------------------------------------------------------------
            Min          -0.4%    -19.2%    -62.3%    -63.4%    -42.9%
            Max          +0.3%     +9.6%     +7.4%    +11.0%    +16.7%
 Geometric Mean          -0.1%     -0.3%    -17.6%    -18.0%     -0.7%

I'm ok with these numbers, remembering that this change removes
an *exponential* increase in code size in some in-the-wild cases.

I investigated compress2.  The difference is entirely caused by this
function no longer inlining

WriteRoutines.$woutputCodes
  = \ (w :: [CodeEvent]) ->
      let result_s1Sr
            = case WriteRoutines.outputCodes_$s$woutput w 0# 0# 8# 9# of
                (# ww1, ww2 #) -> (ww1, ww2)
      in (# case result_s1Sr of (x, _) ->
              map @Int @Char WriteRoutines.outputCodes1 x
         , case result_s1Sr of { (_, y) -> y } #)

It was right on the cusp before, driven by the excessive result
discount.  Too bad!

Happily, the compiler/perf tests show a number of improvements:
    T12227     compiler bytes-alloc  -6.6%
    T12545     compiler bytes-alloc  -4.7%
    T13056     compiler bytes-alloc  -3.3%
    T15263     runtime  bytes-alloc -13.1%
    T17499     runtime  bytes-alloc -14.3%
    T3294      compiler bytes-alloc  -1.1%
    T5030      compiler bytes-alloc -11.7%
    T9872a     compiler bytes-alloc  -2.0%
    T9872b     compiler bytes-alloc  -1.2%
    T9872c     compiler bytes-alloc  -1.5%

Metric Decrease:
    T12227
    T12545
    T13056
    T15263
    T17499
    T3294
    T5030
    T9872a
    T9872b
    T9872c
</pre>
</li>
</ul>
<h4>30 changed files:</h4>
<ul>
<li class="file-stats">
<a href="#0887cf39c5cdf9cf8d6758f410d7dab3023c0d77">
compiler/GHC/Builtin/Names.hs
</a>
</li>
<li class="file-stats">
<a href="#06764eb0158306b83ab1998d18316392a51838c2">
compiler/GHC/Builtin/Names/TH.hs
</a>
</li>
<li class="file-stats">
<a href="#a1519b7fe8a0d4b42e4aaa927fb6ab5b5da0fcdd">
compiler/GHC/Builtin/PrimOps.hs
</a>
</li>
<li class="file-stats">
<a href="#377cfd14c1f92357465df995ec6537b074051322">
compiler/GHC/Builtin/Types.hs
</a>
</li>
<li class="file-stats">
<a href="#8a5cd068459120cddf3814e7b9e02003b87647ba">
compiler/GHC/Builtin/Types/Prim.hs
</a>
</li>
<li class="file-stats">
<a href="#451725cc4e5d443a3b7c2adcdf224840f953b7e2">
compiler/GHC/Builtin/primops.txt.pp
</a>
</li>
<li class="file-stats">
<a href="#2d3721ad8de95e1144493ca545db846672cb109f">
compiler/GHC/Cmm/Info/Build.hs
</a>
</li>
<li class="file-stats">
<a href="#6fbb543d5fcea725882dd3b8d4dcd9b02022a4be">
compiler/GHC/Cmm/Monad.hs
</a>
</li>
<li class="file-stats">
<a href="#5986ebaacfa99d264abfd2f7ef19d99a64db720f">
compiler/GHC/CmmToAsm/BlockLayout.hs
</a>
</li>
<li class="file-stats">
<a href="#ac425fefb01f046d6c5170ebcf3962923cee32b8">
compiler/GHC/CmmToAsm/SPARC/Regs.hs
</a>
</li>
<li class="file-stats">
<a href="#335d279236d65dcf13f2bab3891e515cb803203c">
compiler/GHC/CmmToAsm/X86/Ppr.hs
</a>
</li>
<li class="file-stats">
<a href="#182d6a315e784018aa9c8b2ad736036b97bd5d48">
compiler/GHC/Core.hs
</a>
</li>
<li class="file-stats">
<a href="#91648438362e5a35363d2bb7abb04016dedd7d7e">
compiler/GHC/Core/FamInstEnv.hs
</a>
</li>
<li class="file-stats">
<a href="#36a42448a83a9d1f6df8475f03ead2eed199dd8e">
compiler/GHC/Core/Lint.hs
</a>
</li>
<li class="file-stats">
<a href="#35cff95f9f44690fc50b44bbe8ac3c554c7d5a5e">
compiler/GHC/Core/Make.hs
</a>
</li>
<li class="file-stats">
<a href="#8d589f620b33e18b711e6288c5f5c962634aba03">
compiler/GHC/Core/Multiplicity.hs
</a>
</li>
<li class="file-stats">
<a href="#c3967bb9d3e8f5aae2dd111b5a335b48c21c1999">
compiler/GHC/Core/Opt/Arity.hs
</a>
</li>
<li class="file-stats">
<a href="#aa79261abf782f3dc603af7fbd5c4b08ed3ddb88">
compiler/GHC/Core/Opt/ConstantFold.hs
</a>
</li>
<li class="file-stats">
<a href="#f2f5de8b9f31451d693079c2a2d27fb47b18a3f4">
compiler/GHC/Core/Opt/Driver.hs
</a>
</li>
<li class="file-stats">
<a href="#f168a93cde5e2aec2441d6331dfe500172df4af3">
compiler/GHC/Core/Opt/Simplify.hs
</a>
</li>
<li class="file-stats">
<a href="#2f46b19cb85e3f7b4e72305644bc50015628c41d">
compiler/GHC/Core/Opt/Simplify/Env.hs
</a>
</li>
<li class="file-stats">
<a href="#48fbb5cdea308650de5756521feb28ec68819b9b">
compiler/GHC/Core/Opt/Simplify/Utils.hs
</a>
</li>
<li class="file-stats">
<a href="#b6a5ba32bafb8fbda933538b3007e755fef6f101">
compiler/GHC/Core/Opt/SpecConstr.hs
</a>
</li>
<li class="file-stats">
<a href="#f4421b4e35592648510c877ecf55b1af2b96dcee">
compiler/GHC/Core/Opt/WorkWrap/Utils.hs
</a>
</li>
<li class="file-stats">
<a href="#11ffe98a94d798427bc600e4fcfe899407536346">
compiler/GHC/Core/SimpleOpt.hs
</a>
</li>
<li class="file-stats">
<a href="#708fab0a51bd47227233eda4698e750ff6de66e0">
compiler/GHC/Core/Subst.hs
</a>
</li>
<li class="file-stats">
<a href="#4aad0050db1a8a20db8bbca149111de99cb299c9">
compiler/GHC/Core/TyCon.hs
</a>
</li>
<li class="file-stats">
<a href="#84c9d3ba34173297e7d7747e02caa2e004b164fc">
compiler/GHC/Core/Type.hs
</a>
</li>
<li class="file-stats">
<a href="#2811a7297b8aa206197ac1f5dabd0818e3c7ec5a">
compiler/GHC/Core/Unfold.hs
</a>
</li>
<li class="file-stats">
<a href="#b8812fd502fde0b254e166743c0cfa6fd65f2c2f">
compiler/GHC/Data/Bitmap.hs
</a>
</li>
</ul>
<h5>The diff was not included because it is too large.</h5>

</div>
<div class="footer" style="margin-top: 10px;">
<p style="font-size: small; color: #777;">

<br>
<a href="https://gitlab.haskell.org/ghc/ghc/-/compare/bcfcd27528d6b7794b7ca778eaed444c979b9282...5eae4b2d5883ee27dc6df4fba86fcd6936335cd7">View it on GitLab</a>.
<br>
You're receiving this email because of your account on gitlab.haskell.org.
If you'd like to receive fewer emails, you can
adjust your notification settings.



</p>
</div>
</body>
</html>