<!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>
Krzysztof Gogolewski pushed to branch wip/mono-local-binds
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/4bf18646acbb5a59ad8716aedc32acfe2ead0f58">4bf18646</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-07-03T08:37:42+01:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Improve handling of data type return kinds

Following a long conversation with Richard, this patch tidies up the
handling of return kinds for data/newtype declarations (vanilla,
family, and instance).

I have substantially edited the Notes in TyCl, so they would
bear careful reading.

Fixes #18300, #18357

In GHC.Tc.Instance.Family.newFamInst we were checking some Lint-like
properties with ASSSERT.  Instead Richard and I have added
a proper linter for axioms, and called it from lintGblEnv, which in
turn is called in tcRnModuleTcRnM

New tests (T18300, T18357) cause an ASSERT failure in HEAD.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/41d2649288a5debcb4c8003e54b7d3072ab951c5">41d26492</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-07-03T17:33:59-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">DynFlags: avoid the use of sdocWithDynFlags in GHC.Core.Rules (#17957)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7aa6ef110d8cc6626b1cf18d85a37cbac53e2795">7aa6ef11</a></strong>
<div>
<span>by Hécate</span>
<i>at 2020-07-03T17:34:36-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add the __GHC_FULL_VERSION__ CPP macro to expose the full GHC version
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e61d539527a7398017f759c67621ba18a15878f7">e61d5395</a></strong>
<div>
<span>by Chaitanya Koparkar</span>
<i>at 2020-07-07T13:55:59-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">ghc-prim: Turn some comments into haddocks

[ci skip]
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/37743f91a3f5018a8894ca6d35e8b423e4e08b50">37743f91</a></strong>
<div>
<span>by John Ericson</span>
<i>at 2020-07-07T13:56:00-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Support `timesInt2#` in LLVM backend
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/46397e530e1b107c6b8932f7ca79ebab53a3249a">46397e53</a></strong>
<div>
<span>by John Ericson</span>
<i>at 2020-07-07T13:56:00-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">`genericIntMul2Op`: Call `genericWordMul2Op` directly

This unblocks a refactor, and removes partiality. It might be a PowerPC
regression but that should be fixable.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8a1c0584da40d0f8d1ffd01796efcce3b3d0820d">8a1c0584</a></strong>
<div>
<span>by John Ericson</span>
<i>at 2020-07-07T13:56:00-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Simplify `PrimopCmmEmit`

Follow @simonpj's suggestion of pushing the "into regs" logic into
`emitPrimOp`. With the previous commit getting rid of the recursion in
`genericIntMul2Op`, this is now an easy refactor.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6607f203fb9ad11af1463145810e1bd3c6c4f2c8">6607f203</a></strong>
<div>
<span>by John Ericson</span>
<i>at 2020-07-07T13:56:00-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">`opAllDone` -> `opIntoRegs`

The old name was and terrible and became worse after the previous
commit's refactor moved non-trivial funcationlity into its body.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/fdcc53babbd6c878344d2a3395bbd619428bd2dd">fdcc53ba</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-07-07T13:56:00-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Optimise genericIntMul2Op

We shouldn't directly call 'genericWordMul2Op' in genericIntMul2Op
because a target may provide a faster primop for 'WordMul2Op': we'd
better use it!
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/686e72253aed3880268dd6858eadd8c320f09e97">686e7225</a></strong>
<div>
<span>by Moritz Angermann</span>
<i>at 2020-07-07T13:56:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">[linker/rtsSymbols] More linker symbols

Mostly symbols needed for aarch64/armv7l
and in combination with musl, where we have
to rely on loading *all* objects/archives

- __stack_chk_* only when not DYNAMIC
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/3f60b94de1f460ca3f689152860b108a19ce193e">3f60b94d</a></strong>
<div>
<span>by Moritz Angermann</span>
<i>at 2020-07-07T13:56:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">better if guards.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7abffced01f5680efafe44f6be2733eab321b039">7abffced</a></strong>
<div>
<span>by Moritz Angermann</span>
<i>at 2020-07-07T13:56:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix (1)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/cdfeb3f24f76e8fd30452016676e56fbc827789a">cdfeb3f2</a></strong>
<div>
<span>by Moritz Angermann</span>
<i>at 2020-07-07T13:56:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">AArch32 symbols only on aarch32.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/f496c9550098ffaa3bf25a3447c138626d79bae0">f496c955</a></strong>
<div>
<span>by Adam Sandberg Ericsson</span>
<i>at 2020-07-07T13:56:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">add -flink-rts flag to link the rts when linking a shared or static library #18072

By default we don't link the RTS when linking shared libraries because in the
most usual mode a shared library is an intermediary product, for example a
Haskell library, that will be linked into some executable in the end. So we
wish to defer the RTS flavour to link to the final link.

However sometimes the final product is the shared library, for example when
writing a plugin for some other system, so we do wish the shared library to
link the RTS.

For consistency we also make -staticlib honor this flag and its inversion.
-staticlib currently implies -flink-shared.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c59faf67fec83c98ffd1b65f1be0775b34f36595">c59faf67</a></strong>
<div>
<span>by Stefan Schulze Frielinghaus</span>
<i>at 2020-07-07T13:56:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">hadrian: link check-ppr against debugging RTS if ghcDebugged
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/0effc57d48ace6b719a9f4cbeac67c95ad55010b">0effc57d</a></strong>
<div>
<span>by Adam Sandberg Ericsson</span>
<i>at 2020-07-07T13:56:05-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts linker: teach the linker about GLIBC's special handling of *stat, mknod and atexit functions #7072
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9615343363a68313c4bfdb068696002ecca7786e">96153433</a></strong>
<div>
<span>by Adam Sandberg Ericsson</span>
<i>at 2020-07-07T13:56:06-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">hadrian: make hadrian/ghci use the bootstrap compiler from configure #18190
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4d24f886a428e95eb5e962294c77b12bffa40a52">4d24f886</a></strong>
<div>
<span>by Adam Sandberg Ericsson</span>
<i>at 2020-07-07T13:56:07-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">hadrian: ignore cabal configure verbosity related flags #18131
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7332bbffee9e2a712508540200eb52ed3d227426">7332bbff</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-07-07T13:56:08-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite: Widen T12234 acceptance window to 2%

Previously it wasn't uncommon to see +/-1% fluctuations in compiler
allocations on this test.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/180b63136f25d9fedb764cb9bc23637e7781ed4e">180b6313</a></strong>
<div>
<span>by Gabor Greif</span>
<i>at 2020-07-07T13:56:08-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">When running libtool, report it as such</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d3bd68978476487591fc60f7feb7cfb36b8fc3a3">d3bd6897</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-07-07T13:56:11-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">BigNum: rename BigNat types

Before this patch BigNat names were confusing because we had:

* GHC.Num.BigNat.BigNat: unlifted type used everywhere else
* GHC.Num.BigNat.BigNatW: lifted type only used to share static constants
* GHC.Natural.BigNat: lifted type only used for backward compatibility

After this patch we have:

* GHC.Num.BigNat.BigNat#: unlifted type
* GHC.Num.BigNat.BigNat: lifted type (reexported from GHC.Natural)

Thanks to @RyanGlScott for spotting this.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/929d26db3080ec49ab67690952a316fc082b479f">929d26db</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-07-07T13:56:12-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Bignum: don't build ghc-bignum with stage0

Noticed by @Ericson2314
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d25b6851bbd63b6a65fb7cd08b37c6bc74df9855">d25b6851</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-07-07T13:56:12-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Hadrian: ghc-gmp.h shouldn't be a compiler dependency
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/0ddae2ba979ac2e01d7d9f6b79a9559fbfde46ea">0ddae2ba</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-07-07T13:56:14-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">DynFlags: factor out pprUnitId from "Outputable UnitId" instance
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/204f3f5ddec56403bfb12e74291b3b1d14824138">204f3f5d</a></strong>
<div>
<span>by Krzysztof Gogolewski</span>
<i>at 2020-07-07T13:56:18-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove unused function pprHsForAllExtra (#18423)

The function `pprHsForAllExtra` was called only on `Nothing`
since 2015 (1e041b7382b6aa).
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/3033e0e4940e6ecc43f478f1dcfbd0c3cb1e3ef8">3033e0e4</a></strong>
<div>
<span>by Adam Sandberg Ericsson</span>
<i>at 2020-07-08T20:36:49-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">hadrian: add flag to skip rebuilding dependency information #17636
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b7de4b960a1024adcd0bded6bd320a90979d7ab8">b7de4b96</a></strong>
<div>
<span>by Stefan Schulze Frielinghaus</span>
<i>at 2020-07-09T09:49:22-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix GHCi :print on big-endian platforms

On big-endian platforms executing

  import GHC.Exts
  data Foo = Foo Float# deriving Show
  foo = Foo 42.0#
  foo
  :print foo

results in an arithmetic overflow exception which is caused by function
index where moveBytes equals
  word_size - (r + item_size_b) * 8
Here we have a mixture of units. Both, word_size and item_size_b have
unit bytes whereas r has unit bits.  On 64-bit platforms moveBytes
equals then
  8 - (0 + 4) * 8
which results in a negative and therefore invalid second parameter for a
shiftL operation.

In order to make things more clear the expression
  (word .&. (mask `shiftL` moveBytes)) `shiftR` moveBytes
is equivalent to
  (word `shiftR` moveBytes) .&. mask
On big-endian platforms the shift must be a left shift instead of a
right shift. For symmetry reasons not a mask is used but two shifts in
order to zero out bits. Thus the fixed version equals
  case endian of
    BigEndian    -> (word `shiftL` moveBits) `shiftR` zeroOutBits `shiftL` zeroOutBits
    LittleEndian -> (word `shiftR` moveBits) `shiftL` zeroOutBits `shiftR` zeroOutBits

Fixes #16548 and #14455
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/3656dff8259199d0dab2d1a1f1b887c252a9c1a3">3656dff8</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-07-09T09:50:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">LLVM: fix MO_S_Mul2 support (#18434)

The value indicating if the carry is useful wasn't taken into account.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d9f095060b0f00d7140f8b0858b7a5dcbffea9ef">d9f09506</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-07-10T10:33:44-04: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/bce695cc97cadbc3eced5b53efaaa0ecfd201d61">bce695cc</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-07-10T10:33:44-04: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/2b7c71cb79095a10b9a5964a5a0676a2a196e92d">2b7c71cb</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-07-11T12:17:02-04: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 -1.3%
    T13056    compiler bytes allocated -2.2%

Metric Decrease:
    T3064
    T3294
    T12707
    T13056
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/de139cc496c0e0110e252a1208ae346f47f8061e">de139cc4</a></strong>
<div>
<span>by Artem Pelenitsyn</span>
<i>at 2020-07-12T02:53:20-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">add reproducer for #15630
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c4de6a7a5c6433ae8c4df8a9fa09fbd9f3bbd0bf">c4de6a7a</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-12T02:53:55-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Give Uniq[D]FM a phantom type for its key.

This fixes #17667 and should help to avoid such issues going forward.

The changes are mostly mechanical in nature. With two notable
exceptions.

* The register allocator.

  The register allocator references registers by distinct uniques.
  However they come from the types of VirtualReg, Reg or Unique in
  various places. As a result we sometimes cast the key type of the
  map and use functions which operate on the now typed map but take
  a raw Unique as actual key. The logic itself has not changed it
  just becomes obvious where we do so now.

* <Type>Env Modules.

As an example a ClassEnv is currently queried using the types `Class`,
`Name`, and `TyCon`. This is safe since for a distinct class value all
these expressions give the same unique.

    getUnique cls
    getUnique (classTyCon cls)
    getUnique (className cls)
    getUnique (tcName $ classTyCon cls)

This is for the most part contained within the modules defining the
interface. However it requires us to play dirty when we are given a
`Name` to lookup in a `UniqFM Class a` map. But again the logic did
not change and it's for the most part hidden behind the Env Module.

Some of these cases could be avoided by refactoring but this is left
for future work.

We also bump the haddock submodule as it uses UniqFM.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c2cfdfde20d0d6c0e16aa7a84d8ebe51501bcfa8">c2cfdfde</a></strong>
<div>
<span>by Aaron Allen</span>
<i>at 2020-07-13T09:00:33-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Warn about empty Char enumerations (#18402)

Currently the "Enumeration is empty" warning (-Wempty-enumerations)
only fires for numeric literals. This patch adds support for `Char`
literals so that enumerating an empty list of `Char`s will also
trigger the warning.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c3ac87ece2716b83ad886e81c20f4161e8ec0efd">c3ac87ec</a></strong>
<div>
<span>by Stefan Schulze Frielinghaus</span>
<i>at 2020-07-13T09:01:10-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">hadrian: build check-ppr dynamic if GHC is build dynamic

Fixes #18361
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9ad072b487fe528947f817b0417933a6cd1941b7">9ad072b4</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-07-13T14:52:49-04: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/e78c4efb8735eb97f17e7b4ca35e305b0766f78a">e78c4efb</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-07-13T14:52:49-04: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/7ccb760b1a8034b28171d7540712fd195f65d1fd">7ccb760b</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-07-13T14:52:49-04: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>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7f0b671ee8a65913891c07f157b21d77d6c63036">7f0b671e</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-07-13T14:52:49-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite: Widen acceptance threshold on T5837

This test is positively tiny and consequently the bytes allocated
measurement will be relatively noisy. Consequently I have seen this
fail spuriously quite often.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/118e1c3da622f17c67b4e0fbc12ed7c7084055dc">118e1c3d</a></strong>
<div>
<span>by Alp Mestanogullari</span>
<i>at 2020-07-14T21:30:52-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">compiler: re-engineer the treatment of rebindable if

Executing on the plan described in #17582, this patch changes the way if expressions
are handled in the compiler in the presence of rebindable syntax. We get rid of the
SyntaxExpr field of HsIf and instead, when rebindable syntax is on, we rewrite the HsIf
node to the appropriate sequence of applications of the local `ifThenElse` function.

In order to be able to report good error messages, with expressions as they were
written by the user (and not as desugared by the renamer), we make use of TTG
extensions to extend GhcRn expression ASTs with an `HsExpansion` construct, which
keeps track of a source (GhcPs) expression and the desugared (GhcRn) expression that
it gives rise to. This way, we can typecheck the latter while reporting the former in
error messages.

In order to discard the error context lines that arise from typechecking the desugared
expressions (because they talk about expressions that the user has not written), we
carefully give a special treatment to the nodes fabricated by this new renaming-time
transformation when typechecking them. See Note [Rebindable syntax and HsExpansion]
for more details. The note also includes a recipe to apply the same treatment to
other rebindable constructs.

Tests 'rebindable11' and 'rebindable12' have been added to make sure we report
identical error messages as before this patch under various circumstances.

We also now disable rebindable syntax when processing untyped TH quotes, as per
the discussion in #18102 and document the interaction of rebindable syntax and
Template Haskell, both in Note [Template Haskell quotes and Rebindable Syntax]
and in the user guide, adding a test to make sure that we do not regress in
that regard.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/64c774b043a2d9be3b98e445990c795f070dab3f">64c774b0</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-14T21:31:27-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Explain why keeping DynFlags in AnalEnv saves allocation.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/254245d01e3c1d4f9072abc4372fd3fb0a6ece9f">254245d0</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-07-14T21:32:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">docs/users-guide: Update default -funfolding-use-threshold value

This was changed in 3d2991f8 but I neglected to update the
documentation. Fixes #18419.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4c259f86938f4016f4bd4fde7a300fa83591036f">4c259f86</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-14T21:32:41-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Escape backslashes in json profiling reports properly.

I also took the liberty to do away the fixed buffer size for escaping.
Using a fixed size here can only lead to issues down the line.

Fixes #18438.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2379722438cb551210c4899119ade05989c17166">23797224</a></strong>
<div>
<span>by Sergei Trofimovich</span>
<i>at 2020-07-14T21:33:19-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">.gitlab: re-enable integer-simple substitute (BIGNUM_BACKEND)

Recently build system migrated from INTEGER_LIBRARY to BIGNUM_BACKEND.
But gitlab CI was never updated. Let's enable BIGNUM_BACKEND=native.

Bug: https://gitlab.haskell.org/ghc/ghc/-/issues/18437
Signed-off-by: Sergei Trofimovich <slyfox@gentoo.org>
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e0db878a789e58c2a1aba2e73d42857008174124">e0db878a</a></strong>
<div>
<span>by Sergei Trofimovich</span>
<i>at 2020-07-14T21:33:19-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">ghc-bignum: bring in sync .hs-boot files with module declarations

Before this change `BIGNUM_BACKEND=native` build was failing as:

```
libraries/ghc-bignum/src/GHC/Num/BigNat/Native.hs:708:16: error:
    * Variable not in scope: naturalFromBigNat# :: WordArray# -> t
    * Perhaps you meant one of these:
        `naturalFromBigNat' (imported from GHC.Num.Natural),
        `naturalToBigNat' (imported from GHC.Num.Natural)
    |
708 |           m' = naturalFromBigNat# m
    |
```

This happens because `.hs-boot` files are slightly out of date.
This change brings in data and function types in sync.

Bug: https://gitlab.haskell.org/ghc/ghc/-/issues/18437
Signed-off-by: Sergei Trofimovich <slyfox@gentoo.org>
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c9f65c369a60467dcaf2b37d5f41f00565b4fe25">c9f65c36</a></strong>
<div>
<span>by Stefan Schulze Frielinghaus</span>
<i>at 2020-07-14T21:33:57-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts/Disassembler.c: Use FMT_HexWord for printing values in hex format
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/58ae62ebb5750e4dfbdb171efde8e3064b7afea8">58ae62eb</a></strong>
<div>
<span>by Matthias Andreas Benkard</span>
<i>at 2020-07-14T21:34:35-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">macOS: Load frameworks without stating them first.

macOS Big Sur makes the following change to how frameworks are shipped
with the OS:

> New in macOS Big Sur 11 beta, the system ships with a built-in
> dynamic linker cache of all system-provided libraries. As part of
> this change, copies of dynamic libraries are no longer present on
> the filesystem. Code that attempts to check for dynamic library
> presence by looking for a file at a path or enumerating a directory
> will fail. Instead, check for library presence by attempting to
> dlopen() the path, which will correctly check for the library in the
> cache. (62986286)

https://developer.apple.com/documentation/macos-release-notes/macos-big-sur-11-beta-release-notes/

Therefore, the previous method of checking whether a library exists
before attempting to load it makes GHC.Runtime.Linker.loadFramework
fail to find frameworks installed at /System/Library/Frameworks.

GHC.Runtime.Linker.loadFramework now opportunistically loads the
framework libraries without checking for their existence first,
failing only if all attempts to load a given framework from any of the
various possible locations fail.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/cdc4a6b0f71bbd16a11f23e455b28c0c15720b38">cdc4a6b0</a></strong>
<div>
<span>by Matthias Andreas Benkard</span>
<i>at 2020-07-14T21:34:35-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">loadFramework: Output the errors collected in all loading attempts.

With the recent change away from first finding and then loading a
framework, loadFramework had no way of communicating the real reason
why loadDLL failed if it was any reason other than the framework
missing from the file system.  It now collects all loading attempt
errors into a list and concatenates them into a string to return to
the caller.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/51dbfa52df483822b99bb191d2ffc0943954e1d3">51dbfa52</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-07-15T04:05:34-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">StgToCmm: Use CmmRegOff smart constructor

Previously we would generate expressions of the form
`CmmRegOff BaseReg 0`. This should do no harm (and really should be
handled by the NCG anyways) but it's better to just generate a plain
`CmmReg`.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ae11bdfd98a10266bfc7de9e16b500be220307ac">ae11bdfd</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-07-15T04:06:08-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite: Add regression test for #17744

Test due to @monoidal.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/0e3c277a6c82c5ab529771c1c493d86e7eda0a98">0e3c277a</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-07-15T16:41:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Bump Cabal submodule

Updates a variety of tests as Cabal is now more strict about Cabal file
form.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ceed994acd07259ef3a780ab440185dbb26fff09">ceed994a</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Drop Windows Vista support, require Windows 7
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/00a23bfda4840546075ec2b2e18f61380b360dfc">00a23bfd</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Update Windows FileSystem wrapper utilities.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/459e1c5f7c71e37ed8bb239c57bdec441d278fff">459e1c5f</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Use SlimReaderLocks and ConditonalVariables provided by the OS instead of emulated ones
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/763088fc3c14c8687685fe811eac13d216971840">763088fc</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Small linker comment and ifdef cleanups
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/1a228ff9e04c91bc9b6f62942dc18bf1985a58a4">1a228ff9</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Flush event logs eagerly.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e9e04ddae1bf89902803d86282f41a586620c58f">e9e04dda</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Refactor Buffer structures to be able to track async operations
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/356dc3feae967b1c361130f1f356ef9ad6a693e4">356dc3fe</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Implement new Console API
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/90e69f779b6da755fac472337535a1321cbb7917">90e69f77</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Add IOPort synchronization primitive
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/71245fcce24723910f12f934fbc4c700658b727a">71245fcc</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Add new io-manager cmdline options
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d548a3b3058232cbfd588f6a2c2b9108bbe8d190">d548a3b3</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Init Windows console Codepage to UTF-8.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/58ef63668ec395aa7a2b250d9930641305d646e2">58ef6366</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Add unsafeSplat to GHC.Event.Array
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d660725edbdaeef9be5da4c032e687276dd09b13">d660725e</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Add size and iterate to GHC.Event.IntTable.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/050da6dd42d0cb293c7fce4a5ccdeb5abe1aadb4">050da6dd</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Switch Testsuite to test winio by default
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4bf542bf1cdf2fa468457fc0af21333478293476">4bf542bf</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Multiple refactorings and support changes.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4489af6bad11a198e9e6c192f41e17020f28d0c1">4489af6b</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: core threaded I/O manager
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/64d8f2fe2d27743e2986d2176b1aa934e5484d7a">64d8f2fe</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: core non-threaded I/O manager
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8da15a09955926c4617d3468b84b3f3ca414d48a">8da15a09</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Fix a scheduler bug with the threaded-runtime.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/84ea3d1492127442e2d416f1f576a5921186ada4">84ea3d14</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Relaxing some constraints in io-manager.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ccf0d1073969e3b73fed82cd421d74800f552953">ccf0d107</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Fix issues with non-threaded I/O manager after split.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b492fe6e4bde56341abbdb55d19fdf6e02ff70e9">b492fe6e</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Remove some barf statements that are a bit strict.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/01423fd205809e884fd9b7b69286108ca06a0d98">01423fd2</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Expand comments describing non-threaded loop
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4b69004f3c9518f59a8f0b6f7f77aa92bea85adf">4b69004f</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: fix FileSize unstat-able handles
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9b38427045b8f1621f607fa7ab9c6353aa479ac5">9b384270</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Implement new tempfile routines for winio
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/f1e0be824523c6687e3d8588c46a57b2cd22ecc1">f1e0be82</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Fix input truncation when reading from handle.

This was caused by not upholding the read buffer invariant
that bufR == bufL == 0 for empty read buffers.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e176b625689563d2ccfbfec46e664d17824f1968">e176b625</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Fix output truncation for writes larger than buffer size
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a831ce0e7f0bbd8d81e96074e981fe1972fde6dd">a831ce0e</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Rewrite bufWrite.

I think it's far easier to follow the code now.
It's also correct now as I had still missed a spot
where we didn't update the offset.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6aefdf62b767b7828698c3ec5bf6a15e6e20eddb">6aefdf62</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Fix offset set by bufReadEmpty.

bufReadEmpty returns the bytes read *including* content that
was already buffered,
But for calculating the offset we only care about the number
of bytes read into the new buffer.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/750ebaeec06d7ee118abfbb29142c12fb31730cc">750ebaee</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Clean up code surrounding IOPort primitives.

According to phyx these should only be read and written once per
object. Not neccesarily in that order.

To strengthen that guarantee the primitives will now throw an
exception if we violate this invariant.

As a consequence we can eliminate some code from their primops.
In particular code dealing with multiple queued readers/writers
now simply checks the invariant and throws an exception if it
was violated. That is in contrast to mvars which will do things
like wake up all readers, queue multi writers etc.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ffd31db99f6fb8958900147035ddac9a47b7a764">ffd31db9</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Fix multi threaded threadDelay and a few other small changes.

Multithreaded threadDelay suffered from a race condition
based on the ioManagerStatus. Since the status isn't needed
for WIO I removed it completely.

This resulted in a light refactoring, as consequence we will always
wake up the IO manager using interruptSystemManager, which uses
`postQueuedCompletionStatus` internally.

I also added a few comments which hopefully makes the code easier to
dive into for the next person diving in.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6ec26df241d80e8e5cf39a02757c274067c8078d">6ec26df2</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">wionio: Make IO subsystem check a no-op on non-windows platforms.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/29bcd9363f2712524f7720377f19cb885adf2825">29bcd936</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Set handle offset when opening files in Append mode.

Otherwise we would truncate the file.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/55c29700fba3f35a80acd366b2f05b66464d8258">55c29700</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Remove debug event log trace
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9acb9f40d90b79da9e587022d73f8afb26a46463">9acb9f40</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Fix sqrt and openFile009 test cases
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/57017cb7454cbfaa1b011693e7fb141fbf519ccf">57017cb7</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Allow hp2ps to build with -DDEBUG
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b8cd99951c8e21f82c3a95940de10128b78ab4ab">b8cd9995</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Update output of T9681 since we now actually run it.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/10af5b1418554860e377b0df79026c2ea3669ab4">10af5b14</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: A few more improvements to the IOPort primitives.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/39afc4a785a37f238a9004b2f6882d1951953c07">39afc4a7</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Fix expected tempfiles output.

Tempfiles now works properly on windows, as such we can
delete the win32 specific output.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/99db46e09c50681e35de75d8bfec6cfb9ac3f9fc">99db46e0</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Assign thread labels to IOManager threads.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/be6af7324bcd918c61172f6814b8a70a6cfdd58e">be6af732</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Properly check for the tso of an incall to be zero.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e2c6dac783d6cb15217a3be196abeba6c6105588">e2c6dac7</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Mark FD instances as unsupported under WINIO.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/fd02ceed5661e1c2fa85ec5c663697a3b0cf3e04">fd02ceed</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Fix threadDelay maxBound invocations.

Instead of letting the ns timer overflow now clamp it at
(maxBound :: Word64) ns. That still gives a few hundred
years.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/bc79f9f180b3fc73fe25439faf9cc5f19622acb3">bc79f9f1</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Add comments/cleanup an import in base
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/1d197f4bbe5bf6d7189c329a742917db3f67ad34">1d197f4b</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Mark outstanding_service_requests volatile.

As far as I know C(99) gives no guarantees for code like

    bool condition;

    ...

    while(condition)
        sleep();

that condition will be updated if it's changed by another thread.
So we are explicit here and mark it as volatile, this will force
a reload from memory on each iteration.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/dc4381869748ec25ac9560bf7e89641b560b6862">dc438186</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Make last_event a local variable
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2fc957c52270d93073b7ed9fe42ac51fcd749a45">2fc957c5</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Add comment about thread safety of processCompletion.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4c026b6cf5eb25651f656833e4d312621866330d">4c026b6c</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: nonthreaded: Create io processing threads in main thread.

We now set a flag in the IO thread. The scheduler when looking for work
will check the flag and create/queue threads accordingly.

We used to create these in the IO thread. This improved performance
but caused frequent segfaults. Thread creation/allocation is only safe to
do if nothing currently accesses the storeagemanager. However without
locks in the non-threaded runtime this can't be guaranteed.

This shouldn't change performance all too much.

In the past we had:
* IO: Create/Queue thread.
* Scheduler: Runs a few times. Eventually picks up IO processing thread.

Now it's:
* IO: Set flag to queue thread.
* Scheduler: Pick up flag, if set create/queue thread. Eventually picks up IO processing thread.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/f47c7208c31bdd695ba46e6bdf4a349ae46c79bc">f47c7208</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Add an exported isHeapAlloced function to the RTS
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/cc5d7bb1dcf5603ac47320e83e4fc9ef53e409e9">cc5d7bb1</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Queue IO processing threads at the front of the queue.

This will unblock the IO thread sooner hopefully leading to higher
throughput in some situations.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e763011596ccafccdd476e1cac0ee6088d439e3b">e7630115</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: ThreadDelay001: Use higher resolution timer.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/451b5f96c8a3366584a62034747c8b78fc3b0486">451b5f96</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Update T9681 output, disable T4808 on windows.

T4808 tests functionality of the FD interface which won't be supported
under WINIO.

T9681 just has it's expected output tweaked.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/dd06f930a3228ef7ae8ea5c7225552d6df21f662">dd06f930</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Wake io manager once per registerTimeout.

Which is implicitly done in editTimeouts, so need to wake it
up twice.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e87d0bf9a430bf52a0068b9b53dcc4592c8da930">e87d0bf9</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Update placeholder comment with actual function name.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/fc9025db55345d6b427489b942878d781f70a039">fc9025db</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Always lock win32 event queue
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c24c9a1f2a10e044a31b7d89586f4a19ff61e137">c24c9a1f</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Display thread labels when tracing scheduler events.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/06542b033116bfc4b47c80bdeab44ed1d99005bb">06542b03</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Refactor non-threaded runner thread and scheduler interface.

Only use a single communication point (registerAlertableWait) to inform
the C side aobut both timeouts to use as well as outstanding requests.

Also queue a haskell processing thread after each return from alertable
waits. This way there is no risk of us missing a timer event.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/256299b13e17044d6904a85043130d13bc592a62">256299b1</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Remove outstanding_requests from runner.

We used a variable to keep track of situations where we got
entries from the IO port, but all of them had already been
canceled. While we can avoid some work that way this case
seems quite rare.

So we give up on tracking this and instead always assume at
least one of the returned entries is valid.

If that's not the case no harm is done, we just perform some
additional work. But it makes the runner easier to reason about.

In particular we don't need to care if another thread modifies
oustanding_requests after we return from waiting on the IO Port.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/3ebd8ad9b1f7f77a928f2ff0d3e61ddfae068dd3">3ebd8ad9</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Various fixes related to rebase and testdriver
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6be6bcbac0e39537f3a40c615d1568a3d6391f9b">6be6bcba</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Fix rebase artifacts
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2c649dc3ba7b08817352eb24d9888651290b6eb6">2c649dc3</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Rename unsafeSplat to unsafeCopyFromBuffer
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a18b73f34dc3d177e76259bd65326a94824d97e0">a18b73f3</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Remove unused size/iterate operations from IntTable
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/16bab48ef69866725d2ab20ca7bd1da5f5a70000">16bab48e</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Detect running IO Backend via peeking at RtsConfig
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8b8405a0dd45c16ec305884cadda992327733621">8b8405a0</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: update temp path so GCC etc can handle it.

Also fix PIPE support, clean up error casting, fix memory leaks
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2092bc542516461eeb06d855dfbe9b04438767bc">2092bc54</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Minor comments/renamings
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a5b5b6c0de4e9ea2923beeff488e852aa247000a">a5b5b6c0</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Checking if an error code indicates completion is now a function.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/362176fd9189e73083fd2a2012c9b5be1e3fd05b">362176fd</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Small refactor in withOverlappedEx
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/32e20597b2fe5864b578c732501fe20d899e8f9c">32e20597</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: A few comments and commented out dbxIO
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a4bfc1d9ae59adc58a0df3b25f85873533481e94">a4bfc1d9</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Don't drop buffer offset in byteView/cwcharView
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b3ad2a54bf775e1ca110b501894891d4ccff3d8f">b3ad2a54</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: revert BHandle changes.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/3dcd87e2fd6d03028d18bf1a61e526142ee9b8a1">3dcd87e2</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Fix imports
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/5a3718909e8eb214d4a70082b7fee8d6f3efc975">5a371890</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: update ghc-cabal to handle new Cabal submodule bump
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d07ebe0df6df32bbffbf77ea09e39b6da2e8cbb3">d07ebe0d</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Only compile sources on Windows
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/dcb423937a052496af73e34a315e3d15882b9f19">dcb42393</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Actually return Nothing on EOF for non-blocking read
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/895a3beb26de69f5611ea496dddb2b121c1dd5c1">895a3beb</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Deduplicate logic in encodeMultiByte[Raw]IO.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e06e6734a4d5c49c625605a2675c47fd93f834b2">e06e6734</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Deduplicate openFile logic
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b59430c00f41e18386bc44540180451169f6b9d7">b59430c0</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: fix -werror issue in encoding file
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/f8d39a510c563271e26ec7175b8e538d0b6809da">f8d39a51</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Don't mention windows specific functions when building on Linux.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6a533d2afaab8b8ca0026c9af1a8ed9ff09c4462">6a533d2a</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: add a note about file locking in the RTS.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/cf37ce3499a0367faf7fcaf014d8350e5864fe7a">cf37ce34</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Add version to @since annotation
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/0fafa2eb45d9283526c79f810476a369af21bf3b">0fafa2eb</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Rename GHC.Conc.IOCP -> GHC.Conc.WinIO
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/1854fc23489baa39cb37f8d49ff74b7ee78d7de1">1854fc23</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Expand GHC.Conc.POSIX description

It now explains users may not use these functions when
using the old IO manager.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/fcc7ba414e1dfab70136a824775421b26ce1b81a">fcc7ba41</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Fix potential spaceleak in __createUUIDTempFileErrNo
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6b3fd9fa15e75f646ac6eaa384f54afe853029f4">6b3fd9fa</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Remove redundant -Wno-missing-signatures pragmas
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/916fc861520615149c66c1069f6cb661bc8b8483">916fc861</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Make it explicit that we only create one IO manager
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/f260a7218f71398ad2dbca0f47feaf31c21081b3">f260a721</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Note why we don't use blocking waits.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/aa0a4bbfbae0244313fa99862b97f71c15f9bd81">aa0a4bbf</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Remove commented out pragma
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d679b544e14ad912fddc97b1b735d3c2838a2c4b">d679b544</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Remove redundant buffer write in Handle/Text.hs:bufReadEmpty
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d3f94368cc27e124c07f9c3f90e3f9563a7fc55d">d3f94368</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Rename SmartHandles to StdHandles
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/bd6b8ec1e775441fc943702e93d48ce75f155e9e">bd6b8ec1</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: add comment stating failure behaviour for getUniqueFileInfo.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/12846b85a94b2b73f456e4c441c7890d685deb67">12846b85</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Update IOPort haddocks.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9f39fb14997f1aa3768c89bb8e83c6addc705d92">9f39fb14</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Add a note cross reference
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/62dd5a7309f273b5bb7d6ab44a1d2745010c13a0">62dd5a73</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Name Haskell/OS I/O Manager explicitly in Note
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/fa80782864895fe614e1b83416736014e68c8b35">fa807828</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Expand BlockedOnIOCompletion description.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/f0880a1daea4f3c9fa6fa4624914081f29736ea2">f0880a1d</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Remove historical todos
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8e58e714e9a4b5fe77c4e71802cc4b9ad1998af3">8e58e714</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Update note, remove debugging pragma.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/aa4d84d556b39715ebc1a7860a620ec5a7d9beeb">aa4d84d5</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: flushCharReadBuffer shouldn't need to adjust offsets.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e580893ab8b76ff4b6582b1fb2ed55cc9742d5a2">e580893a</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Remove obsolete comment about cond. variables
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d54e9d7911901ee5bfcba43b2e4e1a4df11c670e">d54e9d79</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: fix initial linux validate build
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/3cd4de46c1f31e2f044c671a4474126fc0d5a8da">3cd4de46</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Fix ThreadDelay001 CPP
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c88b1b9fde4eedcd1b62c51b1a53201ec3cf29c8">c88b1b9f</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Fix openFile009 merge conflict leftover
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/849e8889fe9586bf9e1bf37885537f25743383f2">849e8889</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Accept T9681 output.

GHC now reports String instead of [Char].
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e7701818e75b66957724f48c4aafac146699b667">e7701818</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Fix cabal006 after upgrading cabal submodule

Demand cabal 2.0 syntax instead of >= 1.20 as required by newer cabal versions.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a44f037372feac67793deb919d988468809ce470">a44f0373</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Fix stderr output for ghci/linking/dyn tests.

We used to filter rtsopts, i opted to instead just accept the warning of it having no effect.
This works both for -rtsopts, as well as -with-rtsopts which winio adds.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/515d98960d3cdcdd7d78a9f28d1b0ad39865c67f">515d9896</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Adjust T15261b stdout for --io-manager flag.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/949aaaccf34ef7e28a745081775b01627590fc46">949aaacc</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Adjust T5435_dyn_asm stderr

The warning about rtsopts having no consequences is expected.
So accept new stderr.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7d424e1e31a8f16e614947460e0e4e4b52f8b5cf">7d424e1e</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Also accept T7037 stderr
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/1f0097683f65ee3cd917af843621ed73b5348e68">1f009768</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: fix cabal04 by filtering rts args
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/981a9f2e57728cdf39de9fc173b11be4084997d3">981a9f2e</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: fix cabal01 by accepting expected stderr
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b7b0464eb7a5510fde4a804402491ecad2f1092b">b7b0464e</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: fix safePkg01 by accepting expected stderr
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/32734b29cbe0450d27fa6b4ea67b05aff2c4919d">32734b29</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: fix T5435_dyn_gcc by accepting expected stderr
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/acc5cebf42e38c2b0869117329811c03c4e3f545">acc5cebf</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: fix tempfiles test on linux
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c577b789e8f76f81a99f1731700c27796effb598">c577b789</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Accept accepted stderr for T3807
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c108c52779a6423871ea372be82b94f5274e57da">c108c527</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Accept accepted stderr for linker_unload
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2b0b9a08a3412114f568fb26e3d684ccb7092f88">2b0b9a08</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Accept accepted stderr for linker_unload_multiple_objs
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/67afb03c45cf8a8dc9e51413cf187f36768a5a0b">67afb03c</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: clarify wording on conditional variables.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/3bd415721672da9aa88c4528df8ba15bc616f3be">3bd41572</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: clarify comment on cooked mode.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ded58a037774147073366ff2dfdc8965e02a96e5">ded58a03</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: update lockfile signature and remove mistaken symbol in rts.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2143c49273d7d87ee2f3ef1211856d60b1427af1">2143c492</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite: Add winio and winio_threaded ways

Reverts many of the testsuite changes
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c0979cc53442b3a6202acab9cf164f0a4beea0b7">c0979cc5</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-07-16T10:56:54-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Merge remote-tracking branch 'origin/wip/winio'
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/750a1595ef31cdc335f3bab045b2f19a9c43ff93">750a1595</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-07-18T07:26:41-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts: Add --copying-gc flag to reverse effect of --nonmoving-gc

Fixes #18281.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6ba6a881c58459008f02fb4816f8dec2800c2b73">6ba6a881</a></strong>
<div>
<span>by Hécate</span>
<i>at 2020-07-18T07:26:42-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Implement `fullCompilerVersion`

Follow-up of https://gitlab.haskell.org/ghc/ghc/-/issues/18403

This MR adds `fullCompilerVersion`, a function that shares the same
backend as the `--numeric-version` GHC flag, exposing a full,
three-digit version datatype.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e6cf27dfded59fe42bd6be323573c0d576e6204a">e6cf27df</a></strong>
<div>
<span>by Hécate</span>
<i>at 2020-07-18T07:26:43-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add a Lint hadrian rule and an .hlint.yaml file in base/
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/bcb177dd00c91d825e00ed228bce6cfeb7684bf7">bcb177dd</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-07-18T07:26:43-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Allow multiple case branches to have a higher rank type

As #18412 points out, it should be OK for multiple case alternatives
to have a higher rank type, provided they are all the same.

This patch implements that change.  It sweeps away
GHC.Tc.Gen.Match.tauifyMultipleBranches, and friends, replacing it
with an enhanced version of fillInferResult.

The basic change to fillInferResult is to permit the case in which
another case alternative has already filled in the result; and in
that case simply unify.  It's very simple actually.

See the new Note [fillInferResult] in TcMType

Other refactoring:

- Move all the InferResult code to one place, in GHC.Tc.Utils.TcMType
  (previously some of it was in Unify)

- Move tcInstType and friends from TcMType to Instantiate, where it
  more properly belongs.  (TCMType was getting very long.)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e5525a51900623e04ec914e9dcc7f4ad1fd3b528">e5525a51</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-07-18T07:26:43-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Improve typechecking of NPlusK patterns

This patch (due to Richard Eisenberg) improves
documentation of the wrapper returned by tcSubMult
(see Note [Wrapper returned from tcSubMult] in
 GHC.Tc.Utils.Unify).

And, more substantially, it cleans up the multiplicity
handling in the typechecking of NPlusKPat
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/12f9035200424ec8104484f154a040d612fee99d">12f90352</a></strong>
<div>
<span>by Krzysztof Gogolewski</span>
<i>at 2020-07-18T07:26:45-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove {-# CORE #-} pragma (part of #18048)

This pragma has no effect since 2011.
It was introduced for External Core, which no longer exists.

Updates haddock submodule.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e504c9137dff2b8f51e8ed96b5cbb5a0d19f8e3a">e504c913</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-07-18T07:26:45-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Refactor the simplification of join binders

This MR (for #18449) refactors the Simplifier's treatment
of join-point binders.

Specifically, it puts together, into
     GHC.Core.Opt.Simplify.Env.adjustJoinPointType
two currently-separate ways in which we adjust the type of
a join point. As the comment says:

-- (adjustJoinPointType mult new_res_ty join_id) does two things:
--
--   1. Set the return type of the join_id to new_res_ty
--      See Note [Return type for join points]
--
--   2. Adjust the multiplicity of arrows in join_id's type, as
--      directed by 'mult'. See Note [Scaling join point arguments]

I think this actually fixes a latent bug, by ensuring that the
seIdSubst and seInScope have the right multiplicity on the type
of join points.

I did some tidying up while I was at it.  No more
setJoinResTy, or modifyJoinResTy: instead it's done locally in
Simplify.Env.adjustJoinPointType
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/49b265f08c7ac9c9dea6cfff0d67447728b7b416">49b265f0</a></strong>
<div>
<span>by Chaitanya Koparkar</span>
<i>at 2020-07-18T07:26:46-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix minor typos in a Core.hs note
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8d59aed6e9f494d6eae41c5ba32cde23cecaeb14">8d59aed6</a></strong>
<div>
<span>by Stefan Schulze Frielinghaus</span>
<i>at 2020-07-18T07:26:47-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">GHCi: Fix isLittleEndian
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c26e81d116a653b5259aeb290fb1e697efe3382a">c26e81d1</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-07-18T07:26:47-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite: Mark ghci tests as fragile under unreg compiler

In particular I have seen T16012 fail repeatedly under the
unregisterised compiler.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/868e452340ade3155dd7e552c16bbb3c21c42b8a">868e4523</a></strong>
<div>
<span>by Moritz Angermann</span>
<i>at 2020-07-20T04:30:38-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Revert "AArch32 symbols only on aarch32."

This reverts commit cdfeb3f24f76e8fd30452016676e56fbc827789a.

Signed-off-by: Moritz Angermann <moritz.angermann@gmail.com>
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c915ba84f4ec8c4f0f006bd6aa938d17936dcd93">c915ba84</a></strong>
<div>
<span>by Moritz Angermann</span>
<i>at 2020-07-20T04:30:38-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Revert "Fix (1)"

This reverts commit 7abffced01f5680efafe44f6be2733eab321b039.

Signed-off-by: Moritz Angermann <moritz.angermann@gmail.com>
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/777c452a83ebdb2b50f3f328255a6f36ae49f398">777c452a</a></strong>
<div>
<span>by Moritz Angermann</span>
<i>at 2020-07-20T04:30:38-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Revert "better if guards."

This reverts commit 3f60b94de1f460ca3f689152860b108a19ce193e.

Signed-off-by: Moritz Angermann <moritz.angermann@gmail.com>
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/0dd405529f0f17cd9a5b299e7ae5539a885b4b5a">0dd40552</a></strong>
<div>
<span>by Moritz Angermann</span>
<i>at 2020-07-20T04:30:38-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Revert "[linker/rtsSymbols] More linker symbols"

This reverts commit 686e72253aed3880268dd6858eadd8c320f09e97.

Signed-off-by: Moritz Angermann <moritz.angermann@gmail.com>
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/30caeee75193ea961c55ee847a3156e23116e84e">30caeee7</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-07-21T06:39:33-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">DynFlags: remove use of sdocWithDynFlags from GHC.Stg.* (#17957)

* add StgPprOpts datatype
* remove Outputable instances for types that need `StgPprOpts` to be
  pretty-printed and explicitly call type specific ppr functions
* add default `panicStgPprOpts` for panic messages (when it's not
  convenient to thread StgPprOpts or DynFlags down to the ppr function
  call)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/863c544c9849e49872acac64b8faea56a3311564">863c544c</a></strong>
<div>
<span>by Mark</span>
<i>at 2020-07-21T06:39:34-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix a typo in existential_quantification.rst</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/05910be1ac5c1f485132d2c8bd1ceb4f86e06db5">05910be1</a></strong>
<div>
<span>by Krzysztof Gogolewski</span>
<i>at 2020-07-21T14:47:07-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add release notes entry for #17816

[skip ci]
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a625719284db7c69fa3d122e829291a16960e85f">a6257192</a></strong>
<div>
<span>by Matthew Pickering</span>
<i>at 2020-07-21T14:47:19-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Use a newtype `Code` for the return type of typed quotations (Proposal #195)

There are three problems with the current API:

1. It is hard to properly write instances for ``Quote m => m (TExp a)`` as the type is the composition
   of two type constructors. Doing so in your program involves making your own newtype and
   doing a lot of wrapping/unwrapping.

   For example, if I want to create a language which I can either run immediately or
   generate code from I could write the following with the new API. ::

      class Lang r where
        _int :: Int -> r Int
        _if  :: r Bool -> r a -> r a -> r a

      instance Lang Identity where
        _int = Identity
        _if (Identity b) (Identity t) (Identity f) = Identity (if b then t else f)

      instance Quote m => Lang (Code m) where
        _int = liftTyped
        _if cb ct cf = [|| if $$cb then $$ct else $$cf ||]

2. When doing code generation it is common to want to store code fragments in
   a map. When doing typed code generation, these code fragments contain a
   type index so it is desirable to store them in one of the parameterised
   map data types such as ``DMap`` from ``dependent-map`` or ``MapF`` from
   ``parameterized-utils``.

   ::

      compiler :: Env -> AST a -> Code Q a

      data AST a where ...
      data Ident a = ...

      type Env = MapF Ident (Code Q)

      newtype Code m a = Code (m (TExp a))

   In this example, the ``MapF`` maps an ``Ident String`` directly to a ``Code Q String``.
   Using one of these map types currently requires creating your own newtype and constantly
   wrapping every quotation and unwrapping it when using a splice. Achievable, but
   it creates even more syntactic noise than normal metaprogramming.

3. ``m (TExp a)`` is ugly to read and write, understanding ``Code m a`` is
   easier. This is a weak reason but one everyone
   can surely agree with.

Updates text submodule.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/58235d46bd4e9fbf69bd82969b29cd9c6ab051e1">58235d46</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-07-21T14:47:28-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">users-guide: Fix :rts-flag:`--copying-gc` documentation

It was missing a newline.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/19e80b9af252eee760dc047765a9930ef00067ec">19e80b9a</a></strong>
<div>
<span>by Vladislav Zavialov</span>
<i>at 2020-07-21T14:50:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Accumulate Haddock comments in P (#17544, #17561, #8944)

Haddock comments are, first and foremost, comments. It's very annoying
to incorporate them into the grammar. We can take advantage of an
important property: adding a Haddock comment does not change the parse
tree in any way other than wrapping some nodes in HsDocTy and the like
(and if it does, that's a bug).

This patch implements the following:

* Accumulate Haddock comments with their locations in the P monad.
  This is handled in the lexer.

* After parsing, do a pass over the AST to associate Haddock comments
  with AST nodes using location info.

* Report the leftover comments to the user as a warning (-Winvalid-haddock).
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4c719460611e7af44a67041c1707cb206d724d58">4c719460</a></strong>
<div>
<span>by David Binder</span>
<i>at 2020-07-22T20:17:35-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix dead link to haskell prime discussion
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/f2f817e4c547657c25bb110199f6f0b6014f843b">f2f817e4</a></strong>
<div>
<span>by BinderDavid</span>
<i>at 2020-07-22T20:17:35-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Replace broken links to old haskell-prime site by working links to gitlab instance.
[skip ci]
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/0bf8980ec86cab8d605149bbf47ed2361e2d389e">0bf8980e</a></strong>
<div>
<span>by Daniel Gröber</span>
<i>at 2020-07-22T20:18:11-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove length field from FastString
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/1010c33bb8704fa55a82bc2601d5cae2e6ecc21f">1010c33b</a></strong>
<div>
<span>by Daniel Gröber</span>
<i>at 2020-07-22T20:18:11-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Use ShortByteString for FastString

There are multiple reasons we want this:

- Fewer allocations: ByteString has 3 fields, ShortByteString just has one.
- ByteString memory is pinned:
  - This can cause fragmentation issues (see for example #13110) but also
  - makes using FastStrings in compact regions impossible.

Metric Decrease:
    T5837
    T12150
    T12234
    T12425
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8336ba78e00ec42521ba8314bc65ec766e6bcc7d">8336ba78</a></strong>
<div>
<span>by Daniel Gröber</span>
<i>at 2020-07-22T20:18:11-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Pass specialised utf8DecodeChar# to utf8DecodeLazy# for performance

Currently we're passing a indexWord8OffAddr# type function to
utf8DecodeLazy# which then passes it on to utf8DecodeChar#. By passing one
of utf8DecodeCharAddr# or utf8DecodeCharByteArray# instead we benefit from
the inlining and specialization already done for those.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7484a9a47ad277bb7e51c6357817f7e7c59e744a">7484a9a4</a></strong>
<div>
<span>by Daniel Gröber</span>
<i>at 2020-07-22T20:18:11-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Encoding: Add comment about tricky ForeignPtr lifetime
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/5536ed28b676106810e65bac15305ad2b1b0babd">5536ed28</a></strong>
<div>
<span>by Daniel Gröber</span>
<i>at 2020-07-22T20:18:11-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Use IO constructor instead of `stToIO . ST`
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/5b8902e3975b8275b027b3d1cfe0d8cb8fdd3d13">5b8902e3</a></strong>
<div>
<span>by Daniel Gröber</span>
<i>at 2020-07-22T20:18:11-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Encoding: Remove redundant use of withForeignPtr
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/5976a1614e3da7d77f624103bb67f602738e93b8">5976a161</a></strong>
<div>
<span>by Daniel Gröber</span>
<i>at 2020-07-22T20:18:11-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Encoding: Reformat utf8EncodeShortByteString to be more consistent
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9ddf161492194edb321b87b1977eda8264df35aa">9ddf1614</a></strong>
<div>
<span>by Daniel Gröber</span>
<i>at 2020-07-22T20:18:11-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">FastString: Reintroduce character count cache

Metric Increase:
    ManyConstructors

Metric Decrease:
    T4029
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e9491668640227a7ae7f6d0506d36af3a10cdd49">e9491668</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-07-22T20:18:46-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">get-win32-tarballs: Fix detection of missing tarballs

This fixes the error message given by configure when the user
attempts to configure without first download the win32 tarballs.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9f3ff8fd24b94c9d4a221e6aba3e21de42b0f02c">9f3ff8fd</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-22T20:19:22-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Enable BangPatterns, ScopedTypeVariables for ghc and hadrian by default.

This is only for their respective codebases.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/0f17b930c164f3130caf2215484a8f5f8aa3cc63">0f17b930</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-07-22T20:19:59-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove unused "ncg" flag

This flag has been removed in 066b369de2c6f7da03c88206288dca29ab061b31
in 2011.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/bab4ec8f62352a6361a5fd2cbdc5f12eca8928e7">bab4ec8f</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-07-22T20:19:59-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Don't panic if the NCG isn't built (it is always built)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8ea33edb2beb64cde7d51777787e232d4cd4fef1">8ea33edb</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-07-22T20:19:59-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove unused sGhcWithNativeCodeGen
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e079bb721e25dbc19e1adf8c8051b6ea03752962">e079bb72</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-07-22T20:19:59-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Correctly test active backend

Previously we used a platform settings to detect if the native code
generator was used. This was wrong. We need to use the
`DynFlags.hscTarget` field instead.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/735f9d6bac316a0c1c68a8b49bba465f07b01cdd">735f9d6b</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-07-22T20:19:59-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Replace ghcWithNativeCodeGen with a proper Backend datatype

* Represent backends with a `Backend` datatype in GHC.Driver.Backend

* Don't detect the default backend to use for the target platform at
  compile time in Hadrian/make but at runtime. It makes "Settings"
  simpler and it is a step toward making GHC multi-target.

* The latter change also fixes hadrian which has not been updated to
  take into account that the NCG now supports AIX and PPC64 (cf
  df26b95559fd467abc0a3a4151127c95cb5011b9 and
  d3c1dda60d0ec07fc7f593bfd83ec9457dfa7984)

* Also we don't treat iOS specifically anymore (cf
  cb4878ffd18a3c70f98bdbb413cd3c4d1f054e1f)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/f7cc431341e5b5b31758eecc8504cae8b2390c10">f7cc4313</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-07-22T20:19:59-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Replace HscTarget with Backend

They both have the same role and Backend name is more explicit.

Metric Decrease:
    T3064

Update Haddock submodule
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/15ce1804d2b87ac7bd55632957a4cb897decbbee">15ce1804</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-22T20:20:34-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Deprecate -fdmd-tx-dict-sel.

It's behaviour is now unconditionally enabled as
it's slightly beneficial.

There are almost no benchmarks which benefit from
disabling it, so it's not worth the keep this
configurable.

This fixes #18429.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ff1b7710c9975a3cc1025cb5b9d29197a5f1a98a">ff1b7710</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-07-22T20:21:11-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add test for #18064

It has been fixed by 0effc57d48ace6b719a9f4cbeac67c95ad55010b
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/cfa89149b55837f822ba619b797781813fdcdabc">cfa89149</a></strong>
<div>
<span>by Krzysztof Gogolewski</span>
<i>at 2020-07-22T20:21:48-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Define type Void# = (# #) (#18441)

There's one backwards compatibility issue: GHC.Prim no longer exports
Void#, we now manually re-export it from GHC.Exts.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/02f40b0da2eadbf8a0e2930b95d4cef686acd92f">02f40b0d</a></strong>
<div>
<span>by Sebastian Graf</span>
<i>at 2020-07-22T20:22:23-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add regression test for #18478

!3392 backported !2993 to GHC 8.10.2 which most probably is responsible
for fixing #18478, which triggered a pattern match checker performance
regression in GHC 8.10.1 as first observed in #17977.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7f44df1ec6df2b02be83e41cec4dc3b5f7f540f0">7f44df1e</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-07-22T20:23:00-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Minor refactoring of Unit display

* for consistency, try to always use UnitPprInfo to display units to
  users

* remove some uses of `unitPackageIdString` as it doesn't show the
  component name and it uses String
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/dff1cb3d9c111808fec60190747272b973547c52">dff1cb3d</a></strong>
<div>
<span>by Moritz Angermann</span>
<i>at 2020-07-23T07:55:29-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">[linker] Fix out of range relocations.

mmap may return address all over the place. mmap_next will ensure we get
the next free page after the requested address.

This is especially important for linking on aarch64, where the memory model with PIC
admits relocations in the +-4GB range, and as such we can't work with
arbitrary object locations in memory.

Of note: we map the rts into process space, so any mapped objects must
not be ouside of the 4GB from the processes address space.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/cdd0ff16f20ce920c74f9128a1067cbe1bd378c2">cdd0ff16</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-24T18:12:23-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: restore console cp on exit
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c1f4f81d3a439cd1a8128e4ab11c7caac7cc0ad8">c1f4f81d</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-24T18:13:00-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: change memory allocation strategy and fix double free errors.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ba205046e4f2ea94b1c978c050b917de4daaf092">ba205046</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-07-24T18:13:35-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Care with occCheckExpand in kind of occurrences

Issue #18451 showed that we could get an infinite type, through
over-use of occCheckExpand in the kind of an /occurrence/ of a
type variable.

See Note [Occurrence checking: look inside kinds] in GHC.Core.Type

This patch fixes the problem by making occCheckExpand less eager
to expand synonyms in kinds.

It also improves pretty printing of kinds, by *not* suppressing
the kind on a tyvar-binder like
    (a :: Const Type b)
where type Const p q = p.  Even though the kind of 'a' is Type,
we don't want to suppress the kind ascription.  Example: the
error message for polykinds/T18451{a,b}. See GHC.Core.TyCo.Ppr
Note [Suppressing * kinds].
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/02133353e712e98bfbbc6ed32305b137bb3654eb">02133353</a></strong>
<div>
<span>by Zubin Duggal</span>
<i>at 2020-07-25T00:44:30-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Simplify XRec definition
Change `Located X` usage to `XRec pass X`
This increases the scope of the LPat experiment to almost all of GHC.
Introduce UnXRec and MapXRec classes

Fixes #17587 and #18408

Updates haddock submodule

Co-authored-by: Philipp Krüger <philipp.krueger1@gmail.com>
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e443846ba05c943877e193a9518d5817e15560f3">e443846b</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-07-25T00:45:07-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">DynFlags: store printer in TraceBinIfaceReading

We don't need to pass the whole DynFlags, just pass the logging
function, if any.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/15b2b44fe35292dc3ac93ec215c44fba42165f67">15b2b44f</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-07-25T00:45:08-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Rename GHC.Driver.Ways into GHC.Platform.Ways
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/342a01af624840ba94f22256079ff4f3cee09ca2">342a01af</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-07-25T00:45:08-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add GHC.Platform.Profile
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6333d7391068d8029eed3e8eff019b9e2c104c7b">6333d739</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-07-25T00:45:08-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Put PlatformConstants into Platform
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9dfeca6c2019fdb46613a68ccd6e650e40c7baac">9dfeca6c</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-07-25T00:45:08-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove platform constant wrappers

Platform constant wrappers took a DynFlags parameter, hence implicitly
used the target platform constants. We removed them to allow support
for several platforms at once (#14335) and to avoid having to pass
the full DynFlags to every function (#17957).

Metric Decrease:
   T4801
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/73145d57f961c73b5853da7881d6a21e48e05909">73145d57</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-07-25T00:45:08-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove dead code in utils/derivConstants
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7721b923d53fb9eb93f80bb93b4c3bd976c05b4c">7721b923</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-07-25T00:45:08-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Move GHC.Platform into the compiler

Previously it was in ghc-boot so that ghc-pkg could use it. However it
wasn't necessary because ghc-pkg only uses a subset of it: reading
target arch and OS from the settings file. This is now done via
GHC.Platform.ArchOS (was called PlatformMini before).
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/459afeb592d5ff6d338184f5ef248758ecda57a4">459afeb5</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-07-25T00:45:08-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix build systems
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9e2930c3e18235fda2b8b468cb0fefbe7d65f879">9e2930c3</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-07-25T00:45:08-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Bump CountParserDeps
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6e2db34bdfead7ad309d8fd01d4423554650cf4c">6e2db34b</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-07-25T00:45:08-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add accessors to ArchOS
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/fc0f6fbcd95f2dc69a8efabbee2d8a485c34cc47">fc0f6fbc</a></strong>
<div>
<span>by Stefan Schulze Frielinghaus</span>
<i>at 2020-07-25T00:45:45-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Require SMP support in order to build a threaded stage1

Fixes 18266
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a7c4439a407ad85b76aab9301fda61e7c10183ff">a7c4439a</a></strong>
<div>
<span>by Matthias Andreas Benkard</span>
<i>at 2020-07-26T13:23:24-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Document loadFramework changes. (#18446)

Adds commentary on the rationale for the changes made in merge request
!3689.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/da7269a4472856ba701d956a247599f721e9915e">da7269a4</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-07-26T13:23:59-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts/win32: Exit with EXIT_HEAPOVERFLOW if memory commit fails

Since switching to the two-step allocator, the `outofmem` test fails via
`osCommitMemory` failing to commit. However, this was previously exiting
with `EXIT_FAILURE`, rather than `EXIT_HEAPOVERFLOW`. I think the latter
is a more reasonable exit code for this case and matches the behavior on
POSIX platforms.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/f153a1d0a3351ad4d94cef4cef8e63bab5b47008">f153a1d0</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-07-26T13:23:59-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite: Update win32 output for parseTree
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e91672f0b7185bbafbe8ed1f2ae2cb775111f950">e91672f0</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-07-26T13:23:59-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite: Normalise WinIO error message differences

Previously the old Windows IO manager threw different errors than WinIO.
We now canonicalise these to the WinIO errors.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9cbfe0868418a531da0872b0c477a15aa67f8861">9cbfe086</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-07-26T13:23:59-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">gitlab-ci: Kill ssh-agent after pushing test metrics

Otherwise the Windows builds hang forever waiting for the process to
terminate.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8236925fc8cc2e6e3fed61a0676fa65270a4a538">8236925f</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-26T13:24:35-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: remove dead argument to stg_newIOPortzh
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ce0a1d678fbc8efa5fd384fd0227b7b3dc97cadd">ce0a1d67</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-26T13:25:11-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: fix detection of tty terminals
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/52685cf7c077c51e3719e3c4dd5ca8257a99c4ea">52685cf7</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-26T13:25:48-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: update codeowners
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/aee45d9ea8c6cf4ebad4d5c732748923c7865cbe">aee45d9e</a></strong>
<div>
<span>by Vladislav Zavialov</span>
<i>at 2020-07-27T07:06:56-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Improve NegativeLiterals (#18022, GHC Proposal #344)

Before this patch, NegativeLiterals used to parse x-1 as x (-1).

This may not be what the user expects, and now it is fixed:
x-1 is parsed as (-) x 1.

We achieve this by the following requirement:

  * When lexing a negative literal,
    it must not be preceded by a 'closing token'.

This also applies to unboxed literals, e.g. -1#.

See GHC Proposal #229 for the definition of a closing token.

A nice consequence of this change is that -XNegativeLiterals becomes a
subset of -XLexicalNegation. In other words, enabling both of those
extensions has the same effect as enabling -XLexicalNegation alone.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/667ab69e5edacb2ce2f42fb810cd54c8f856d30b">667ab69e</a></strong>
<div>
<span>by leiftw</span>
<i>at 2020-07-27T07:07:32-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">fix typo referring to non-existent `-ohidir` flag, should be `-hidir` I think</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6ff89c173f39813f74d7bbf95770c5e40039f155">6ff89c17</a></strong>
<div>
<span>by Vladislav Zavialov</span>
<i>at 2020-07-27T07:08:07-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Refactor the parser a little

* Create a dedicated production for type operators
* Create a dedicated type for the UNPACK pragma
* Remove an outdated part of Note [Parsing data constructors is hard]
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/aa054d32a8ff69c334293a0d6c9d11b83a236a96">aa054d32</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-07-27T20:09:07-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Drop 32-bit Windows support

As noted in #18487, we have reached the end of this road.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6da73bbf97cca8bd64d70a26298e7f7ddad2ce52">6da73bbf</a></strong>
<div>
<span>by Michalis Pardalos</span>
<i>at 2020-07-27T20:09:44-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add minimal test for #12492
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/47680cb76b068508fd16d052e0a3bed12e38ea5f">47680cb7</a></strong>
<div>
<span>by Michalis Pardalos</span>
<i>at 2020-07-27T20:09:44-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Use allocate, not ALLOC_PRIM_P for unpackClosure#

ALLOC_PRIM_P fails for large closures, by directly using allocate
we can handle closures which are larger than the block size.

Fixes #12492
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/3d345c9680ab3d766ef43dd8389ccc1eaeca066c">3d345c96</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-07-27T20:10:19-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Eta-expand the Simplifier monad

This patch eta-expands the Simplifier's monad, using the method
explained in GHC.Core.Unify Note [The one-shot state monad trick].
It's part of the exta-expansion programme in #18202.

It's a tiny patch, but is worth a 1-2% reduction in bytes-allocated
by the compiler.  Here's the list, based on the compiler-performance
tests in perf/compiler:

                    Reduction in bytes allocated
   T10858(normal)      -0.7%
   T12425(optasm)      -1.3%
   T13056(optasm)      -1.8%
   T14683(normal)      -1.1%
   T15164(normal)      -1.3%
   T15630(normal)      -1.4%
   T17516(normal)      -2.3%
   T18282(normal)      -1.6%
   T18304(normal)      -0.8%
   T1969(normal)       -0.6%
   T4801(normal)       -0.8%
   T5321FD(normal)     -0.7%
   T5321Fun(normal)    -0.5%
   T5642(normal)       -0.9%
   T6048(optasm)       -1.1%
   T9020(optasm)       -2.7%
   T9233(normal)       -0.7%
   T9675(optasm)       -0.5%
   T9961(normal)       -2.9%
   WWRec(normal)       -1.2%

Metric Decrease:
    T12425
    T9020
    T9961
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/57aca6bba1c000f8542ce94e8b724b0334ff96d4">57aca6bb</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-07-27T20:10:54-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">gitlab-ci: Ensure that Hadrian jobs don't download artifacts

Previously the Hadrian jobs had the default dependencies, meaning that
they would download artifacts from all jobs of earlier stages. This is
unneccessary.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/0a815cea9fa11ce6ef22aec3525dd7a0df541daf">0a815cea</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-07-27T20:10:54-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">gitlab-ci: Bump bootstrap compiler to 8.8.4

Hopefully this will make the Windows jobs a bit more reliable.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/0bd60059b0edfee9e8f66c6817257bbb946656cd">0bd60059</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-07-28T02:01:49-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">This patch addresses the exponential blow-up in the simplifier.

Specifically:
  #13253 exponential inlining
  #10421 ditto
  #18140 strict constructors
  #18282 another nested-function call case

This patch makes one really significant changes: change the way that
mkDupableCont handles StrictArg.  The details are explained in
GHC.Core.Opt.Simplify Note [Duplicating StrictArg].

Specific changes

* In mkDupableCont, when making auxiliary bindings for the other arguments
  of a call, add extra plumbing so that we don't forget the demand on them.
  Otherwise we haev to wait for another round of strictness analysis. But
  actually all the info is to hand.  This change affects:
  - Make the strictness list in ArgInfo be [Demand] instead of [Bool],
    and rename it to ai_dmds.
  - Add as_dmd to ValArg
  - Simplify.makeTrivial takes a Demand
  - mkDupableContWithDmds takes a [Demand]

There are a number of other small changes

1. For Ids that are used at most once in each branch of a case, make
   the occurrence analyser record the total number of syntactic
   occurrences.  Previously we recorded just OneBranch or
   MultipleBranches.

   I thought this was going to be useful, but I ended up barely
   using it; see Note [Note [Suppress exponential blowup] in
   GHC.Core.Opt.Simplify.Utils

   Actual changes:
     * See the occ_n_br field of OneOcc.
     * postInlineUnconditionally

2. I found a small perf buglet in SetLevels; see the new
   function GHC.Core.Opt.SetLevels.hasFreeJoin

3. Remove the sc_cci field of StrictArg.  I found I could get
   its information from the sc_fun field instead.  Less to get
   wrong!

4. In ArgInfo, arrange that ai_dmds and ai_discs have a simpler
   invariant: they line up with the value arguments beyond ai_args
   This allowed a bit of nice refactoring; see isStrictArgInfo,
   lazyArgcontext, strictArgContext

There is virtually no difference in nofib. (The runtime numbers
are bogus -- I tried a few manually.)

        Program           Size    Allocs   Runtime   Elapsed  TotalMem
--------------------------------------------------------------------------------
            fft          +0.0%     -2.0%    -48.3%    -49.4%      0.0%
     multiplier          +0.0%     -2.2%    -50.3%    -50.9%      0.0%
--------------------------------------------------------------------------------
            Min          -0.4%     -2.2%    -59.2%    -60.4%      0.0%
            Max          +0.0%     +0.1%     +3.3%     +4.9%      0.0%
 Geometric Mean          +0.0%     -0.0%    -33.2%    -34.3%     -0.0%

Test T18282 is an existing example of these deeply-nested strict calls.
We get a big decrease in compile time (-85%) because so much less
inlining takes place.

Metric Decrease:
    T18282
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6ee07b494ddd0131d53ea2fd6a4bb29cd05f4dd8">6ee07b49</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-07-28T02:02:27-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Bignum: add support for negative shifts (fix #18499)

shiftR/shiftL support negative arguments despite Haskell 2010 report
saying otherwise. We explicitly test for negative values which is bad
(it gets in the way of constant folding, etc.). Anyway, for consistency
we fix Bits instancesof Integer/Natural.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/f305bbfd0d7afee8fe7464252fbfc167205220ae">f305bbfd</a></strong>
<div>
<span>by Peter Trommler</span>
<i>at 2020-07-28T02:03:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">config: Fix Haskell platform constructor w/ params

Fixes #18505
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/318bb17c9d3fbbe68eff706c38eb8e653cea3d83">318bb17c</a></strong>
<div>
<span>by Oleg Grenrus</span>
<i>at 2020-07-28T20:54:13-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix typo in haddock

Spotted by `vilpan` on `#haskell`
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/39c89862161bf488a6aca9372cbb67690f436ce7">39c89862</a></strong>
<div>
<span>by Sergei Trofimovich</span>
<i>at 2020-07-28T20:54:50-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">ghc/mk: don't build gmp packages for BIGNUM_BACKEND=native

Before this change make-based `BIGNUM_BACKEND=native` build was failing as:

```
x86_64-pc-linux-gnu-gcc: error: libraries/ghc-bignum/gmp/objs/*.o: No such file or directory
```

This happens because ghc.mk was pulling in gmp-dependent
ghc-bignum library unconditionally. The change avoid building
ghc-bignum.

Bug: https://gitlab.haskell.org/ghc/ghc/-/issues/18437
Signed-off-by: Sergei Trofimovich <slyfox@gentoo.org>
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b9a880fce484d0a87bb794b9d2d8a73e54819011">b9a880fc</a></strong>
<div>
<span>by Felix Wiemuth</span>
<i>at 2020-07-29T15:06:35-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix typo</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c59064b0c60d3d779f5fd067be4b6648d8de23cf">c59064b0</a></strong>
<div>
<span>by Brandon Chinn</span>
<i>at 2020-07-29T15:07:11-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add regression test for #16341
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a61411cab31fcc08f1dcd629b85c736e2b5b6bc7">a61411ca</a></strong>
<div>
<span>by Brandon Chinn</span>
<i>at 2020-07-29T15:07:11-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Pass dit_rep_tc_args to dsm_stock_gen_fn
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a26498daa4d87a15b3e829c204ed6e9b4323f684">a26498da</a></strong>
<div>
<span>by Brandon Chinn</span>
<i>at 2020-07-29T15:07:11-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Pass tc_args to gen_fn
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/44b11bad052eabf43246acba6aab814376b08713">44b11bad</a></strong>
<div>
<span>by Brandon Chinn</span>
<i>at 2020-07-29T15:07:11-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Filter out unreachable constructors when deriving stock instances (#16431)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/bbc5191640761ca9773abc898c077363b7beb4e7">bbc51916</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-07-29T15:07:47-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Kill off sc_mult and as_mult fields

They are readily derivable from other fields, so this is more
efficient, and less error prone.

Fixes #18494
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e3db4b4c5b7f5d2a62ebd88e174fca07d04c4e18">e3db4b4c</a></strong>
<div>
<span>by Peter Trommler</span>
<i>at 2020-07-29T15:08:22-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">configure: Fix build system on ARM
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/96c31ea1f0303ebabc59edccff2e88444fe02722">96c31ea1</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-07-29T15:09:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix bug in Natural multiplication (fix #18509)

A bug was lingering in Natural multiplication (inverting two limbs)
despite QuickCheck tests used during the development leading to wrong
results (independently of the selected backend).
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e1dc3d7b89ea79aea158ee487234d3730e857f04">e1dc3d7b</a></strong>
<div>
<span>by Krzysztof Gogolewski</span>
<i>at 2020-07-29T15:09:39-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix validation errors (#18510)

Test T2632 is a stage1 test that failed because of the Q => Quote change.

The remaining tests did not use quotation and failed when the path
contained a space.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6c68a84254d70280e2dc73485f361787a3503850">6c68a842</a></strong>
<div>
<span>by John Ericson</span>
<i>at 2020-07-30T07:11:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">For `-fkeep-going` do not duplicate dependency edge code

We now compute the deps for `-fkeep-going` the same way that the
original graph calculates them, so the edges are correct. Upsweep really
ought to take the graph rather than a topological sort so we are never
recalculating anything, but at least things are recaluclated
consistently now.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/502de55676a38572db60848c13392f5f115e1c8a">502de556</a></strong>
<div>
<span>by cgibbard</span>
<i>at 2020-07-30T07:11:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add haddock comment for unfilteredEdges
and move the note about drop_hs_boot_nodes into it.</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/01c948eba4bea2d2c8ad340e12c1e7b732b334f7">01c948eb</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-07-30T07:11:37-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Clean up the inferred type variable restriction

This patch primarily:

* Documents `checkInferredVars` (previously called
  `check_inferred_vars`) more carefully. This is the
  function which throws an error message if a user quantifies an
  inferred type variable in a place where specificity cannot be
  observed. See `Note [Unobservably inferred type variables]` in
  `GHC.Rename.HsType`.

  Note that I now invoke `checkInferredVars` _alongside_
  `rnHsSigType`, `rnHsWcSigType`, etc. rather than doing so _inside_
  of these functions. This results in slightly more call sites for
  `checkInferredVars`, but it makes it much easier to enumerate the
  spots where the inferred type variable restriction comes into
  effect.
* Removes the inferred type variable restriction for default method
  type signatures, per the discussion in #18432. As a result, this
  patch fixes #18432.

Along the way, I performed some various cleanup:

* I moved `no_nested_foralls_contexts_err` into `GHC.Rename.Utils`
  (under the new name `noNestedForallsContextsErr`), since it now
  needs to be invoked from multiple modules. I also added a helper
  function `addNoNestedForallsContextsErr` that throws the error
  message after producing it, as this is a common idiom.
* In order to ensure that users cannot sneak inferred type variables
  into `SPECIALISE instance` pragmas by way of nested `forall`s, I
  now invoke `addNoNestedForallsContextsErr` when renaming
  `SPECIALISE instance` pragmas, much like when we rename normal
  instance declarations. (This probably should have originally been
  done as a part of the fix for #18240, but this task was somehow
  overlooked.) As a result, this patch fixes #18455 as a side effect.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d47324ce49b0c4f419823cbd7fd47e134a1b255a">d47324ce</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-07-30T07:12:16-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Don't mark closed type family equations as occurrences

Previously, `rnFamInstEqn` would mark the name of the type/data
family used in an equation as an occurrence, regardless of what sort
of family it is. Most of the time, this is the correct thing to do.
The exception is closed type families, whose equations constitute its
definition and therefore should not be marked as occurrences.
Overzealously counting the equations of a closed type family as
occurrences can cause certain warnings to not be emitted, as observed
in #18470.  See `Note [Type family equations and occurrences]` in
`GHC.Rename.Module` for the full story.

This fixes #18470 with a little bit of extra-casing in
`rnFamInstEqn`. To accomplish this, I added an extra
`ClosedTyFamInfo` field to the `NonAssocTyFamEqn` constructor of
`AssocTyFamInfo` and refactored the relevant call sites accordingly
so that this information is propagated to `rnFamInstEqn`.

While I was in town, I moved `wrongTyFamName`, which checks that the
name of a closed type family matches the name in an equation for that
family, from the renamer to the typechecker to avoid the need for an
`ASSERT`. As an added bonus, this lets us simplify the details of
`ClosedTyFamInfo` a bit.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ebe2cf4538fa46994ef67663ac8fd5e579579803">ebe2cf45</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-07-30T07:12:52-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove an incorrect WARN in extendLocalRdrEnv

I noticed this warning going off, and discovered that it's
really fine.  This small patch removes the warning, and docments
what is going on.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9f71f69714255165d0fdc2790a588487ff9439dc">9f71f697</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-07-30T07:13:27-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add two bangs to improve perf of flattening

This tiny patch improves the compile time of flatten-heavy
programs by 1-2%, by adding two bangs.

Addresses (somewhat) #18502

This reduces allocation by
   T9872b   -1.1%
   T9872d   -3.3%

   T5321Fun -0.2%
   T5631    -0.2%
   T5837    +0.1%
   T6048    +0.1%

Metric Decrease:
    T9872b
    T9872d
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7c274cd530cc42a26028050b75d56b3437e06ec1">7c274cd5</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-07-30T22:54:48-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix minimal imports dump for boot files (fix #18497)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/175cb5b4044e6f4ad2224f54115f42e7a8b08f9b">175cb5b4</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-07-30T22:55:25-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">DynFlags: don't use sdocWithDynFlags in datacon ppr

We don't need to use `sdocWithDynFlags` to know whether we should
display linear types for datacon types, we already have
`sdocLinearTypes` field in `SDocContext`.  Moreover we want to remove
`sdocWithDynFlags` (#10143, #17957)).
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/380638a33691ba43fdcd2e18bca636750e5f66f1">380638a3</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-07-30T22:56:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Bignum: fix powMod for gmp backend (#18515)

Also reenable integerPowMod test which had never been reenabled by
mistake.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/56a7c19337c5b2aa21d521a6d7c965174ec8379b">56a7c193</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-07-31T19:32:09+02:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Refactor CLabel pretty-printing

Pretty-printing CLabel relies on sdocWithDynFlags that we want to remove
(#10143, #17957). It uses it to query the backend and the platform.

This patch exposes Clabel ppr functions specialised for each backend so
that backend code can directly use them.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/3b15dc3cfb1a33e3d4d952af62d4d0b841a731f5">3b15dc3c</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-07-31T19:32:09+02:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">DynFlags: don't use sdocWithDynFlags in GHC.CmmToAsm.Dwarf.Types
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e30fed6c6de1f881ce313900274294a793e42677">e30fed6c</a></strong>
<div>
<span>by Vladislav Zavialov</span>
<i>at 2020-08-01T04:23:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Test case for #17652

The issue was fixed by 19e80b9af252eee760dc047765a9930ef00067ec
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/226417424b2b578fd3c5424588367cb24e7720eb">22641742</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-08-02T16:44:11-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove ConDeclGADTPrefixPs

This removes the `ConDeclGADTPrefixPs` per the discussion in #18517.
Most of this patch simply removes code, although the code in the
`rnConDecl` case for `ConDeclGADTPrefixPs` had to be moved around a
bit:

* The nested `forall`s check now lives in the `rnConDecl` case for
  `ConDeclGADT`.
* The `LinearTypes`-specific code that used to live in the
  `rnConDecl` case for `ConDeclGADTPrefixPs` now lives in
  `GHC.Parser.PostProcess.mkGadtDecl`, which is now monadic so that
  it can check if `-XLinearTypes` is enabled.

Fixes #18157.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/f2d1accf67cb6e1dab6b2c78fef4b64526c31a4a">f2d1accf</a></strong>
<div>
<span>by Leon Schoorl</span>
<i>at 2020-08-02T16:44:47-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix GHC_STAGE definition generated by make

Fixes #18070

GHC_STAGE is the stage of the compiler we're building, it should be 1,2(,3?).
But make was generating 0 and 1.

Hadrian does this correctly using a similar `+ 1`:
https://gitlab.haskell.org/ghc/ghc/-/blob/eb8115a8c4cbc842b66798480fefc7ab64d31931/hadrian/src/Rules/Generate.hs#L245
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/947206f478d4eef641dfc58cb4c13471a23260c3">947206f4</a></strong>
<div>
<span>by Niklas Hambüchen</span>
<i>at 2020-08-03T07:52:33+02:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">hadrian: Fix running stage0/bin/ghc with wrong package DB. Fixes #17468.

In the invocation of `cabal configure`, `--ghc-pkg-option=--global-package-db`
was already given correctly to tell `stage0/bin/ghc-pkg` that it should use
the package DB in `stage1/`.

However, `ghc` needs to be given this information as well, not only `ghc-pkg`!
Until now that was not the case; the package DB in `stage0` was given to
`ghc` instead.
This was wrong, because there is no binary compatibility guarantee that says
that the `stage0` DB's `package.cache` (which is written by the
stage0 == system-provided ghc-pkg) can be deserialised by the `ghc-pkg`
from the source code tree.

As a result, when trying to add fields to `InstalledPackageInfo` that get
serialised into / deserialised from the `package.cache`, errors like

    _build/stage0/lib/package.conf.d/package.cache: GHC.PackageDb.readPackageDb: inappropriate type (Not a valid Unicode code point!)

would appear. This was because the `stage0/bin/ghc would try to
deserialise the newly added fields from
`_build/stage0/lib/package.conf.d/package.cache`, but they were not in there
because the system `ghc-pkg` doesn't know about them and thus didn't write them
there.
It would try to do that because any GHC by default tries to read the global
package db in `../lib/package.conf.d/package.cache`.
For `stage0/bin/ghc` that *can never work* as explained above, so we
must disable this default via `-no-global-package-db` and give it the
correct package DB explicitly.

This is the same problem as #16534, and the same fix as in MR !780
(but in another context; that one was for developers trying out the
`stage0/bin/ghc` == `_build/ghc-stage1` interactively, while this fix
is for a `cabal configure` invocation).

I also noticed that the fix for #16534 forgot to pass `-no-global-package-db`,
and have fixed that in this commit as well.
It only worked until now because nobody tried to add a new ghc-pkg `.conf`
field since the introduction of Hadrian.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ef2ae81a394df573510b12b7e11bba0c931249d8">ef2ae81a</a></strong>
<div>
<span>by Alex Biehl</span>
<i>at 2020-08-03T07:52:33+02:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Hardcode RTS includes to cope with unregistered builds
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d613ed7624cbf39192d2a8cf29ab0c0fd2980a15">d613ed76</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-08-05T03:59:27-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Bignum: add backward compat integer-gmp functions

Also enhance bigNatCheck# and isValidNatural test
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/3f2f771869c65125ba013a5dd2b213061efe0fc2">3f2f7718</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-08-05T03:59:27-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Bignum: add more BigNat compat functions in integer-gmp
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/5e12cd1733b581f48a5873b12971b6974778eabb">5e12cd17</a></strong>
<div>
<span>by Krzysztof Gogolewski</span>
<i>at 2020-08-05T04:00:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Rename Core.Opt.Driver -> Core.Opt.Pipeline

Closes #18504.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2bff2f87e43985e02bdde8c6fa39279df86cb617">2bff2f87</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-08-05T04:00:39-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Revert "iserv: Don't pass --export-dynamic on FreeBSD"

This reverts commit 2290eb02cf95e9cfffcb15fc9c593d5ef79c75d9.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/53ce0db5a06598c88c6b8cb32043b878e7083dd4">53ce0db5</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-08-05T04:00:39-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Refactor handling of object merging

Previously to merge a set of object files we would invoke the linker as
usual, adding -r to the command-line. However, this can result in
non-sensical command-lines which causes lld to balk (#17962).

To avoid this we introduce a new tool setting into GHC, -pgmlm, which is
the linker which we use to merge object files.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/eb7013c3037538aa9c947a21dbbfd7c297929ac8">eb7013c3</a></strong>
<div>
<span>by Hécate</span>
<i>at 2020-08-05T04:01:15-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove all the unnecessary LANGUAGE pragmas
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/fbcb886d503dd7aaebc4c40e59615068b3fd0bd7">fbcb886d</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-08-05T04:01:51-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Make CodeQ and TExpQ levity polymorphic

The patch is quite straightforward. The only tricky part is that
`Language.Haskell.TH.Lib.Internal` now must be `Trustworthy` instead
of `Safe` due to the `GHC.Exts` import (in order to import `TYPE`).

Since `CodeQ` has yet to appear in any released version of
`template-haskell`, I didn't bother mentioning the change to `CodeQ`
in the `template-haskell` release notes.

Fixes #18521.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/686e06c59c3aa6b66895e8a501c7afb019b09e36">686e06c5</a></strong>
<div>
<span>by Vladislav Zavialov</span>
<i>at 2020-08-06T13:34:05-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Grammar for types and data/newtype constructors

Before this patch, we parsed types into a reversed sequence
of operators and operands. For example, (F x y + G a b * X)
would be parsed as [X, *, b, a, G, +, y, x, F],
using a simple grammar:

        tyapps
          : tyapp
          | tyapps tyapp

        tyapp
          : atype
          | PREFIX_AT atype
          | tyop
          | unpackedness

Then we used a hand-written state machine to assemble this
 either into a type,        using 'mergeOps',
     or into a constructor, using 'mergeDataCon'.

This is due to a syntactic ambiguity:

        data T1 a =          MkT1 a
        data T2 a = Ord a => MkT2 a

In T1, what follows after the = sign is a data/newtype constructor
declaration. However, in T2, what follows is a type (of kind
Constraint). We don't know which of the two we are parsing until we
encounter =>, and we cannot check for => without unlimited lookahead.

This poses a few issues when it comes to e.g. infix operators:

        data I1 = Int :+ Bool :+ Char          -- bad
        data I2 = Int :+ Bool :+ Char => MkI2  -- fine

By this issue alone we are forced into parsing into an intermediate
representation and doing a separate validation pass.

However, should that intermediate representation be as low-level as a
flat sequence of operators and operands?

Before GHC Proposal #229, the answer was Yes, due to some particularly
nasty corner cases:

        data T = ! A :+ ! B          -- used to be fine, hard to parse
        data T = ! A :+ ! B => MkT   -- bad

However, now the answer is No, as this corner case is gone:

        data T = ! A :+ ! B          -- bad
        data T = ! A :+ ! B => MkT   -- bad

This means we can write a proper grammar for types, overloading it in
the DisambECP style, see Note [Ambiguous syntactic categories].

With this patch, we introduce a new class, DisambTD. Just like
DisambECP is used to disambiguate between expressions, commands, and patterns,
DisambTD  is used to disambiguate between types and data/newtype constructors.

This way, we get a proper, declarative grammar for constructors and
types:

        infixtype
          : ftype
          | ftype tyop infixtype
          | unpackedness infixtype

        ftype
          : atype
          | tyop
          | ftype tyarg
          | ftype PREFIX_AT tyarg

        tyarg
          : atype
          | unpackedness atype

And having a grammar for types means we are a step closer to using a
single grammar for types and expressions.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6770e199645b0753d2edfddc68c199861a1be980">6770e199</a></strong>
<div>
<span>by Vladislav Zavialov</span>
<i>at 2020-08-06T13:34:05-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Clean up the story around runPV/runECP_P/runECP_PV

This patch started as a small documentation change, an attempt to make
Note [Parser-Validator] and Note [Ambiguous syntactic categories]
more clear and up-to-date.

But it turned out that runECP_P/runECP_PV are weakly motivated,
and it's easier to remove them than to find a good rationale/explanation
for their existence.

As the result, there's a bit of refactoring in addition to
a documentation update.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/826d07db0e0f31fe2b2d2e0661be7f0cb3cde3c7">826d07db</a></strong>
<div>
<span>by Vladislav Zavialov</span>
<i>at 2020-08-06T13:34:06-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix debug_ppr_ty ForAllTy (#18522)

Before this change, GHC would
pretty-print   forall k. forall a -> ()
          as   forall @k a. ()
which isn't even valid Haskell.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/0ddb43848b9fc24f5404915f57dc504546e68292">0ddb4384</a></strong>
<div>
<span>by Vladislav Zavialov</span>
<i>at 2020-08-06T13:34:06-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix visible forall in ppr_ty (#18522)

Before this patch, this type:
  T :: forall k -> (k ~ k) => forall j -> k -> j -> Type
was printed incorrectly as:
  T :: forall k j -> (k ~ k) => k -> j -> Type
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d2a432258fa00e22ca386ef30d0a77ff5b277db8">d2a43225</a></strong>
<div>
<span>by Richard Eisenberg</span>
<i>at 2020-08-06T13:34:06-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fail eagerly on a lev-poly datacon arg

Close #18534.

See commentary in the patch.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/63348155404c64334fa864454132630f9d2a4d7f">63348155</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-08-06T13:34:08-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Use a type alias for Ways
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9570c21295a2b4a1d1e40939869124f0b9b9bf91">9570c212</a></strong>
<div>
<span>by Takenobu Tani</span>
<i>at 2020-08-06T19:46:46-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">users-guide: Rename 8.12 to 9.0

GHC 8.12.1 has been renamed to GHC 9.0.1.

See also:
  https://mail.haskell.org/pipermail/ghc-devs/2020-July/019083.html

[skip ci]
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/3907ee01e68b383fa30386d163decf203acedb19">3907ee01</a></strong>
<div>
<span>by Cale Gibbard</span>
<i>at 2020-08-07T08:34:46-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">A fix to an error message in monad comprehensions, and a move of dsHandleMonadicFailure
as suggested by comments on !2330.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/fa9bb70a3fefef681cb0e80cc78977386c1dcf0a">fa9bb70a</a></strong>
<div>
<span>by Cale Gibbard</span>
<i>at 2020-08-07T08:34:46-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add some tests for fail messages in do-expressions and monad-comprehensions.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/5f03606319f745b10e9918c76a47426b293f0bf9">5f036063</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-08-07T08:35:21-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">cmm: Clean up Notes a bit
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6402c1240d5bd768b8fe8b4368413932bedbe107">6402c124</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-08-07T08:35:21-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">CmmLint: Check foreign call argument register invariant

As mentioned in Note [Register parameter passing] the arguments of
foreign calls cannot refer to caller-saved registers.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/15b36de030ecdd60897bc7a6a02bdeabd0825be4">15b36de0</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-08-07T08:35:21-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">nativeGen: One approach to fix #18527

Previously the code generator could produce corrupt C call sequences due
to register overlap between MachOp lowerings and the platform's calling
convention. We fix this using a hack described in Note [Evaluate C-call
arguments before placing in destination registers].
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/3847ae0ccf67bddf73304a39f5320c3ba285aa48">3847ae0c</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-08-07T08:35:21-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite: Add test for #18527
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/dd51d53be42114c105b5ab15fcbdb387526b1c17">dd51d53b</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-08-07T08:35:21-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite: Fix prog001

Previously it failed as the `ghc` package was not visible.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e4f1b73ad9f292a6bbeb21fee44b0ba1a7f3c33b">e4f1b73a</a></strong>
<div>
<span>by Alan Zimmerman</span>
<i>at 2020-08-07T23:58:10-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">ApiAnnotations; tweaks for ghc-exactprint update

Remove unused ApiAnns, add one for linear arrow.

Include API Annotations for trailing comma in export list.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8a665db6174eaedbbae925c0ccb4c22b3f29bcaf">8a665db6</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-08-07T23:58:45-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">configure: Fix double-negation in ld merge-objects check

We want to only run the check if ld is gold.

Fixes the fix to #17962.</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a11c9678409b2e0a01e8aba153e094800f3641bf">a11c9678</a></strong>
<div>
<span>by Adam Sandberg Ericsson</span>
<i>at 2020-08-09T11:32:25+02:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">hadrian: depend on boot compiler version #18001
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c8873b52f6a16202c3cb839e988c1406b8f67cfe">c8873b52</a></strong>
<div>
<span>by Alan Zimmerman</span>
<i>at 2020-08-09T21:17:54-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Api Annotations : Adjust SrcSpans for prefix bang (!).

And prefix ~

(cherry picked from commit 8dbee2c578b1f642d45561be3f416119863e01eb)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/77398b678aba45ba25932a39b7e8a7a31d0dd6f3">77398b67</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-08-09T21:18:34-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Avoid allocations in `splitAtList` (#18535)

As suspected by @simonpj in #18535, avoiding allocations in
`GHC.Utils.Misc.splitAtList` when there are no leftover arguments is
beneficial for performance:

   On CI validate-x86_64-linux-deb9-hadrian:
    T12227 -7%
    T12545 -12.3%
    T5030  -10%
    T9872a -2%
    T9872b -2.1%
    T9872c -2.5%

Metric Decrease:
    T12227
    T12545
    T5030
    T9872a
    T9872b
    T9872c
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8ba41a0f7f5a8eeb39b73d0f0041a53549c377ab">8ba41a0f</a></strong>
<div>
<span>by Felix Yan</span>
<i>at 2020-08-10T20:23:29-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Correct a typo in ghc.mk</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/1c4692641dcaca3e90116c28d012c506108b386f">1c469264</a></strong>
<div>
<span>by Felix Yan</span>
<i>at 2020-08-10T20:23:29-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add a closing parenthesis too
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/acf537f9fefa31883b7cb28ff61b837ab7f8a44a">acf537f9</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-08-10T20:24:09-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Make splitAtList strict in its arguments

Also fix its slightly wrong comment

Metric Decrease:
    T5030
    T12227
    T12545
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ab4d15898c03a5db6741feb2028488facf032fa4">ab4d1589</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-08-11T22:18:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">typecheck: Drop SPECIALISE pragmas when there is no unfolding

Previously the desugarer would instead fall over when it realized that
there was no unfolding for an imported function with a SPECIALISE
pragma. We now rather drop the SPECIALISE pragma and throw a warning.

Fixes #18118.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/0ac8c0a551619b52e0f151d6781b11dd66cf2110">0ac8c0a5</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-08-11T22:18:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite: Add test for #18118
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c43078d7b78b4722dd30b56674c27189d2689ffe">c43078d7</a></strong>
<div>
<span>by Sven Tennie</span>
<i>at 2020-08-11T22:18:38-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add hie.yaml to ghc-heap

This enables IDE support by haskell-language-server for ghc-heap.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/f1088b3f31ceddf918a319c97557fb1f08a9a387">f1088b3f</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-08-11T22:19:15-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite: Specify metrics collected by T17516

Previously it collected everything, including "max bytes used". This is
problematic since the test makes no attempt to control for deviations in
GC timing, resulting in high variability. Fix this by only collecting
"bytes allocated".
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/accbc242e555822a2060091af7188ce6e9b0144e">accbc242</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-08-12T03:50:12-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">DynFlags: disentangle Outputable

- put panic related functions into GHC.Utils.Panic
- put trace related functions using DynFlags in GHC.Driver.Ppr

One step closer making Outputable fully independent of DynFlags.

Bump haddock submodule
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/db6dd810eb7986a39657f7f028f1f4de92b321dd">db6dd810</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-08-12T03:50:48-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite: Increase tolerance of T16916

T16916 (testing #16916) has been slightly fragile in CI due to its
reliance on CPU times. While it's hard to see how to eliminate
the time-dependence entirely, we can nevertheless make it more tolerant.

Fixes #16966.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/bee43aca827387aa81a64801d82adcb596d01d9a">bee43aca</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-08-12T20:52:50-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Rewrite and move the monad-state hack note

The note has been rewritten by @simonpj in !3851

[skip ci]
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/25fdf25eb574d6d291673603ab36ac5ec7e37066">25fdf25e</a></strong>
<div>
<span>by Alan Zimmerman</span>
<i>at 2020-08-12T20:53:26-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">ApiAnnotations: Fix parser for new GHC 9.0 features
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7831fe05021caa90d4696ca91ae2b31a82e65b3d">7831fe05</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-08-13T03:44:17-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">parser: Suggest ImportQualifiedPost in prepositive import warning

As suggested in #18545.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/55dec4dc6e8f8430810d212c73e78ffbb92e0a48">55dec4dc</a></strong>
<div>
<span>by Sebastian Graf</span>
<i>at 2020-08-13T03:44:52-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">PmCheck: Better long-distance info for where bindings (#18533)

Where bindings can see evidence from the pattern match of the `GRHSs`
they belong to, but not from anything in any of the guards (which belong
to one of possibly many RHSs).

Before this patch, we did *not* consider said evidence, causing #18533,
where the lack of considering type information from a case pattern match
leads to failure to resolve the vanilla COMPLETE set of a data type.

Making available that information required a medium amount of
refactoring so that `checkMatches` can return a
`[(Deltas, NonEmpty Deltas)]`; one `(Deltas, NonEmpty Deltas)` for each
`GRHSs` of the match group. The first component of the pair is the
covered set of the pattern, the second component is one covered set per
RHS.

Fixes #18533.
Regression test case: T18533
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/cf97889a38edc3314a7b61e6e0b6e6d0f434c8a2">cf97889a</a></strong>
<div>
<span>by Hécate</span>
<i>at 2020-08-13T03:45:29-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Re-add BangPatterns to CodePage.hs
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ffc0d578ea22de02a68c64c094602701e65d8895">ffc0d578</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-08-13T09:49:56-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add HomeUnit type

Since Backpack the "home unit" is much more involved than what it was
before (just an identifier obtained with `-this-unit-id`). Now it is
used in conjunction with `-component-id` and `-instantiated-with` to
configure module instantiations and to detect if we are type-checking an
indefinite unit or compiling a definite one.

This patch introduces a new HomeUnit datatype which is much easier to
understand. Moreover to make GHC support several packages in the same
instances, we will need to handle several HomeUnits so having a
dedicated (documented) type is helpful.

Finally in #14335 we will also need to handle the case where we have no
HomeUnit at all because we are only loading existing interfaces for
plugins which live in a different space compared to units used to
produce target code. Several functions will have to be refactored to
accept "Maybe HomeUnit" parameters instead of implicitly querying the
HomeUnit fields in DynFlags. Having a dedicated type will make this
easier.

Bump haddock submodule
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8a51b2ab7433c06bddca9699b0dfd8ab1d11879b">8a51b2ab</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-08-13T21:09:15-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Make IOEnv monad one-shot (#18202)

On CI (x86_64-linux-deb9-hadrian, compile_time/bytes_allocated):

    T10421     -1.8%    (threshold: +/- 1%)
    T10421a    -1.7%    (threshold: +/- 1%)
    T12150     -4.9%    (threshold: +/- 2%)
    T12227     -1.6     (threshold: +/- 1%)
    T12425     -1.5%    (threshold: +/- 1%)
    T12545     -3.8%    (threshold: +/- 1%)
    T12707     -3.0%    (threshold: +/- 1%)
    T13035     -3.0%    (threshold: +/- 1%)
    T14683     -10.3%   (threshold: +/- 2%)
    T3064      -6.9%    (threshold: +/- 2%)
    T4801      -4.3%    (threshold: +/- 2%)
    T5030      -2.6%    (threshold: +/- 2%)
    T5321FD    -3.6%    (threshold: +/- 2%)
    T5321Fun   -4.6%    (threshold: +/- 2%)
    T5631      -19.7%   (threshold: +/- 2%)
    T5642      -13.0%   (threshold: +/- 2%)
    T783       -2.7     (threshold: +/- 2%)
    T9020      -11.1    (threshold: +/- 2%)
    T9961      -3.4%    (threshold: +/- 2%)

    T1969 (compile_time/bytes_allocated)  -2.2%  (threshold: +/-1%)
    T1969 (compile_time/max_bytes_used)   +24.4% (threshold: +/-20%)

Additionally on other CIs:

    haddock.Cabal                  -10.0%   (threshold: +/- 5%)
    haddock.compiler               -9.5%    (threshold: +/- 5%)
    haddock.base (max bytes used)  +24.6%   (threshold: +/- 15%)
    T10370 (max bytes used, i386)  +18.4%   (threshold: +/- 15%)

Metric Decrease:
    T10421
    T10421a
    T12150
    T12227
    T12425
    T12545
    T12707
    T13035
    T14683
    T3064
    T4801
    T5030
    T5321FD
    T5321Fun
    T5631
    T5642
    T783
    T9020
    T9961
    haddock.Cabal
    haddock.compiler
Metric Decrease 'compile_time/bytes allocated':
    T1969
Metric Increase 'compile_time/max_bytes_used':
    T1969
    T10370
    haddock.base
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9f66fdf69b7bcdacbfc46e636668ad0fe509b1b6">9f66fdf6</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-08-14T15:50:34-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite: Drop --io-manager flag from testsuite configuration

This is no longer necessary as there are now dedicated testsuite ways
which run tests with WinIO.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/55fd1dc55990623dcf3b2e6143e766242315d757">55fd1dc5</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-08-14T15:51:10-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">llvm-targets: Add i686 targets

Addresses #18422.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/f4cc57fa2df08f5b33a4cf86c3e041b8de9f6ebf">f4cc57fa</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-08-18T15:38:55-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Allow unsaturated runRW# applications

Previously we had a very aggressive Core Lint check which caught
unsaturated applications of runRW#. However, there is nothing
wrong with such applications and they may naturally arise in desugared
Core. For instance, the desugared Core of Data.Primitive.Array.runArray#
from the `primitive` package contains:

    case ($) (runRW# @_ @_) (\s -> ...) of ...

In this case it's almost certain that ($) will be inlined, turning the
application into a saturated application. However, even if this weren't
the case there isn't a problem: CorePrep (after deleting an unnecessary
case) can simply generate code in its usual way, resulting in a call to
the Haskell definition of runRW#.

Fixes #18291.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/3ac6ae7c8d5a66bfe36973d1e92f3feef482d589">3ac6ae7c</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-08-18T15:38:55-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite: Add test for #18291
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a87a0b498f4c93c33e3db8d7f68fbaa5d812b408">a87a0b49</a></strong>
<div>
<span>by Eli Schwartz</span>
<i>at 2020-08-18T15:39:30-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">install: do not install sphinx doctrees

These files are 100% not needed at install time, and they contain
unreproducible info. See https://reproducible-builds.org/ for why this
matters.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/194b25ee97d93bc4bcb5bed9a0454debba7f2b6a">194b25ee</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-08-18T15:40:05-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite: Allow baseline commit to be set explicitly
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/fdcf76450348d0554b7fd1768331f9efaf691e13">fdcf7645</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-08-18T15:40:05-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">gitlab-ci: Use MR base commit as performance baseline
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9ad5cab33b8b78a346896cc6de555365c73e6298">9ad5cab3</a></strong>
<div>
<span>by Fendor</span>
<i>at 2020-08-18T15:40:42-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Expose UnitInfoMap as it is part of the public API
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/aa4b744d51aa6bdb46064f981ea8e001627921d6">aa4b744d</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-08-18T22:11:36-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite: Only run llvm ways if llc is available

As noted in #18560, we previously would always run the LLVM ways since
`configure` would set `SettingsLlcCommand` to something non-null when
it otherwise couldn't find the `llc` executable. Now we rather probe for
the existence of the `llc` executable in the testsuite driver.

Fixes #18560.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/0c5ed5c7eb30bc5462b67ff097c3388597265a4b">0c5ed5c7</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-08-18T22:12:13-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">DynFlags: refactor GHC.CmmToAsm (#17957, #10143)

This patch removes the use of `sdocWithDynFlags` from GHC.CmmToAsm.*.Ppr

To do that I've had to make some refactoring:

* X86' and PPC's `Instr` are no longer `Outputable` as they require a
  `Platform` argument

* `Instruction` class now exposes `pprInstr :: Platform -> instr -> SDoc`

* as a consequence, I've refactored some modules to avoid .hs-boot files

* added (derived) functor instances for some datatypes parametric in the
  instruction type. It's useful for pretty-printing as we just have to
  map `pprInstr` before pretty-printing the container datatype.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/731c8d3bc5a84515793e5dadb26adf52f9280e13">731c8d3b</a></strong>
<div>
<span>by nineonine</span>
<i>at 2020-08-19T18:47:39-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Implement -Wredundant-bang-patterns (#17340)

Add new flag '-Wredundant-bang-patterns' that enables checks for "dead" bangs.
Dead bangs are the ones that under no circumstances can force a thunk that
wasn't already forced. Dead bangs are a form of redundant bangs. The new check
is performed in Pattern-Match Coverage Checker along with other checks (namely,
redundant and inaccessible RHSs). Given

    f :: Bool -> Int
    f True = 1
    f !x   = 2

we can detect dead bang patterns by checking whether @x ~ ⊥@ is satisfiable
where the PmBang appears in 'checkGrdTree'. If not, then clearly the bang is
dead. Such a dead bang is then indicated in the annotated pattern-match tree by
a 'RedundantSrcBang' wrapping. In 'redundantAndInaccessibles', we collect
all dead bangs to warn about.

Note that we don't want to warn for a dead bang that appears on a redundant
clause. That is because in that case, we recommend to delete the clause wholly,
including its leading pattern match.

Dead bang patterns are redundant. But there are bang patterns which are
redundant that aren't dead, for example

    f !() = 0

the bang still forces the match variable, before we attempt to match on (). But
it is redundant with the forcing done by the () match. We currently don't
detect redundant bangs that aren't dead.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/eb9bdaef6024558696e1e50b12d7fefb70483a9f">eb9bdaef</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-08-19T18:48:14-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add right-to-left rule for pattern bindings

Fix #18323 by adding a few lines of code to handle non-recursive
pattern bindings.  see GHC.Tc.Gen.Bind
Note [Special case for non-recursive pattern bindings]

Alas, this confused the pattern-match overlap checker; see #18323.

Note that this patch only affects pattern bindings like that
for (x,y) in this program

  combine :: (forall a . [a] -> a) -> [forall a. a -> a]
          -> ((forall a . [a] -> a), [forall a. a -> a])

  breaks = let (x,y) = combine head ids
           in x y True

We need ImpredicativeTypes for those [forall a. a->a] types to be
valid. And with ImpredicativeTypes the old, unprincipled "allow
unification variables to unify with a polytype" story actually
works quite well. So this test compiles fine (if delicatedly) with
old GHCs; but not with QuickLook unless we add this patch
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/293c7fba6cde31151baaf2a92c723605ed458ade">293c7fba</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-08-21T09:36:38-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Put CFG weights into their own module (#17957)

It avoids having to query DynFlags to get them
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/50eb4460cd8412387e0c3755a9e0bafaced12bb2">50eb4460</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-08-21T09:36:38-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Don't use DynFlags in CmmToAsm.BlockLayout (#17957)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/659eb31b7a40f0aa2ba43c3454b5d9006fde837d">659eb31b</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-08-21T09:36:38-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">NCG: Dwarf configuration

* remove references to DynFlags in GHC.CmmToAsm.Dwarf
* add specific Dwarf options in NCGConfig instead of directly querying
  the debug level
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2d8ca9170328249a436c3b5647b8e548d32b11c8">2d8ca917</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-08-21T09:37:15-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix -ddump-stg flag

-ddump-stg was dumping the initial STG (just after Core-to-STG pass)
which was misleading because we want the final STG to know if a function
allocates or not. Now we have a new flag -ddump-stg-from-core for this and
-ddump-stg is deprecated.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/fddddbf47d6ba2b1b3b6ec89bd40c8fa020e6606">fddddbf4</a></strong>
<div>
<span>by Vladislav Zavialov</span>
<i>at 2020-08-21T09:37:49-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Import qualified Prelude in Cmm/Parser.y

In preparation for the next version of 'happy', c95920 added a qualified
import to GHC/Parser.y but for some reason neglected GHC/Cmm/Parser.y

This patch adds the missing qualified import to GHC/Cmm/Parser.y and
also adds a clarifying comment to explain why this import is needed.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/989c1c27b1ec69d8cf56b438f0173d92c3547ab5">989c1c27</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-08-21T11:27:53-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">gitlab-ci: Test master branch as well

While these builds are strictly speaking redundant (since every commit
is tested by @marge-bot before making it into `master`), they are nevertheless
useful as they are displayed in the branch's commit list in GitLab's web interface.

Fixes #18595.</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e67ae884ebe42cb31fc4230301a5f555ae23cce8">e67ae884</a></strong>
<div>
<span>by Aditya Gupta</span>
<i>at 2020-08-22T03:29:00-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">mkUnique refactoring (#18362)

Move uniqFromMask from Unique.Supply to Unique.
Move the the functions that call mkUnique from Unique to Builtin.Uniques
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/03cfcfd450335d5ecb63fec1f55d9feafabb2b4c">03cfcfd4</a></strong>
<div>
<span>by Wander Hillen</span>
<i>at 2020-08-22T03:29:36-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add ubuntu 20.04 jobs for nightly and release
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/3f50154591ada9064351ccec4adfe6df53ca2439">3f501545</a></strong>
<div>
<span>by Craig Ferguson</span>
<i>at 2020-08-22T03:30:13-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Utils: clarify docs slightly

The previous comment implies `nTimes n f` is either `f^{n+1}` or
`f^{2^n}` (when in fact it's `f^n`).
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8b86509270227dbc61f0700c7d9261a4c7672361">8b865092</a></strong>
<div>
<span>by Krzysztof Gogolewski</span>
<i>at 2020-08-23T14:12:53+02:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Do not print synonyms in :i (->), :i Type (#18594)

This adds a new printing flag `sdocPrintTypeAbbreviations` that is used
specifically to avoid ghci printing 'type (->) = (->)' and 'type Type = Type'.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d8f61182c3bdd1b6121c83be632b4941b907de88">d8f61182</a></strong>
<div>
<span>by Krzysztof Gogolewski</span>
<i>at 2020-08-23T14:12:56+02:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Move pprTyTcApp' inside pprTyTcApp

No semantic change
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/364258e0ad25bc95e69745554f5ca831ce80baf8">364258e0</a></strong>
<div>
<span>by Krzysztof Gogolewski</span>
<i>at 2020-08-24T00:32:31-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix types in silly shifts (#18589)

Patch written by Simon. I have only added a testcase.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b1eb38a0a7168d7612c791c4289cc02d900d402f">b1eb38a0</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-08-24T00:33:13-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Perf: make SDoc monad one-shot (#18202)

With validate-x86_64-linux-deb9-hadrian:
   T1969  -3.4% (threshold: +/-1%)
   T3294  -3.3% (threshold: +/-1%)
   T12707 -1.4% (threshold: +/-1%)

Additionally with validate-x86_64-linux-deb9-unreg-hadrian:
   T4801  -2.4% (threshold: +/-2%)
   T13035 -1.4% (threshold: +/-1%)
   T13379 -2.4% (threshold: +/-2%)
   ManyAlternatives -2.5% (threshold: +/-2%)
   ManyConstructors -3.0% (threshold: +/-2%)

Metric Decrease:
    T12707
    T1969
    T3294
    ManyAlternatives
    ManyConstructors
    T13035
    T13379
    T4801
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a77b9ec2a6153065565bca7bb154fff35b830b82">a77b9ec2</a></strong>
<div>
<span>by Krzysztof Gogolewski</span>
<i>at 2020-08-24T10:04:20-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add a test for #18397

The bug was fixed by !3421.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/05550a5abc369e1cc4fc48def532ca9ba9adcad7">05550a5a</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-08-24T10:04:59-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Avoid roundtrip through SDoc

As found by @monoidal on https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3885#note_295126
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/0a1ecc5fd45a46372c3935df596f05432db1b270">0a1ecc5f</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-08-25T07:37:05-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">SysTools.Process: Handle exceptions in readCreateProcessWithExitCode'

In #18069 we are observing MVar deadlocks from somewhere in ghc.exe.
This use of MVar stood out as being one of the more likely culprits.
Here we make sure that it is exception-safe.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/db8793ad417ebfcb57d42e8111674a90706a7918">db8793ad</a></strong>
<div>
<span>by Richard Eisenberg</span>
<i>at 2020-08-25T07:37:40-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Use tcView, not coreView, in the pure unifier.

Addresses a lingering point within #11715.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/fb77207a23deade8e3f8598c34598535711264cc">fb77207a</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-08-25T07:38:16-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Use LIdP rather than (XRec p (IdP p))

This patch mainly just replaces use of
    XRec p (IdP p)
with
    LIdP p

One slightly more significant change is to parameterise
HsPatSynDetails over the pass rather than the argument type,
so that it's uniform with HsConDeclDetails and HsConPatDetails.

I also got rid of the dead code GHC.Hs.type.conDetailsArgs

But this is all just minor refactoring. No change in functionality.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8426a1364ba450fe48fc41a95b2ba76c8d1bb7c8">8426a136</a></strong>
<div>
<span>by Krzysztof Gogolewski</span>
<i>at 2020-08-25T07:38:54-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add a test for #18585
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2d635a50b81732b2512b68c652aee36f489b5969">2d635a50</a></strong>
<div>
<span>by Takenobu Tani</span>
<i>at 2020-08-26T04:50:21-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">linters: Make CPP linter skip image files

This patch adds an exclusion rule for `docs/users_guide/images`,
to avoid lint errors of PDF files.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b7d98cb2606997e05ad6406929dae3aba746fbb9">b7d98cb2</a></strong>
<div>
<span>by Takenobu Tani</span>
<i>at 2020-08-26T04:50:21-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">users-guide: Color the logo on the front page of the PDF

This patch updates the logo with a recent color scheme.
This affects only the PDF version of the user's guide.

See also:
* https://mail.haskell.org/pipermail/ghc-devs/2020-August/019139.html
* https://gitlab.haskell.org/ghc/ghc/-/wikis/logo
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/0b17fa185aec793861364afd9a05aa4219fbc019">0b17fa18</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-08-26T04:50:58-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Refactor UnitId pretty-printing

When we pretty-print a UnitId for the user, we try to map it back to its
origin package name, version and component to print
"package-version:component" instead of some hash.

The UnitId type doesn't carry these information, so we have to look into
a UnitState to find them. This is why the Outputable instance of
UnitId used `sdocWithDynFlags` in order to access the `unitState` field
of DynFlags.

This is wrong for several reasons:

1. The DynFlags are accessed when the message is printed, not when it is
   generated. So we could imagine that the unitState may have changed
   in-between. Especially if we want to allow unit unloading.

2. We want GHC to support several independent sessions at once, hence
   several UnitState. The current approach supposes there is a unique
   UnitState as a UnitId doesn't indicate which UnitState to use.

See the Note [Pretty-printing UnitId] in GHC.Unit for the new approach
implemented by this patch.

One step closer to remove `sdocDynFlags` field from `SDocContext`
(#10143).

Fix #18124.

Also fix some Backpack code to use SDoc instead of String.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/dc476a5040cdc64c177de0f78edaafec0972cff4">dc476a50</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-08-26T04:51:35-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Bignum: fix BigNat subtraction (#18604)

There was a confusion between the boolean expected by
withNewWordArrayTrimedMaybe and the boolean returned by subtracting
functions.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/fcb10b6c69e388d8c6e777baf39920e2cc694501">fcb10b6c</a></strong>
<div>
<span>by Peter Trommler</span>
<i>at 2020-08-26T10:42:30-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">PPC and X86: Portable printing of IEEE floats

GNU as and the AIX assembler support floating point literals.
SPARC seems to have support too but I cannot test on SPARC.
Curiously, `doubleToBytes` is also used in the LLVM backend.

To avoid endianness issues when cross-compiling float and double literals
are printed as C-style floating point values. The assembler then takes
care of memory layout and endianness.

This was brought up in #18431 by @hsyl20.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/770100e0266750a313b34a52a60968410fcf0769">770100e0</a></strong>
<div>
<span>by Krzysztof Gogolewski</span>
<i>at 2020-08-26T10:43:13-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">primops: Remove Monadic and Dyadic categories

There were four categories of primops: Monadic, Dyadic, Compare, GenPrimOp.

The compiler does not treat Monadic and Dyadic in any special way,
we can just replace them with GenPrimOp.

Compare is still used in isComparisonPrimOp.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/01ff8c89727a91cbc1571ae54f73f5919d6aaa71">01ff8c89</a></strong>
<div>
<span>by Aditya Gupta</span>
<i>at 2020-08-27T14:19:26-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Consolidate imports in getMinimalImports (#18264)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/bacccb73c9b080c3c01a5e55ecb0a00cd8a77e55">bacccb73</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-08-27T14:20:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Make {hsExpr,hsType,pat}NeedsParens aware of boxed 1-tuples

`hsExprNeedsParens`, `hsTypeNeedsParens`, and `patNeedsParens`
previously assumed that all uses of explicit tuples in the source
syntax never need to be parenthesized. This is true save for one
exception: boxed one-tuples, which use the `Solo` data type from
`GHC.Tuple` instead of special tuple syntax. This patch adds the
necessary logic to the three `*NeedsParens` functions to handle
`Solo` correctly.

Fixes #18612.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c6f50cea42a9ffc947bf4243986663cc820b0ec8">c6f50cea</a></strong>
<div>
<span>by Krzysztof Gogolewski</span>
<i>at 2020-08-28T02:22:36-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add missing primop documentation (#18454)

- Add three pseudoops to primops.txt.pp, so that Haddock renders
  the documentation
- Update comments
- Remove special case for "->" - it's no longer exported from GHC.Prim
- Remove reference to Note [Compiling GHC.Prim] - the ad-hoc fix is no
  longer there after updates to levity polymorphism.
- Document GHC.Prim
- Remove the comment that lazy is levity-polymorphic.
  As far as I can tell, it never was: in 80e399639,
  only the unfolding was given an open type variable.
- Remove haddock hack in GHC.Magic - no longer neccessary after
  adding realWorld# to primops.txt.pp.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/f065b6b012fb8f73689bc5c2a4904d5e6e377af8">f065b6b0</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-08-28T02:23:13-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix use distro toolchian
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4517a38215eb72a4824c72d97377b9325059bf55">4517a382</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-08-28T02:23:13-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">document how build system find toolchains on Windows
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2c906b385b4c6453c72260c87aaa48cb11c40098">2c906b38</a></strong>
<div>
<span>by Sebastian Graf</span>
<i>at 2020-09-01T17:33:36+02:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Turn on -XMonoLocalBinds by default (#18430)

And fix the resulting type errors.

Co-authored-by: Krzysztof Gogolewski <krz.gogolewski@gmail.com>

Metric Decrease:
    parsing001
</pre>
</li>
</ul>
<h4>29 changed files:</h4>
<ul>
<li class="file-stats">
<a href="#587d266bb27a4dc3022bbed44dfa19849df3044c">
.gitlab-ci.yml
</a>
</li>
<li class="file-stats">
<a href="#157f7634c25bc6366cb7c9c9edb48e819dce38db">
.gitlab/ci.sh
</a>
</li>
<li class="file-stats">
<a href="#412267f7d5ed866deae5ac2ca598ff8092b826b6">
.gitlab/linters/check-cpp.py
</a>
</li>
<li class="file-stats">
<a href="#f656107cc03a27946448887125380c358788500e">
.gitlab/test-metrics.sh
</a>
</li>
<li class="file-stats">
<a href="#abe895765c4ce08c5dfbc95e5e3c5db67ff92ded">
CODEOWNERS
</a>
</li>
<li class="file-stats">
<a href="#836efb6e25a091dcb4ff8e1dbb2f0be6a5cbf14c">
Makefile
</a>
</li>
<li class="file-stats">
<a href="#9ab3868b23ed5d5a6e12ef902049902556fa4009">
aclocal.m4
</a>
</li>
<li class="file-stats">
<a href="#d0d96a6d03668aeab20ebe05e2c4ccb798c7e64c">
compiler/GHC.hs
</a>
</li>
<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="#5f4b3cf094f6e2fc46805a6c447613ae13a08942">
<span class="new-file">
+
compiler/GHC/Builtin/RebindableNames.hs
</span>
</a>
</li>
<li class="file-stats">
<a href="#377cfd14c1f92357465df995ec6537b074051322">
compiler/GHC/Builtin/Types.hs
</a>
</li>
<li class="file-stats">
<a href="#be7a5c9dc04ecfe7bedb2a2afcc2a51be6719577">
compiler/GHC/Builtin/Types.hs-boot
</a>
</li>
<li class="file-stats">
<a href="#8a5cd068459120cddf3814e7b9e02003b87647ba">
compiler/GHC/Builtin/Types/Prim.hs
</a>
</li>
<li class="file-stats">
<a href="#8dc7109003a77f8a82e987dc1de31466aa956174">
compiler/GHC/Builtin/Uniques.hs
</a>
</li>
<li class="file-stats">
<a href="#6bcb866fdb5388db4ecc395e443a3af4888d9dd5">
compiler/GHC/Builtin/Uniques.hs-boot
</a>
</li>
<li class="file-stats">
<a href="#d95fdf6575459444666f72b2281534e0558a4ba0">
compiler/GHC/Builtin/Utils.hs
</a>
</li>
<li class="file-stats">
<a href="#451725cc4e5d443a3b7c2adcdf224840f953b7e2">
compiler/GHC/Builtin/primops.txt.pp
</a>
</li>
<li class="file-stats">
<a href="#2f6f8d6d05acc04b08fff94df4b3996c65b87892">
compiler/GHC/ByteCode/Asm.hs
</a>
</li>
<li class="file-stats">
<a href="#16db773e94d0938489b415eb3231cadb2565b84d">
compiler/GHC/ByteCode/InfoTable.hs
</a>
</li>
<li class="file-stats">
<a href="#f73a4fa90a8eb153bccdcfcc9f63c15edcd66785">
compiler/GHC/Cmm.hs
</a>
</li>
<li class="file-stats">
<a href="#db697f6aea9f93f1583f1d5c62d25570a1e07f73">
compiler/GHC/Cmm/CLabel.hs
</a>
</li>
<li class="file-stats">
<a href="#d088ba20f051734394bf7ca283f33ed8127bc8ab">
compiler/GHC/Cmm/CallConv.hs
</a>
</li>
<li class="file-stats">
<a href="#806448db91cc2906ebcc088107220a663d3d43eb">
compiler/GHC/Cmm/CommonBlockElim.hs
</a>
</li>
<li class="file-stats">
<a href="#92b713d88390e6ea489e24b6cff8a3960384c0d0">
compiler/GHC/Cmm/DebugBlock.hs
</a>
</li>
<li class="file-stats">
<a href="#56e23d78cfece2c83f03ed9b9a8ce9b20be26462">
compiler/GHC/Cmm/Expr.hs
</a>
</li>
<li class="file-stats">
<a href="#29368208fbfcaee57ce84000cdccaba639e85a75">
compiler/GHC/Cmm/Graph.hs
</a>
</li>
<li class="file-stats">
<a href="#47cba74ae8965f1665cd11bf2b023760ea27594e">
compiler/GHC/Cmm/Info.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/d216a2c818235cfa1cbd0756b146223e08430d59...2c906b385b4c6453c72260c87aaa48cb11c40098">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>