<!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>
Vladislav Zavialov pushed to branch wip/haddock-accum
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/dcfe29c8520244764146c7a5f336be1f9700db6c">dcfe29c8</a></strong>
<div>
<span>by Ömer Sinan Ağacan</span>
<i>at 2020-04-06T13:16:08-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Don't override proc CafInfos in ticky builds

Fixes #17947

When we have a ticky label for a proc, IdLabels for the ticky counter
and proc entry share the same Name. This caused overriding proc CafInfos
with the ticky CafInfos (i.e. NoCafRefs) during SRT analysis.

We now ignore the ticky labels when building SRTMaps. This makes sense
because:

- When building the current module they don't need to be in SRTMaps as
  they're initialized as non-CAFFY (see mkRednCountsLabel), so they
  don't take part in the dependency analysis and they're never added to
  SRTs.

  (Reminder: a "dependency" in the SRT analysis is a CAFFY dependency,
  non-CAFFY uses are not considered as dependencies for the algorithm)

- They don't appear in the interfaces as they're not exported, so it
  doesn't matter for cross-module concerns whether they're in the SRTMap
  or not.

See also the new Note [Ticky labels in SRT analysis].
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/cec2c71fe91c88649628c6e83416533b816b86a5">cec2c71f</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-04-06T13:16:44-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix an tricky specialiser loop

Issue #17151 was a very tricky example of a bug in which the
specialiser accidentally constructs a recurive dictionary,
so that everything turns into bottom.

I have fixed variants of this bug at least twice before:
see Note [Avoiding loops].  It was a bit of a struggle
to isolate the problem, greatly aided by the work that
Alexey Kuleshevich did in distilling a test case.

Once I'd understood the problem, it was not difficult to fix,
though it did lead me a bit of refactoring in specImports.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e850d14ffbeea39ad386b1e888cd97375758d6d6">e850d14f</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-04-06T13:16:44-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Refactoring only

This refactors DictBinds into a data type rather than a pair.
No change in behaviour, just better code
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/f38e8d61f066c3064c600c352eebcd87f28d989a">f38e8d61</a></strong>
<div>
<span>by Daniel Gröber</span>
<i>at 2020-04-07T02:00:05-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts: ProfHeap: Fix memory leak when not compiled with profiling

If we're doing heap profiling on an unprofiled executable we keep
allocating new space in initEra via nextEra on each profiler run but we
don't have a corresponding freeEra call.

We do free the last era in endHeapProfiling but previous eras will have
been overwritten by initEra and will never get free()ed.

Metric Decrease:
    space_leak_001
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/bcd668593e1c9e00c5d9c72960b4833dd526cb9a">bcd66859</a></strong>
<div>
<span>by Sebastian Graf</span>
<i>at 2020-04-07T02:00:41-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Re-export GHC.Magic.noinline from base
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/3d2991f8b4c1b686323b2c9452ce845a60b8d94c">3d2991f8</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-04-07T18:36:09-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">simplifier: Kill off ufKeenessFactor

We used to have another factor, ufKeenessFactor, which would scale the
discounts before they were subtracted from the size. This was justified
with the following comment:

  -- We multiple the raw discounts (args_discount and result_discount)
  -- ty opt_UnfoldingKeenessFactor because the former have to do with
  --  *size* whereas the discounts imply that there's some extra
  --  *efficiency* to be gained (e.g. beta reductions, case reductions)
  -- by inlining.

