<!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>
Andreas Klebinger pushed to branch wip/andreask/strict_dicts
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/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/b8c212b98fe949feccbc4788cabedd3562fec842">b8c212b9</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-21T17:53:46+02:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Enable strict dicts by default at -O2.

In the common case this is a straight performance win
at a compile time cost so we enable it at -O2.

In rare cases it can lead to compile time regressions
because of changed inlining behaviour. Which can very
rarely also affect runtime performance.

Increasing the inlining threshold can help to avoid this
which is documented in the user guide.
</pre>
</li>
</ul>
<h4>30 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="#836efb6e25a091dcb4ff8e1dbb2f0be6a5cbf14c">
Makefile
</a>
</li>
<li class="file-stats">
<a href="#0887cf39c5cdf9cf8d6758f410d7dab3023c0d77">
compiler/GHC/Builtin/Names.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="#8a5cd068459120cddf3814e7b9e02003b87647ba">
compiler/GHC/Builtin/Types/Prim.hs
</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="#066085df29cc928ac539d8feae6e5215cbbf1e14">
compiler/GHC/Cmm/LayoutStack.hs
</a>
</li>
<li class="file-stats">
<a href="#71e696f452eb493722d70306c6f304fc9b2f6a95">
compiler/GHC/Cmm/Parser.y
</a>
</li>
<li class="file-stats">
<a href="#b1390f6749e1a2dddcae35f88d55623ea6269f56">
compiler/GHC/Cmm/Sink.hs
</a>
</li>
<li class="file-stats">
<a href="#10b61652f9817945bb54ccf8fc40f8a664ca3c30">
compiler/GHC/CmmToAsm.hs
</a>
</li>
<li class="file-stats">
<a href="#5986ebaacfa99d264abfd2f7ef19d99a64db720f">
compiler/GHC/CmmToAsm/BlockLayout.hs
</a>
</li>
<li class="file-stats">
<a href="#ea29061dab1b843e0ea9294afc614998f3a8d08f">
compiler/GHC/CmmToAsm/Monad.hs
</a>
</li>
<li class="file-stats">
<a href="#eb63fd2d9f8f64c1063f9ce3e162f92c2e6e508c">
compiler/GHC/CmmToAsm/Reg/Graph.hs
</a>
</li>
<li class="file-stats">
<a href="#b5d9809f48ef349a168fb08742fa95fb2a059129">
compiler/GHC/CmmToAsm/Reg/Graph/Coalesce.hs
</a>
</li>
<li class="file-stats">
<a href="#02f4cb4badaefd6ed6f1ae3ff38a357c449fc286">
compiler/GHC/CmmToAsm/Reg/Graph/Spill.hs
</a>
</li>
<li class="file-stats">
<a href="#3aba9ceb20d68f25343fe3a27b2b7a4f8fea68da">
compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs
</a>
</li>
<li class="file-stats">
<a href="#18fcc4c56813c879ea69a2e6b2bdf6b09dd037c5">
compiler/GHC/CmmToAsm/Reg/Graph/SpillCost.hs
</a>
</li>
<li class="file-stats">
<a href="#23fa440e58d1f384d18650b52802ad6d03891572">
compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs
</a>
</li>
<li class="file-stats">
<a href="#83a3b2df5c77503c3a8c6df05a7654333d30cac3">
compiler/GHC/CmmToAsm/Reg/Linear.hs
</a>
</li>
<li class="file-stats">
<a href="#e7e32ef13a93a68891f700047f89c45df0e3772d">
compiler/GHC/CmmToAsm/Reg/Linear/Base.hs
</a>
</li>
<li class="file-stats">
<a href="#6b7e521fe89077442c3d86c888eb96793606049a">
compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs
</a>
</li>
<li class="file-stats">
<a href="#a25615433d8186f543ea64f55fdf156b7b1e6996">
compiler/GHC/CmmToAsm/Reg/Linear/StackMap.hs
</a>
</li>
<li class="file-stats">
<a href="#62e26243bb502b18583ce19f1a921417090459c7">
compiler/GHC/CmmToAsm/Reg/Linear/Stats.hs
</a>
</li>
<li class="file-stats">
<a href="#b4cadffdafb6a1f441fede8639ba742ae903afca">
compiler/GHC/CmmToAsm/Reg/Liveness.hs
</a>
</li>
<li class="file-stats">
<a href="#d0fd0c4522f53657c4f3e9d6433bfc05f0e303df">
<span class="new-file">
+
compiler/GHC/CmmToAsm/Reg/Utils.hs
</span>
</a>
</li>
<li class="file-stats">
<a href="#522ba674004d5ebf69a7ec80b0d7c765e08b60cc">
compiler/GHC/CmmToAsm/X86/RegInfo.hs
</a>
</li>
<li class="file-stats">
<a href="#b5ac041c7f79084a7a7626eda4cdadda3457d235">
compiler/GHC/CmmToLlvm/Base.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/3a60e34a0a78f6917b03d960f3393058cbb83b7f...b8c212b98fe949feccbc4788cabedd3562fec842">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>