However, this is highly suspect since it means that we subtract a
*scaled* size from an absolute size, resulting in crazy (e.g. negative)
scores in some cases (#15304). We consequently killed off
ufKeenessFactor and bumped up the ufUseThreshold to compensate.

Adjustment of unfolding use threshold
=====================================

Since this removes a discount from our inlining heuristic, I revisited our
default choice of -funfolding-use-threshold to minimize the change in
overall inlining behavior. Specifically, I measured runtime allocations
and executable size of nofib and the testsuite performance tests built
using compilers (and core libraries) built with several values of
-funfolding-use-threshold.

This comes as a result of a quantitative comparison of testsuite
performance and code size as a function of ufUseThreshold, comparing
GHC trees using values of 50, 60, 70, 80, 90, and 100. The test set
consisted of nofib and the testsuite performance tests.
A full summary of these measurements are found in the description of
!2608

Comparing executable sizes (relative to the base commit) across all
nofib tests, we see that sizes are similar to the baseline:

            gmean      min      max   median
thresh
50         -6.36%   -7.04%   -4.82%   -6.46%
60         -5.04%   -5.97%   -3.83%   -5.11%
70         -2.90%   -3.84%   -2.31%   -2.92%
80         -0.75%   -2.16%   -0.42%   -0.73%
90         +0.24%   -0.41%   +0.55%   +0.26%
100        +1.36%   +0.80%   +1.64%   +1.37%
baseline   +0.00%   +0.00%   +0.00%   +0.00%

Likewise, looking at runtime allocations we see that 80 gives slightly
better optimisation than the baseline:

            gmean      min      max   median
thresh
50         +0.16%   -0.16%   +4.43%   +0.00%
60         +0.09%   -0.00%   +3.10%   +0.00%
70         +0.04%   -0.09%   +2.29%   +0.00%
80         +0.02%   -1.17%   +2.29%   +0.00%
90         -0.02%   -2.59%   +1.86%   +0.00%
100        +0.00%   -2.59%   +7.51%   -0.00%
baseline   +0.00%   +0.00%   +0.00%   +0.00%

Finally, I had to add a NOINLINE in T4306 to ensure that `upd` is
worker-wrappered as the test expects. This makes me wonder whether the
inlining heuristic is now too liberal as `upd` is quite a large
function. The same measure was taken in T12600.

             Wall clock time compiling Cabal with -O0
thresh       50     60     70     80     90      100    baseline
build-Cabal  93.88  89.58  92.59  90.09  100.26  94.81  89.13

Also, this change happens to avoid the spurious test output in
`plugin-recomp-change` and `plugin-recomp-change-prof` (see #17308).

Metric Decrease:
    hie002
    T12234
    T13035
    T13719
    T14683
    T4801
    T5631
    T5642
    T9020
    T9872d
    T9961
Metric Increase:
    T12150
    T12425
    T13701
    T14697
    T15426
    T1969
    T3064
    T5837
    T6048
    T9203
    T9872a
    T9872b
    T9872c
    T9872d
    haddock.Cabal
    haddock.base
    haddock.compiler
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/255418da5d264fb2758bc70925adb2094f34adc3">255418da</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-04-07T18:36:49-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Modules: type-checker (#13009)

Update Haddock submodule
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/04b6cf947ea065a210a216cc91f918cc1660d430">04b6cf94</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-04-07T19:43:20-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Make NoExtCon fields strict

This changes every unused TTG extension constructor to be strict in
its field so that the pattern-match coverage checker is smart enough
any such constructors are unreachable in pattern matches. This lets
us remove nearly every use of `noExtCon` in the GHC API. The only
ones we cannot remove are ones underneath uses of `ghcPass`, but that
is only because GHC 8.8's and 8.10's coverage checkers weren't smart
enough to perform this kind of reasoning. GHC HEAD's coverage
checker, on the other hand, _is_ smart enough, so we guard these uses
of `noExtCon` with CPP for now.

Bumps the `haddock` submodule.

Fixes #17992.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7802fa17a9a1a0f02fbf95170c13d7a9711a681e">7802fa17</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-04-08T16:43:44-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Handle promoted data constructors in typeToLHsType correctly

Instead of using `nlHsTyVar`, which hardcodes `NotPromoted`, have
`typeToLHsType` pick between `Promoted` and `NotPromoted` by checking
if a type constructor is promoted using `isPromotedDataCon`.

Fixes #18020.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ce481361fc95405cfadcd8f930629381e80e7f84">ce481361</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-04-09T16:17:21-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">hadrian: Use --export-dynamic when linking iserv

As noticed in #17962, the make build system currently does this (see
3ce0e0ba) but the change was never ported to Hadrian.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/fa66f143a61f2285618c611a27c23815ca588299">fa66f143</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-04-09T16:17:21-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">iserv: Don't pass --export-dynamic on FreeBSD

This is definitely a hack but it's probably the best we can do for now.
Hadrian does the right thing here by passing --export-dynamic only to
the linker.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/390751768104cd3d2cb57e2037062916476ebd10">39075176</a></strong>
<div>
<span>by Ömer Sinan Ağacan</span>
<i>at 2020-04-09T16:18:00-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix CNF handling in compacting GC

Fixes #17937

Previously compacting GC simply ignored CNFs. This is mostly fine as
most (see "What about small compacts?" below) CNF objects don't have
outgoing pointers, and are "large" (allocated in large blocks) and large
objects are not moved or compacted.

However if we do GC *during* sharing-preserving compaction then the CNF
will have a hash table mapping objects that have been moved to the CNF
to their location in the CNF, to be able to preserve sharing.

This case is handled in the copying collector, in `scavenge_compact`,
where we evacuate hash table entries and then rehash the table.

Compacting GC ignored this case.

We now visit CNFs in all generations when threading pointers to the
compacted heap and thread hash table keys. A visited CNF is added to the
list `nfdata_chain`. After compaction is done, we re-visit the CNFs in
that list and rehash the tables.

The overhead is minimal: the list is static in `Compact.c`, and link
field is added to `StgCompactNFData` closure. Programs that don't use
CNFs should not be affected.

To test this CNF tests are now also run in a new way 'compacting_gc',
which just passes `-c` to the RTS, enabling compacting GC for the oldest
generation. Before this patch the result would be:

    Unexpected failures:
       compact_gc.run          compact_gc [bad exit code (139)] (compacting_gc)
       compact_huge_array.run  compact_huge_array [bad exit code (1)] (compacting_gc)

With this patch all tests pass. I can also pass `-c -DS` without any
failures.

What about small compacts? Small CNFs are still not handled by the
compacting GC. However so far I'm unable to write a test that triggers a
runtime panic ("update_fwd: unknown/strange object") by allocating a
small CNF in a compated heap. It's possible that I'm missing something
and it's not possible to have a small CNF.

NoFib Results:

--------------------------------------------------------------------------------
        Program           Size    Allocs    Instrs     Reads    Writes
--------------------------------------------------------------------------------
             CS          +0.1%      0.0%      0.0%     +0.0%     +0.0%
            CSD          +0.1%      0.0%      0.0%      0.0%      0.0%
             FS          +0.1%      0.0%      0.0%      0.0%      0.0%
              S          +0.1%      0.0%      0.0%      0.0%      0.0%
             VS          +0.1%      0.0%      0.0%      0.0%      0.0%
            VSD          +0.1%      0.0%     +0.0%     +0.0%     -0.0%
            VSM          +0.1%      0.0%     +0.0%     -0.0%      0.0%
           anna          +0.0%      0.0%     -0.0%     -0.0%     -0.0%
           ansi          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
           atom          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
         awards          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
         banner          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
     bernouilli          +0.1%      0.0%      0.0%     -0.0%     +0.0%
   binary-trees          +0.1%      0.0%     -0.0%     -0.0%      0.0%
          boyer          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
         boyer2          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
           bspt          +0.1%      0.0%     -0.0%     -0.0%     -0.0%
      cacheprof          +0.1%      0.0%     -0.0%     -0.0%     -0.0%
       calendar          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
       cichelli          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
        circsim          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
       clausify          +0.1%      0.0%     -0.0%     +0.0%     +0.0%
  comp_lab_zift          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
       compress          +0.1%      0.0%     +0.0%     +0.0%      0.0%
      compress2          +0.1%      0.0%     -0.0%      0.0%      0.0%
    constraints          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
   cryptarithm1          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
   cryptarithm2          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
            cse          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
   digits-of-e1          +0.1%      0.0%     +0.0%     -0.0%     -0.0%
   digits-of-e2          +0.1%      0.0%     -0.0%     -0.0%     -0.0%
         dom-lt          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
          eliza          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
          event          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
    exact-reals          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
         exp3_8          +0.1%      0.0%     +0.0%     -0.0%      0.0%
         expert          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
 fannkuch-redux          +0.1%      0.0%     -0.0%      0.0%      0.0%
          fasta          +0.1%      0.0%     -0.0%     +0.0%     +0.0%
            fem          +0.1%      0.0%     -0.0%     +0.0%      0.0%
            fft          +0.1%      0.0%     -0.0%     +0.0%     +0.0%
           fft2          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
       fibheaps          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
           fish          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
          fluid          +0.0%      0.0%     +0.0%     +0.0%     +0.0%
         fulsom          +0.1%      0.0%     -0.0%     +0.0%      0.0%
         gamteb          +0.1%      0.0%     +0.0%     +0.0%      0.0%
            gcd          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
    gen_regexps          +0.1%      0.0%     -0.0%     +0.0%      0.0%
         genfft          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
             gg          +0.1%      0.0%      0.0%     +0.0%     +0.0%
           grep          +0.1%      0.0%     -0.0%     +0.0%     +0.0%
         hidden          +0.1%      0.0%     +0.0%     -0.0%      0.0%
            hpg          +0.1%      0.0%     -0.0%     -0.0%     -0.0%
            ida          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
          infer          +0.1%      0.0%     +0.0%      0.0%     -0.0%
        integer          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
      integrate          +0.1%      0.0%     -0.0%     -0.0%     -0.0%
   k-nucleotide          +0.1%      0.0%     +0.0%     +0.0%      0.0%
          kahan          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
        knights          +0.1%      0.0%     -0.0%     -0.0%     -0.0%
         lambda          +0.1%      0.0%     +0.0%     +0.0%     -0.0%
     last-piece          +0.1%      0.0%     +0.0%      0.0%      0.0%
           lcss          +0.1%      0.0%     +0.0%     +0.0%      0.0%
           life          +0.1%      0.0%     -0.0%     +0.0%     +0.0%
           lift          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
         linear          +0.1%      0.0%     -0.0%     +0.0%      0.0%
      listcompr          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
       listcopy          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
       maillist          +0.1%      0.0%     +0.0%     -0.0%     -0.0%
         mandel          +0.1%      0.0%     +0.0%     +0.0%      0.0%
        mandel2          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
           mate          +0.1%      0.0%     +0.0%      0.0%     +0.0%
        minimax          +0.1%      0.0%     -0.0%      0.0%     -0.0%
        mkhprog          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
     multiplier          +0.1%      0.0%     +0.0%      0.0%      0.0%
         n-body          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
       nucleic2          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
           para          +0.1%      0.0%      0.0%     +0.0%     +0.0%
      paraffins          +0.1%      0.0%     +0.0%     -0.0%      0.0%
         parser          +0.1%      0.0%     -0.0%     -0.0%     -0.0%
        parstof          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
            pic          +0.1%      0.0%     -0.0%     -0.0%      0.0%
       pidigits          +0.1%      0.0%     +0.0%     -0.0%     -0.0%
          power          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
         pretty          +0.1%      0.0%     -0.0%     -0.0%     -0.1%
         primes          +0.1%      0.0%     -0.0%     -0.0%     -0.0%
      primetest          +0.1%      0.0%     -0.0%     -0.0%     -0.0%
         prolog          +0.1%      0.0%     -0.0%     -0.0%     -0.0%
         puzzle          +0.1%      0.0%     -0.0%     -0.0%     -0.0%
         queens          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
        reptile          +0.1%      0.0%     -0.0%     -0.0%     +0.0%
reverse-complem          +0.1%      0.0%     +0.0%      0.0%     -0.0%
        rewrite          +0.1%      0.0%     -0.0%     -0.0%     -0.0%
           rfib          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
            rsa          +0.1%      0.0%     -0.0%     +0.0%     -0.0%
            scc          +0.1%      0.0%     -0.0%     -0.0%     -0.1%
          sched          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
            scs          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
         simple          +0.1%      0.0%     -0.0%     -0.0%     -0.0%
          solid          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
        sorting          +0.1%      0.0%     -0.0%     -0.0%     -0.0%
  spectral-norm          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
         sphere          +0.1%      0.0%     -0.0%     -0.0%     -0.0%
         symalg          +0.1%      0.0%     -0.0%     -0.0%     -0.0%
            tak          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
      transform          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
       treejoin          +0.1%      0.0%     +0.0%     -0.0%     -0.0%
      typecheck          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
        veritas          +0.0%      0.0%     +0.0%     +0.0%     +0.0%
           wang          +0.1%      0.0%      0.0%     +0.0%     +0.0%
      wave4main          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
   wheel-sieve1          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
   wheel-sieve2          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
           x2n1          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
--------------------------------------------------------------------------------
            Min          +0.0%      0.0%     -0.0%     -0.0%     -0.1%
            Max          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
 Geometric Mean          +0.1%     -0.0%     -0.0%     -0.0%     -0.0%

Bumping numbers of nonsensical perf tests:

Metric Increase:
    T12150
    T12234
    T12425
    T13035
    T5837
    T6048

It's simply not possible for this patch to increase allocations, and
I've wasted enough time on these test in the past (see #17686). I think
these tests should not be perf tests, but for now I'll bump the numbers.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/dce50062e35d3246b63fba9357dea6313c23c780">dce50062</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-04-09T16:18:44-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Rts: show errno on failure (#18033)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/045139f40089f288866c1c59c7379be82ecdaf34">045139f4</a></strong>
<div>
<span>by Hécate</span>
<i>at 2020-04-09T23:10:44-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add an example to liftIO and explain its purpose
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/101fab6ee6cee72b9ffce40e45ebf39466d1c01a">101fab6e</a></strong>
<div>
<span>by Sebastian Graf</span>
<i>at 2020-04-09T23:11:21-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Special case `isConstraintKindCon` on `AlgTyCon`

Previously, the `tyConUnique` record selector would unfold into a huge
case expression that would be inlined in all call sites, such as the
`INLINE`-annotated `coreView`, see #18026. `constraintKindTyConKey` only
occurs as the `Unique` of an `AlgTyCon` anyway, so we can make the code
a lot more compact, but have to move it to GHC.Core.TyCon.

Metric Decrease:
    T12150
    T12234
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/f5212dfc10414212e42247c2f2dcc45252f7e1d2">f5212dfc</a></strong>
<div>
<span>by Sebastian Graf</span>
<i>at 2020-04-09T23:11:57-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">DmdAnal: No need to attach a StrictSig to DataCon workers

In GHC.Types.Id.Make we were giving a strictness signature to every data
constructor wrapper Id that we weren't looking at in demand analysis
anyway. We used to use its CPR info, but that has its own CPR signature
now.

`Note [Data-con worker strictness]` then felt very out of place, so I
moved it to GHC.Core.DataCon.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/75a185dc2a648ab1f592d401daa5efcacb451c83">75a185dc</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-04-09T23:12:37-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Hadrian: fix --summary
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/723062edf6191084a99787d3f235183cf6b7d051">723062ed</a></strong>
<div>
<span>by Ömer Sinan Ağacan</span>
<i>at 2020-04-10T09:18:14+03:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite: Move no_lint to the top level, tweak hie002

- We don't want to benchmark linting so disable lints in hie002 perf
  test

- Move no_lint to the top-level to be able to use it in tests other than
  those in `testsuite/tests/perf/compiler`.

- Filter out -dstg-lint in no_lint.

- hie002 allocation numbers on 32-bit are unstable, so skip it on 32-bit

Metric Decrease:
    hie002
    ManyConstructors
    T12150
    T12234
    T13035
    T1969
    T4801
    T9233
    T9961
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/bcafaa82a0223afd5d103e052ab9a097a676e5ea">bcafaa82</a></strong>
<div>
<span>by Peter Trommler</span>
<i>at 2020-04-10T19:29:33-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Testsuite: mark T11531 fragile

The test depends on a link editor allowing undefined symbols in an ELF
shared object. This is the standard but it seems some distributions
patch their link editor. See the report by @hsyl20 in #11531.

Fixes #11531
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/0889f5eecfea8af6a9d74d48d9d86ff3aea331d6">0889f5ee</a></strong>
<div>
<span>by Takenobu Tani</span>
<i>at 2020-04-12T11:44:52+09:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite: Fix comment for a language extension

[skip ci]
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/cd4f92b5f4251f1a37d1e08ee97d99f2ccb41f26">cd4f92b5</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-04-12T11:20:58-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Significant refactor of Lint

This refactoring of Lint was triggered by #17923, which is
fixed by this patch.

The main change is this.  Instead of
   lintType :: Type -> LintM LintedKind
we now have
   lintType :: Type -> LintM LintedType

Previously, all of typeKind was effectively duplicate in lintType.
Moreover, since we have an ambient substitution, we still had to
apply the substition here and there, sometimes more than once. It
was all very tricky, in the end, and made my head hurt.

Now, lintType returns a fully linted type, with all substitutions
performed on it.  This is much simpler.

The same thing is needed for Coercions.  Instead of
  lintCoercion :: OutCoercion
               -> LintM (LintedKind, LintedKind,
                         LintedType, LintedType, Role)
we now have
  lintCoercion :: Coercion -> LintM LintedCoercion

Much simpler!  The code is shorter and less bug-prone.

There are a lot of knock on effects.  But life is now better.

Metric Decrease:
    T1969
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/0efaf301fec9ed9ea827392cbe03de3335e995c7">0efaf301</a></strong>
<div>
<span>by Josh Meredith</span>
<i>at 2020-04-12T11:21:34-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Implement extensible interface files
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/54ca66a7d30d7f7cfbf3753ebe547f5a20d76b96">54ca66a7</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-04-12T11:22:10-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Use conLikeUserTyVarBinders to quantify field selector types

This patch:

1. Writes up a specification for how the types of top-level field
   selectors should be determined in a new section of the GHC User's
   Guide, and
2. Makes GHC actually implement that specification by using
   `conLikeUserTyVarBinders` in `mkOneRecordSelector` to preserve the
   order and specificity of type variables written by the user.

Fixes #18023.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/35799dda07813e4c510237290a631d4d11fb92d2">35799dda</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-04-12T11:22:50-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">hadrian: Don't --export-dynamic on Darwin

When fixing #17962 I neglected to consider that --export-dynamic is only
supported on ELF platforms.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e8029816fda7602a8163c4d2703ff02982a3e48c">e8029816</a></strong>
<div>
<span>by Alexis King</span>
<i>at 2020-04-12T11:23:27-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add an INLINE pragma to Control.Category.>>>

This fixes #18013 by adding INLINE pragmas to both Control.Category.>>>
and GHC.Desugar.>>>. The functional change in this patch is tiny (just
two lines of pragmas!), but an accompanying Note explains in gory
detail what’s going on.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/0da186c1b5a47e08e91c1c674d46c040c83932fc">0da186c1</a></strong>
<div>
<span>by Krzysztof Gogolewski</span>
<i>at 2020-04-14T07:55:20-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Change zipWith to zipWithEqual in a few places
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/074c1ccd3f8c3fcab117e336316173e8e869230a">074c1ccd</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-04-14T07:55:55-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Small change to the windows ticker.

We already have a function to go from time to ms so use it.
Also expand on the state of timer resolution.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b69cc8842aa7e2df52b92a9c9ad3b9d8dcf624ab">b69cc884</a></strong>
<div>
<span>by Alp Mestanogullari</span>
<i>at 2020-04-14T07:56:38-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">hadrian: get rid of unnecessary levels of nesting in source-dist
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d0c3b0696f1ca809ebd83b5fc2c0b911cde38e77">d0c3b069</a></strong>
<div>
<span>by Julien Debon</span>
<i>at 2020-04-14T07:57:16-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">doc (Foldable): Add examples to Data.Foldable

See #17929
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/5b08e0c06e038448a63aa9bd7f163b23d824ba4b">5b08e0c0</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-04-14T23:28:20-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">StgCRun: Enable unwinding only on Linux

It's broken on macOS due and SmartOS due to assembler differences
(#15207) so let's be conservative in enabling it. Also, refactor things
to make the intent clearer.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/27cc2e7b1c1268e59c9d16b4530f27c0d40e9464">27cc2e7b</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-04-14T23:28:57-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts: Don't mark evacuate_large as inline

This function has two callsites and is quite large. GCC consequently
decides not to inline and warns instead. Given the situation, I can't
blame it. Let's just remove the inline specifier.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9853fc5e3556e733b56976b0a2fce9e82130a9ef">9853fc5e</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-04-14T23:29:48-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">base: Enable large file support for OFD locking impl.

Not only is this a good idea in general but this should also avoid
issue #17950 by ensuring that off_t is 64-bits.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7b41f21bbfa9e266ba6654b08c3f9fec549c8bca">7b41f21b</a></strong>
<div>
<span>by Matthew Pickering</span>
<i>at 2020-04-14T23:30:24-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Hadrian: Make -i paths absolute

The primary reason for this change is that ghcide does not work with
relative paths. It also matches what cabal and stack do, they always
pass absolute paths.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/41230e2601703df0233860be3f7d53f3a01bdbe5">41230e26</a></strong>
<div>
<span>by Daniel Gröber</span>
<i>at 2020-04-14T23:31:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Zero out pinned block alignment slop when profiling

The heap profiler currently cannot traverse pinned blocks because of
alignment slop. This used to just be a minor annoyance as the whole block
is accounted into a special cost center rather than the respective object's
CCS, cf. #7275. However for the new root profiler we would like to be able
to visit _every_ closure on the heap. We need to do this so we can get rid
of the current 'flip' bit hack in the heap traversal code.

Since info pointers are always non-zero we can in principle skip all the
slop in the profiler if we can rely on it being zeroed. This assumption
caused problems in the past though, commit a586b33f8e ("rts: Correct
handling of LARGE ARR_WORDS in LDV profiler"), part of !1118, tried to use
the same trick for BF_LARGE objects but neglected to take into account that
shrink*Array# functions don't ensure that slop is zeroed when not
compiling with profiling.

Later, commit 0c114c6599 ("Handle large ARR_WORDS in heap census (fix
as we will only be assuming slop is zeroed when profiling is on.

This commit also reduces the ammount of slop we introduce in the first
place by calculating the needed alignment before doing the allocation for
small objects where we know the next available address. For large objects
we don't know how much alignment we'll have to do yet since those details
are hidden behind the allocateMightFail function so there we continue to
allocate the maximum additional words we'll need to do the alignment.

So we don't have to duplicate all this logic in the cmm code we pull it
into the RTS allocatePinned function instead.

Metric Decrease:
    T7257
    haddock.Cabal
    haddock.base
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/15fa9bd6dd2d0b8d1fcd7135c85ea0d60853340d">15fa9bd6</a></strong>
<div>
<span>by Daniel Gröber</span>
<i>at 2020-04-14T23:31:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts: Expand and add more notes regarding slop
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/caf3f444bcc29f75145834207da00d938c08c2d3">caf3f444</a></strong>
<div>
<span>by Daniel Gröber</span>
<i>at 2020-04-14T23:31:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts: allocatePinned: Fix confusion about word/byte units
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c3c0f662df06500a11970fd391d0a88e081a5296">c3c0f662</a></strong>
<div>
<span>by Daniel Gröber</span>
<i>at 2020-04-14T23:31:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts: Underline some Notes as is conventional
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e149dea9bb89b77d34f50075946d6b4751a974f0">e149dea9</a></strong>
<div>
<span>by Daniel Gröber</span>
<i>at 2020-04-14T23:31:38-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts: Fix nomenclature in OVERWRITING_CLOSURE macros

The additional commentary introduced by commit 8916e64e5437 ("Implement
shrinkSmallMutableArray# and resizeSmallMutableArray#.") unfortunately got
this wrong. We set 'prim' to true in overwritingClosureOfs because we
_don't_ want to call LDV_recordDead().

The reason is because of this "inherently used" distinction made in the LDV
profiler so I rename the variable to be more appropriate.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/1dd3d18c2afd9e6009cd53295d26f8b31ca58fec">1dd3d18c</a></strong>
<div>
<span>by Daniel Gröber</span>
<i>at 2020-04-14T23:31:38-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove call to LDV_RECORD_CREATE for array resizing
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/19de2fb090a25ab0d640d0cd5aef09f35e7455a0">19de2fb0</a></strong>
<div>
<span>by Daniel Gröber</span>
<i>at 2020-04-14T23:31:38-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts: Assert LDV_recordDead is not called for inherently used closures

The comments make it clear LDV_recordDead should not be called for
inhererently used closures, so add an assertion to codify this fact.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/0b934e30417a767063625494ecf135c9d6006f71">0b934e30</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-04-14T23:32:14-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Bump template-haskell version to 2.17.0.0

This requires bumping the `exceptions` and `text` submodules to bring
in commits that bump their respective upper version bounds on
`template-haskell`.

Fixes #17645. Fixes #17696.

Note that the new `text` commit includes a fair number of additions
to the Haddocks in that library. As a result, Haddock has to do more
work during the `haddock.Cabal` test case, increasing the number of
allocations it requires. Therefore,

-------------------------
Metric Increase:
    haddock.Cabal
-------------------------
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/22cc8e513fcfa89a4391f075534d903596a05895">22cc8e51</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-04-15T17:48:47-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix #18052 by using pprPrefixOcc in more places

This fixes several small oversights in the choice of pretty-printing
function to use. Fixes #18052.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ec77b2f16a78b13f54794c954953d8878dea9db2">ec77b2f1</a></strong>
<div>
<span>by Daniel Gröber</span>
<i>at 2020-04-15T17:49:24-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts: ProfHeap: Fix wrong time in last heap profile sample

We've had this longstanding issue in the heap profiler, where the time of
the last sample in the profile is sometimes way off causing the rendered
graph to be quite useless for long runs.

It seems to me the problem is that we use mut_user_time() for the last
sample as opposed to getRTSStats(), which we use when calling heapProfile()
in GC.c.

The former is equivalent to getProcessCPUTime() but the latter does
some additional stuff:

    getProcessCPUTime() - end_init_cpu - stats.gc_cpu_ns -
    stats.nonmoving_gc_cpu_ns

So to fix this just use getRTSStats() in both places.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/85fc32f03a6df92ec8d4ec9accca3c11b31a1596">85fc32f0</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-04-17T12:45:25-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Hadrian: fix dyn_o/dyn_hi rule (#17534)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/bfde3b76ac7f5a72eca012fe34ac1340a5ce2011">bfde3b76</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-04-17T12:46:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix #18065 by fixing an InstCo oversight in Core Lint

There was a small thinko in Core Lint's treatment of `InstCo`
coercions that ultimately led to #18065. The fix: add an apostrophe.
That's it!

Fixes #18065.

Co-authored-by: Simon Peyton Jones <simonpj@microsoft.com>
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a05348ebaa11d563ab2e33325055317ff3cb8afc">a05348eb</a></strong>
<div>
<span>by Cale Gibbard</span>
<i>at 2020-04-17T13:08:47-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Change the fail operator argument of BindStmt to be a Maybe

Don't use noSyntaxExpr for it. There is no good way to defensively case
on that, nor is it clear one ought to do so.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/79e27144db7011f6d01a2f5ed15fd110d579bb8e">79e27144</a></strong>
<div>
<span>by John Ericson</span>
<i>at 2020-04-17T13:08:47-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Use trees that grow for rebindable operators for `<-` binds

Also add more documentation.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/18bc16ed78dfa1fe9498c5ac1ca38e9f84267872">18bc16ed</a></strong>
<div>
<span>by Cale Gibbard</span>
<i>at 2020-04-17T13:08:47-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Use FailOperator in more places, define a couple datatypes (XBindStmtRn and XBindStmtTc) to help clarify the meaning of XBindStmt in the renamer and typechecker
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/84cc8394d075cea236faa0bcd9ef0a84de89ee8c">84cc8394</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-04-18T13:20:29-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add a missing zonk in tcHsPartialType

I omitted a vital zonk when refactoring tcHsPartialType in
   commit 48fb3482f8cbc8a4b37161021e846105f980eed4
   Author: Simon Peyton Jones <simonpj@microsoft.com>
   Date:   Wed Jun 5 08:55:17 2019 +0100

   Fix typechecking of partial type signatures

This patch fixes it and adds commentary to explain why.

Fixes #18008
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2ee96ac1aa2cbff4e70bc45988930d64599029f2">2ee96ac1</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-04-18T13:21:05-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">gitlab-ci: Bump FreeBSD bootstrap compiler to 8.10.1
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/434312e5fdde91d6ad7b6d199bbb560a72ab6b89">434312e5</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-04-18T13:21:05-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">gitlab-ci: Enable FreeBSD job for so-labelled MRs
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ddffb2278a22b7c0e3a9fce11ada67a471243409">ddffb227</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-04-18T13:21:05-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">gitlab-ci: Use rules syntax for conditional jobs
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e2586828a30202a28dcacac9ab7fc83c43da9e02">e2586828</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-04-18T13:21:05-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Bump hsc2hs submodule
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/15ab6cd548f284732a7f89d78c2b89b1bfc4ea1d">15ab6cd5</a></strong>
<div>
<span>by Ömer Sinan Ağacan</span>
<i>at 2020-04-18T13:21:44-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Improve prepForeignCall error reporting

Show parameters and description of the error code when ffi_prep_cif
fails.

This may be helpful for debugging #17018.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/3ca52151881451ce5b3a7740d003e811b586140d">3ca52151</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-04-18T20:04:14+02:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">GHC.Core.Opt renaming

* GHC.Core.Op                  => GHC.Core.Opt
* GHC.Core.Opt.Simplify.Driver => GHC.Core.Opt.Driver
* GHC.Core.Opt.Tidy            => GHC.Core.Tidy
* GHC.Core.Opt.WorkWrap.Lib    => GHC.Core.Opt.WorkWrap.Utils

As discussed in:
 * https://mail.haskell.org/pipermail/ghc-devs/2020-April/018758.html
 * https://gitlab.haskell.org/ghc/ghc/issues/13009#note_264650
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/15312bbb53f247c9ed2c5cf75100a9f44c1c7227">15312bbb</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-04-18T20:04:46+02:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Modules (#13009)

* SysTools
* Parser
* GHC.Builtin
* GHC.Iface.Recomp
* Settings

Update Haddock submodule

Metric Decrease:
    Naperian
    parsing001
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/eaed0a3289e4c24ff1a70c6fc4b7f8bae6cd2dd3">eaed0a32</a></strong>
<div>
<span>by Alexis King</span>
<i>at 2020-04-19T03:16:44-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add missing addInScope call for letrec binders in OccurAnal

This fixes #18044, where a shadowed variable was incorrectly substituted
by the binder swap on the RHS of a floated-in letrec. This can only
happen when the uniques line up *just* right, so writing a regression
test would be very difficult, but at least the fix is small and
straightforward.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/36882493fcaa9dd2eefa7184929765189ac339ad">36882493</a></strong>
<div>
<span>by Shayne Fletcher</span>
<i>at 2020-04-20T04:36:43-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Derive Ord instance for Extension

Metric Increase:
   T12150
   T12234
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b43365ad62d73afd5c58467ab9a4f9523ab09c18">b43365ad</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-04-20T04:37:20-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix a buglet in redundant-constraint warnings

Ticket #18036 pointed out that we were reporting a redundant
constraint when it really really wasn't.

Turned out to be a buglet in the SkolemInfo for the
relevant implication constraint.  Easily fixed!
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d5fae7da02cff1c7ec7b8e472f85d23aef098968">d5fae7da</a></strong>
<div>
<span>by Ömer Sinan Ağacan</span>
<i>at 2020-04-20T14:39:28-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Mark T12010 fragile on 32-bit
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/bca02fca0119354a6201fd5d019a553015ba2dd8">bca02fca</a></strong>
<div>
<span>by Adam Sandberg Ericsson</span>
<i>at 2020-04-21T06:38:45-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">docs: drop note about not supporting shared libraries on unix systems

[skip ci]
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6655f93324b7f1d30a6baaedfecae455d5e08e39">6655f933</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-04-21T06:39:32-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Use ParserFlags in GHC.Runtime.Eval (#17957)

Instead of passing `DynFlags` to functions such as `isStmt` and
`hasImport` in `GHC.Runtime.Eval` we pass `ParserFlags`. It's a much
simpler structure that can be created purely with `mkParserFlags'`.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/70be0fbcefa07ff164437476bf2809ea7c3ff495">70be0fbc</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-04-21T06:39:32-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">GHC.Runtime: avoid DynFlags (#17957)

* add `getPlatform :: TcM Platform` helper
* remove unused `DynFlags` parameter from `emptyPLS`
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/35e43d48a9a3ab22da90c4c2ea2c805fe762b9c5">35e43d48</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-04-21T06:39:32-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Avoid DynFlags in Ppr code (#17957)

* replace `DynFlags` parameters with `SDocContext` parameters for a few
  Ppr related functions: `bufLeftRenderSDoc`, `printSDoc`,
  `printSDocLn`, `showSDocOneLine`.

* remove the use of `pprCols :: DynFlags -> Int` in Outputable. We
  already have the information via `sdocLineLength :: SDocContext ->
  Int`
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ce5c2999d2e356d034fbf1045a2383c0ac24f15f">ce5c2999</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-04-21T06:39:32-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Avoid using sdocWithDynFlags (#17957)

Remove one use of `sdocWithDynFlags` from `GHC.CmmToLlvm.llvmCodeGen'`
and from `GHC.Driver.CodeOutput.profilingInitCode`
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/f2a98996e7792f572ab685f29742e3476be81166">f2a98996</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-04-21T06:39:32-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Avoid `sdocWithDynFlags` in `pprCLbl` (#17957)

* add a `DynFlags` parameter to `pprCLbl`
* put `maybe_underscore` and `pprAsmCLbl` in a `where` clause to avoid
  `DynFlags` parameters
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/747093b7c23a1cf92b564eb3d9efe2adc15330df">747093b7</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-04-21T06:39:32-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">CmmToAsm DynFlags refactoring (#17957)

* Remove `DynFlags` parameter from `isDynLinkName`: `isDynLinkName` used
  to test the global `ExternalDynamicRefs` flag. Now we test it outside of
  `isDynLinkName`

* Add new fields into `NCGConfig`: current unit id, sse/bmi versions,
  externalDynamicRefs, etc.

* Replace many uses of `DynFlags` by `NCGConfig`

* Moved `BMI/SSE` datatypes into `GHC.Platform`
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ffd7eef22f197ba44f0ced97ebc988f2d7d643a4">ffd7eef2</a></strong>
<div>
<span>by Takenobu Tani</span>
<i>at 2020-04-22T23:09:50-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">stg-spec: Modify file paths according to new module hierarchy

This patch updates file paths according to new module hierarchy [1]:

  * GHC/Stg/Syntax.hs       <= stgSyn/StgSyn.hs
  * GHC/Types/Literal.hs    <= basicTypes/Literal.hs
  * GHC/Types/CostCentre.hs <= profiling/CostCentre.hs

This patch also updates old file path [2]:

  * utils/genapply/Main.hs  <= utils/genapply/GenApply.hs

[1]: https://gitlab.haskell.org/ghc/ghc/-/wikis/Make-GHC-codebase-more-modular
[2]: commit 0cc4aad36f

[skip ci]
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e8a5d81b9358466f8889f679bfea9f796d85f7f3">e8a5d81b</a></strong>
<div>
<span>by Jonathan DK Gibbons</span>
<i>at 2020-04-22T23:10:28-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Refactor the `MatchResult` type in the desugarer

This way, it does a better job of proving whether or not the fail operator is used.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/dcb7fe5aa2bc331fa71b537b042ec08a7c79b1ac">dcb7fe5a</a></strong>
<div>
<span>by John Ericson</span>
<i>at 2020-04-22T23:10:28-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove panic in dsHandleMonadicFailure

Rework dsHandleMonadicFailure to be correct by construction instead of
using an unreachable panic.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/cde23cd47170cc33845b6859a47dd06ee85094d8">cde23cd4</a></strong>
<div>
<span>by John Ericson</span>
<i>at 2020-04-22T23:10:28-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Inline `adjustMatchResult`

It is just `fmap`
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/72cb6bcc23d2540274aac7d1b80682ef092f1615">72cb6bcc</a></strong>
<div>
<span>by John Ericson</span>
<i>at 2020-04-22T23:10:28-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Generalize type of `matchCanFail`
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/401f7bb312aa6c570287d313f8b587aaebca72b2">401f7bb3</a></strong>
<div>
<span>by John Ericson</span>
<i>at 2020-04-22T23:10:28-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">`MatchResult'` -> `MatchResult`

Inline `MatchResult` alias accordingly.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6c9fae2342f19ab3e6ac688825a3817b23bf1fcc">6c9fae23</a></strong>
<div>
<span>by Alexis King</span>
<i>at 2020-04-22T23:11:12-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Mark DataCon wrappers CONLIKE

Now that DataCon wrappers don’t inline until phase 0 (see commit
b78cc64e923716ac0512c299f42d4d0012306c05), it’s important that
case-of-known-constructor and RULE matching be able to see saturated
applications of DataCon wrappers in unfoldings. Making them conlike is a
natural way to do it, since they are, in fact, precisely the sort of
thing the CONLIKE pragma exists to solve.

Fixes #18012.

This also bumps the version of the parsec submodule to incorporate a
patch that avoids a metric increase on the haddock perf tests. The
increase was not really a flaw in this patch, as parsec was implicitly
relying on inlining heuristics. The patch to parsec just adds some
INLINABLE pragmas, and we get a nice performance bump out of it (well
beyond the performance we lost from this patch).

Metric Decrease:
    T12234
    WWRec
    haddock.Cabal
    haddock.base
    haddock.compiler
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/48b8951e819e5d7d06ad7e168323de320d87bbd6">48b8951e</a></strong>
<div>
<span>by Roland Senn</span>
<i>at 2020-04-22T23:11:51-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix tab-completion for :break (#17989)

In tab-completion for the `:break` command, only those
identifiers should be shown, that are accepted in the
`:break` command. Hence these identifiers must be

- defined in an interpreted module
- top-level
- currently in scope
- listed in a `ModBreaks` value as a possible breakpoint.

The identifiers my be qualified or unqualified.

To get all possible top-level breakpoints for tab-completeion
with the correct qualification do:

1. Build the  list called `pifsBreaks` of all pairs of
(Identifier, module-filename) from the `ModBreaks` values.
Here all identifiers are unqualified.

2. Build the list called `pifInscope` of all pairs of
(Identifiers, module-filename) with identifiers from
the `GlobalRdrEnv`. Take only those identifiers that are
in scope and have the  correct prefix.
Here the identifiers may be qualified.

3. From the `pifInscope` list seclect all pairs that can be
found in the `pifsBreaks` list, by comparing only the
unqualified part of the identifier.
The remaining identifiers can be used for tab-completion.

This ensures, that we show only identifiers, that can be used
in a `:break` command.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/34a45ee600d5346f5d1728047fa185698ed7ee84">34a45ee6</a></strong>
<div>
<span>by Peter Trommler</span>
<i>at 2020-04-22T23:12:27-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">PPC NCG: Add DWARF constants and debug labels

Fixes #11261
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ffde234854f49dba9ec4735aad74b30fd2deee29">ffde2348</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-04-22T23:13:06-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Do eager instantation in terms

This patch implements eager instantiation, a small but critical change
to the type inference engine, #17173.  The main change is this:

  When inferring types, always return an instantiated type
  (for now, deeply instantiated; in future shallowly instantiated)

There is more discussion in
https://www.tweag.io/posts/2020-04-02-lazy-eager-instantiation.html

There is quite a bit of refactoring in this patch:

* The ir_inst field of GHC.Tc.Utils.TcType.InferResultk
  has entirely gone.  So tcInferInst and tcInferNoInst have collapsed
  into tcInfer.

* Type inference of applications, via tcInferApp and
  tcInferAppHead, are substantially refactored, preparing
  the way for Quick Look impredicativity.

* New pure function GHC.Tc.Gen.Expr.collectHsArgs and applyHsArgs
  are beatifully dual.  We can see the zipper!

* GHC.Tc.Gen.Expr.tcArgs is now much nicer; no longer needs to return
  a wrapper

* In HsExpr, HsTypeApp now contains the the actual type argument,
  and is used in desugaring, rather than putting it in a mysterious
  wrapper.

* I struggled a bit with good error reporting in
  Unify.matchActualFunTysPart. It's a little bit simpler than before,
  but still not great.

Some smaller things

* Rename tcPolyExpr --> tcCheckExpr
         tcMonoExpr --> tcLExpr
* tcPatSig moves from GHC.Tc.Gen.HsType to GHC.Tc.Gen.Pat

Metric Decrease:
    T9961

Reduction of 1.6% in comiler allocation on T9961, I think.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6f84aca31290afc11acde0f86969a535e519e1d5">6f84aca3</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-04-22T23:13:43-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts: Ensure that sigaction structs are initialized

I noticed these may have uninitialized fields when looking into #18037.
The reporter says that zeroing them doesn't fix the MSAN failures they
observe but zeroing them is the right thing to do regardless.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c29f0fa6ee831ec8a223561312d7176ef87a7ece">c29f0fa6</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-04-22T23:14:21-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add "ddump-cmm-opt" as alias for "ddump-opt-cmm".
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4b4a8b60a5b403e02117ab0a30a386664845586b">4b4a8b60</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-04-22T23:14:57-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">llvmGen: Remove -fast-llvm flag

Issue #18076 drew my attention to the undocumented `-fast-llvm` flag for
the LLVM code generator introduced in
22733532171330136d87533d523f565f2a4f102f. Speaking to Moritz about this,
the motivation for this flag was to avoid potential incompatibilities
between LLVM and the assembler/linker toolchain by making LLVM
responsible for machine-code generation.

Unfortunately, this cannot possibly work: the LLVM backend's mangler
performs a number of transforms on the assembler generated by LLVM that
are necessary for correctness. These are currently:

 * mangling Haskell functions' symbol types to be `object` instead of
   `function` on ELF platforms (necessary for tables-next-to-code)
 * mangling AVX instructions to ensure that we don't assume alignment
   (which LLVM otherwise does)
 * mangling Darwin's  subsections-via-symbols directives

Given that these are all necessary I don't believe that we can support
`-fast-llvm`. Let's rather remove it.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/831b66425aa3a24e769ace8d4649299ade021717">831b6642</a></strong>
<div>
<span>by Moritz Angermann</span>
<i>at 2020-04-22T23:15:33-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix build warning; add more informative information to the linker; fix linker for empty sections
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c409961aea59d2fe2ae71036a1ae6d94c4ee05c8">c409961a</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-04-22T23:16:12-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Update commentary and slightly refactor GHC.Tc.Deriv.Infer

There was some out-of-date commentary in `GHC.Tc.Deriv.Infer` that
has been modernized. Along the way, I removed the `bad` constraints
in `simplifyDeriv`, which did not serve any useful purpose (besides
being printed in debugging output).

Fixes #18073.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/125aa2b8b8bb402d7819c3a35255b65c15b8bf9a">125aa2b8</a></strong>
<div>
<span>by Ömer Sinan Ağacan</span>
<i>at 2020-04-22T23:16:51-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove leftover comment in tcRnModule', redundant bind

The code for the comment was moved in dc8c03b2a5c but the comment was
forgotten.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8ea37b01b6ab16937f7b528b6bbae9fade9f1361">8ea37b01</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-04-22T23:17:34-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">RTS: workaround a Linux kernel bug in timerfd

Reading a timerfd may return 0: https://lkml.org/lkml/2019/8/16/335.

This is currently undocumented behavior and documentation "won't happen
anytime soon" (https://lkml.org/lkml/2020/2/13/295).

With this patch, we just ignore the result instead of crashing. It may
fix #18033 but we can't be sure because we don't have enough
information.

See also this discussion about the kernel bug:
https://github.com/Azure/sonic-swss-common/pull/302/files/1f070e7920c2e5d63316c0105bf4481e73d72dc9
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/cd8409c26d4370bf2cdcd76801974e99a9adf7b0">cd8409c2</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-04-23T11:39:24-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Create di_scoped_tvs for associated data family instances properly

See `Note [Associated data family instances and di_scoped_tvs]` in
`GHC.Tc.TyCl.Instance`, which explains all of the moving parts.

Fixes #18055.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/339e8ece1c844af5c9165efbc3a928890c2f75c7">339e8ece</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-04-23T11:40:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">hadrian/ghci: Allow arguments to be passed to GHCi

Previously the arguments passed to hadrian/ghci were passed both to
`hadrian` and GHCi. This is rather odd given that there are essentially
not arguments in the intersection of the two. Let's just pass them to
GHCi; this allows `hadrian/ghci -Werror`.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/5946c85abcf66555cdbcd3eed02cb8f512b6110c">5946c85a</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-04-23T11:40:38-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite: Don't attempt to read .std{err,out} files if they don't exist

Simon reports that he was previously seeing framework failures due to
an attempt to read the non-existing T13456.stderr. While I don't know
exactly what this is due to, it does seem like a non-existing
.std{out,err} file should be equivalent to an empty file. Teach the
testsuite driver to treat it as such.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c42754d5fdd3c2db554d9541bab22d1b3def4be7">c42754d5</a></strong>
<div>
<span>by John Ericson</span>
<i>at 2020-04-23T18:32:43-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Trees That Grow refactor for `ConPat` and `CoPat`

- `ConPat{In,Out}` -> `ConPat`

- `CoPat` -> `XPat (CoPat ..)`

Note that `GHC.HS.*` still uses `HsWrap`, but only when `p ~ GhcTc`.
After this change, moving the type family instances out of `GHC.HS.*` is
sufficient to break the cycle.

Add XCollectPat class to decide how binders are collected from XXPat based on the pass.

Previously we did this with IsPass, but that doesn't work for Haddock's
DocNameI, and the constraint doesn't express what actual distinction is being
made. Perhaps a class for collecting binders more generally is in order, but we
haven't attempted this yet.

Pure refactor of code around ConPat

 - InPat/OutPat synonyms removed

 - rename several identifiers

 - redundant constraints removed

 - move extension field in ConPat to be first

 - make ConPat use record syntax more consistently

Fix T6145 (ConPatIn became ConPat)

Add comments from SPJ.

Add comment about haddock's use of CollectPass.

Updates haddock submodule.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/72da0c29cd7c336cdce3b36d1dd9e8b65a53afbd">72da0c29</a></strong>
<div>
<span>by mniip</span>
<i>at 2020-04-23T18:33:21-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add :doc to GHC.Prim
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2c23e2e37d6c937a425c53da643aec90bda01ef6">2c23e2e3</a></strong>
<div>
<span>by mniip</span>
<i>at 2020-04-23T18:33:21-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Include docs for non-primop entries in primops.txt as well
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/0ac29c885fba7ed69de83a597cdbd03696c9ed13">0ac29c88</a></strong>
<div>
<span>by mniip</span>
<i>at 2020-04-23T18:33:21-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">GHC.Prim docs: note and test
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b0fbfc7582fb81314dc28a056536737fb5eeaa6e">b0fbfc75</a></strong>
<div>
<span>by John Ericson</span>
<i>at 2020-04-24T12:07:14-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Switch order on `GhcMake.IsBoot`

In !1798 we were requested to replace many `Bool`s with this data type.
But those bools had `False` meaning `NotBoot`, so the `Ord` instance
would be flipped if we use this data-type as-is.

Since the planned formally-`Bool` occurrences vastly outnumber the
current occurrences, we figured it would be better to conform the `Ord`
instance to how the `Bool` is used now, fixing any issues, rather than
fix them currently with the bigger refactor later in !1798. That way,
!1798 can be a "pure" refactor with no behavioral changes.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/af332442123878c1b61d236dce46418efcbe8750">af332442</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-04-26T13:55:14-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Modules: Utils and Data (#13009)

Update Haddock submodule

Metric Increase:
   haddock.compiler
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/cd4434c8e77213bf3e6f83227fd8802c9f2a6fe2">cd4434c8</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-04-26T13:55:16-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix misleading Ptr phantom type in SerializedCompact (#15653)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/22bf5c738e0339fa12940414d6448896c6733808">22bf5c73</a></strong>
<div>
<span>by Ömer Sinan Ağacan</span>
<i>at 2020-04-26T13:55:22-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Tweak includes in non-moving GC headers

We don't use hash tables in non-moving GC so remove the includes.

This breaks Compact.c as existing includes no longer include Hash.h, so
include Hash.h explicitly in Compact.c.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/99823ed24b22447b14202ca57f75550773c44dbe">99823ed2</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-04-27T20:24:46-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">TH: fix Show/Eq/Ord instances for Bytes (#16457)

We shouldn't compare pointer values but the actual bytes.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c62271a21b1ba1d207aaebf370c87dd884fa6ae1">c62271a2</a></strong>
<div>
<span>by Alp Mestanogullari</span>
<i>at 2020-04-27T20:25:33-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">hadrian: always capture both stdout and stderr when running a builder fails

The idea being that when a builder('s command) fails, we quite likely want to
have all the information available to figure out why. Depending on the builder
_and_ the particular problem, the useful bits of information can be printed
on stdout or stderr.

We accomplish this by defining a simple wrapper for Shake's `cmd` function,
that just _always_ captures both streams in case the command returns a non-zero
exit code, and by using this wrapper everywhere in `hadrian/src/Builder.hs`.

Fixes #18089.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4b9764db7c190de377c06dfc71bfe6e4b37c7eb0">4b9764db</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-04-28T15:40:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Define a Quote IO instance

Fixes #18103.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/518a63d4d7e31e49a81ad66d5e5ccb1f790f6de9">518a63d4</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-04-28T15:40:42-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Make boxed 1-tuples have known keys

Unlike other tuples, which use special syntax and are "known" by way
of a special `isBuiltInOcc_maybe` code path, boxed 1-tuples do not
use special syntax. Therefore, in order to make sure that the
internals of GHC are aware of the `data Unit a = Unit a` definition
in `GHC.Tuple`, we give `Unit` known keys. For the full details, see
`Note [One-tuples] (Wrinkle: Make boxed one-tuple names have known keys)`
in `GHC.Builtin.Types`.

Fixes #18097.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2cfc4ab9710c873a55e9a44aac9dacb06ecce36f">2cfc4ab9</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-04-30T01:56:56-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Document backpack fields in DynFlags
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/10a2ba90aa6a788677104cc43318c66f46e2e2b0">10a2ba90</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-04-30T01:56:56-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Refactor UnitInfo

* Rename InstalledPackageInfo into GenericUnitInfo

The name InstalledPackageInfo is only kept for alleged backward
compatibility reason in Cabal. ghc-boot has its own stripped down copy
of this datatype but it doesn't need to keep the name. Internally we
already use type aliases (UnitInfo in GHC, PackageCacheFormat in
ghc-pkg).

* Rename UnitInfo fields: add "unit" prefix and fix misleading names

* Add comments on every UnitInfo field

* Rename SourcePackageId into PackageId

"Package" already indicates that it's a "source package". Installed
package components are called units.

Update Haddock submodule
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/69562e34fb5d9571e9efc1cb90c879e50129a510">69562e34</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-04-30T01:56:56-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove unused `emptyGenericUnitInfo`
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9e2c8e0e37a2709d5790d6c9a877a1463d6e88b5">9e2c8e0e</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-04-30T01:56:56-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Refactor UnitInfo load/store from databases

Converting between UnitInfo stored in package databases and UnitInfo as
they are used in ghc-pkg and ghc was done in a very convoluted way (via
BinaryStringRep and DbUnitModuleRep type classes using fun deps, etc.).
It was difficult to understand and even more to modify (I wanted to
try to use a GADT for UnitId but fun deps got in the way).

The new code uses much more straightforward functions to convert between
the different representations. Much simpler.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ea717aa4248b2122e1f7550f30239b50ab560e4f">ea717aa4</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-04-30T01:56:56-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Factorize mungePackagePaths code

This patch factorizes the duplicated code used in ghc-pkg and in GHC to
munge package paths/urls.

It also fixes haddock-html munging in GHC (allowed to be either a file
or a url) to mimic ghc-pkg behavior.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/10d15f1ec4bab4dd6152d87fc66e61658a705eb3">10d15f1e</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-04-30T01:56:56-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Refactoring unit management code

Over the years the unit management code has been modified a lot to keep
up with changes in Cabal (e.g. support for several library components in
the same package), to integrate BackPack, etc. I found it very hard to
understand as the terminology wasn't consistent, was referring to past
concepts, etc.

The terminology is now explained as clearly as I could in the Note
"About Units" and the code is refactored to reflect it.

-------------------

Many names were misleading: UnitId is not an Id but could be a virtual
unit (an indefinite one instantiated on the fly), IndefUnitId
constructor may contain a definite instantiated unit, etc.

   * Rename IndefUnitId into InstantiatedUnit
   * Rename IndefModule into InstantiatedModule
   * Rename UnitId type into Unit
   * Rename IndefiniteUnitId constructor into VirtUnit
   * Rename DefiniteUnitId constructor into RealUnit
   * Rename packageConfigId into mkUnit
   * Rename getPackageDetails into unsafeGetUnitInfo
   * Rename InstalledUnitId into UnitId

Remove references to misleading ComponentId: a ComponentId is just an
indefinite unit-id to be instantiated.

   * Rename ComponentId into IndefUnitId
   * Rename ComponentDetails into UnitPprInfo
   * Fix display of UnitPprInfo with empty version: this is now used for
     units dynamically generated by BackPack

Generalize several types (Module, Unit, etc.) so that they can be used
with different unit identifier types: UnitKey, UnitId, Unit, etc.

   * GenModule: Module, InstantiatedModule and InstalledModule are now
     instances of this type
   * Generalize DefUnitId, IndefUnitId, Unit, InstantiatedUnit,
     PackageDatabase

Replace BackPack fake "hole" UnitId by a proper HoleUnit constructor.

Add basic support for UnitKey. They should be used more in the future to
avoid mixing them up with UnitId as we do now.

Add many comments.

Update Haddock submodule
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8bfb0219587b969d5c8f723c46d433e9493958b4">8bfb0219</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-04-30T01:56:56-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Unit: split and rename modules

Introduce GHC.Unit.* hierarchy for everything concerning units, packages
and modules.

Update Haddock submodule
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/71484b09fa3c676e99785b3d68f69d4cfb14266e">71484b09</a></strong>
<div>
<span>by Alexis King</span>
<i>at 2020-04-30T01:57:35-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Allow block arguments in arrow control operators

Arrow control operators have their own entries in the grammar, so they
did not cooperate with BlockArguments. This was just a minor oversight,
so this patch adjusts the grammar to add the desired behavior.

fixes #18050
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a48cd2a045695c5f34ed7b00184a8d91c4fcac0e">a48cd2a0</a></strong>
<div>
<span>by Alexis King</span>
<i>at 2020-04-30T01:57:35-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Allow LambdaCase to be used as a command in proc notation
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/f4d3773c7f4209cd3a0495ab9a29b978da48e2ff">f4d3773c</a></strong>
<div>
<span>by Alexis King</span>
<i>at 2020-04-30T01:57:35-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Document BlockArguments/LambdaCase support in arrow notation
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/5bdfdd139e5aff57631e9f1c6654dc7b8590c63f">5bdfdd13</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-04-30T01:58:15-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add tests for #17873
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/19b701c216246596710f0eba112ed5ee7b6bf870">19b701c2</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-04-30T07:30:13-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Mark rule args as non-tail-called

This was just an omission...b I'd failed to call markAllNonTailCall on
rule args.  I think this bug has been here a long time, but it's quite
hard to trigger.

Fixes #18098
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/014ef4a3d9ee30b8add9118950f1f5007143bd1c">014ef4a3</a></strong>
<div>
<span>by Matthew Pickering</span>
<i>at 2020-04-30T07:30:50-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Hadrian: Improve tool-args command to support more components

There is a new command to hadrian, tool:path/to/file.hs, which returns
the options needed to compile that file in GHCi.

This is now used in the ghci script with argument `ghc/Main.hs` but its
main purpose is to support the new multi-component branch of ghcide.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2aa676114bca40d6124ba90d13242c7c102369e0">2aa67611</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-04-30T21:34:44-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">nonmoving: Clear bitmap after initializing block size

Previously nonmovingInitSegment would clear the bitmap before
initializing the segment's block size. This is broken since
nonmovingClearBitmap looks at the segment's block size to determine how
much bitmap to clear.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/54dad3cf1e04f16ea00fb6a41b378e948c8ebf0f">54dad3cf</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-04-30T21:34:44-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">nonmoving: Explicitly memoize block count

A profile cast doubt on whether the compiler hoisted the bound out the
loop as I would have expected here. It turns out it did but nevertheless
it seems clearer to just do this manually.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/99ff8145044288a8a58c8028516903937ba3935c">99ff8145</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-04-30T21:34:44-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">nonmoving: Eagerly flush all capabilities' update remembered sets

(cherry picked from commit 2fa79119570b358a4db61446396889b8260d7957)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/05b0a9fd136869f71245e12fdae64d42dc2ee1df">05b0a9fd</a></strong>
<div>
<span>by Ömer Sinan Ağacan</span>
<i>at 2020-04-30T21:35:24-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove OneShotInfo field of LFReEntrant, document OneShotInfo

The field is only used in withNewTickyCounterFun and it's easier to
directly pass a parameter for one-shot info to withNewTickyCounterFun
instead of passing it via LFReEntrant. This also makes !2842 simpler.

Other changes:

- New Note (by SPJ) [OneShotInfo overview] added.
- Arity argument of thunkCode removed as it's always 0.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a43620c621563deed76ba6b417e3a7a707c15d23">a43620c6</a></strong>
<div>
<span>by Ömer Sinan Ağacan</span>
<i>at 2020-04-30T21:35:24-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">GHC.StgToCmm.Ticky: remove a few unused stuff
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/780de9e11014a88a4f676eb296c30fec2b07b5c2">780de9e1</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-05-01T10:37:39-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Use platform in Iface Binary
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/f8386c7b6a9d26bc5fd2c1d74d944c8df6337690">f8386c7b</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-05-01T10:37:39-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Refactor PprDebug handling

If `-dppr-debug` is set, then PprUser and PprDump styles are silently
replaced with PprDebug style. This was done in `mkUserStyle` and
`mkDumpStyle` smart constructors. As a consequence they needed a
DynFlags parameter.

Now we keep the original PprUser and PprDump styles until they are used
to create an `SDocContext`. I.e. the substitution is only performed in
`initSDocContext`.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b3df9e780fb2f5658412c644849cd0f1e6f50331">b3df9e78</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-05-01T10:37:39-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove PprStyle param of logging actions

Use `withPprStyle` instead to apply a specific style to a SDoc.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/de9fc995c2170bc34600ee3fc80393c67cfecad1">de9fc995</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-05-01T10:37:39-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fully remove PprDebug

PprDebug was a pain to deal with consistently as it is implied by
`-dppr-debug` but it isn't really a PprStyle. We remove it completely
and query the appropriate SDoc flag instead (`sdocPprDebug`) via
helpers (`getPprDebug` and its friends).
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8b51fcbd67ca17a6dcc2f9e5a29176f836bf11d2">8b51fcbd</a></strong>
<div>
<span>by Sebastian Graf</span>
<i>at 2020-05-01T10:38:16-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">PmCheck: Only call checkSingle if we would report warnings
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/fd7ea0fee92a60f9658254cc4fe3abdb4ff299b1">fd7ea0fe</a></strong>
<div>
<span>by Sebastian Graf</span>
<i>at 2020-05-01T10:38:16-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">PmCheck: Pick up `EvVar`s bound in `HsWrapper`s for long-distance info

`HsWrapper`s introduce evidence bindings through `WpEvLam` which the
pattern-match coverage checker should be made aware of.

Failing to do so caused #18049, where the resulting impreciseness of
imcompleteness warnings seemingly contradicted with
`-Winaccessible-code`.

The solution is simple: Collect all the evidence binders of an
`HsWrapper` and add it to the ambient `Deltas` before desugaring
the wrapped expression.

But that means we pick up many more evidence bindings, even when they
wrap around code without a single pattern match to check! That regressed
`T3064` by over 300%, so now we are adding long-distance info lazily
through judicious use of `unsafeInterleaveIO`.

Fixes #18049.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7bfe9ac514e18c0b0e24ff55230fe98ec9db894c">7bfe9ac5</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-05-03T04:41:33-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts: Enable tracing of nonmoving heap census with -ln

Previously this was not easily available to the user. Fix this.
Non-moving collection lifecycle events are now reported with -lg.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c560dd07f506810eaabae2f582491138aa224819">c560dd07</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-05-03T04:41:33-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">users guide: Move eventlog documentation users guide
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/02543d5ef9bd7a910fc9fece895780583ab9635a">02543d5e</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-05-03T04:41:33-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">users guide: Add documentation for non-moving GC events
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b465dd4500beffe919e8b8dcd075008399fbf446">b465dd45</a></strong>
<div>
<span>by Alexis King</span>
<i>at 2020-05-03T04:42:12-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Flatten nested casts in the simple optimizer

Normally, we aren’t supposed to generated any nested casts, since mkCast
takes care to flatten them, but the simple optimizer didn’t use mkCast,
so they could show up after inlining. This isn’t really a problem, since
the simplifier will clean them up immediately anyway, but it can clutter
the -ddump-ds output, and it’s an extremely easy fix.

closes #18112
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8bdc03d61cb7a2f96887c86bd0b253f7c108fcde">8bdc03d6</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-05-04T01:56:59-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Don't return a panic in tcNestedSplice

In GHC.Tc.Gen.Splice.tcNestedSplice we were returning a
typechecked expression of "panic". That is usually OK, because
the result is discarded.  But it happens that tcApp now looks at
the typechecked expression, trivially, to ask if it is tagToEnum.
So being bottom is bad.

Moreover a debug-trace might print it out.

So better to return a civilised expression, even though it is
usually discarded.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/0bf640b19d7a7ad0800152752a71c1dd4e6c696d">0bf640b1</a></strong>
<div>
<span>by Baldur Blöndal</span>
<i>at 2020-05-04T01:57:36-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Don't require parentheses around via type (`-XDerivingVia'). Fixes #18130".
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/30272412fa437ab8e7a8035db94a278e10513413">30272412</a></strong>
<div>
<span>by Artem Pelenitsyn</span>
<i>at 2020-05-04T13:19:59-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove custom ExceptionMonad class (#18075) (updating haddock submodule accordingly)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b9f7c08ff5aa71b7673c8136b897e6f29de01330">b9f7c08f</a></strong>
<div>
<span>by jneira</span>
<i>at 2020-05-04T13:20:37-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove unused hs-boot file
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/1d8f80cd64edd1ea6a5d4c4aa2e09ad0d077ae1b">1d8f80cd</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-05-05T03:22:46-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove references to -package-key

* remove references to `-package-key` which has been removed in 2016
  (240ddd7c39536776e955e881d709bbb039b48513)

* remove support for `-this-package-key` which has been deprecated at the
  same time
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7bc3a65b467c4286377b9bded277d5a2f69160b3">7bc3a65b</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-05-05T03:23:31-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove SpecConstrAnnotation (#13681)

This has been deprecated since 2013. Use GHC.Types.SPEC instead.

Make GHC.Exts "not-home" for haddock

Metric Decrease:
   haddock.base
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/3c862f635394b02c121f917a4d9ea7802033eebb">3c862f63</a></strong>
<div>
<span>by DenisFrezzato</span>
<i>at 2020-05-05T03:24:15-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix Haskell98 short description in documentation
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2420c555e6cb681f4ef7c4ae3192a850ab431759">2420c555</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-05-05T03:24:53-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add regression tests for #16244, #16245, #16758

Commit e3c374cc5bd7eb49649b9f507f9f7740697e3f70 ended up
fixing quite a few bugs:

* This commit fixes #16244 completely. A regression test has been
  added.
* This commit fixes one program from #16245. (The program in
  https://gitlab.haskell.org/ghc/ghc/issues/16245#note_211369 still
  panics, and the program in
  https://gitlab.haskell.org/ghc/ghc/issues/16245#note_211400 still
  loops infinitely.) A regression test has been added for this
  program.
* This commit fixes #16758. Accordingly, this patch removes the
  `expect_broken` label from the `T16758` test case, moves it from
  `should_compile` to `should_fail` (as it should produce an error
  message), and checks in the expected stderr.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/40c71c2cf38b4e134d81b7184a4d5e02949ae70c">40c71c2c</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-05-05T03:25:31-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix colorized error messages (#18128)

In b3df9e780fb2f5658412c644849cd0f1e6f50331 I broke colorized messages
by using "dump" style instead of "user" style. This commits fixes it.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7ab6ab093c86227b6d33a5185ebbd11928ac9754">7ab6ab09</a></strong>
<div>
<span>by Richard Eisenberg</span>
<i>at 2020-05-06T04:39:32-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Refactor hole constraints.

Previously, holes (both expression holes / out of scope variables and
partial-type-signature wildcards) were emitted as *constraints* via
the CHoleCan constructor. While this worked fine for error reporting,
there was a fair amount of faff in keeping these constraints in line.
In particular, and unlike other constraints, we could never change
a CHoleCan to become CNonCanonical. In addition:
 * the "predicate" of a CHoleCan constraint was really the type
   of the hole, which is not a predicate at all
 * type-level holes (partial type signature wildcards) carried
   evidence, which was never used
 * tcNormalise (used in the pattern-match checker) had to create
   a hole constraint just to extract it again; it was quite messy

The new approach is to record holes directly in WantedConstraints.
It flows much more nicely now.

Along the way, I did some cleaning up of commentary in
GHC.Tc.Errors.Hole, which I had a hard time understanding.

This was instigated by a future patch that will refactor
the way predicates are handled. The fact that CHoleCan's
"predicate" wasn't really a predicate is incompatible with
that future patch.

No test case, because this is meant to be purely internal.

It turns out that this change improves the performance of
the pattern-match checker, likely because fewer constraints
are sloshing about in tcNormalise. I have not investigated
deeply, but an improvement is not a surprise here:

-------------------------
Metric Decrease:
    PmSeriesG
-------------------------
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/420b957df9d831632a3edab682778b11734255f1">420b957d</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-05-06T04:40:08-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts: Zero block flags with -DZ

Block flags are very useful for determining the state of a block.
However, some block allocator users don't touch them, leading to
misleading values. Ensure that we zero then when zero-on-gc is set. This
is safe and makes the flags more useful during debugging.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/740b3b8df76dabd88bdb3474aad2b287b0960f07">740b3b8d</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-05-06T04:40:08-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">nonmoving: Fix incorrect failed_to_evac value during deadlock gc

Previously we would incorrectly set the failed_to_evac flag if we
evacuated a value due to a deadlock GC. This would cause us to mark more
things as dirty than strictly necessary. It also turned up a nasty but
which I will fix next.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b2d72c758233830446230800d0045badc01b42ca">b2d72c75</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-05-06T04:40:08-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">nonmoving: Fix handling of dirty objects

Previously we (incorrectly) relied on failed_to_evac to be "precise".
That is, we expected it to only be true if *all* of an object's fields
lived outside of the non-moving heap. However, does not match the
behavior of failed_to_evac, which is true if *any* of the object's
fields weren't promoted (meaning that some others *may* live in the
non-moving heap).

This is problematic as we skip the non-moving write barrier for dirty
objects (which we can only safely do if *all* fields point outside of
the non-moving heap).

Clearly this arises due to a fundamental difference in the behavior
expected of failed_to_evac in the moving and non-moving collector.
e.g., in the moving collector it is always safe to conservatively say
failed_to_evac=true whereas in the non-moving collector the safe value
is false.

This issue went unnoticed as I never wrote down the dirtiness
invariant enforced by the non-moving collector. We now define this
invariant as

    An object being marked as dirty implies that all of its fields are
    on the mark queue (or, equivalently, update remembered set).

To maintain this invariant we teach nonmovingScavengeOne to push the
fields of objects which we fail to evacuate to the update remembered
set. This is a simple and reasonably cheap solution and avoids the
complexity and fragility that other, more strict alternative invariants
would require.

All of this is described in a new Note, Note [Dirty flags in the
non-moving collector] in NonMoving.c.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9f3e6884e338015f2953c4c0844e04d467f53dd5">9f3e6884</a></strong>
<div>
<span>by Zubin Duggal</span>
<i>at 2020-05-06T04:41:08-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Allow atomic update of NameCache in readHieFile

The situation arises in ghcide where multiple different threads may need to
update the name cache, therefore with the older interface it could happen
that you start reading a hie file with name cache A and produce name cache
A + B, but another thread in the meantime updated the namecache to A +
C. Therefore if you write the new namecache you will lose the A' updates
from the second thread.

Updates haddock submodule
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/edec6a6c205378caf15d1d874d7e901ba76dd293">edec6a6c</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-05-06T04:41:57-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Make isTauTy detect higher-rank contexts

Previously, `isTauTy` would only detect higher-rank `forall`s, not
higher-rank contexts, which led to some minor bugs observed
in #18127. Easily fixed by adding a case for
`(FunTy InvisArg _ _)`.

Fixes #18127.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a95e7fe02efd2fdeec91ba46de64bc78c81381eb">a95e7fe0</a></strong>
<div>
<span>by Ömer Sinan Ağacan</span>
<i>at 2020-05-06T04:42:39-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">ELF linker: increment curSymbol after filling in fields of current entry

The bug was introduced in a8b7cef4d45 which added a field to the
`symbols` array elements and then updated this code incorrectly:

    - oc->symbols[curSymbol++] = nm;
    + oc->symbols[curSymbol++].name = nm;
    + oc->symbols[curSymbol].addr = symbol->addr;
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/cab1871ab93feeacf2bf9a1c65b1c919ca9c5399">cab1871a</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-05-06T04:43:21-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Move LeadingUnderscore into Platform (#17957)

Avoid direct use of DynFlags to know if symbols must be prefixed by an
underscore.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/94e7c563ab24fe452a16900a6777349970df1945">94e7c563</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-05-06T04:43:21-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Don't use DynFlags in showLinkerState (#17957)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9afd92512b41cf6c6de3a17b474d8d4bb01158c3">9afd9251</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-05-06T04:43:58-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Refactoring: Use bindSigTyVarsFV in rnMethodBinds

`rnMethodBinds` was explicitly using `xoptM` to determine if
`ScopedTypeVariables` is enabled before bringing type variables
bound by the class/instance header into scope. However, this `xoptM`
logic is already performed by the `bindSigTyVarsFV` function. This
patch uses `bindSigTyVarsFV` in `rnMethodBinds` to reduce the number
of places where we need to consult if `ScopedTypeVariables` is on.

This is purely refactoring, and there should be no user-visible
change in behavior.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6f6d72b2c382860a5f7a08779b2405da8473814c">6f6d72b2</a></strong>
<div>
<span>by Brian Foley</span>
<i>at 2020-05-08T15:29:25-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove further dead code found by a simple Python script.

Avoid removing some functions that are part of an API even
though they're not used in-tree at the moment.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/78bf8bf967551f8667b766328504cfbd24df9bfb">78bf8bf9</a></strong>
<div>
<span>by Julien Debon</span>
<i>at 2020-05-08T15:29:28-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add doc examples for Bifoldable

See #17929
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/66f0a847255f15ec656a37d639556b7918f6aac2">66f0a847</a></strong>
<div>
<span>by Julien Debon</span>
<i>at 2020-05-08T15:29:29-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">doc (Bitraversable): Add examples to Bitraversable

* Add examples to Data.Bitraversable
* Fix formatting for (,) in Bitraversable and Bifoldable
* Fix mistake on bimapAccumR documentation

See #17929
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9749fe1223d182b1f8e7e4f7378df661c509f396">9749fe12</a></strong>
<div>
<span>by Baldur Blöndal</span>
<i>at 2020-05-08T15:29:32-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Specify kind variables for inferred kinds in base.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4e9aef9ea732e8157ee0b7fbb85b2cdfbf49de5f">4e9aef9e</a></strong>
<div>
<span>by John Ericson</span>
<i>at 2020-05-08T15:29:36-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">HsSigWcTypeScoping: Pull in documentation from stray location
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/f4d5c6df56a28be5448acf43e4f45b1695ae9eb5">f4d5c6df</a></strong>
<div>
<span>by John Ericson</span>
<i>at 2020-05-08T15:29:36-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Rename local `real_fvs` to `implicit_vs`

It doesn't make sense to call the "free" variables we are about to
implicitly bind the real ones.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/20570b4b5e741912d1dc3f1826ee1f78e33f3b90">20570b4b</a></strong>
<div>
<span>by John Ericson</span>
<i>at 2020-05-08T15:29:36-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">A few tiny style nits with renaming

 - Use case rather than guards that repeatedly scrutenize same thing.

 - No need for view pattern when `L` is fine.

 - Use type synnonym to convey the intent like elsewhere.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/09ac8de5777d5ca953279a6c0ee42a6fba0fcba6">09ac8de5</a></strong>
<div>
<span>by John Ericson</span>
<i>at 2020-05-08T15:29:36-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add `forAllOrNothing` function with note
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/bb35c0e573b0bc8fe6a28c00734fa124da02a755">bb35c0e5</a></strong>
<div>
<span>by Joseph C. Sible</span>
<i>at 2020-05-08T15:29:40-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Document lawlessness of Ap's Num instance</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/cdd229fff24ab19a41dd2af218108dd8c514fff7">cdd229ff</a></strong>
<div>
<span>by Joseph C. Sible</span>
<i>at 2020-05-08T15:29:40-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Apply suggestion to libraries/base/Data/Monoid.hs</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/926d2aab83dc6068cba76f71a19b040eddc6dee9">926d2aab</a></strong>
<div>
<span>by Joseph C. Sible</span>
<i>at 2020-05-08T15:29:40-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Apply more suggestions from Simon Jakobi</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7a763cff78d2d4b23d05554e68138678cb4ba627">7a763cff</a></strong>
<div>
<span>by Adam Gundry</span>
<i>at 2020-05-08T15:29:41-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Reject all duplicate declarations involving DuplicateRecordFields (fixes #17965)

This fixes a bug that resulted in some programs being accepted that used the same
identifier as a field label and another declaration, depending on the order they
appeared in the source code.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/88e3c8150d2b2d96c3ebc0b2942c9af44071c511">88e3c815</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-05-08T15:29:41-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix specialisation for DFuns

When specialising a DFun we must take care to saturate the
unfolding.  See Note [Specialising DFuns] in Specialise.

Fixes #18120
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/86c77b36628dcce7bc9b066fc24c8c521fecc3ee">86c77b36</a></strong>
<div>
<span>by Greg Steuck</span>
<i>at 2020-05-08T15:29:45-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove unused SEGMENT_PROT_RWX

It's been unused for a year and is problematic on any OS which
requires W^X for security.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9d97f4b5ddcfdf32b52734188f595d9a11fd4879">9d97f4b5</a></strong>
<div>
<span>by nineonine</span>
<i>at 2020-05-08T15:30:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add test for #16167
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/aa318338b753ab6e9db44cf2c2d285827eb35a03">aa318338</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-05-08T15:30:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Bump exceptions submodule so that dist-boot is .gitignore'd

`exceptions` is a stage-0 boot library as of commit
30272412fa437ab8e7a8035db94a278e10513413, which means that building
`exceptions` in a GHC tree will generate a `dist-boot` directory.
However, this directory was not specified in `exceptions`'
`.gitignore` file, which causes it to dirty up the current `git`
working directory.

Accordingly, this bumps the `exceptions` submodule to commit
ghc/packages/exceptions@23c0b8a50d7592af37ca09beeec16b93080df98f,
which adds `dist-boot` to the `.gitignore` file.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ea86360f21e8c9812acba8dc1bc2a54fef700ece">ea86360f</a></strong>
<div>
<span>by Ömer Sinan Ağacan</span>
<i>at 2020-05-08T15:30:30-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Linker.c: initialize n_symbols of ObjectCode with other fields
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/951c1fb03d80094c8b0d9bcc463d86fa71695b3a">951c1fb0</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-05-09T21:46:38-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix unboxed-sums GC ptr-slot rubbish value (#17791)

This patch allows boot libraries to use unboxed sums without implicitly
depending on `base` package because of `absentSumFieldError`.

See updated Note [aBSENT_SUM_FIELD_ERROR_ID] in GHC.Core.Make
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b352d63cbbfbee69358c198edd876fe7ef9d63ef">b352d63c</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-05-09T21:47:14-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts: Make non-existent linker search path merely a warning

As noted in #18105, previously this resulted in a rather intrusive error
message. This is in contrast to the general expectation that search
paths are merely places to look, not places that must exist.

Fixes #18105.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/cf4f1e2f78840d25b132de55bce1e02256334ace">cf4f1e2f</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-05-13T02:02:33-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts/CNF: Fix fixup comparison function

Previously we would implicitly convert the difference between two words
to an int, resulting in an integer overflow on 64-bit machines.

Fixes #16992
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a03da9bfcf130bec616e0f77bbefbf62022753de">a03da9bf</a></strong>
<div>
<span>by Ömer Sinan Ağacan</span>
<i>at 2020-05-13T02:03:16-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Pack some of IdInfo fields into a bit field

This reduces residency of compiler quite a bit on some programs.
Example stats when building T10370:

Before:

   2,871,242,832 bytes allocated in the heap
   4,693,328,008 bytes copied during GC
      33,941,448 bytes maximum residency (276 sample(s))
         375,976 bytes maximum slop
              83 MiB total memory in use (0 MB lost due to fragmentation)

After:

   2,858,897,344 bytes allocated in the heap
   4,629,255,440 bytes copied during GC
      32,616,624 bytes maximum residency (278 sample(s))
         314,400 bytes maximum slop
              80 MiB total memory in use (0 MB lost due to fragmentation)

So -3.9% residency, -1.3% bytes copied and -0.4% allocations.

Fixes #17497

Metric Decrease:
    T9233
    T9675
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/670c3e5c84c5b638dc6277289db3cbbc39a03c36">670c3e5c</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-05-13T02:03:54-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">get-win32-tarballs: Fix base URL

Revert a change previously made for testing purposes.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8ad8dc412f0b070df63e42e68468df08ac0f559a">8ad8dc41</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-05-13T02:03:54-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">get-win32-tarballs: Improve diagnostics output
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8c0740b7c38184378aedefdca8fff35707c80de9">8c0740b7</a></strong>
<div>
<span>by Simon Jakobi</span>
<i>at 2020-05-13T02:04:33-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">docs: Add examples for Data.Semigroup.Arg{Min,Max}

Context: #17153
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/cb22348fb92411c66f1a39fe2c34b167a9926bc7">cb22348f</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-05-13T02:05:11-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add few cleanups of the CAF logic

Give the NameSet of non-CAFfy names a proper newtype to distinguish it
from all of the other NameSets floating about.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/90e38b8139c10854280da56664c040120256bacc">90e38b81</a></strong>
<div>
<span>by Emeka Nkurumeh</span>
<i>at 2020-05-13T02:05:51-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">fix printf warning when using with ghc with clang on mingw</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/86d8ac22608eb8f04ceaff65e76dbeec23b76753">86d8ac22</a></strong>
<div>
<span>by Sebastian Graf</span>
<i>at 2020-05-13T02:06:29-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">CprAnal: Don't attach CPR sigs to expandable bindings (#18154)

Instead, look through expandable unfoldings in `cprTransform`.
See the new Note [CPR for expandable unfoldings]:

```
Long static data structures (whether top-level or not) like

  xs = x1 : xs1
  xs1 = x2 : xs2
  xs2 = x3 : xs3

should not get CPR signatures, because they

  * Never get WW'd, so their CPR signature should be irrelevant after analysis
    (in fact the signature might even be harmful for that reason)
  * Would need to be inlined/expanded to see their constructed product
  * Recording CPR on them blows up interface file sizes and is redundant with
    their unfolding. In case of Nested CPR, this blow-up can be quadratic!

But we can't just stop giving DataCon application bindings the CPR property,
for example

  fac 0 = 1
  fac n = n * fac (n-1)

fac certainly has the CPR property and should be WW'd! But FloatOut will
transform the first clause to

  lvl = 1
  fac 0 = lvl

If lvl doesn't have the CPR property, fac won't either. But lvl doesn't have a
CPR signature to extrapolate into a CPR transformer ('cprTransform'). So
instead we keep on cprAnal'ing through *expandable* unfoldings for these arity
0 bindings via 'cprExpandUnfolding_maybe'.

In practice, GHC generates a lot of (nested) TyCon and KindRep bindings, one
for each data declaration. It's wasteful to attach CPR signatures to each of
them (and intractable in case of Nested CPR).
```

Fixes #18154.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e34bf65613f0062ea902fb3d59623701b7cd01d5">e34bf656</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-05-13T02:07:08-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">users-guide: Add discussion of shared object naming

Fixes #18074.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/5d0f244528f8f7ba3058a4cf7b075a474c63fa1b">5d0f2445</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-05-13T02:07:47-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite: Print sign of performance changes

Executes the minor formatting change in the tabulated performance
changes suggested in #18135.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9e4b981ff7a0852c7bdc93039eed13582d923241">9e4b981f</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-05-13T02:08:24-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite: Add testcase for #18129
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/266310c300f2254dfdeb5eb2123737f765ed18f8">266310c3</a></strong>
<div>
<span>by Ivan-Yudin</span>
<i>at 2020-05-13T02:09:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">doc: Reformulate the opening paragraph of Ch. 4 in User's guide

Removes mentioning of Hugs
(it is not helpful for new users anymore).

Changes the wording for the rest of the paragraph.

Fixes #18132.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/55e35c0b7e0f4b907dc21d42827b1cea4317226e">55e35c0b</a></strong>
<div>
<span>by Baldur Blöndal</span>
<i>at 2020-05-13T20:02:48-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Predicate, Equivalence derive via `.. -> a -> All'
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d7e0b57fda289e2715e7be86d4871503e3c09ee8">d7e0b57f</a></strong>
<div>
<span>by Alp Mestanogullari</span>
<i>at 2020-05-13T20:03:30-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">hadrian: add a --freeze2 option to freeze stage 1 and 2
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d880d6b2e48268f5ed4d3eb751fe24cc833e9221">d880d6b2</a></strong>
<div>
<span>by Artem Pelenitsyn</span>
<i>at 2020-05-13T20:04:11-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Don't reload environment files on every setSessionDynFlags

Makes `interpretPackageEnv` (which loads envirinment files) a part of
`parseDynamicFlags` (parsing command-line arguments, which is typically
done once) instead of `setSessionDynFlags` (which is typically called
several times). Making several (transitive) calls to `interpretPackageEnv`,
as before, caused #18125 #16318, which should be fixed now.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/102cfd6784d16a0d0cc8bdf42d4de4c7b8dd0190">102cfd67</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-05-13T20:04:46-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Factor out HsPatSigType for pat sigs/RULE term sigs (#16762)

This implements chunks (2) and (3) of
https://gitlab.haskell.org/ghc/ghc/issues/16762#note_270170. Namely,
it introduces a dedicated `HsPatSigType` AST type, which represents
the types that can appear in pattern signatures and term-level `RULE`
binders. Previously, these were represented with `LHsSigWcType`.
Although `LHsSigWcType` is isomorphic to `HsPatSigType`, the intended
semantics of the two types are slightly different, as evidenced by
the fact that they have different code paths in the renamer and
typechecker.

See also the new `Note [Pattern signature binders and scoping]` in
`GHC.Hs.Types`.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b17574f74173d0fa83b0def070dcba51b710be2e">b17574f7</a></strong>
<div>
<span>by Hécate</span>
<i>at 2020-05-13T20:05:28-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">fix(documentation): Fix the RST links to GHC.Prim
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/df021fb15bcef313f30e772997bcb263c8f34078">df021fb1</a></strong>
<div>
<span>by Baldur Blöndal</span>
<i>at 2020-05-13T20:06:06-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Document (->) using inferred quantification for its runtime representations.

Fixes #18142.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/1a93ea57355d521b92daf4e3120de88a1f94deee">1a93ea57</a></strong>
<div>
<span>by Takenobu Tani</span>
<i>at 2020-05-13T20:06:54-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Tweak man page for ghc command

This commit updates the ghc command's man page as followings:

* Enable `man_show_urls` to show URL addresses in the `DESCRIPTION`
section of ghc.rst, because sphinx currently removes hyperlinks
for man pages.

* Add a `SEE ALSO` section to point to the GHC homepage
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a951e1bab3dfd3e9de31b0d8bf5699a9216b181d">a951e1ba</a></strong>
<div>
<span>by Takenobu Tani</span>
<i>at 2020-05-13T20:07:37-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">GHCi: Add link to the user's guide in help message

This commit adds a link to the user's guide in ghci's
`:help` message.

Newcomers could easily reach to details of ghci.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/404581eaa3bf8d3f100da7610a6a38158bea17c4">404581ea</a></strong>
<div>
<span>by Jeff Happily</span>
<i>at 2020-05-13T20:08:15-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Handle single unused import
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/1c999e5d4e63e7b407b174f51913cfa38e2dec46">1c999e5d</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-05-13T20:09:07-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Ensure that printMinimalImports closes handle

Fixes #18166.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c9f5a8f4653c4696a1fbb768bd0d8f672d4c7d5f">c9f5a8f4</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-05-13T20:09:51-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">hadrian: Tell testsuite driver about LLVM availability

This reflects the logic present in the Make build system into Hadrian.

Fixes #18167.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c05c06596bd1b2852454af6243fc15ee852d2f45">c05c0659</a></strong>
<div>
<span>by Simon Jakobi</span>
<i>at 2020-05-14T03:31:21-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Improve some folds over Uniq[D]FM

* Replace some non-deterministic lazy folds with
  strict folds.
* Replace some O(n log n) folds in deterministic order
  with O(n) non-deterministic folds.
* Replace some folds with set-operations on the underlying
  IntMaps.

This reduces max residency when compiling
`nofib/spectral/simple/Main.hs` with -O0 by about 1%.

Maximum residency when compiling Cabal also seems reduced on the
order of 3-9%.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/477f13bb4c5c2ba969d2c90890c51d7de01c5312">477f13bb</a></strong>
<div>
<span>by Simon Jakobi</span>
<i>at 2020-05-14T03:31:58-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Use Data.IntMap.disjoint

Data.IntMap gained a dedicated `disjoint` function in containers-0.6.2.1.

This patch applies this function where appropriate in hopes of modest
compiler performance improvements.

Closes #16806.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e9c0110ce9e753360d7e6523114109b7616f2f08">e9c0110c</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-05-14T12:25:53-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">IdInfo: Add reference to bitfield-packing ticket
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9bd20e83ff9b65bd5496fbb29d27072c9e4e84b9">9bd20e83</a></strong>
<div>
<span>by Sebastian Graf</span>
<i>at 2020-05-15T10:42:09-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">DmdAnal: Improve handling of precise exceptions

This patch does two things: Fix possible unsoundness in what was called
the "IO hack" and implement part 2.1 of the "fixing precise exceptions"
plan in
https://gitlab.haskell.org/ghc/ghc/wikis/fixing-precise-exceptions,
which, in combination with !2956, supersedes !3014 and !2525.

**IO hack**

The "IO hack" (which is a fallback to preserve precise exceptions
semantics and thus soundness, rather than some smart thing that
increases precision) is called `exprMayThrowPreciseException` now.
I came up with two testcases exemplifying possible unsoundness (if
twisted enough) in the old approach:

- `T13380d`: Demonstrating unsoundness of the "IO hack" when resorting
             to manual state token threading and direct use of primops.
             More details below.
- `T13380e`: Demonstrating unsoundness of the "IO hack" when we have
             Nested CPR. Not currently relevant, as we don't have Nested
             CPR yet.
- `T13380f`: Demonstrating unsoundness of the "IO hack" for safe FFI
             calls.

Basically, the IO hack assumed that precise exceptions can only be
thrown from a case scrutinee of type `(# State# RealWorld, _ #)`. I
couldn't come up with a program using the `IO` abstraction that violates
this assumption. But it's easy to do so via manual state token threading
and direct use of primops, see `T13380d`. Also similar code might be
generated by Nested CPR in the (hopefully not too) distant future, see
`T13380e`. Hence, we now have a more careful test in `forcesRealWorld`
that passes `T13380{d,e}` (and will hopefully be robust to Nested CPR).

**Precise exceptions**

In #13380 and #17676 we saw that we didn't preserve precise exception
semantics in demand analysis. We fixed that with minimal changes in
!2956, but that was terribly unprincipled.

That unprincipledness resulted in a loss of precision, which is tracked
by these new test cases:

- `T13380b`: Regression in dead code elimination, because !2956 was too
             syntactic about `raiseIO#`
- `T13380c`: No need to apply the "IO hack" when the IO action may not
             throw a precise exception (and the existing IO hack doesn't
             detect that)

Fixing both issues in !3014 turned out to be too complicated and had
the potential to regress in the future. Hence we decided to only fix
`T13380b` and augment the `Divergence` lattice with a new middle-layer
element, `ExnOrDiv`, which means either `Diverges` (, throws an
imprecise exception) or throws a *precise* exception.

See the wiki page on Step 2.1 for more implementational details:
https://gitlab.haskell.org/ghc/ghc/wikis/fixing-precise-exceptions#dead-code-elimination-for-raiseio-with-isdeadenddiv-introducing-exnordiv-step-21
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/568d7279a80cf945271f0659f11a94eea3f1433d">568d7279</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-05-15T10:42:46-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">GHC.Cmm.Opt: Handle MO_XX_Conv

This MachOp was introduced by 2c959a1894311e59cd2fd469c1967491c1e488f3
but a wildcard match in cmmMachOpFoldM hid the fact that it wasn't
handled. Ideally we would eliminate the match but this appears to be a
larger task.

Fixes #18141.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/5bcf86063c0e5b6ee0d162ea64c88fdaad89e620">5bcf8606</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-05-17T08:46:38-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove duplicate Note [When to print foralls] in GHC.Core.TyCo.Ppr

There are two different Notes named `[When to print foralls]`. The
most up-to-date one is in `GHC.Iface.Type`, but there is a second
one in `GHC.Core.TyCo.Ppr`. The latter is less up-to-date, as it was
written before GHC switched over to using ifaces to pretty-print
types. I decided to just remove the latter and replace it with a
reference to the former.

[ci skip]
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/55f0e783d234af103cf4e1d51cd31c99961c5abe">55f0e783</a></strong>
<div>
<span>by Fumiaki Kinoshita</span>
<i>at 2020-05-21T12:10:44-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">base: Add Generic instances to various datatypes under GHC.*

* GHC.Fingerprint.Types: Fingerprint
* GHC.RTS.Flags: GiveGCStats, GCFlags, ConcFlags, DebugFlags, CCFlags, DoHeapProfile, ProfFlags, DoTrace, TraceFlags, TickyFlags, ParFlags and RTSFlags
* GHC.Stats: RTSStats and GCStats
* GHC.ByteOrder: ByteOrder
* GHC.Unicode: GeneralCategory
* GHC.Stack.Types: SrcLoc

Metric Increase:
    haddock.base
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a9311cd53d33439e8fe79967ba5fb85bcd114fec">a9311cd5</a></strong>
<div>
<span>by Gert-Jan Bottu</span>
<i>at 2020-05-21T12:11:31-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Explicit Specificity

Implementation for Ticket #16393.
Explicit specificity allows users to manually create inferred type variables,
by marking them with braces.
This way, the user determines which variables can be instantiated through
visible type application.

The additional syntax is included in the parser, allowing users to write
braces in type variable binders (type signatures, data constructors etc).
This information is passed along through the renamer and verified in the
type checker.
The AST for type variable binders, data constructors, pattern synonyms,
partial signatures and Template Haskell has been updated to include the
specificity of type variables.

Minor notes:
- Bumps haddock submodule
- Disables pattern match checking in GHC.Iface.Type with GHC 8.8
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/24e61aad37355fa3a5503b11a60ab7b314a3f405">24e61aad</a></strong>
<div>
<span>by Ben Price</span>
<i>at 2020-05-21T12:12:17-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Lint should say when it is checking a rule

It is rather confusing that when lint finds an error in a rule attached
to a binder, it reports the error as in the RHS, not the rule:
  ...
  In the RHS of foo

We add a clarifying line:
  ...
  In the RHS of foo
  In a rule attached to foo

The implication that the rule lives inside the RHS is a bit odd, but
this niggle is already present for unfoldings, whose pattern we are
following.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/78c6523c5106fc56b653fc14fda5741913da8fdc">78c6523c</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-05-21T12:13:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">nonmoving: Optimise the write barrier
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/13f6c9d0376214b22d4cd16bd3a8cd7b8d864990">13f6c9d0</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-05-21T12:13:45-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Refactor linear reg alloc to remember past assignments.

When assigning registers we now first try registers we
assigned to in the past, instead of picking the "first"
one.

This is in extremely helpful when dealing with loops for
which variables are dead for part of the loop.

This is important for patterns like this:

        foo = arg1
    loop:
        use(foo)
        ...
        foo = getVal()
        goto loop;

There we:
* assign foo to the register of arg1.
* use foo, it's dead after this use as it's overwritten after.
* do other things.
* look for a register to put foo in.

If we pick an arbitrary one it might differ from the register the
start of the loop expect's foo to be in.
To fix this we simply look for past register assignments for
the given variable. If we find one and the register is free we
use that register.

This reduces the need for fixup blocks which match the register
assignment between blocks. In the example above between the end
and the head of the loop.

This patch also moves branch weight estimation ahead of register
allocation and adds a flag to control it (cmm-static-pred).
* It means the linear allocator is more likely to assign the hotter
  code paths first.
* If it assign these first we are:
  + Less likely to spill on the hot path.
  + Less likely to introduce fixup blocks on the hot path.

These two measure combined are surprisingly effective. Based on nofib
we get in the mean:

* -0.9% instructions executed
* -0.1% reads/writes
* -0.2% code size.
* -0.1% compiler allocations.
* -0.9% compile time.
* -0.8% runtime.

Most of the benefits are simply a result of removing redundant moves
and spills.

Reduced compiler allocations likely are the result of less code being
generated. (The added lookup is mostly non-allocating).
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/edc2cc588add3f23b3650f15d3f495943f2c06f9">edc2cc58</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-05-21T12:14:25-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">NCG: Codelayout: Distinguish conditional and other branches.

In #18053 we ended up with a suboptimal code layout because
the code layout algorithm didn't distinguish between conditional
and unconditional control flow.

We can completely eliminate unconditional control flow instructions
by placing blocks next to each other, not so much for conditionals.

In terms of implementation we simply give conditional branches less
weight before computing the layout.

Fixes #18053
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b7a6b2f4c690a9711339462114a538a85dcb7d83">b7a6b2f4</a></strong>
<div>
<span>by Gleb Popov</span>
<i>at 2020-05-21T12:15:26-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">gitlab-ci: Set locale to C.UTF-8.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a8c27cf6eef51adfa6ac9931d4f620645dc24dd3">a8c27cf6</a></strong>
<div>
<span>by Stefan Holdermans</span>
<i>at 2020-05-21T12:16:08-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Allow spaces in GHCi :script file names

This patch updates the user interface of GHCi so that file names passed
to the ':script' command may contain spaces escaped with a backslash.

For example:

  :script foo\ bar.script

The implementation uses a modified version of 'words' that does not
break on escaped spaces.

Fixes #18027.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/82663959d2f1ddbb514a652593bc8064fd69d6aa">82663959</a></strong>
<div>
<span>by Stefan Holdermans</span>
<i>at 2020-05-21T12:16:08-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add extra tests for GHCi :script syntax checks

The syntax for GHCi's ":script" command allows for only a single file
name to be passed as an argument. This patch adds a test for the cases
in which a file name is missing or multiple file names are passed.

Related to #T18027.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a0b79e1b16887371d5cd14d53a607772ca730fb5">a0b79e1b</a></strong>
<div>
<span>by Stefan Holdermans</span>
<i>at 2020-05-21T12:16:08-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Allow GHCi :script file names in double quotes

This patch updates the user interface of GHCi so that file names passed
to the ':script' command can be wrapped in double quotes.

For example:

  :script "foo bar.script"

The implementation uses a modified version of 'words' that treats
character sequences enclosed in double quotes as single words.

Fixes #18027.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/cf5663300c3d8b8b3c7dc2cd0dce2c923ec68987">cf566330</a></strong>
<div>
<span>by Stefan Holdermans</span>
<i>at 2020-05-21T12:16:08-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Update documentation for GHCi :script

This patch adds the fixes that allow for file names containing spaces to
be passed to GHCi's ':script' command to the release notes for 8.12 and
expands the user-guide documentation for ':script' by mentioning how
such file names can be passed.

Related to #18027.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/0004ccb885e534c386ceae21580fc59ec7ad0ede">0004ccb8</a></strong>
<div>
<span>by Tuan Le</span>
<i>at 2020-05-21T12:16:46-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">llvmGen: Consider Relocatable read-only data as not constantReferences: #18137
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/964d3ea21e734a4b2ad3ab97955274a003242121">964d3ea2</a></strong>
<div>
<span>by John Ericson</span>
<i>at 2020-05-21T12:17:30-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Use `Checker` for `tc_pat`
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b797aa420b65c8ee214a4fc94813d0d597352bb4">b797aa42</a></strong>
<div>
<span>by John Ericson</span>
<i>at 2020-05-21T12:17:30-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Use `Checker` for `tc_lpat` and `tc_lpats`
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/5108e84abb102920ab28e3aeb083ab6e483eb2f6">5108e84a</a></strong>
<div>
<span>by John Ericson</span>
<i>at 2020-05-21T12:17:30-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">More judiciously panic in `ts_pat`
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/510e04515bb3eaed95d374d685b5322ad7e6389d">510e0451</a></strong>
<div>
<span>by John Ericson</span>
<i>at 2020-05-21T12:17:30-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Put `PatEnv` first in `GHC.Tc.Gen.Pat.Checker`
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/cb4231db322f4a2bb146c456852df6cdf1498dca">cb4231db</a></strong>
<div>
<span>by John Ericson</span>
<i>at 2020-05-21T12:17:30-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Tiny cleaup eta-reduce away a function argument

In GHC, not in the code being compiled!
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6890c38d4568ca444cccc47dd1a86c5e020c3521">6890c38d</a></strong>
<div>
<span>by John Ericson</span>
<i>at 2020-05-21T12:17:30-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Use braces with do in `SplicePat` case for consistency
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/3451584f98d4a6b26dba4079b9a703e70a49a3ab">3451584f</a></strong>
<div>
<span>by buggymcbugfix</span>
<i>at 2020-05-21T12:18:06-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix spelling mistakes and typos
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b552e53136abfd6d728563338df99bf899d16139">b552e531</a></strong>
<div>
<span>by buggymcbugfix</span>
<i>at 2020-05-21T12:18:06-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add INLINABLE pragmas to Enum list producers

The INLINABLE pragmas ensure that we export stable (unoptimised) unfoldings in
the interface file so we can do list fusion at usage sites.

Related tickets: #15185, #8763, #18178.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e748006355d85fcddd17ba206873b0051219abb1">e7480063</a></strong>
<div>
<span>by buggymcbugfix</span>
<i>at 2020-05-21T12:18:06-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Piggyback on Enum Word methods for Word64

If we are on a 64 bit platform, we can use the efficient Enum Word
methods for the Enum Word64 instance.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/892b0c41816fca4eeea42ca03a43aac473311837">892b0c41</a></strong>
<div>
<span>by buggymcbugfix</span>
<i>at 2020-05-21T12:18:06-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Document INLINE(ABLE) pragmas that enable fusion
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2b363ebb988cbf8c92df24eef5366293a80ecb19">2b363ebb</a></strong>
<div>
<span>by Richard Eisenberg</span>
<i>at 2020-05-21T12:18:45-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">MR template should ask for key part</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a95bbd0bdf06d7d61b0bef6de77b59ca31b2c32d">a95bbd0b</a></strong>
<div>
<span>by Sebastian Graf</span>
<i>at 2020-05-21T12:19:37-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Make `Int`'s `mod` and `rem` strict in their first arguments

They used to be strict until 4d2ac2d (9 years ago).

It's obviously better to be strict for performance reasons.
It also blocks #18067.

NoFib results:

```
--------------------------------------------------------------------------------
        Program         Allocs    Instrs
--------------------------------------------------------------------------------
        integer          -1.1%     +0.4%
   wheel-sieve2         +21.2%    +20.7%
--------------------------------------------------------------------------------
            Min          -1.1%     -0.0%
            Max         +21.2%    +20.7%
 Geometric Mean          +0.2%     +0.2%
```

The regression in `wheel-sieve2` is due to reboxing that likely will go
away with the resolution of #18067. See !3282 for details.

Fixes #18187.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d3d055b8d10a549e42d18ae4859bc902f939f534">d3d055b8</a></strong>
<div>
<span>by Galen Huntington</span>
<i>at 2020-05-21T12:20:18-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Clarify pitfalls of NegativeLiterals; see #18022.</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/1b508a9e14c7c894ff4f080f099f3947813f41ec">1b508a9e</a></strong>
<div>
<span>by Alexey Kuleshevich</span>
<i>at 2020-05-21T12:21:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix wording in primops documentation to reflect the correct reasoning:

* Besides resizing functions, shrinking ones also mutate the
  size of a mutable array and because of those two `sizeofMutabeByteArray`
  and `sizeofSmallMutableArray` are now deprecated
* Change reference in documentation to the newer functions `getSizeof*`
  instead of `sizeof*` for shrinking functions
* Fix incorrect mention of "byte" instead of "small"
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4ca0c8a17b9d3a7e8ff8a93cc9e83be5173f8e14">4ca0c8a1</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-05-21T12:21:53-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Don't variable-length encode magic iface constant.

We changed to use variable length encodings for many types by default,
including Word32. This makes sense for numbers but not when Word32 is
meant to represent four bytes.

I added a FixedLengthEncoding newtype to Binary who's instances
interpret their argument as a collection of bytes instead of a number.

We then use this when writing/reading magic numbers to the iface file.

I also took the libery to remove the dummy iface field.

This fixes #18180.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a127508137ba69d2fe1e563d2bbb9fdd9120ae85">a1275081</a></strong>
<div>
<span>by Krzysztof Gogolewski</span>
<i>at 2020-05-21T12:22:35-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add a regression test for #11506

The testcase works now.
See explanation in https://gitlab.haskell.org/ghc/ghc/issues/11506#note_273202
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8a816e5fbe02c476f51ec92563cad8247ffc90ba">8a816e5f</a></strong>
<div>
<span>by Krzysztof Gogolewski</span>
<i>at 2020-05-21T12:23:55-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Sort deterministically metric output

Previously, we sorted according to the test name and way,
but the metrics (max_bytes_used/peak_megabytes_allocated etc.)
were appearing in nondeterministic order.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/566cc73f46d67e2b36fda95d0253067bb0ecc12f">566cc73f</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-05-21T12:24:45-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Move isDynLinkName into GHC.Types.Name

It doesn't belong into GHC.Unit.State
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d830bbc9921bcc59164a0a18f0e0874ae4ce226e">d830bbc9</a></strong>
<div>
<span>by Adam Sandberg Ericsson</span>
<i>at 2020-05-23T13:36:20-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">docs: fix formatting and add some links

[skip ci]
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/49301ad6226d9a83d110bee8c419615dd94f5ded">49301ad6</a></strong>
<div>
<span>by Andrew Martin</span>
<i>at 2020-05-23T13:37:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Implement cstringLength# and FinalPtr

This function and its accompanying rule resolve issue #5218.
A future PR to the bytestring library will make the internal
Data.ByteString.Internal.unsafePackAddress compute string length
with cstringLength#. This will improve the status quo because it is
eligible for constant folding.

Additionally, introduce a new data constructor to ForeignPtrContents
named FinalPtr. This additional data constructor, when used in the
IsString instance for ByteString, leads to more Core-to-Core
optimization opportunities, fewer runtime allocations, and smaller
binaries.

Also, this commit re-exports all the functions from GHC.CString
(including cstringLength#) in GHC.Exts. It also adds a new test
driver. This test driver is used to perform substring matches on Core
that is dumped after all the simplifier passes. In this commit, it is
used to check that constant folding of cstringLength# works.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/dcd6bdcce57430d08b335014625722c487ea08e4">dcd6bdcc</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-05-23T13:37:48-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">simplCore: Ignore ticks in rule templates

This fixes #17619, where a tick snuck in to the template of a rule,
resulting in a panic during rule matching. The tick in question was
introduced via post-inlining, as discussed in `Note [Simplifying
rules]`. The solution we decided upon was to simply ignore ticks in the
rule template, as discussed in `Note [Tick annotations in RULE
matching]`.

Fixes #18162.
Fixes #17619.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/82cb8913b38d44ef20e928ff8b08f3f0770ebf80">82cb8913</a></strong>
<div>
<span>by John Ericson</span>
<i>at 2020-05-23T13:38:32-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix #18145 and also avoid needless work with implicit vars

 - `forAllOrNothing` now is monadic, so we can trace whether we bind
   an explicit `forall` or not.

 - #18145 arose because the free vars calculation was needlessly
   complex. It is now greatly simplified.

 - Replaced some other implicit var code with `filterFreeVarsToBind`.

Co-authored-by: Ryan Scott <ryan.gl.scott@gmail.com>
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a60dc83552c38af9bbc159bd4e092531196db9c0">a60dc835</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-05-23T13:39:12-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Bump process submodule

Fixes #17926.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/856adf54ab50fc3be66d17a0b94ba3074453b279">856adf54</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-05-23T13:40:21-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">users-guide: Clarify meaning of -haddock flag

Fixes #18206.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7ae57afd7abee9dec1050d9feace254ac04800bc">7ae57afd</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-05-23T13:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">git: Add ignored commits file

This can be used to tell git to ignore bulk renaming commits like the
recently-finished module hierarchy refactoring. Configured with,

    git config blame.ignoreRevsFile .git-ignore-revs
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/63d30e60b9ab76ed48fa9539957e7b29a2a8c611">63d30e60</a></strong>
<div>
<span>by jneira</span>
<i>at 2020-05-24T01:54:42-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add hie-bios script for windows systems
It is a direct translation of the sh script
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/59182b88aaa72d346b480b6aa14a9244915e1189">59182b88</a></strong>
<div>
<span>by jneira</span>
<i>at 2020-05-24T01:54:42-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Honour previous values for CABAL and CABFLAGS
The immediate goal is let the hie-bios.bat script
set CABFLAGS with `-v0` and remove all cabal output
except the compiler arguments
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/932dc54e13a8e2f60ea90af98682cc1011b9533e">932dc54e</a></strong>
<div>
<span>by jneira</span>
<i>at 2020-05-24T01:54:42-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add specific configuration for windows in hie.yaml
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e0eda0707d6cc3d5a85cfb13543df61623e82070">e0eda070</a></strong>
<div>
<span>by jneira</span>
<i>at 2020-05-24T01:54:42-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove not needed hie-bios output
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a0ea59d641d400543e9e803007500da01eedf48a">a0ea59d6</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-05-24T01:55:24-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Move Config module into GHC.Settings
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/37430251c3f684c46e893552dba78653d80e5243">37430251</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-05-24T01:55:24-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Rename GHC.Core.Arity into GHC.Core.Opt.Arity
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a426abb9b41de6097e888b9fdca7b275306b17c9">a426abb9</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-05-24T01:55:24-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Rename GHC.Hs.Types into GHC.Hs.Type

See discussion in https://gitlab.haskell.org/ghc/ghc/issues/13009#note_268610
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/1c91a7a095331d8c776f6ecd74803026e0104502">1c91a7a0</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-05-24T01:55:24-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Bump haddock submodule
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/66bd24d197251b9907cbffba3d5d8a3f5e3c2e80">66bd24d1</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-05-24T01:56:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add orderingTyCon to wiredInTyCons (#18185)

`Ordering` needs to be wired in for use in the built-in `CmpNat` and
`CmpSymbol` type families, but somehow it was never added to the list
of `wiredInTyCons`, leading to the various oddities observed
in #18185. Easily fixed by moving `orderingTyCon` from
`basicKnownKeyNames` to `wiredInTyCons`.

Fixes #18185.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/01c43634d443bd3cc0b95b43a7180e12230b845d">01c43634</a></strong>
<div>
<span>by Matthew Pickering</span>
<i>at 2020-05-24T01:56:42-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove unused hs-boot file
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7a07aa718110071ee30eebadf0b4b372e8e7fc8e">7a07aa71</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-05-24T15:22:17-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Hadrian: fix cross-compiler build (#16051)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/15ccca16e2ecdde0a4e646c6d7515e00a7f364d3">15ccca16</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-05-24T15:22:17-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Hadrian: fix distDir per stage
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b420fb2474650e6dfbd66afd199f28492f900f75">b420fb24</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-05-24T15:22:17-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Hadrian: fix hp2ps error during cross-compilation

Fixed by @alp (see https://gitlab.haskell.org/ghc/ghc/issues/16051#note_274265)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/cd339ef0e8ce940902df79ed1d93b3af50ea6f77">cd339ef0</a></strong>
<div>
<span>by Joshua Price</span>
<i>at 2020-05-24T15:22:56-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Make Unicode brackets opening/closing tokens (#18225)

The tokens `[|`, `|]`, `(|`, and `|)` are opening/closing tokens as
described in GHC Proposal #229. This commit makes the unicode
variants (`⟦`, `⟧`, `⦇`, and `⦈`) act the same as their ASCII
counterparts.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/013d71204be44d660f01f8eb255db2d48b832421">013d7120</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-05-25T09:48:17-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Revert "Specify kind variables for inferred kinds in base."

As noted in !3132, this has rather severe knock-on consequences in
user-code. We'll need to revisit this before merging something along
these lines.

This reverts commit 9749fe1223d182b1f8e7e4f7378df661c509f396.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4c4312edd988b8aeeb65e095056743c30678df15">4c4312ed</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-05-25T09:48:53-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Coverage: Drop redundant ad-hoc boot module check

To determine whether the module is a boot module
Coverage.addTicksToBinds was checking for a `boot` suffix in the module
source filename. This is quite ad-hoc and shouldn't be necessary; the
callsite in `deSugar` already checks that the module isn't a boot
module.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/1abf3c844821c98dad7f6f5b23cc3f7889dce64c">1abf3c84</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-05-25T09:48:53-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Coverage: Make tickBoxCount strict

This could otherwise easily cause a leak of (+) thunks.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b28137505a2fc3a15f2c0ba31c39c1869ce65cdc">b2813750</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-05-25T09:48:53-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Coverage: Make ccIndices strict

This just seems like a good idea.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/02e278eb2ace60cf2acadd2f632b51b9017d5b56">02e278eb</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-05-25T09:48:53-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Coverage: Don't produce ModBreaks if not HscInterpreted

emptyModBreaks contains a bottom and consequently it's important that we
don't use it unless necessary.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b8c014ce27c279e0d506d5391a4e9bfa7f1c31f2">b8c014ce</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-05-25T09:48:53-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Coverage: Factor out addMixEntry
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/53814a6424240ab50201fdde81a6e7832c1aad3d">53814a64</a></strong>
<div>
<span>by Zubin Duggal</span>
<i>at 2020-05-26T03:03:24-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add info about typeclass evidence to .hie files

See `testsuite/tests/hiefile/should_run/HieQueries.hs` and
`testsuite/tests/hiefile/should_run/HieQueries.stdout` for an example of this

We add two new fields, `EvidenceVarBind` and `EvidenceVarUse` to the
`ContextInfo` associated with an Identifier. These are associated with the
appropriate identifiers for the evidence variables collected when we come across
`HsWrappers`, `TcEvBinds` and `IPBinds` while traversing the AST.

Instance dictionary and superclass selector dictionaries from `tcg_insts` and
classes defined in `tcg_tcs` are also recorded in the AST as originating from
their definition span

This allows us to save a complete picture of the evidence constructed by the
constraint solver, and will let us report this to the user, enabling features
like going to the instance definition from the invocation of a class method(or
any other method taking a constraint) and finding all usages of a particular
instance.

Additionally,

- Mark NodeInfo with an origin so we can differentiate between bindings
  origininating in the source vs those in ghc
- Along with typeclass evidence info, also include information on Implicit
  Parameters
- Add a few utility functions to HieUtils in order to query the new info

Updates haddock submodule
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6604906c8cfa37f5780a6d5c40506b751b1740db">6604906c</a></strong>
<div>
<span>by Sebastian Graf</span>
<i>at 2020-05-26T03:04:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Make WorkWrap.Lib.isWorkerSmallEnough aware of the old arity

We should allow a wrapper with up to 82 parameters when the original
function had 82 parameters to begin with.

I verified that this made no difference on NoFib, but then again
it doesn't use huge records...

Fixes #18122.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/cf772f19c06944f0fd03b4bdcd4a49e437084ba5">cf772f19</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-05-26T03:04:45-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Enhance Note [About units] for Backpack
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ede241268171e8eee1e750d88ff356ddbfc357f2">ede24126</a></strong>
<div>
<span>by Takenobu Tani</span>
<i>at 2020-05-27T00:13:55-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">core-spec: Modify file paths according to new module hierarchy

This patch updates file paths according to new module hierarchy [1]:

  * GHC/Core.hs                <= coreSyn/CoreSyn.hs
  * GHC/Core/Coercion.hs       <= types/Coercion.hs
  * GHC/Core/Coercion/Axiom.hs <= types/CoAxiom.hs
  * GHC/Core/Coercion/Opt.hs   <= types/OptCoercion.hs
  * GHC/Core/DataCon.hs        <= basicTypes/DataCon.hs
  * GHC/Core/FamInstEnv.hs     <= types/FamInstEnv.hs
  * GHC/Core/Lint.hs           <= coreSyn/CoreLint.hs
  * GHC/Core/Subst.hs          <= coreSyn/CoreSubst.hs
  * GHC/Core/TyCo/Rep.hs       <= types/TyCoRep.hs
  * GHC/Core/TyCon.hs          <= types/TyCon.hs
  * GHC/Core/Type.hs           <= types/Type.hs
  * GHC/Core/Unify.hs          <= types/Unify.hs
  * GHC/Types/Literal.hs       <= basicTypes/Literal.hs
  * GHC/Types/Var.hs           <= basicTypes/Var.hs

[1]: https://gitlab.haskell.org/ghc/ghc/-/wikis/Make-GHC-codebase-more-modular

[skip ci]
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/04750304deae2128a8350e28224e1f62ae949820">04750304</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-05-27T00:14:33-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">eventlog: Fix racy flushing

Previously no attempt was made to avoid multiple threads writing their
capability-local eventlog buffers to the eventlog writer simultaneously.
This could result in multiple eventlog streams being interleaved. Fix
this by documenting that the EventLogWriter's write() and flush()
functions may be called reentrantly and fix the default writer to
protect its FILE* by a mutex.

Fixes #18210.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d6203f24cf421749616a247c047a9b44192f963a">d6203f24</a></strong>
<div>
<span>by Joshua Price</span>
<i>at 2020-05-27T00:15:17-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Make `identifier` parse unparenthesized `->` (#18060)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/28deee2872d2501a781ae5b89f1db3dbf796ee74">28deee28</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-05-28T16:23:21-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">GHC.Core.Unfold: Refactor traceInline

This reduces duplication as well as fixes a bug wherein -dinlining-check
would override -ddump-inlinings. Moreover, the new variant
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/1f393e1e0a2998fe67cfd06501e35f495758b98f">1f393e1e</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-05-28T16:23:21-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Avoid unnecessary allocations due to tracing utilities

While ticky-profiling the typechecker I noticed that hundreds of
millions of SDocs are being allocated just in case -ddump-*-trace is
enabled. This is awful.

We avoid this by ensuring that the dump flag check is inlined into the
call site, ensuring that the tracing document needn't be allocated
unless it's actually needed.

See Note [INLINE conditional tracing utilities] for details.

Fixes #18168.

Metric Decrease:
  T9961
  haddock.Cabal
  haddock.base
  haddock.compiler
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/5f621a78217237a4bdfb299b68827da6cc8f357e">5f621a78</a></strong>
<div>
<span>by Vladislav Zavialov</span>
<i>at 2020-05-28T16:23:58-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add Semigroup/Monoid for Q (#18123)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/dc5f004c4dc27d78d3415adc54e9b6694b865145">dc5f004c</a></strong>
<div>
<span>by Xavier Denis</span>
<i>at 2020-05-28T16:24:37-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix #18071

Run the core linter on candidate instances to ensure they are
well-kinded.

Better handle quantified constraints by using a CtWanted to avoid
having unsolved constraints thrown away at the end by the solver.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/10e6982c6117e55b0151dc456e75ebc4798df73f">10e6982c</a></strong>
<div>
<span>by Sebastian Graf</span>
<i>at 2020-05-28T16:25:14-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">FloatOut: Only eta-expand dead-end RHS if arity will increase (#18231)

Otherwise we risk turning trivial RHS into non-trivial RHS, introducing
unnecessary bindings in the next Simplifier run, resulting in more
churn.

Fixes #18231.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/08dab5f74e021ad054112cc5f6bb7e55d8796cd7">08dab5f7</a></strong>
<div>
<span>by Sebastian Graf</span>
<i>at 2020-05-28T16:25:14-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">DmdAnal: Recognise precise exceptions from case alternatives (#18086)

Consider

```hs
m :: IO ()
m = do
  putStrLn "foo"
  error "bar"
```

`m` (from #18086) always throws a (precise or imprecise) exception or
diverges. Yet demand analysis infers `<L,A>` as demand signature instead
of `<L,A>x` for it.

That's because the demand analyser sees `putStrLn` occuring in a case
scrutinee and decides that it has to `deferAfterPreciseException`,
because `putStrLn` throws a precise exception on some control flow
paths. This will mask the `botDiv` `Divergence`of the single case alt
containing `error` to `topDiv`. Since `putStrLn` has `topDiv` itself,
the final `Divergence` is `topDiv`.

This is easily fixed: `deferAfterPreciseException` works by `lub`ing
with the demand type of a virtual case branch denoting the precise
exceptional control flow. We used `nopDmdType` before, but we can be
more precise and use `exnDmdType`, which is `nopDmdType` with `exnDiv`.

Now the `Divergence` from the case alt will degrade `botDiv` to `exnDiv`
instead of `topDiv`, which combines with the result from the scrutinee
to `exnDiv`, and all is well.

Fixes #18086.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/aef95f11f946f7d3f2c4c9b695d632cbfc4a993d">aef95f11</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-05-28T16:25:53-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Ticky-ticky: Record DataCon name in ticker name

This makes it significantly easier to spot the nature of
allocations regressions and comes at a reasonably low cost.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8f021b8c474f328441982c90c6a12f716b5607eb">8f021b8c</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-05-28T16:26:34-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">hadrian: Don't track GHC's verbosity argument

Teach hadrian to ignore GHC's -v argument in its recompilation check,
thus fixing #18131.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/13d9380b1fc8b67057a9ad4fffe244040a7f9bc0">13d9380b</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-05-28T16:27:20-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Rip out CmmStackInfo(updfr_space)

As noted in #18232, this field is currently completely unused and
moreover doesn't have a clear meaning.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/f10d11fa49fa9a7a506c4fdbdf86521c2a8d3495">f10d11fa</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-05-29T01:38:42-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix "build/elem" RULE.

An redundant constraint prevented the rule from matching.

Fixing this allows a call to elem on a known list to be translated
into a series of equality checks, and eventually a simple case
expression.

Surprisingly this seems to regress elem for strings. To avoid
this we now also allow foldrCString to inline and add an UTF8
variant. This results in elem being compiled to a tight
non-allocating loop over the primitive string literal which
performs a linear search.

In the process this commit adds UTF8 variants for some of the
functions in GHC.CString. This is required to make this work for
both ASCII and UTF8 strings.

There are also small tweaks to the CString related rules.
We now allow ourselfes the luxury to compare the folding function
via eqExpr, which helps to ensure the rule fires before we inline
foldrCString*. Together with a few changes to allow matching on both
the UTF8 and ASCII variants of the CString functions.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/bbeb2389596df61ace5778ec580895ea32cc3c6f">bbeb2389</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-05-29T01:39:19-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">CoreToStg: Add Outputable ArgInfo instance
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/0e3361ca414012e3ec40a260c2323986ce770db6">0e3361ca</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-05-29T01:39:19-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Make Lint check return type of a join point

Consider
   join x = rhs in body
It's important that the type of 'rhs' is the same as the type of
'body', but Lint wasn't checking that invariant.

Now it does!  This was exposed by investigation into !3113.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c49f7df02ff02c8f09e6a6e00a271b867ca6b092">c49f7df0</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-05-29T01:39:19-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Do not float join points in exprIsConApp_maybe

We hvae been making exprIsConApp_maybe cleverer in recent times:

    commit b78cc64e923716ac0512c299f42d4d0012306c05
    Date:   Thu Nov 15 17:14:31 2018 +0100
    Make constructor wrappers inline only during the final phase

    commit 7833cf407d1f608bebb1d38bb99d3035d8d735e6
    Date:   Thu Jan 24 17:58:50 2019 +0100
    Look through newtype wrappers (Trac #16254)

    commit c25b135ff5b9c69a90df0ccf51b04952c2dc6ee1
    Date:   Thu Feb 21 12:03:22 2019 +0000
    Fix exprIsConApp_maybe

But alas there was still a bug, now immortalised in
  Note [Don't float join points]
in SimpleOpt.

It's quite hard to trigger because it requires a dead
join point, but it came up when compiling Cabal
Cabal.Distribution.Fields.Lexer.hs, when working on
!3113.

Happily, the fix is extremly easy.  Finding the
bug was not so easy.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/46720997a0b1fa2971a884adf43de096ce130a7e">46720997</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-05-29T01:39:19-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Allow simplification through runRW#

Because runRW# inlines so late, we were previously able to do very
little simplification across it. For instance, given even a simple
program like

    case runRW# (\s -> let n = I# 42# in n) of
      I# n# -> f n#

we previously had no way to avoid the allocation of the I#.

This patch allows the simplifier to push strict contexts into the
continuation of a runRW# application, as explained in
in Note [Simplification of runRW#] in GHC.CoreToStg.Prep.

Fixes #15127.

Metric Increase:
    T9961
Metric Decrease:
    ManyConstructors

Co-Authored-By: Simon Peyton-Jone <simonpj@microsoft.com>
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/277c2f26e6966e0cfaa1ddcd297af44766f37958">277c2f26</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-05-29T01:39:55-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Eta expand un-saturated primops

Now since we no longer try to predict CAFfyness we have no need for the
solution to #16846. Eta expanding unsaturated primop applications is
conceptually simpler, especially in the presence of levity polymorphism.

This essentially reverts cac8dc9f51e31e4c0a6cd9bc302f7e1bc7c03beb,
as suggested in #18079.

Closes #18079.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/f44d7ae08442ae6227db37cacc97fe0def8017c5">f44d7ae0</a></strong>
<div>
<span>by Simon Jakobi</span>
<i>at 2020-05-29T01:40:34-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">base: Scrap deprecation plan for Data.Monoid.{First,Last}

See the discussion on the libraries mailing list for context:

https://mail.haskell.org/pipermail/libraries/2020-April/030357.html
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8b4948951198f93290191d4ee32f92dffed803f4">8b494895</a></strong>
<div>
<span>by Jeremy Schlatter</span>
<i>at 2020-05-29T01:41:12-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix typo in documentation
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/998450f4c67e8f701455927c9619b8d53f2b733b">998450f4</a></strong>
<div>
<span>by Gleb Popov</span>
<i>at 2020-05-29T01:41:53-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Always define USE_PTHREAD_FOR_ITIMER for FreeBSD.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/f9a513e064bd8a33ad6f8aa5fb8673931507eca1">f9a513e0</a></strong>
<div>
<span>by Alp Mestanogullari</span>
<i>at 2020-05-29T01:42:36-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">hadrian: introduce 'install' target

Its logic is very simple. It `need`s the `binary-dist-dir` target
and runs suitable `configure` and `make install` commands for the
user. A new `--prefix` command line argument is introduced to
specify where GHC should be installed.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/67738db10010fd28a8e997b5c8f83ea591b88a0e">67738db1</a></strong>
<div>
<span>by Travis Whitaker</span>
<i>at 2020-05-29T13:34:48-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Build a threaded stage 1 if the bootstrapping GHC supports it.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/aac19e6caa0c94e159610f124114186ee20bcdd1">aac19e6c</a></strong>
<div>
<span>by Peter Trommler</span>
<i>at 2020-05-29T13:35:24-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">PPC NCG: No per-symbol .section ".toc" directives

All position independent symbols are collected during code generation
and emitted in one go. Prepending each symbol with a .section ".toc"
directive is redundant. This patch drops the per-symbol directives
leading to smaller assembler files.

Fixes #18250
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4413828b7c507872c56719fb8920e1c2322830f8">4413828b</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-05-30T06:07:31-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts: Teach getNumProcessors to return available processors

Previously we would report the number of physical processors, which
can be quite wrong in a containerized setting. Now we rather return how
many processors are in our affinity mask when possible.

I also refactored the code to prefer platform-specific since this will
report logical CPUs instead of physical (using
`machdep.cpu.thread_count` on Darwin and `cpuset_getaffinity` on FreeBSD).

Fixes #14781.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/1449435c7bf1075f5cd11098d8c98b99f8fe150a">1449435c</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-05-30T06:07:31-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">users-guide: Note change in getNumProcessors in users guide
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/3d96016926cc88506db416f87b6e4b68a3a0d25f">3d960169</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-05-30T06:07:31-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts: Drop compatibility shims for Windows Vista

We can now assume that the thread and processor group interfaces are
available.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7f8f948c024c46282228243391238d09b297cd9d">7f8f948c</a></strong>
<div>
<span>by Peter Trommler</span>
<i>at 2020-05-30T06:08:07-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">PPC NCG: Fix .size directive on powerpc64 ELF v1

Thanks to Sergei Trofimovich for pointing out the issue.

Fixes #18237
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7c555b054bf074a9ab612f9d93e3475bfb8c6594">7c555b05</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-05-30T06:08:43-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Optimize GHC.Utils.Monad.

Many functions in this module are recursive and as such are marked
loop breakers. Which means they are unlikely to get an unfolding.

This is *bad*. We always want to specialize them to specific Monads.
Which requires a visible unfolding at the use site.

I rewrote the recursive ones from:

    foo f x = ... foo x' ...

to

    foo f x = go x
      where
        go x = ...

As well as giving some pragmas to make all of them available
for specialization.

The end result is a reduction of allocations of about -1.4% for
nofib/spectral/simple/Main.hs when compiled with `-O`.

-------------------------
Metric Decrease:
    T12425
    T14683
    T5631
    T9233
    T9675
    T9961
    WWRec
-------------------------
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8b1cb5df126b1829fca8e8caf050dff4ca9df3f3">8b1cb5df</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-05-30T06:09:20-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Windows: Bump Windows toolchain to 0.2
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6947231abd8c33840860ad51699b76efd4725f0e">6947231a</a></strong>
<div>
<span>by Zubin Duggal</span>
<i>at 2020-05-30T06:10:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Simplify contexts in GHC.Iface.Ext.Ast
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2ee4f36c779674f7237d730460ca83aec9a6808a">2ee4f36c</a></strong>
<div>
<span>by Daniel Gröber</span>
<i>at 2020-06-01T06:32:56-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Cleanup OVERWRITING_CLOSURE logic

The code is just more confusing than it needs to be. We don't need to mix
the threaded check with the ldv profiling check since ldv's init already
checks for this. Hence they can be two separate checks. Taking the sanity
checking into account is also cleaner via DebugFlags.sanity. No need for
checking the DEBUG define.

The ZERO_SLOP_FOR_LDV_PROF and ZERO_SLOP_FOR_SANITY_CHECK definitions the
old code had also make things a lot more opaque IMO so I removed those.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6159559b5eb71ed7287998e954f96cdfb2d48f04">6159559b</a></strong>
<div>
<span>by Daniel Gröber</span>
<i>at 2020-06-01T06:32:56-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix OVERWRITING_CLOSURE assuming closures are not inherently used

The new ASSERT in LDV_recordDead() was being tripped up by MVars when
removeFromMVarBlockedQueue() calls OVERWRITING_CLOSURE() via
OVERWRITE_INFO().
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/389920858e0b9efe5234cb7dac55d06e955768f7">38992085</a></strong>
<div>
<span>by Daniel Gröber</span>
<i>at 2020-06-01T06:32:56-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Always zero shrunk mutable array slop when profiling

When shrinking arrays in the profiling way we currently don't always zero
the leftover slop. This means we can't traverse such closures in the heap
profiler. The old Note [zeroing slop] and #8402 have some rationale for why
this is so but I belive the reasoning doesn't apply to mutable
closures. There users already have to ensure multiple threads don't step on
each other's toes so zeroing should be safe.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b0c1f2a619855a6fa22021a3118365c49f4cc0c4">b0c1f2a6</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-06-01T06:33:37-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite: Add test for #18151
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9a99a1787da1dda15c6da7509ab678f4131c7d68">9a99a178</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-06-01T06:33:37-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite: Add test for desugaring of PostfixOperators
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2b89ca5b850b4097447cc4908cbb0631011ce979">2b89ca5b</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-06-01T06:33:37-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">HsToCore: Eta expand left sections

Strangely, the comment next to this code already alluded to the fact
that even simply eta-expanding will sacrifice laziness. It's quite
unclear how we regressed so far.

See #18151.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d412d7a3783b4fc5d3078541a60996e249b4157c">d412d7a3</a></strong>
<div>
<span>by Kirill Elagin</span>
<i>at 2020-06-01T06:34:21-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Winferred-safe-imports: Do not exit with error

Currently, when -Winferred-safe-imports is enabled, even when it is not
turned into an error, the compiler will still exit with exit code 1 if
this warning was emitted.

Make sure it is really treated as a warning.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/f945eea569993a4e5ed953f4573e6eab785f309f">f945eea5</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-06-01T06:34:58-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">nonmoving: Optimise log2_ceil
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/aab606e4f028d3c418aafc9710003f32f8d8fe12">aab606e4</a></strong>
<div>
<span>by Bodigrim</span>
<i>at 2020-06-01T06:35:36-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Clarify description of fromListN</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7e5220e25baedfa7ae0ec055c03cb4429dd1af05">7e5220e2</a></strong>
<div>
<span>by Bodigrim</span>
<i>at 2020-06-01T06:35:36-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Apply suggestion to libraries/base/GHC/Exts.hs</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/f3fb1ce9759d1ca57b9ea4acf5518df8d086688e">f3fb1ce9</a></strong>
<div>
<span>by fendor</span>
<i>at 2020-06-01T06:36:18-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add `isInScope` check to `lintCoercion`

Mirrors the behaviour of `lintType`.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/5ac4d94607d4a898f0015114e929ee9a38118985">5ac4d946</a></strong>
<div>
<span>by fendor</span>
<i>at 2020-06-01T06:36:18-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Lint rhs of IfaceRule
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/1cef6126a97ea1f406ffe5e780478f6e200c0496">1cef6126</a></strong>
<div>
<span>by Jeremy Schlatter</span>
<i>at 2020-06-01T06:37:00-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix wording in documentation

The duplicate "orphan instance" phrase here doesn't make sense, and was
probably an accident.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/5aaf08f25ef0629432c792880dfc6785ff3ec8a3">5aaf08f2</a></strong>
<div>
<span>by Takenobu Tani</span>
<i>at 2020-06-01T06:37:43-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">configure: Modify aclocal.m4 according to new module hierarchy

This patch updates file paths according to new module hierarchy [1]:

* Rename:
  * compiler/GHC/Parser.hs       <= compiler/parser/Parser.hs
  * compiler/GHC/Parser/Lexer.hs <= compiler/Parser/Lexer.hs

* Add:
  * compiler/GHC/Cmm/Lexer.hs

[1]: https://gitlab.haskell.org/ghc/ghc/-/wikis/Make-GHC-codebase-more-modular
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/15857ad856b6072d2c6a34b2bf7aa7316d7e2b12">15857ad8</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-06-01T06:38:26-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite: Don't fail if we can't unlink __symlink_test

Afterall, it's possible we were unable to create it due to lack of
symlink permission.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4a7229ef361307e16574b85f71f473f936728890">4a7229ef</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-06-01T06:38:26-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite: Refactor ghostscript detection

Tamar reported that he saw crashes due to unhandled exceptions.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2ab37eaf9668b5aacc953c6d01fcab9e4f181bf7">2ab37eaf</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-06-01T06:38:26-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite/perf_notes: Fix ill-typed assignments
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e45d5b667653f4c3ffc89fe7a83eac56d60b9364">e45d5b66</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-06-01T06:38:26-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite/testutil: Fix bytes/str mismatch
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7002d0cbbe1581dd157b530e95c62195f37cfe00">7002d0cb</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-06-01T06:38:26-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite: Work around spurious mypy failure
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/11390e3ab038a18c2a7bf6b2423657614a439afb">11390e3a</a></strong>
<div>
<span>by Takenobu Tani</span>
<i>at 2020-06-01T06:39:05-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Clean up file paths for new module hierarchy

This updates comments only.
This patch replaces file references according to new module hierarchy.

See also:
* https://gitlab.haskell.org/ghc/ghc/-/wikis/Make-GHC-codebase-more-modular
* https://gitlab.haskell.org/ghc/ghc/issues/13009
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8f2e5732b0eec2d99b821a7f622aee8b2c00739a">8f2e5732</a></strong>
<div>
<span>by Takenobu Tani</span>
<i>at 2020-06-01T06:39:05-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Modify file paths to module paths for new module hierarchy

This updates comments only.

This patch replaces module references according to new module
hierarchy [1][2].

For files under the `compiler/` directory, I replace them as
module paths instead of file paths. For instance,
`GHC.Unit.State` instead of `compiler/GHC/Unit/State.hs` [3].

For current and future haddock's markup, this patch encloses
the module name with "" [4].

[1]: https://gitlab.haskell.org/ghc/ghc/-/wikis/Make-GHC-codebase-more-modular
[2]: https://gitlab.haskell.org/ghc/ghc/issues/13009
[3]: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3375#note_276613
[4]: https://haskell-haddock.readthedocs.io/en/latest/markup.html#linking-to-modules
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/68b71c4a99ef7c009e0095823950cd12408ad7fe">68b71c4a</a></strong>
<div>
<span>by Tom Ellis</span>
<i>at 2020-06-01T06:39:55-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Rename the singleton tuple GHC.Tuple.Unit to GHC.Tuple.Solo
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/95da76c2b9ffe2a4fb4230de0061918de3fc89a9">95da76c2</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-01T06:40:41-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Hadrian: fix binary-dist target for cross-compilation
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/730fcd54467e82083d56fa87e44bbe346458c531">730fcd54</a></strong>
<div>
<span>by Vladislav Zavialov</span>
<i>at 2020-06-01T06:41:18-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Improve parser error messages for the @-operator

Since GHC diverges from the Haskell Report by allowing the user
to define (@) as an infix operator, we better give a good
error message when the user does so unintentionally.

In general, this is rather hard to do, as some failures will be
discovered only in the renamer or the type checker:

        x :: (Integer, Integer)
        x @ (a, b) = (1, 2)

This patch does *not* address this general case.

However, it gives much better error messages when the binding
is not syntactically valid:

        pairs xs @ (_:xs') = zip xs xs'

Before this patch, the error message was rather puzzling:

        <interactive>:1:1: error: Parse error in pattern: pairs

After this patch, the error message includes a hint:

        <interactive>:1:1: error:
            Parse error in pattern: pairs
            In a function binding for the ‘@’ operator.
            Perhaps you meant an as-pattern, which must not be surrounded by whitespace
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/0fde53770cacb0d54f0583707ef7ceec78f92c41">0fde5377</a></strong>
<div>
<span>by Vladislav Zavialov</span>
<i>at 2020-06-01T06:41:18-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Improve parser error messages for TypeApplications

With this patch, we always parse  f @t  as a type application,
thereby producing better error messages.

This steals two syntactic forms:

* Prefix form of the @-operator in expressions. Since the @-operator is
  a divergence from the Haskell Report anyway, this is not a major loss.

* Prefix form of @-patterns. Since we are stealing loose infix form
  anyway, might as well sacrifice the prefix form for the sake of much
  better error messages.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c68e7e1e4c0bddd8b07cd8a2b3651c8cbb4b7851">c68e7e1e</a></strong>
<div>
<span>by Vladislav Zavialov</span>
<i>at 2020-06-01T06:41:18-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Improve parser error messages for TemplateHaskellQuotes

While [e| |], [t| |], [d| |], and so on, steal syntax from list
comprehensions, [| |] and [|| ||] do not steal any syntax.

Thus we can improve error messages by always accepting them in the
lexer. Turns out the renamer already performs necessary validation.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/120aedbdff7dbb9b394dadabb1f431608b42de67">120aedbd</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-06-01T16:07:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">gitlab-ci: Disable use of ld.lld on ARMv7

It turns out that lld non-deterministically fails on ARMv7. I suspect
this may be due to the a kernel regression as this only started
happening when we upgraded to 5.4. Nevertheless, easily avoided by
simply sticking with gold.

Works around #18280.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d6279ff0841edee10a665275ed0d2402565fac6d">d6279ff0</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-06-02T13:03:30-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">gitlab-ci: Ensure that workaround for #18280 applies to bindisttest

We need to ensure that the `configure` flags working around #18280 are
propagated to the bindisttest `configure` as well.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/cb5c31b51b021ce86890bba73276fe6f7405f5d3">cb5c31b5</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-06-03T17:55:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">gitlab-ci: Allow ARMv7 job to fail

Due to #18298.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/32a4ae90b50cc56f2955f489ad0cf8c7ff5e131a">32a4ae90</a></strong>
<div>
<span>by John Ericson</span>
<i>at 2020-06-04T04:34:42-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Clean up boot vs non-boot disambiguating types

We often have (ModuleName, Bool) or (Module, Bool) pairs for "extended"
module names (without or with a unit id) disambiguating boot and normal
modules. We think this is important enough across the compiler that it
deserves a new nominal product type. We do this with synnoyms and a
functor named with a `Gen` prefix, matching other newly created
definitions.

It was also requested that we keep custom `IsBoot` / `NotBoot` sum type.
So we have it too. This means changing many the many bools to use that
instead.

Updates `haddock` submodule.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c05756cdef800f1d8e92114222bcc480bce758b9">c05756cd</a></strong>
<div>
<span>by Niklas Hambüchen</span>
<i>at 2020-06-04T04:35:24-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">docs: Add more details on InterruptibleFFI.

Details from https://gitlab.haskell.org/ghc/ghc/issues/8684
and https://github.com/takano-akio/filelock/pull/7#discussion_r280332430
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/1b975aedb1b74b8694d14ba8fdc5955497f8f31c">1b975aed</a></strong>
<div>
<span>by Andrew Martin</span>
<i>at 2020-06-04T04:36:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Allow finalizeForeignPtr to be called on FinalPtr/PlainPtr.

MR 2165 (commit 49301ad6226d9a83d110bee8c419615dd94f5ded) regressed
finalizeForeignPtr by throwing exceptions when PlainPtr was encounterd.
This regression did not make it into a release of GHC. Here, the
original behavior is restored, and FinalPtr is given the same treatment
as PlainPtr.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2bd3929ad1b06b01c1d22d513902507eefadc131">2bd3929a</a></strong>
<div>
<span>by Luke Lau</span>
<i>at 2020-06-04T04:36:41-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix documentation on type families not being extracted

It looks like the location of the Names used for CoAxioms on type
families are now located at their type constructors. Previously, Docs.hs
thought the Names were located in the RHS, so the RealSrcSpan in the
instanceMap and getInstLoc didn't match up. Fixes #18241
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6735b9d94605b4c7f75e70339bfaa4207f23e52b">6735b9d9</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-06-04T04:37:21-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">GHC.Hs.Instances: Compile with -O0

This module contains exclusively Data instances, which are going to be
slow no matter what we do. Furthermore, they are incredibly slow to
compile with optimisation (see #9557). Consequently we compile this with
-O0.  See #18254.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c330331adc0a686f24b94844d0eb3a0711b928d7">c330331a</a></strong>
<div>
<span>by nineonine</span>
<i>at 2020-06-04T04:37:59-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add test for #17669
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/cab684f0857c71c40996201d6fb3ba93eb38a701">cab684f0</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-06-04T04:38:36-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts: Add Windows-specific implementation of rtsSleep

Previously we would use the POSIX path, which uses `nanosleep`. However,
it turns out that `nanosleep` is provided by `libpthread` on Windows. In
general we don't want to incur such a dependency. Avoid this by simply
using `Sleep` on Windows.

Fixes #18272.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ad44b50484f27beceab8213a061aa60c7a03f7ca">ad44b504</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-06-04T04:38:36-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">compiler: Disable use of process jobs with process < 1.6.9

Due to #17926.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6a4098a4bb89b3d30cca26d82b82724913062536">6a4098a4</a></strong>
<div>
<span>by Moritz Angermann</span>
<i>at 2020-06-04T04:55:51-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">[linker] Adds void printLoadedObjects(void);

This allows us to dump in-memory object code locations for debugging.

Fixup printLoadedObjects prototype
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/af5e3a885ddd09dd5f550552c535af3661ff3dbf">af5e3a88</a></strong>
<div>
<span>by Artem Pelenitsyn</span>
<i>at 2020-06-05T03:18:49-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">base: fix sign confusion in log1mexp implementation (fix #17125)

author: claude (https://gitlab.haskell.org/trac-claude)

The correct threshold for log1mexp is -(log 2) with the current specification
of log1mexp. This change improves accuracy for large negative inputs.

To avoid code duplication, a small helper function is added;
it isn't the default implementation in Floating because it needs Ord.

This patch does nothing to address that the Haskell specification is
different from that in common use in other languages.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2b792facab46f7cdd09d12e79499f4e0dcd4293f">2b792fac</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-06-05T09:27:50-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Simple subsumption

This patch simplifies GHC to use simple subsumption.
  Ticket #17775

Implements GHC proposal #287
   https://github.com/ghc-proposals/ghc-proposals/blob/master/
   proposals/0287-simplify-subsumption.rst

All the motivation is described there; I will not repeat it here.
The implementation payload:
 * tcSubType and friends become noticably simpler, because it no
   longer uses eta-expansion when checking subsumption.
 * No deeplyInstantiate or deeplySkolemise

That in turn means that some tests fail, by design; they can all
be fixed by eta expansion.  There is a list of such changes below.

Implementing the patch led me into a variety of sticky corners, so
the patch includes several othe changes, some quite significant:

* I made String wired-in, so that
    "foo" :: String   rather than
    "foo" :: [Char]
  This improves error messages, and fixes #15679

* The pattern match checker relies on knowing about in-scope equality
  constraints, andd adds them to the desugarer's environment using
  addTyCsDs.  But the co_fn in a FunBind was missed, and for some reason
  simple-subsumption ends up with dictionaries there. So I added a
  call to addTyCsDs.  This is really part of #18049.

* I moved the ic_telescope field out of Implication and into
  ForAllSkol instead.  This is a nice win; just expresses the code
  much better.

* There was a bug in GHC.Tc.TyCl.Instance.tcDataFamInstHeader.
  We called checkDataKindSig inside tc_kind_sig, /before/
  solveEqualities and zonking.  Obviously wrong, easily fixed.

* solveLocalEqualitiesX: there was a whole mess in here, around
  failing fast enough.  I discovered a bad latent bug where we
  could successfully kind-check a type signature, and use it,
  but have unsolved constraints that could fill in coercion
  holes in that signature --  aargh.

  It's all explained in Note [Failure in local type signatures]
  in GHC.Tc.Solver. Much better now.

* I fixed a serious bug in anonymous type holes. IN
    f :: Int -> (forall a. a -> _) -> Int
  that "_" should be a unification variable at the /outer/
  level; it cannot be instantiated to 'a'.  This was plain
  wrong.  New fields mode_lvl and mode_holes in TcTyMode,
  and auxiliary data type GHC.Tc.Gen.HsType.HoleMode.

  This fixes #16292, but makes no progress towards the more
  ambitious #16082

* I got sucked into an enormous refactoring of the reporting of
  equality errors in GHC.Tc.Errors, especially in
      mkEqErr1
      mkTyVarEqErr
      misMatchMsg
      misMatchMsgOrCND
  In particular, the very tricky mkExpectedActualMsg function
  is gone.

  It took me a full day.  But the result is far easier to understand.
  (Still not easy!)  This led to various minor improvements in error
  output, and an enormous number of test-case error wibbles.

  One particular point: for occurs-check errors I now just say
     Can't match 'a' against '[a]'
  rather than using the intimidating language of "occurs check".

* Pretty-printing AbsBinds

Tests review

* Eta expansions
   T11305: one eta expansion
   T12082: one eta expansion (undefined)
   T13585a: one eta expansion
   T3102:  one eta expansion
   T3692:  two eta expansions (tricky)
   T2239:  two eta expansions
   T16473: one eta
   determ004: two eta expansions (undefined)
   annfail06: two eta (undefined)
   T17923: four eta expansions (a strange program indeed!)
   tcrun035: one eta expansion

* Ambiguity check at higher rank.  Now that we have simple
  subsumption, a type like
     f :: (forall a. Eq a => Int) -> Int
  is no longer ambiguous, because we could write
     g :: (forall a. Eq a => Int) -> Int
     g = f
  and it'd typecheck just fine.  But f's type is a bit
  suspicious, and we might want to consider making the
  ambiguity check do a check on each sub-term.  Meanwhile,
  these tests are accepted, whereas they were previously
  rejected as ambiguous:
     T7220a
     T15438
     T10503
     T9222

* Some more interesting error message wibbles
   T13381: Fine: one error (Int ~ Exp Int)
           rather than two (Int ~ Exp Int, Exp Int ~ Int)
   T9834:  Small change in error (improvement)
   T10619: Improved
   T2414:  Small change, due to order of unification, fine
   T2534:  A very simple case in which a change of unification order
           means we get tow unsolved constraints instead of one
   tc211: bizarre impredicative tests; just accept this for now

Updates Cabal and haddock submodules.

Metric Increase:
  T12150
  T12234
  T5837
  haddock.base
Metric Decrease:
  haddock.compiler
  haddock.Cabal
  haddock.base

Merge note: This appears to break the
`UnliftedNewtypesDifficultUnification` test. It has been marked as
broken in the interest of merging.

(cherry picked from commit 66b7b195cb3dce93ed5078b80bf568efae904cc5)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2dff814158e08aed53036bf6ebd7c3c8394af438">2dff8141</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-06-05T14:21:24-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Simplify bindLHsTyVarBndrs and bindHsQTyVars

Both `bindLHsTyVarBndrs` and `bindHsQTyVars` take two separate
`Maybe` arguments, which I find terribly confusing. Thankfully, it's
possible to remove one `Maybe` argument from each of these functions,
which this patch accomplishes:

* `bindHsQTyVars` takes a `Maybe SDoc` argument, which is `Just` if
  GHC should warn about any of the quantified type variables going
  unused. However, every call site uses `Nothing` in practice. This
  makes sense, since it doesn't really make sense to warn about
  unused type variables bound by an `LHsQTyVars`. For instance, you
  wouldn't warn about the `a` in `data Proxy a = Proxy` going unused.

  As a result, I simply remove this `Maybe SDoc` argument altogether.
* `bindLHsTyVarBndrs` also takes a `Maybe SDoc` argument for the same
  reasons that `bindHsQTyVars` took one. To make things more
  confusing, however, `bindLHsTyVarBndrs` also takes a separate
  `HsDocContext` argument, which is pretty-printed (to an `SDoc`) in
  warnings and error messages.

  In practice, the `Maybe SDoc` and the `HsDocContext` often contain
  the same text. See the call sites for `bindLHsTyVarBndrs` in
  `rnFamInstEqn` and `rnConDecl`, for instance. There are only a
  handful of call sites where the text differs between the
  `Maybe SDoc` and `HsDocContext` arguments:

  * In `rnHsRuleDecl`, where the `Maybe SDoc` says "`In the rule`"
    and the `HsDocContext` says "`In the transformation rule`".
  * In `rnHsTyKi`/`rn_ty`, where the `Maybe SDoc` says
    "`In the type`" but the `HsDocContext` is inhereted from the
    surrounding context (e.g., if `rnHsTyKi` were called on a
    top-level type signature, the `HsDocContext` would be
    "`In the type signature`" instead)

  In both cases, warnings/error messages arguably _improve_ by
  unifying making the `Maybe SDoc`'s text match that of the
  `HsDocContext`. As a result, I decided to remove the `Maybe SDoc`
  argument to `bindLHsTyVarBndrs` entirely and simply reuse the text
  from the `HsDocContext`. (I decided to change the phrase
  "transformation rule" to "rewrite rule" while I was in the area.)

  The `Maybe SDoc` argument has one other purpose: signaling when to
  emit "`Unused quantified type variable`" warnings. To recover this
  functionality, I replaced the `Maybe SDoc` argument with a
  boolean-like `WarnUnusedForalls` argument. The only
  `bindLHsTyVarBndrs` call site that chooses _not_ to emit these
  warnings in `bindHsQTyVars`.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e372331b3212e5d8eddfa6f8d2c3840b7e95c2b3">e372331b</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-06-07T08:46:41-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">hadrian: Add missing deriveConstants dependency on ghcplatform.h

deriveConstants wants to compile C sources which #include PosixSource.h,
which itself #includes ghcplatform.h. Make sure that Hadrian knows
about this dependency.

Fixes #18290.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b022051a50d30e39d86ee21e565e899e7e98255f">b022051a</a></strong>
<div>
<span>by Moritz Angermann</span>
<i>at 2020-06-07T08:46:42-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">ghc-prim needs to depend on libc and libm

libm is just an empty shell on musl, and all the math functions are contained in
libc.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6dae65484f9552239652f743e2303fa17aae953b">6dae6548</a></strong>
<div>
<span>by Moritz Angermann</span>
<i>at 2020-06-07T08:46:42-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Disable DLL loading if without system linker

Some platforms (musl, aarch64) do not have a working dynamic linker
implemented in the libc, even though we might see dlopen.  It will
ultimately just return that this is not supported.  Hence we'll add
a flag to the compiler to flat our disable loading dlls.  This is
needed as we will otherwise try to load the shared library even
if this will subsequently fail.  At that point we have given up
looking for static options though.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4a158ffc4e0ac250897aefaf6caf03eb5f688182">4a158ffc</a></strong>
<div>
<span>by Moritz Angermann</span>
<i>at 2020-06-07T08:46:43-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Range is actually +/-2^32, not +/-2^31

See also: https://static.docs.arm.com/ihi0056/g/aaelf64.pdf
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/f1bfb806683b3092fc5ead84e7ecff928c55fbc4">f1bfb806</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-06-07T10:49:30-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">OccurAnal: Avoid exponential behavior due to where clauses

Previously the `Var` case of `occAnalApp` could in some cases (namely
in the case of `runRW#` applications) call `occAnalRhs` two. In the case
of nested `runRW#`s this results in exponential complexity. In some
cases the compilation time that resulted would be very long indeed
(see #18296).

Fixes #18296.

Metric Decrease:
    T9961
    T12150
    T12234
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9b607671b9158c60470b2bd57804a7684d3ea33f">9b607671</a></strong>
<div>
<span>by Takenobu Tani</span>
<i>at 2020-06-09T08:05:46-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add link to GHC's wiki in the GHC API header

This adds a URL to point to GHC's wiki in the GHC API header.
Newcomers could easily find more information from the GHC API's
web like [1].

[1]: Current version, https://ghc.gitlab.haskell.org/ghc/doc/libraries/ghc-8.11.0.20200604/index.html

[skip ci]
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/72c7fe9a1e147dfeaf043f6d591d724a126cce45">72c7fe9a</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-06-09T08:06:24-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Make GADT constructors adhere to the forall-or-nothing rule properly

Issue #18191 revealed that the types of GADT constructors don't quite
adhere to the `forall`-or-nothing rule. This patch serves to clean up
this sad state of affairs somewhat. The main change is not in the
code itself, but in the documentation, as this patch introduces two
sections to the GHC User's Guide:

* A "Formal syntax for GADTs" section that presents a BNF-style
  grammar for what is and isn't allowed in GADT constructor types.
  This mostly exists to codify GHC's existing behavior, but it also
  imposes a new restriction that addresses #18191: the outermost
  `forall` and/or context in a GADT constructor is not allowed to be
  surrounded by parentheses. Doing so would make these
  `forall`s/contexts nested, and GADTs do not support nested
  `forall`s/contexts at present.

* A "`forall`-or-nothing rule" section that describes exactly what
  the `forall`-or-nothing rule is all about. Surprisingly, there was
  no mention of this anywhere in the User's Guide up until now!

To adhere the new specification in the "Formal syntax for GADTs"
section of the User's Guide, the following code changes were made:

* A new function, `GHC.Hs.Type.splitLHsGADTPrefixTy`, was introduced.
  This is very much like `splitLHsSigmaTy`, except that it avoids
  splitting apart any parentheses, which can be syntactically
  significant for GADT types. See
  `Note [No nested foralls or contexts in GADT constructors]` in
  `GHC.Hs.Type`.

* `ConDeclGADTPrefixPs`, an extension constructor for `XConDecl`, was
  introduced so that `GHC.Parser.PostProcess.mkGadtDecl` can return
  it when given a prefix GADT constructor. Unlike `ConDeclGADT`,
  `ConDeclGADTPrefixPs` does not split the GADT type into its argument
  and result types, as this cannot be done until after the type is
  renamed (see `Note [GADT abstract syntax]` in `GHC.Hs.Decls` for why
  this is the case).

* `GHC.Renamer.Module.rnConDecl` now has an additional case for
  `ConDeclGADTPrefixPs` that (1) splits apart the full `LHsType` into
  its `forall`s, context, argument types, and result type, and
  (2) checks for nested `forall`s/contexts. Step (2) used to be
  performed the typechecker (in `GHC.Tc.TyCl.badDataConTyCon`) rather
  than the renamer, but now the relevant code from the typechecker
  can simply be deleted.

  One nice side effect of this change is that we are able to give a
  more accurate error message for GADT constructors that use visible
  dependent quantification (e.g., `MkFoo :: forall a -> a -> Foo a`),
  which improves the stderr in the `T16326_Fail6` test case.

Fixes #18191. Bumps the Haddock submodule.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a47e6442bc4be4a33339499d876792ba109e8d32">a47e6442</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-06-10T03:39:12-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Always use rnImplicitBndrs to bring implicit tyvars into scope

This implements a first step towards #16762 by changing the renamer
to always use `rnImplicitBndrs` to bring implicitly bound type
variables into scope. The main change is in `rnFamInstEqn` and
`bindHsQTyVars`, which previously used _ad hoc_ methods of binding
their implicit tyvars.

There are a number of knock-on consequences:

* One of the reasons that `rnFamInstEqn` used an _ad hoc_ binding
  mechanism was to give more precise source locations in
  `-Wunused-type-patterns` warnings. (See
  https://gitlab.haskell.org/ghc/ghc/issues/16762#note_273343 for an
  example of this.) However, these warnings are actually a little
  _too_ precise, since implicitly bound type variables don't have
  exact binding sites like explicitly bound type variables do.
  A similar problem existed for
  "`Different names for the same type variable`" errors involving
  implicit tyvars bound by `bindHsQTyVars`.
  Therefore, we simply accept the less precise (but more accurate)
  source locations from `rnImplicitBndrs` in `rnFamInstEqn` and
  `bindHsQTyVars`. See
  `Note [Source locations for implicitly bound type variables]` in
  `GHC.Rename.HsType` for the full story.
* In order for `rnImplicitBndrs` to work in `rnFamInstEqn`, it needs
  to be able to look up names from the parent class (in the event
  that we are renaming an associated type family instance). As a
  result, `rnImplicitBndrs` now takes an argument of type
  `Maybe assoc`, which is `Just` in the event that a type family
  instance is associated with a class.
* Previously, GHC kept track of three type synonyms for free type
  variables in the renamer: `FreeKiTyVars`, `FreeKiTyVarsDups`
  (which are allowed to contain duplicates), and
  `FreeKiTyVarsNoDups` (which contain no duplicates). However, making
  is a distinction between `-Dups` and `-NoDups` is now pointless, as
  all code that returns `FreeKiTyVars{,Dups,NoDups}` will eventually
  end up being passed to `rnImplicitBndrs`, which removes duplicates.
  As a result, I decided to just get rid of `FreeKiTyVarsDups` and
  `FreeKiTyVarsNoDups`, leaving only `FreeKiTyVars`.
* The `bindLRdrNames` and `deleteBys` functions are now dead code, so
  I took the liberty of removing them.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2487912938f188cb264e4a11d21bf750adccc5e7">24879129</a></strong>
<div>
<span>by Takenobu Tani</span>
<i>at 2020-06-10T03:39:59-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Clarify leaf module names for new module hierarchy

This updates comments only.

This patch replaces leaf module names according to new module
hierarchy [1][2] as followings:

* Expand leaf names to easily find the module path:
  for instance, `Id.hs` to `GHC.Types.Id`.

* Modify leaf names according to new module hierarchy:
  for instance, `Convert.hs` to `GHC.ThToHs`.

* Fix typo:
  for instance, `GHC.Core.TyCo.Rep.hs` to `GHC.Core.TyCo.Rep`

See also !3375

[1]: https://gitlab.haskell.org/ghc/ghc/-/wikis/Make-GHC-codebase-more-modular
[2]: https://gitlab.haskell.org/ghc/ghc/issues/13009
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/92de9e25aa1a6f7aa73154868521bcf4f0dc9d1e">92de9e25</a></strong>
<div>
<span>by Ömer Sinan Ağacan</span>
<i>at 2020-06-10T03:41:07-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts: Remove unused GET_ENTRY closure macro

This macro is not used and got broken in the meantime, as ENTRY_CODE was
deleted.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/87102928cce33d9029ca4cc449dde6efc802b8ec">87102928</a></strong>
<div>
<span>by Ömer Sinan Ağacan</span>
<i>at 2020-06-10T03:41:50-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix -fkeep-cafs flag name in users guide
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ccd6843d4a39920b4fa02badbe82e529390d4a74">ccd6843d</a></strong>
<div>
<span>by Shayne Fletcher</span>
<i>at 2020-06-10T04:14:57-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Expose impliedGFlags, impledOffGFlags, impliedXFlags
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7a737e898014d92bdbeed2e1cf5c35fc0a91a547">7a737e89</a></strong>
<div>
<span>by Ömer Sinan Ağacan</span>
<i>at 2020-06-10T04:14:58-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Cross-module LambdaFormInfo passing

- Store LambdaFormInfos of exported Ids in interface files
- Use them in importing modules

This is for optimization purposes: if we know LambdaFormInfo of imported
Ids we can generate more efficient calling code, see `getCallMethod`.

Exporting (putting them in interface files or in ModDetails) and
importing (reading them from interface files) are both optional. We
don't assume known LambdaFormInfos anywhere and do not change how we
call Ids with unknown LambdaFormInfos.

Runtime, allocation, and residency numbers when building
Cabal-the-library (commit 0d4ee7ba3):

(Log and .hp files are in the MR: !2842)

|     | GHC HEAD | This patch | Diff           |
|-----|----------|------------|----------------|
| -O0 |  0:35.89 |    0:34.10 | -1.78s, -4.98% |
| -O1 |  2:24.01 |    2:23.62 | -0.39s, -0.27% |
| -O2 |  2:52.23 |    2:51.35 | -0.88s, -0.51% |

|     | GHC HEAD        | This patch      | Diff                       |
|-----|-----------------|-----------------|----------------------------|
| -O0 |  54,843,608,416 |  54,878,769,544 |  +35,161,128 bytes, +0.06% |
| -O1 | 227,136,076,400 | 227,569,045,168 | +432,968,768 bytes, +0.19% |
| -O2 | 266,147,063,296 | 266,749,643,440 | +602,580,144 bytes, +0.22% |

NOTE: Residency is measured with extra runtime args: `-i0 -h` which effectively
turn all GCs into major GCs, and do GC more often.

|     | GHC HEAD                   | This patch                   | Diff                       |
|-----|----------------------------|------------------------------|----------------------------|
| -O0 | 410,284,000 (910 samples)  | 411,745,008 (906 samples)    | +1,461,008 bytes, +0.35%   |
| -O1 | 928,580,856 (2109 samples) | 943,506,552 (2103 samples)   | +14,925,696 bytes, +1.60%  |
| -O2 | 993,951,352 (2549 samples) | 1,010,156,328 (2545 samples) | +16,204,9760 bytes, +1.63% |

NoFib results:

--------------------------------------------------------------------------------
        Program           Size    Allocs    Instrs     Reads    Writes
--------------------------------------------------------------------------------
             CS           0.0%      0.0%     +0.0%     +0.0%     +0.0%
            CSD           0.0%      0.0%      0.0%     +0.0%     +0.0%
             FS           0.0%      0.0%     +0.0%     +0.0%     +0.0%
              S           0.0%      0.0%     +0.0%     +0.0%     +0.0%
             VS           0.0%      0.0%     +0.0%     +0.0%     +0.0%
            VSD           0.0%      0.0%     +0.0%     +0.0%     +0.1%
            VSM           0.0%      0.0%     +0.0%     +0.0%     +0.0%
           anna           0.0%      0.0%     -0.3%     -0.8%     -0.0%
           ansi           0.0%      0.0%     -0.0%     -0.0%      0.0%
           atom           0.0%      0.0%     -0.0%     -0.0%      0.0%
         awards           0.0%      0.0%     -0.1%     -0.3%      0.0%
         banner           0.0%      0.0%     -0.0%     -0.0%     -0.0%
     bernouilli           0.0%      0.0%     -0.0%     -0.0%     -0.0%
   binary-trees           0.0%      0.0%     -0.0%     -0.0%     +0.0%
          boyer           0.0%      0.0%     -0.0%     -0.0%      0.0%
         boyer2           0.0%      0.0%     -0.0%     -0.0%      0.0%
           bspt           0.0%      0.0%     -0.0%     -0.2%      0.0%
      cacheprof           0.0%      0.0%     -0.1%     -0.4%     +0.0%
       calendar           0.0%      0.0%     -0.0%     -0.0%      0.0%
       cichelli           0.0%      0.0%     -0.9%     -2.4%      0.0%
        circsim           0.0%      0.0%     -0.0%     -0.0%      0.0%
       clausify           0.0%      0.0%     -0.1%     -0.3%      0.0%
  comp_lab_zift           0.0%      0.0%     -0.0%     -0.0%     +0.0%
       compress           0.0%      0.0%     -0.0%     -0.0%     -0.0%
      compress2           0.0%      0.0%     -0.0%     -0.0%      0.0%
    constraints           0.0%      0.0%     -0.1%     -0.2%     -0.0%
   cryptarithm1           0.0%      0.0%     -0.0%     -0.0%      0.0%
   cryptarithm2           0.0%      0.0%     -1.4%     -4.1%     -0.0%
            cse           0.0%      0.0%     -0.0%     -0.0%     -0.0%
   digits-of-e1           0.0%      0.0%     -0.0%     -0.0%     -0.0%
   digits-of-e2           0.0%      0.0%     -0.0%     -0.0%     -0.0%
         dom-lt           0.0%      0.0%     -0.1%     -0.2%      0.0%
          eliza           0.0%      0.0%     -0.5%     -1.5%      0.0%
          event           0.0%      0.0%     -0.0%     -0.0%     -0.0%
    exact-reals           0.0%      0.0%     -0.1%     -0.3%     +0.0%
         exp3_8           0.0%      0.0%     -0.0%     -0.0%     -0.0%
         expert           0.0%      0.0%     -0.3%     -1.0%     -0.0%
 fannkuch-redux           0.0%      0.0%     +0.0%     +0.0%     +0.0%
          fasta           0.0%      0.0%     -0.0%     -0.0%     +0.0%
            fem           0.0%      0.0%     -0.0%     -0.0%      0.0%
            fft           0.0%      0.0%     -0.0%     -0.0%      0.0%
           fft2           0.0%      0.0%     -0.0%     -0.0%      0.0%
       fibheaps           0.0%      0.0%     -0.0%     -0.0%     +0.0%
           fish           0.0%      0.0%      0.0%     -0.0%     +0.0%
          fluid           0.0%      0.0%     -0.4%     -1.2%     +0.0%
         fulsom           0.0%      0.0%     -0.0%     -0.0%      0.0%
         gamteb           0.0%      0.0%     -0.1%     -0.3%      0.0%
            gcd           0.0%      0.0%     -0.0%     -0.0%      0.0%
    gen_regexps           0.0%      0.0%     -0.0%     -0.0%     -0.0%
         genfft           0.0%      0.0%     -0.0%     -0.0%      0.0%
             gg           0.0%      0.0%     -0.0%     -0.0%     +0.0%
           grep           0.0%      0.0%     -0.0%     -0.0%     -0.0%
         hidden           0.0%      0.0%     -0.1%     -0.4%     -0.0%
            hpg           0.0%      0.0%     -0.2%     -0.5%     +0.0%
            ida           0.0%      0.0%     -0.0%     -0.0%     +0.0%
          infer           0.0%      0.0%     -0.3%     -0.8%     -0.0%
        integer           0.0%      0.0%     -0.0%     -0.0%     +0.0%
      integrate           0.0%      0.0%     -0.0%     -0.0%      0.0%
   k-nucleotide           0.0%      0.0%     -0.0%     -0.0%     +0.0%
          kahan           0.0%      0.0%     -0.0%     -0.0%     +0.0%
        knights           0.0%      0.0%     -2.2%     -5.4%      0.0%
         lambda           0.0%      0.0%     -0.6%     -1.8%      0.0%
     last-piece           0.0%      0.0%     -0.0%     -0.0%      0.0%
           lcss           0.0%      0.0%     -0.0%     -0.1%      0.0%
           life           0.0%      0.0%     -0.0%     -0.1%      0.0%
           lift           0.0%      0.0%     -0.2%     -0.6%     +0.0%
         linear           0.0%      0.0%     -0.0%     -0.0%     -0.0%
      listcompr           0.0%      0.0%     -0.0%     -0.0%      0.0%
       listcopy           0.0%      0.0%     -0.0%     -0.0%      0.0%
       maillist           0.0%      0.0%     -0.1%     -0.3%     +0.0%
         mandel           0.0%      0.0%     -0.0%     -0.0%      0.0%
        mandel2           0.0%      0.0%     -0.0%     -0.0%     -0.0%
           mate          +0.0%      0.0%     -0.0%     -0.0%     -0.0%
        minimax           0.0%      0.0%     -0.2%     -1.0%      0.0%
        mkhprog           0.0%      0.0%     -0.1%     -0.2%     -0.0%
     multiplier           0.0%      0.0%     -0.0%     -0.0%     -0.0%
         n-body           0.0%      0.0%     -0.0%     -0.0%     +0.0%
       nucleic2           0.0%      0.0%     -0.1%     -0.2%      0.0%
           para           0.0%      0.0%     -0.0%     -0.0%     -0.0%
      paraffins           0.0%      0.0%     -0.0%     -0.0%      0.0%
         parser           0.0%      0.0%     -0.2%     -0.7%      0.0%
        parstof           0.0%      0.0%     -0.0%     -0.0%     +0.0%
            pic           0.0%      0.0%     -0.0%     -0.0%      0.0%
       pidigits           0.0%      0.0%     +0.0%     +0.0%     +0.0%
          power           0.0%      0.0%     -0.2%     -0.6%     +0.0%
         pretty           0.0%      0.0%     -0.0%     -0.0%     -0.0%
         primes           0.0%      0.0%     -0.0%     -0.0%      0.0%
      primetest           0.0%      0.0%     -0.0%     -0.0%     -0.0%
         prolog           0.0%      0.0%     -0.3%     -1.1%      0.0%
         puzzle           0.0%      0.0%     -0.0%     -0.0%      0.0%
         queens           0.0%      0.0%     -0.0%     -0.0%     +0.0%
        reptile           0.0%      0.0%     -0.0%     -0.0%      0.0%
reverse-complem           0.0%      0.0%     -0.0%     -0.0%     +0.0%
        rewrite           0.0%      0.0%     -0.7%     -2.5%     -0.0%
           rfib           0.0%      0.0%     -0.0%     -0.0%      0.0%
            rsa           0.0%      0.0%     -0.0%     -0.0%      0.0%
            scc           0.0%      0.0%     -0.1%     -0.2%     -0.0%
          sched           0.0%      0.0%     -0.0%     -0.0%     -0.0%
            scs           0.0%      0.0%     -1.0%     -2.6%     +0.0%
         simple           0.0%      0.0%     +0.0%     -0.0%     +0.0%
          solid           0.0%      0.0%     -0.0%     -0.0%      0.0%
        sorting           0.0%      0.0%     -0.6%     -1.6%      0.0%
  spectral-norm           0.0%      0.0%     +0.0%      0.0%     +0.0%
         sphere           0.0%      0.0%     -0.0%     -0.0%     -0.0%
         symalg           0.0%      0.0%     -0.0%     -0.0%     +0.0%
            tak           0.0%      0.0%     -0.0%     -0.0%      0.0%
      transform           0.0%      0.0%     -0.0%     -0.0%      0.0%
       treejoin           0.0%      0.0%     -0.0%     -0.0%      0.0%
      typecheck           0.0%      0.0%     -0.0%     -0.0%     +0.0%
        veritas          +0.0%      0.0%     -0.2%     -0.4%     +0.0%
           wang           0.0%      0.0%     -0.0%     -0.0%      0.0%
      wave4main           0.0%      0.0%     -0.0%     -0.0%     -0.0%
   wheel-sieve1           0.0%      0.0%     -0.0%     -0.0%     -0.0%
   wheel-sieve2           0.0%      0.0%     -0.0%     -0.0%     +0.0%
           x2n1           0.0%      0.0%     -0.0%     -0.0%     -0.0%
--------------------------------------------------------------------------------
            Min           0.0%      0.0%     -2.2%     -5.4%     -0.0%
            Max          +0.0%      0.0%     +0.0%     +0.0%     +0.1%
 Geometric Mean          -0.0%     -0.0%     -0.1%     -0.3%     +0.0%

Metric increases micro benchmarks tracked in #17686:

Metric Increase:
    T12150
    T12234
    T12425
    T13035
    T5837
    T6048
    T9233

Co-authored-by: Andreas Klebinger <klebinger.andreas@gmx.at>
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/3b22b14a7a1c1819fc8682fc127acf7448c5630c">3b22b14a</a></strong>
<div>
<span>by Shayne Fletcher</span>
<i>at 2020-06-10T04:15:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Give Language a Bounded instance
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9454511b0bdfcd79a1899d7f24bf65a3eb0d06e3">9454511b</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-06-10T04:17:06-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Optimisation in Unique.Supply

This patch switches on -fno-state-hack in GHC.Types.Unique.Supply.

It turned out that my fixes for #18078 (coercion floating) changed the
optimisation pathway for mkSplitUniqSupply in such a way that we had
an extra allocation inside the inner loop.  Adding -fno-state-hack
fixed that -- and indeed the loop in mkSplitUniqSupply is a classic
example of the way in which -fno-state-hack can be bad; see #18238.

Moreover, the new code is better than the old.  They allocate
the same, but the old code ends up with a partial application.
The net effect is that the test
    perf/should_run/UniqLoop
runs 20% faster!   From 2.5s down to 2.0s.  The allocation numbers
are the same -- but elapsed time falls. Good!

The bad thing about this is that it's terribly delicate.  But
at least it's a good example of such delicacy in action.

There is a long Note [Optimising the unique supply] which now
explains all this.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6d49d5be904c0c01788fa7aae1b112d5b4dfaf1c">6d49d5be</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-06-10T04:17:06-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Implement cast worker/wrapper properly

The cast worker/wrapper transformation transforms
   x = e |> co
into
   y = e
   x = y |> co

This is done by the simplifier, but we were being
careless about transferring IdInfo from x to y,
and about what to do if x is a NOINLNE function.
This resulted in a series of bugs:
     #17673, #18093, #18078.

This patch fixes all that:

* Main change is in GHC.Core.Opt.Simplify, and
  the new prepareBinding function, which does this
  cast worker/wrapper transform.
  See Note [Cast worker/wrappers].

* There is quite a bit of refactoring around
  prepareRhs, makeTrivial etc.  It's nicer now.

* Some wrappers from strictness and cast w/w, notably those for
  a function with a NOINLINE, should inline very late. There
  wasn't really a mechanism for that, which was an existing bug
  really; so I invented a new finalPhase = Phase (-1).  It's used
  for all simplifier runs after the user-visible phase 2,1,0 have
  run.  (No new runs of the simplifier are introduced thereby.)

  See new Note [Compiler phases] in GHC.Types.Basic;
  the main changes are in GHC.Core.Opt.Driver

* Doing this made me trip over two places where the AnonArgFlag on a
  FunTy was being lost so we could end up with (Num a -> ty)
  rather than (Num a => ty)
    - In coercionLKind/coercionRKind
    - In contHoleType in the Simplifier

  I fixed the former by defining mkFunctionType and using it in
  coercionLKind/RKind.

  I could have done the same for the latter, but the information
  is almost to hand.  So I fixed the latter by
    - adding sc_hole_ty to ApplyToVal (like ApplyToTy),
    - adding as_hole_ty to ValArg (like TyArg)
    - adding sc_fun_ty to StrictArg
  Turned out I could then remove ai_type from ArgInfo.  This is
  just moving the deck chairs around, but it worked out nicely.

  See the new Note [AnonArgFlag] in GHC.Types.Var

* When looking at the 'arity decrease' thing (#18093) I discovered
  that stable unfoldings had a much lower arity than the actual
  optimised function.  That's what led to the arity-decrease
  message.  Simple solution: eta-expand.

  It's described in Note [Eta-expand stable unfoldings]
  in GHC.Core.Opt.Simplify

* I also discovered that unsafeCoerce wasn't being inlined if
  the context was boring.  So (\x. f (unsafeCoerce x)) would
  create a thunk -- yikes!  I fixed that by making inlineBoringOK
  a bit cleverer: see Note [Inline unsafeCoerce] in GHC.Core.Unfold.

  I also found that unsafeCoerceName was unused, so I removed it.

I made a test case for #18078, and a very similar one for #17673.

The net effect of all this on nofib is very modest, but positive:

--------------------------------------------------------------------------------
        Program           Size    Allocs   Runtime   Elapsed  TotalMem
--------------------------------------------------------------------------------
           anna          -0.4%     -0.1%     -3.1%     -3.1%      0.0%
 fannkuch-redux          -0.4%     -0.3%     -0.1%     -0.1%      0.0%
       maillist          -0.4%     -0.1%     -7.8%     -1.0%    -14.3%
      primetest          -0.4%    -15.6%     -7.1%     -6.6%      0.0%
--------------------------------------------------------------------------------
            Min          -0.9%    -15.6%    -13.3%    -14.2%    -14.3%
            Max          -0.3%      0.0%    +12.1%    +12.4%      0.0%
 Geometric Mean          -0.4%     -0.2%     -2.3%     -2.2%     -0.1%

All following metric decreases are compile-time allocation decreases
between -1% and -3%:

Metric Decrease:
  T5631
  T13701
  T14697
  T15164
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/32fd37f5e1e6dc6e3b664ae41e0041ed8a19ae21">32fd37f5</a></strong>
<div>
<span>by Luke Lau</span>
<i>at 2020-06-10T04:17:22-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix lookupGlobalOccRn_maybe sometimes reporting an error

In some cases it was possible for lookupGlobalOccRn_maybe to return an
error, when it should be returning a Nothing. If it called
lookupExactOcc_either when there were no matching GlobalRdrElts in the
otherwise case, it would return an error message. This could be caused
when lookupThName_maybe in Template Haskell was looking in different
namespaces (thRdrNameGuesses), guessing different namespaces that the
name wasn't guaranteed to be found in.

However, by addressing this some more accurate errors were being lost in
the conversion to Maybes. So some of the lookup* functions have been
shuffled about so that errors should always be ignored in
lookup*_maybes, and propagated otherwise.

This fixes #18263
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9b283e1b2a46af614d89b0e3a0dfd23871511c17">9b283e1b</a></strong>
<div>
<span>by Roland Senn</span>
<i>at 2020-06-10T04:17:34-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Initialize the allocation counter in GHCi to 0 (Fixes #16012)

According to the documentation for the function `getAllocationCounter` in
[System.Mem](http://hackage.haskell.org/package/base-4.14.0.0/docs/System-Mem.html)
initialize the allocationCounter also in GHCi to 0.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8d07c48ce3fde32a3c08c84764e0859b84eee461">8d07c48c</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-10T04:17:36-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">test: fix conc038

We had spurious failures of conc038 test on CI with stdout:

```
 newThread started
-mainThread
-Haskell: 2
 newThread back again
+mainThread
 1 sec later

 shutting down
+Haskell: 2
```
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4c7e9689f6fcc3eb974f0a76ae8078abda30026d">4c7e9689</a></strong>
<div>
<span>by Sebastian Graf</span>
<i>at 2020-06-11T10:37:38+02:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Release Notes: Add news from the pattern-match checker [skip ci]
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/3445b9652671280920755ee3d2b49780eeb3a991">3445b965</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Only test T16190 with the NCG

T16190 is meant to test a NCG feature. It has already caused spurious
failures in other MRs (e.g. !2165) when LLVM is used.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2517a51c0f949c1021de9f7c16f67345c6ab78a9">2517a51c</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">DynFlags refactoring VIII (#17957)

* Remove several uses of `sdocWithDynFlags`, especially in GHC.Llvm.*

* Add LlvmOpts datatype to store Llvm backend options

* Remove Outputable instances (for LlvmVar, LlvmLit, LlvmStatic and
  Llvm.MetaExpr) which require LlvmOpts.

* Rename ppMetaExpr into ppMetaAnnotExpr (pprMetaExpr is now used in place of `ppr :: MetaExpr -> SDoc`)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7a02599afe836ac32c2e732671415d0afdfbf7fb">7a02599a</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove unused code
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/72d086106d49bc18277f3a066e671e87e9b37a1b">72d08610</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Refactor homeUnit

* rename thisPackage into homeUnit
* document and refactor several Backpack things
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8dc71f5577a541168951371bd55b51a588b57813">8dc71f55</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Rename unsafeGetUnitInfo into unsafeLookupUnit
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/f6be6e432e53108075905c1fc7785d8b1f18a33f">f6be6e43</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add allowVirtualUnits field in PackageState

Instead of always querying DynFlags to know whether we are allowed to
use virtual units (i.e. instantiated on-the-fly, cf Note [About units]
in GHC.Unit), we store it once for all in
`PackageState.allowVirtualUnits`.

This avoids using DynFlags too much (cf #17957) and is preliminary work
for #14335.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e7272d53e67e72580caceae40e766c4bfeb1c398">e7272d53</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Enhance UnitId use

* use UnitId instead of String to identify wired-in units
* use UnitId instead of Unit in the backend (Unit are only use by
  Backpack to produce type-checked interfaces, not real code)
* rename lookup functions for consistency
* documentation
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9c5572cd29924dcc6effd8e102c9bb30d7b39bec">9c5572cd</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove LinkerUnitId type alias
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d345edfe96a3fdf35b8e953c1a4aacc325ca948e">d345edfe</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Refactor WiredMap

* Remove WiredInUnitId and WiredUnitId type aliases
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/3d171cd6d5cfbc8eae12cd1b152541d4f285b245">3d171cd6</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Document and refactor `mkUnit` and `mkUnitInfoMap`
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d2109b4f10ddbe09ac3397486922142f0cadaacc">d2109b4f</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove PreloadUnitId type alias
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/f50c19b8a78da9252cb39f49c1c66db4a684cc3b">f50c19b8</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Rename listUnitInfoMap into listUnitInfo

There is no Map involved
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ed533ec217667423e4fce30040f24053dbcc7de4">ed533ec2</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Rename Package into Unit

The terminology changed over time and now package databases contain
"units" (there can be several units compiled from a single Cabal
package: one per-component, one for each option set, one per
instantiation, etc.). We should try to be consistent internally and use
"units": that's what this renaming does. Maybe one day we'll fix the UI
too (e.g. replace -package-id with -unit-id, we already have
-this-unit-id and ghc-pkg has -unit-id...) but it's not done in this
patch.

* rename getPkgFrameworkOpts into getUnitFrameworkOpts
* rename UnitInfoMap into ClosureUnitInfoMap
* rename InstalledPackageIndex into UnitInfoMap
* rename UnusablePackages into UnusableUnits
* rename PackagePrecedenceIndex into UnitPrecedenceMap
* rename PackageDatabase into UnitDatabase
* rename pkgDatabase into unitDatabases
* rename pkgState into unitState
* rename initPackages into initUnits
* rename renamePackage into renameUnitInfo
* rename UnusablePackageReason into UnusableUnitReason
* rename getPackage* into getUnit*
* etc.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/202728e529f2faa88731b9f4b34b2ac567eb7c95">202728e5</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Make ClosureUnitInfoMap uses UnitInfoMap
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/55b4263e1a53cc27b1da9227249bdcd20139ddc9">55b4263e</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove ClosureUnitInfoMap
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/653d17bdd57ec8ca9b11b19e45860982bd1e7c9e">653d17bd</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Rename Package into Unit (2)

* rename PackageState into UnitState
* rename findWiredInPackages into findWiredInUnits
* rename lookupModuleInAll[Packages,Units]
* etc.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ae900605c4860684c51584dac271956635eb60cc">ae900605</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Move dump_mod_map into initUnits
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/598cc1dde543807902fd502b5e2f8050ebac1fa5">598cc1dd</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Move wiring of homeUnitInstantiations outside of mkUnitState
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/437265eb26b45a2de3ac537b6bc9a81986d4f7ae">437265eb</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Avoid timing module map dump in initUnits
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9400aa934880695b83201e192998de2576cfdf92">9400aa93</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove preload parameter of mkUnitState

* Remove preload parameter (unused)
* Don't explicitly return preloaded units: redundant because already
  returned as "preloadUnits" field of UnitState
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/266bc3d9c3735620598ab18ff6ac9c44134cbbff">266bc3d9</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">DynFlags: refactor unwireUnit
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9e715c1b84702dc60fe31fd19dacf85335d59b27">9e715c1b</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Document getPreloadUnitsAnd
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/bd5810dc4e23331ca4f73ec3b1818c3350b5bbd7">bd5810dc</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">DynFlags: remove useless add_package parameter
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/36e1daf0a604d98a34d9a066a01dd4f5439b4aca">36e1daf0</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">DynFlags: make listVisibleModuleNames take a UnitState
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/5226da37845ae82bff0e3e6b16be7453e3d9370d">5226da37</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Refactor and document add_package
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4b53aac1e2128fa9baa5fd4623fcb3afd2602870">4b53aac1</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Refactor and document closeUnitDeps
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/42c054f6cd7a9890c3e9d2d0c444252abe08a8d5">42c054f6</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">DynFlags: findWiredInUnits
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a444d01bc97be99b7743b752a33ca9982de4c0f1">a444d01b</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">DynFlags: reportCycles, reportUnusable
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8408d521a67e2af4012d886d6a7e2af02ce42add">8408d521</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">DynFlags: merge_databases
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/fca2d25ff76d442d0825847643ed7448492e0e55">fca2d25f</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">DynFlags: add UnitConfig datatype

Avoid directly querying flags from DynFlags to build the UnitState.
Instead go via UnitConfig so that we could reuse this to make another
UnitState for plugins.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4274688a6333abffdfe7c7bda252c566f947afdf">4274688a</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Move distrustAll into mkUnitState
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/28d804e1e12a6be9bcd94b4667e27ba73beade38">28d804e1</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Create helper upd_wired_in_home_instantiations
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ac964c8350ba41082e9dca9cf1b7ff02aea2a636">ac964c83</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Put database cache in UnitConfig
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/bfd0a78cdd0287c26998a4d9419174e4dc305c6f">bfd0a78c</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Don't return preload units when we set DyNFlags

Preload units can be retrieved in UnitState when needed (i.e. in GHCi)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/1fbb4bf5f3d31f115e5a824588efc529cebf3185">1fbb4bf5</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">NCGConfig: remove useless ncgUnitId field
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c10ff7e7e5e5bd687938b5a4256e980cf58fcad1">c10ff7e7</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Doc: fix some comments
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/456e17f035238984e487870fe8007f5fb5f726cf">456e17f0</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Bump haddock submodule and allow metric decrease

Metric Decrease:
    T12150
    T12234
    T5837

Metric Increase:
    T16190
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/429539025450757e30124fa9ee33206deeb951a2">42953902</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Trim the demand for recursive product types

Ticket #18304 showed that we need to be very careful
when exploring the demand (esp usage demand) on recursive
product types.

This patch solves the problem by trimming the demand on such types --
in effect, a form of "widening".

See the Note [Trimming a demand to a type] in DmdAnal, which explains
how I did this by piggy-backing on an existing mechansim for trimming
demands becuase of GADTs.  The significant payload of this patch is
very small indeed:

* Make GHC.Core.Opt.WorkWrap.Utils.typeShape use RecTcChecker to
  avoid looking through recursive types.

But on the way

* I found that ae_rec_tc was entirely inoperative and did nothing.
  So I removed it altogether from DmdAnal.

* I moved some code around in DmdAnal and Demand.
  (There are no actual changes in dmdFix.)

* I changed the API of DmsAnal.dmdAnalRhsLetDown to return
  a StrictSig rather than a decorated Id

* I removed the dead function peelTsFuns from Demand

Performance effects:

Nofib: 0.0% changes.  Not surprising, because they don't
       use recursive products

Perf tests

T12227:
  1% increase in compiler allocation, becuase $cto gets w/w'd.
  It did not w/w before because it takes a deeply nested
  argument, so the worker gets too many args, so we abandon w/w
  altogether (see GHC.Core.Opt.WorkWrap.Utils.isWorkerSmallEnough)

  With this patch we trim the demands.  That is not strictly
  necessary (since these Generic type constructors are like
  tuples -- they can't cause a loop) but the net result is that
  we now w/w $cto which is fine.

UniqLoop:
  16% decrease in /runtime/ allocation. The UniqSupply is a
  recursive product, so currently we abandon all strictness on
  'churn'.  With this patch 'churn' gets useful strictness, and
  we w/w it.  Hooray

Metric Decrease:
    UniqLoop

Metric Increase:
    T12227
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/87d504f475471c61305b29578da2656f9ff9653e">87d504f4</a></strong>
<div>
<span>by Viktor Dukhovni</span>
<i>at 2020-06-13T02:13:05-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add introductory prose for Data.Traversable
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9f09b608eecf07ad6c27729f7b6f74aca4e17e6c">9f09b608</a></strong>
<div>
<span>by Oleg Grenrus</span>
<i>at 2020-06-13T02:13:07-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix #12073: Add MonadFix Q instance
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/220c2d34a34727d696cc4b44a1b87aba83231ce4">220c2d34</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-06-13T02:13:07-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite: Increase size of T12150

As noted in #18319, this test was previously very fragile. Increase its
size to make it more likely that its fails with its newly-increased
acceptance threshold.

Metric Increase:
    T12150
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8bba1c26193e704d2d6bb2be9a2fac668b0ea54c">8bba1c26</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-06-13T04:59:06-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">gitlab-ci: Always push perf notes

Previously we ci.sh would run with `set -e` implying that we wouldn't
push perf notes if the testsuite were to fail, even if it *only* failed
due to perf notes. This rendered the whole performance testing story
quite fragile as a single regressing commit would cause every successive
commit to fail since a new baseline would not be uploaded.

Fix this by ensuring that we always push performance notes.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7a773f169cfe072c7b29924c53075e4dfa4e2adb">7a773f16</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-06-13T15:10:55-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">gitlab-ci: Eliminate redundant push of CI metrics
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a31218f7737a65b6333ec7905e88dc094703f025">a31218f7</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-06-13T15:58:37-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Use HsForAllTelescope to avoid inferred, visible foralls

Currently, `HsForAllTy` permits the combination of `ForallVis` and
`Inferred`, but you can't actually typecheck code that uses it
(e.g., `forall {a} ->`). This patch refactors `HsForAllTy` to use a
new `HsForAllTelescope` data type that makes a type-level distinction
between visible and invisible `forall`s such that visible `forall`s
do not track `Specificity`. That part of the patch is actually quite
small; the rest is simply changing consumers of `HsType` to
accommodate this new type.

Fixes #18235. Bumps the `haddock` submodule.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c0e6dee99242eff08420176a36d77b715972f1f2">c0e6dee9</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-06-14T09:07:44-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Add Atomic Exchange PrimOp and implement Atomic Ptr exchanges.

The initial version was rewritten by Tamar Christina.
It was rewritten in large parts by Andreas Klebinger.

Co-authored-by: Andreas Klebinger <klebinger.andreas@gmx.at>
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9a7462fb6b8bdd6326a607bbd7b9453eb588193b">9a7462fb</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-06-14T15:35:23-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">codeGen: Don't discard live case binders in unsafeEqualityProof logic

Previously CoreToStg would unconditionally discard cases of the form:

    case unsafeEqualityProof of wild { _ -> rhs }

and rather replace the whole thing with `rhs`. However, in some cases
(see #18227) the case binder is still live, resulting in unbound
occurrences in `rhs`. Fix this by only discarding the case if the case
binder is dead.

Fixes #18227.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e4137c486a3df66b49395beea7efc6e200cc9bac">e4137c48</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-06-14T15:35:23-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite: Add tests for #18227

T18227A is the original issue which gave rise to the ticket and depends
upon bytestring. T18227B is a minimized reproducer.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8bab9ff1e09c1566a4105146bd636634a24928b9">8bab9ff1</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-06-14T15:35:59-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">hadrian: Fix rts include and library paths

Fixes two bugs:

 * (?) and (<>) associated in a surprising way
 * We neglected to include libdw paths in the rts configure flags
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/bd761185561747fe0b3adc22602f75d7b50cd248">bd761185</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-06-14T15:35:59-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">hadrian: Drop redundant GHC arguments

Cabal should already be passing this arguments to GHC.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/01f7052cc182c0ced85522dc775ebc490bf094ce">01f7052c</a></strong>
<div>
<span>by Peter Trommler</span>
<i>at 2020-06-14T15:36:38-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">FFI: Fix pass small ints in foreign call wrappers

The Haskell calling convention requires integer parameters smaller
than wordsize to be promoted to wordsize (where the upper bits are
don't care). To access such small integer parameter read a word from
the parameter array and then cast that word to the small integer
target type.

Fixes #15933
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/502647f7583be626319482adf4ea3d905db0006d">502647f7</a></strong>
<div>
<span>by Krzysztof Gogolewski</span>
<i>at 2020-06-14T15:37:14-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix "ndecreasingIndentation" in manual (#18116)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9a9cc0897b676ffd6612562a46600ea98c53a58d">9a9cc089</a></strong>
<div>
<span>by Simon Jakobi</span>
<i>at 2020-06-15T13:10:00-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Use foldl' in unionManyUniqDSets
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/761dcb84cd4c50c6fbb361eb26fb429af87392a3">761dcb84</a></strong>
<div>
<span>by Moritz Angermann</span>
<i>at 2020-06-15T13:10:36-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Load .lo as well.

Some archives contain so called linker objects, with the affectionate
.lo suffic.  For example the musl libc.a will come in that form.  We
still want to load those objects, hence we should not discard them and
look for .lo as well.  Ultimately we might want to fix this proerly by
looking at the file magic.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/cf01477f03da13caaf78caacc5b001cb46a86685">cf01477f</a></strong>
<div>
<span>by Vladislav Zavialov</span>
<i>at 2020-06-15T13:11:20-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">User's Guide: KnownNat evidence is Natural

This bit of documentation got outdated after commit
1fcede43d2b30f33b7505e25eb6b1f321be0407f
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d0dcbfe646e52d0a1ef6d6e59a059323485775eb">d0dcbfe6</a></strong>
<div>
<span>by Jan Hrček</span>
<i>at 2020-06-16T20:36:38+02:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix typos and formatting in user guide
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/56a9e95fd6c2f213d676c9a2bd0a6cf93c531dbb">56a9e95f</a></strong>
<div>
<span>by Jan Hrček</span>
<i>at 2020-06-16T20:36:38+02:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Resolve TODO
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/3e884d14102948ad49d75611da247beff25911a4">3e884d14</a></strong>
<div>
<span>by Jan Hrček</span>
<i>at 2020-06-16T20:36:38+02:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Rename TcHoleErrors to GHC.Tc.Errors.Hole
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d23fc67847a27222ad8a0c193e6a10b5a4c0cf48">d23fc678</a></strong>
<div>
<span>by Stefan Schulze Frielinghaus</span>
<i>at 2020-06-17T15:31:09-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">hadrian: Build with threaded runtime if available

See #16873.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/0639dc10e214280a90dd6b75ce86cf43d1eb2286">0639dc10</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-17T15:31:53-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">T16190: only measure bytes_allocated

Just adding `{-# LANGUAGE BangPatterns #-}` makes the two other metrics
fluctuate by 13%.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4cab68974dba3e674016514c939946ce60e58273">4cab6897</a></strong>
<div>
<span>by Adam Sandberg Ericsson</span>
<i>at 2020-06-17T15:32:44-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">docs: fix formatting in users guide
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/eb8115a8c4cbc842b66798480fefc7ab64d31931">eb8115a8</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-17T15:33:23-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Move CLabel assertions into smart constructors (#17957)

It avoids using DynFlags in the Outputable instance of Clabel to check
assertions at pretty-printing time.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7faa4509cd7dbc6e2f873e4997e8888bd6ec3507">7faa4509</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-06-17T15:43:31-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">base: Bump to 4.15.0.0
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/20616959a7f4821034e14a64c3c9bf288c9bc956">20616959</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-06-17T15:43:31-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">configure: Use grep -q instead of --quiet

The latter is apparently not supported by busybox.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/40fa237e1daab7a76b9871bb6c50b953a1addf23">40fa237e</a></strong>
<div>
<span>by Krzysztof Gogolewski</span>
<i>at 2020-06-17T16:21:58-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Linear types (#15981)

This is the first step towards implementation of the linear types proposal
(https://github.com/ghc-proposals/ghc-proposals/pull/111).

It features

* A language extension -XLinearTypes
* Syntax for linear functions in the surface language
* Linearity checking in Core Lint, enabled with -dlinear-core-lint
* Core-to-core passes are mostly compatible with linearity
* Fields in a data type can be linear or unrestricted; linear fields
  have multiplicity-polymorphic constructors.
  If -XLinearTypes is disabled, the GADT syntax defaults to linear fields

The following items are not yet supported:

* a # m -> b syntax (only prefix FUN is supported for now)
* Full multiplicity inference (multiplicities are really only checked)
* Decent linearity error messages
* Linear let, where, and case expressions in the surface language
  (each of these currently introduce the unrestricted variant)
* Multiplicity-parametric fields
* Syntax for annotating lambda-bound or let-bound with a multiplicity
* Syntax for non-linear/multiple-field-multiplicity records
* Linear projections for records with a single linear field
* Linear pattern synonyms
* Multiplicity coercions (test LinearPolyType)

A high-level description can be found at
https://ghc.haskell.org/trac/ghc/wiki/LinearTypes/Implementation
Following the link above you will find a description of the changes made to Core.
This commit has been authored by

* Richard Eisenberg
* Krzysztof Gogolewski
* Matthew Pickering
* Arnaud Spiwack

With contributions from:

* Mark Barbone
* Alexander Vershilov

Updates haddock submodule.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6cb84c469bf1ab6b03e099f5d100e78800ca09e0">6cb84c46</a></strong>
<div>
<span>by Krzysztof Gogolewski</span>
<i>at 2020-06-17T16:22:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Various performance improvements

This implements several general performance improvements to GHC,
to offset the effect of the linear types change.

General optimisations:
- Add a `coreFullView` function which iterates `coreView` on the
  head. This avoids making function recursive solely because the
  iterate `coreView` themselves. As a consequence, this functions can
  be inlined, and trigger case-of-known constructor (_e.g._
  `kindRep_maybe`, `isLiftedRuntimeRep`, `isMultiplicityTy`,
  `getTyVar_maybe`, `splitAppTy_maybe`, `splitFunType_maybe`,
  `tyConAppTyCon_maybe`). The common pattern about all these functions
  is that they are almost always used as views, and immediately
  consumed by a case expression. This commit also mark them asx `INLINE`.
- In `subst_ty` add a special case for nullary `TyConApp`, which avoid
  allocations altogether.
- Use `mkTyConApp` in `subst_ty` for the general `TyConApp`. This
  required quite a bit of module shuffling.
  case. `myTyConApp` enforces crucial sharing, which was lost during
  substitution. See also !2952 .
- Make `subst_ty` stricter.
- In `eqType` (specifically, in `nonDetCmpType`), add a special case,
  tested first, for the very common case of nullary `TyConApp`.
  `nonDetCmpType` has been made `INLINE` otherwise it is actually a
  regression. This is similar to the optimisations in !2952.

Linear-type specific optimisations:
- Use `tyConAppTyCon_maybe` instead of the more complex `eqType` in
  the definition of the pattern synonyms `One` and `Many`.
- Break the `hs-boot` cycles between `Multiplicity.hs` and `Type.hs`:
  `Multiplicity` now import `Type` normally, rather than from the
  `hs-boot`. This way `tyConAppTyCon_maybe` can inline properly in the
  `One` and `Many` pattern synonyms.
- Make `updateIdTypeAndMult` strict in its type and multiplicity
- The `scaleIdBy` gets a specialised definition rather than being an
  alias to `scaleVarBy`
- `splitFunTy_maybe` is given the type `Type -> Maybe (Mult, Type,
  Type)` instead of `Type -> Maybe (Scaled Type, Type)`
- Remove the `MultMul` pattern synonym in favour of a view `isMultMul`
  because pattern synonyms appear not to inline well.
- in `eqType`, in a `FunTy`, compare multiplicities last: they are
  almost always both `Many`, so it helps failing faster.
- Cache `manyDataConTy` in `mkTyConApp`, to make sure that all the
  instances of `TyConApp ManyDataConTy []` are physically the same.

This commit has been authored by
* Richard Eisenberg
* Krzysztof Gogolewski
* Arnaud Spiwack

Metric Decrease:
    haddock.base
    T12227
    T12545
    T12990
    T1969
    T3064
    T5030
    T9872b

Metric Increase:
    haddock.base
    haddock.Cabal
    haddock.compiler
    T12150
    T12234
    T12425
    T12707
    T13035
    T13056
    T15164
    T16190
    T18304
    T1969
    T3064
    T3294
    T5631
    T5642
    T5837
    T6048
    T9020
    T9233
    T9675
    T9872a
    T9961
    WWRec
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/57db91d8ee501c7cf176c4bb1e2101d3092fd0f6">57db91d8</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-17T16:22:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove integer-simple

integer-simple uses lists of words (`[Word]`) to represent big numbers
instead of ByteArray#:

   * it is less efficient than the newer ghc-bignum native backend

   * it isn't compatible with the big number representation that is now
     shared by all the ghc-bignum backends (based on the one that was
     used only in integer-gmp before).

As a consequence, we simply drop integer-simple
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9f96bc127d6231b5e76bbab442244eb303b08867">9f96bc12</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-17T16:22:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">ghc-bignum library

ghc-bignum is a newer package that aims to replace the legacy
integer-simple and integer-gmp packages.

* it supports several backends. In particular GMP is still supported and
  most of the code from integer-gmp has been merged in the "gmp"
  backend.

* the pure Haskell "native" backend is new and is much faster than the
  previous pure Haskell implementation provided by integer-simple

* new backends are easier to write because they only have to provide a
  few well defined functions. All the other code is common to all
  backends. In particular they all share the efficient small/big number
  distinction previously used only in integer-gmp.

* backends can all be tested against the "native" backend with a simple
  Cabal flag. Backends are only allowed to differ in performance, their
  results should be the same.

* Add `integer-gmp` compat package: provide some pattern synonyms and
  function aliases for those in `ghc-bignum`. It is intended to avoid
  breaking packages that depend on `integer-gmp` internals.

Update submodules: text, bytestring

Metric Decrease:
    Conversions
    ManyAlternatives
    ManyConstructors
    Naperian
    T10359
    T10547
    T10678
    T12150
    T12227
    T12234
    T12425
    T13035
    T13719
    T14936
    T1969
    T4801
    T4830
    T5237
    T5549
    T5837
    T8766
    T9020
    parsing001
    space_leak_001
    T16190
    haddock.base

On ARM and i386, T17499 regresses (+6% > 5%).
On x86_64 unregistered, T13701 sometimes regresses (+2.2% > 2%).

Metric Increase:
    T17499
    T13701
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/96aa57878fd6e6a7b92e841a0df8b5255a559c97">96aa5787</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-17T16:22:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Update compiler

Thanks to ghc-bignum, the compiler can be simplified:

* Types and constructors of Integer and Natural can be wired-in. It
  means that we don't have to query them from interfaces. It also means
  that numeric literals don't have to carry their type with them.

* The same code is used whatever ghc-bignum backend is enabled. In
  particular, conversion of bignum literals into final Core expressions
  is now much more straightforward. Bignum closure inspection too.

* GHC itself doesn't depend on any integer-* package anymore

* The `integerLibrary` setting is gone.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/0f67e3447e5a0089b5348940d404ed876fddddfc">0f67e344</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-17T16:22:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Update `base` package

* GHC.Natural isn't implemented in `base` anymore. It is provided by
  ghc-bignum in GHC.Num.Natural. It means that we can safely use Natural
  primitives in `base` without fearing issues with built-in rewrite
  rules (cf #15286)

* `base` doesn't conditionally depend on an integer-* package anymore,
  it depends on ghc-bignum

* Some duplicated code in integer-* can now be factored in GHC.Float

* ghc-bignum tries to use a uniform naming convention so most of the
  other changes are renaming
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/aa9e7b7196f03f84579e3b4a09068c668cbe6ffb">aa9e7b71</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-17T16:22:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Update `make` based build system

* replace integer-* package selection with ghc-bignum backend selection
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/f817d816e60a487bca64037095c01e9956225b64">f817d816</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-17T16:22:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Update testsuite

* support detection of slow ghc-bignum backend (to replace the detection
  of integer-simple use). There are still some test cases that the
  native backend doesn't handle efficiently enough.

* remove tests for GMP only functions that have been removed from
  ghc-bignum

* fix test results showing dependent packages (e.g. integer-gmp) or
  showing suggested instances

* fix test using Integer/Natural API or showing internal names
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/dceecb093c3ee1e4dc970bb6669ff855ec37f6ac">dceecb09</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-17T16:22:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Update Hadrian

* support ghc-bignum backend selection in flavours and command-line

* support ghc-bignum "--check" flag (compare results of selected backend
  against results of the native one) in flavours and command-line (e.g.
  pass --bignum=check-gmp" to check the "gmp" backend)

* remove the hack to workaround #15286

* build GMP only when the gmp backend is used

* remove hacks to workaround `text` package flags about integer-*. We
  fix `text` to use ghc-bignum unconditionally in another patch
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/fa4281d672e462b8421098b3506bd3c4c6a1f819">fa4281d6</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-17T16:22:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Bump bytestring and text submodules
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/1a3f6f348004a80d3d7add81b22e4217b648b145">1a3f6f34</a></strong>
<div>
<span>by Adam Sandberg Ericsson</span>
<i>at 2020-06-18T23:03:36-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">docs: mention -hiedir in docs for -outputdir

[skip ci]
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/729bcb02716593ae46d7baecce4776b3f353e3f7">729bcb02</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-18T23:04:17-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Hadrian: fix build on Mac OS Catalina (#17798)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/95e18292731cd799e024976f11c18fdf34bcb777">95e18292</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-06-18T23:04:58-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Relax allocation threshold for T12150.

This test performs little work, so the most minor allocation
changes often cause the test to fail.

Increasing the threshold to 2% should help with this.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8ce6c393888fad5d52dfe0bff9b72cd1cf9facc0">8ce6c393</a></strong>
<div>
<span>by Sebastian Graf</span>
<i>at 2020-06-18T23:05:36-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">hadrian: Bump pinned cabal.project to an existent index-state
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/08c1cb0f30770acbf366423f085f8ef92f7f6a06">08c1cb0f</a></strong>
<div>
<span>by Ömer Sinan Ağacan</span>
<i>at 2020-06-18T23:06:21-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix uninitialized field read in Linker.c

Valgrind report of the bug when running the test `linker_unload`:

    ==29666== Conditional jump or move depends on uninitialised value(s)
    ==29666==    at 0x369C5B4: setOcInitialStatus (Linker.c:1305)
    ==29666==    by 0x369C6C5: mkOc (Linker.c:1347)
    ==29666==    by 0x36C027A: loadArchive_ (LoadArchive.c:522)
    ==29666==    by 0x36C0600: loadArchive (LoadArchive.c:626)
    ==29666==    by 0x2C144CD: ??? (in /home/omer/haskell/ghc_2/testsuite/tests/rts/linker/linker_unload.run/linker_unload)
    ==29666==
    ==29666== Conditional jump or move depends on uninitialised value(s)
    ==29666==    at 0x369C5B4: setOcInitialStatus (Linker.c:1305)
    ==29666==    by 0x369C6C5: mkOc (Linker.c:1347)
    ==29666==    by 0x369C9F6: preloadObjectFile (Linker.c:1507)
    ==29666==    by 0x369CA8D: loadObj_ (Linker.c:1536)
    ==29666==    by 0x369CB17: loadObj (Linker.c:1557)
    ==29666==    by 0x3866BC: main (linker_unload.c:33)

The problem is `mkOc` allocates a new `ObjectCode` and calls
`setOcInitialStatus` without initializing the `status` field.
`setOcInitialStatus` reads the field as first thing:

    static void setOcInitialStatus(ObjectCode* oc) {
        if (oc->status == OBJECT_DONT_RESOLVE)
          return;

        if (oc->archiveMemberName == NULL) {
            oc->status = OBJECT_NEEDED;
        } else {
            oc->status = OBJECT_LOADED;
        }
    }

`setOcInitialStatus` is unsed in two places for two different purposes:
in `mkOc` where we don't have the `status` field initialized yet (`mkOc`
is supposed to initialize it), and `loadOc` where we do have `status`
field initialized and we want to update it. Instead of splitting the
function into two functions which are both called just once I inline the
functions in the use sites and remove it.

Fixes #18342
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/da18ff9935e72c7fe6127cb5d5d0c53654a204b0">da18ff99</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-06-18T23:07:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">fix windows bootstrap due to linker changes
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2af0ec9059b94e1fa6b37eda60216e0222e1a53d">2af0ec90</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-18T23:07:47-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">DynFlags: store default depth in SDocContext (#17957)

It avoids having to use DynFlags to reach for pprUserLength.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d4a0be758003f32b9d9d89cfd14b9839ac002f4d">d4a0be75</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-18T23:08:35-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Move tablesNextToCode field into Platform

tablesNextToCode is a platform setting and doesn't belong into DynFlags
(#17957). Doing this is also a prerequisite to fix #14335 where we deal
with two platforms (target and host) that may have different platform
settings.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c2237329e68c67e3eacc240d03dfb41f2fcd44eb">c2237329</a></strong>
<div>
<span>by Vladislav Zavialov</span>
<i>at 2020-06-21T22:06:03+03:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Accumulate Haddock comments in P (#17544, #17561)

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).

Metric Increase:
    T13719
    ManyConstructors
    haddock.Cabal
    haddock.base
    haddock.compiler
</pre>
</li>
</ul>
<h4>27 changed files:</h4>
<ul>
<li class="file-stats">
<a href="#70f0e3f682e0543f692942cb7bafd17134d6b88b">
<span class="new-file">
+
.git-ignore-revs
</span>
</a>
</li>
<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="#b25b374c2459de3e2aaed42163f492c8b8614385">
.gitlab/merge_request_templates/merge-request.md
</a>
</li>
<li class="file-stats">
<a href="#7445606fbf8f3683cd42bdc54b05d7a0bc2dfc44">
.gitmodules
</a>
</li>
<li class="file-stats">
<a href="#abe895765c4ce08c5dfbc95e5e3c5db67ff92ded">
CODEOWNERS
</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/prelude/PrelNames.hs

compiler/GHC/Builtin/Names.hs
</a>
</li>
<li class="file-stats">
<a href="#06764eb0158306b83ab1998d18316392a51838c2">
compiler/prelude/THNames.hs

compiler/GHC/Builtin/Names/TH.hs
</a>
</li>
<li class="file-stats">
<a href="#a1519b7fe8a0d4b42e4aaa927fb6ab5b5da0fcdd">
compiler/prelude/PrimOp.hs

compiler/GHC/Builtin/PrimOps.hs
</a>
</li>
<li class="file-stats">
<a href="#dc9d549002b8cd260ee6d1d2fb35877c74412f91">
<span class="new-file">
+
compiler/GHC/Builtin/PrimOps.hs-boot
</span>
</a>
</li>
<li class="file-stats">
<a href="#377cfd14c1f92357465df995ec6537b074051322">
compiler/prelude/TysWiredIn.hs

compiler/GHC/Builtin/Types.hs
</a>
</li>
<li class="file-stats">
<a href="#be7a5c9dc04ecfe7bedb2a2afcc2a51be6719577">
compiler/prelude/TysWiredIn.hs-boot

compiler/GHC/Builtin/Types.hs-boot
</a>
</li>
<li class="file-stats">
<a href="#02362b473a022fb921814e97a6beba08107d38b1">
compiler/typecheck/TcTypeNats.hs

compiler/GHC/Builtin/Types/Literals.hs
</a>
</li>
<li class="file-stats">
<a href="#8a5cd068459120cddf3814e7b9e02003b87647ba">
compiler/prelude/TysPrim.hs

compiler/GHC/Builtin/Types/Prim.hs
</a>
</li>
<li class="file-stats">
<a href="#8dc7109003a77f8a82e987dc1de31466aa956174">
compiler/prelude/KnownUniques.hs

compiler/GHC/Builtin/Uniques.hs
</a>
</li>
<li class="file-stats">
<a href="#6bcb866fdb5388db4ecc395e443a3af4888d9dd5">
compiler/prelude/KnownUniques.hs-boot

compiler/GHC/Builtin/Uniques.hs-boot
</a>
</li>
<li class="file-stats">
<a href="#d95fdf6575459444666f72b2281534e0558a4ba0">
compiler/prelude/PrelInfo.hs

compiler/GHC/Builtin/Utils.hs
</a>
</li>
<li class="file-stats">
<a href="#451725cc4e5d443a3b7c2adcdf224840f953b7e2">
compiler/prelude/primops.txt.pp

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="#073b107caa98ea426694eacd6c08b492801a51a0">
compiler/GHC/ByteCode/Instr.hs
</a>
</li>
<li class="file-stats">
<a href="#11e6f6a348be9920cecad0893a25350137524b4f">
compiler/GHC/ByteCode/Linker.hs
</a>
</li>
<li class="file-stats">
<a href="#5c66928780aaad0eb5888511dc4b0b08492c69fa">
compiler/GHC/ByteCode/Types.hs
</a>
</li>
<li class="file-stats">
<a href="#f73a4fa90a8eb153bccdcfcc9f63c15edcd66785">
compiler/GHC/Cmm.hs
</a>
</li>
<li class="file-stats">
<a href="#2635960270885615c76f7437d2eb6c5bd6082895">
compiler/GHC/Cmm/BlockId.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/b204b5b404a26b794f9ff9893463bd2f95b1b811...c2237329e68c67e3eacc240d03dfb41f2fcd44eb">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>