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



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

<h3>
Andreas Klebinger pushed to branch wip/andreask/strict_dicts
at <a href="https://gitlab.haskell.org/ghc/ghc">Glasgow Haskell Compiler / GHC</a>
</h3>
<h4>
Commits:
</h4>
<ul>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/30caeee75193ea961c55ee847a3156e23116e84e">30caeee7</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-07-21T06:39:33-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">DynFlags: remove use of sdocWithDynFlags from GHC.Stg.* (#17957)

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

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

There are three problems with the current API:

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

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

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

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

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

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

   ::

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

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

      type Env = MapF Ident (Code Q)

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

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

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

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

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

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

This patch implements the following:

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

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

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

There are multiple reasons we want this:

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

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

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

Metric Increase:
    ManyConstructors

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

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

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

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

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

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

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

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

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

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

Metric Decrease:
    T3064

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Fixes #17587 and #18408

Updates haddock submodule

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

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

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

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

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

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

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

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

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

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

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

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

We achieve this by the following requirement:

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Specific changes

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

There are a number of other small changes

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

This patch primarily:

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

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

Along the way, I performed some various cleanup:

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

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

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

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

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

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

Addresses (somewhat) #18502

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

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

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

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

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

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

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

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

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

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

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

Fixes #18070

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

        tyapps
          : tyapp
          | tyapps tyapp

        tyapp
          : atype
          | PREFIX_AT atype
          | tyop
          | unpackedness

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

This is due to a syntactic ambiguity:

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

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

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

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

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

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

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

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

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

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

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

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

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

        infixtype
          : ftype
          | ftype tyop infixtype
          | unpackedness infixtype

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

        tyarg
          : atype
          | unpackedness atype

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

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

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

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

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

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

Close #18534.

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

GHC 8.12.1 has been renamed to GHC 9.0.1.

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

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

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

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

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

Remove unused ApiAnns, add one for linear arrow.

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

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

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

And prefix ~

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

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

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

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

Also fix its slightly wrong comment

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

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

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

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

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

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

One step closer making Outputable fully independent of DynFlags.

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

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

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

The note has been rewritten by @simonpj in !3851

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

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

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

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

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

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

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

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

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

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

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

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

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

Additionally on other CIs:

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    f !() = 0

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

This is wrong for several reasons:

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

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

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

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

Fix #18124.

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

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

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

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

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

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

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

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

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

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

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

Previously we would produce a rather unhelpful pattern match failure
error in the case where the user called `getSystemTimerManager` in a
program which isn't built with `-threaded`. This understandably confused
the user in #15616.

Fixes #15616.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/f6d70a8ff6a6cd628738fec902fc984936105264">f6d70a8f</a></strong>
<div>
<span>by Roland Senn</span>
<i>at 2020-08-31T22:59:50-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add tests for #15617.

Avoid a similar regression in the future.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e5969fd06ad4b4c31a8bdce51d35f9aa05594b49">e5969fd0</a></strong>
<div>
<span>by Roland Senn</span>
<i>at 2020-08-31T23:00:27-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add additional tests for #18172 (Followup MR 3543)

There was still one active discussion [thread](https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3543#note_284325) when MR !3543 got merged.

This MR adds the requested tests exercising the changes in
`compiler/GHC/HsToCore/Match/Literal.hs:warnAboutEmptyEnumerations` and its sub-functions.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/fe18b4825c3289089a65b7b16b25e9d216a5b0fd">fe18b482</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-08-31T23:01:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Bump Win32 and process submodules
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2da933084b766fc424b11f5b671574d4c7317134">2da93308</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-08-31T23:01:39-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Hadrian: fix slow-validate flavour (#18586)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/85e13008fb9a319c0b79db7c626f37bf20731beb">85e13008</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-08-31T23:02:15-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Update dominator code with fixes from the dom-lt package.

Two bugs turned out in the package that have been fixed since.
This MR includes this fixes in the GHC port of the code.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/dffb38fab00ac1cd1cbc75156abcf373976581f7">dffb38fa</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-08-31T23:02:15-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Dominators.hs: Use unix line endings
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6189cc04ca6c3d79126744e988b487f75ccef9e2">6189cc04</a></strong>
<div>
<span>by Moritz Angermann</span>
<i>at 2020-08-31T23:02:50-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">[fixup 3433] move debugBelch into IF_DEBUG(linker)

The commit in dff1cb3d9c111808fec60190747272b973547c52 incorrectly left
the `debugBelch` function without a comment or IF_DEBUG(linker,)
decoration. This rectifies it.

Needs at least a 8.10 backport, as it was backported in 6471cc6aff80d5deebbdb1bf7b677b31ed2af3d5
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/bcb68a3f7f85b9fdef6f4845e608d086b01e6a58">bcb68a3f</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-08-31T23:03:27-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Don't store HomeUnit in UnitConfig

Allow the creation of a UnitConfig (hence of a UnitState) without having
a HomeUnit. It's required for #14335.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/0a3723876c6c79a0a407d50f4baa2818a13f232e">0a372387</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-08-31T23:04:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix documentation and fix "check" bignum backend (#18604)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/eb85f125a227f6b5703d4a2e997c5ea320dfa31f">eb85f125</a></strong>
<div>
<span>by Moritz Angermann</span>
<i>at 2020-08-31T23:04:39-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Set the dynamic-system-linker flag to Manual

This flag should be user controllable, hence Manual: True.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/380ef84587fb6890d100c338d1992a6994a4f02a">380ef845</a></strong>
<div>
<span>by Sven Tennie</span>
<i>at 2020-08-31T23:05:14-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Ignore more files

Ignore files from "new style" cabal builds (dist-newstyle folders) and
from clangd (C language server).
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/74a7fbff5a8f244cd44345bf987e26413bb1989e">74a7fbff</a></strong>
<div>
<span>by Takenobu Tani</span>
<i>at 2020-08-31T23:05:51-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Limit upper version of Happy for ghc-9.0 and earlier (#18620)

This patch adds the upper bound of a happy version for ghc-9.0
and earlier.

Currently, we can't use happy-1.20.0 for ghc-9.0.

See #18620.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a4473f02ae2e685601e257b8668bea2ec721b294">a4473f02</a></strong>
<div>
<span>by Takenobu Tani</span>
<i>at 2020-08-31T23:05:51-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Limit upper version of Happy for ghc-9.2 (#18620)

This patch adds the upper bound of a happy version for ghc-9.2.

Currently, We can use happy-1.19 or happy-1.20 for ghc-9.2.

See #18620.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a8a2568b7b64e5b9fca5b12df7da759de4db39ae">a8a2568b</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-08-31T23:06:28-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Bignum: add BigNat compat functions (#18613)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/884245dd29265b7bee12cda8c915da9c916251ce">884245dd</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-09-01T12:39:36-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix FastString lexicographic ordering (fix #18562)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4b4fbc58d37d37457144014ef82bdd928de175df">4b4fbc58</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-09-01T12:39:36-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove "Ord FastString" instance

FastStrings can be compared in 2 ways: by Unique or lexically. We don't
want to bless one particular way with an "Ord" instance because it leads
to bugs (#18562) or to suboptimal code (e.g. using lexical comparison
while a Unique comparison would suffice).

UTF-8 encoding has the advantage that sorting strings by their encoded
bytes also sorts them by their Unicode code points, without having to
decode the actual code points. BUT GHC uses Modified UTF-8 which
diverges from UTF-8 by encoding \0 as 0xC080 instead of 0x00 (to avoid
null bytes in the middle of a String so that the string can still be
null-terminated). This patch adds a new `utf8CompareShortByteString`
function that performs sorting by bytes but that also takes Modified
UTF-8 into account. It is much more performant than decoding the strings
into [Char] to perform comparisons (which we did in the previous patch).

Bump haddock submodule
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b4edcde70160820dd23c53d9019f895930e2c0e7">b4edcde7</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-09-01T14:53:42-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite: Add broken test for #18302
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/bfab2a30be5cc68e7914c3f6bb9ae4ad33283ffc">bfab2a30</a></strong>
<div>
<span>by Sebastian Graf</span>
<i>at 2020-09-02T15:54:55-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Turn on -XMonoLocalBinds by default (#18430)

And fix the resulting type errors.

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

Metric Decrease:
    parsing001
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c30cc0e9c3704b24ad0f6d9a0199bf8b5835bd40">c30cc0e9</a></strong>
<div>
<span>by David Feuer</span>
<i>at 2020-09-02T15:55:31-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove potential space leak from Data.List.transpose

Previously, `transpose` produced a list of heads
and a list of tails independently. This meant that
a function using only some heads, and only some tails,
could potentially leak space. Use `unzip` to work
around the problem by producing pairs and selector
thunks instead. Time and allocation behavior will
be worse, but there should be no more leak potential.</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ffc3da474bd6febf8a120ebd432ad69f92fe03e0">ffc3da47</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-09-02T15:56:11-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove outdated note
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/85e621234916e9b5d40174831a3b422bd99f8f83">85e62123</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-09-02T15:56:48-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Bignum: add missing compat import/export functions
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/397c2b03e90e74c94ff55849adb6aa2a84e3e783">397c2b03</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-09-03T17:31:47-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">configure: Work around Raspbian's silly packaging decisions

See #17856.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4891c18a49876958b44e50dc6e2f24326d92052f">4891c18a</a></strong>
<div>
<span>by Kathryn Spiers</span>
<i>at 2020-09-03T17:32:24-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">expected-undocumented-flags remove kill flags

It looks like the flags were removed in https://gitlab.haskell.org/ghc/ghc/-/commit/3e27205a66b06a4501d87eb31e285eadbc693eb7
and can safely be removed here</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/1d6d648866da9e7754859c48235f8009b8c130fd">1d6d6488</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-09-04T16:24:20-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Don't rely on CLabel's Outputable instance in CmmToC

This is in preparation of the removal of sdocWithDynFlags (#10143),
hence of the refactoring of CLabel's Outputable instance.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/89ce7cdf977304cb7d0f325a013f822600c1bfbf">89ce7cdf</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-09-04T16:24:59-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">DynFlags: use Platform in foldRegs*
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/220ad8d67af345cf3decf82ff26c1e696d21ac93">220ad8d6</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-09-04T16:24:59-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">DynFlags: don't pass DynFlags to cmmImplementSwitchPlans
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c1e54439be3d38a1f972ac772cca7eec5e1519a9">c1e54439</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-09-04T16:25:35-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Introduce isBoxedTupleDataCon and use it to fix #18644

The code that converts promoted tuple data constructors to
`IfaceType`s in `GHC.CoreToIface` was using `isTupleDataCon`, which
conflates boxed and unboxed tuple data constructors. To avoid this,
this patch introduces `isBoxedTupleDataCon`, which is like
`isTupleDataCon` but only works for _boxed_ tuple data constructors.

While I was in town, I was horribly confused by the fact that there
were separate functions named `isUnboxedTupleCon` and
`isUnboxedTupleTyCon` (similarly, `isUnboxedSumCon` and
`isUnboxedSumTyCon`). It turns out that the former only works for
data constructors, despite its very general name! I opted to rename
`isUnboxedTupleCon` to `isUnboxedTupleDataCon` (similarly, I renamed
`isUnboxedSumCon` to `isUnboxedSumDataCon`) to avoid this potential
confusion, as well as to be more consistent with
the naming convention I used for `isBoxedTupleDataCon`.

Fixes #18644.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/07bdcac38c90e79db9e4327f87c5400630dfe74b">07bdcac3</a></strong>
<div>
<span>by GHC GitLab CI</span>
<i>at 2020-09-04T22:26:25-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">configure: Avoid hard-coded ld path on Windows

The fix to #17962 ended up regressing on Windows as it failed to
replicate the logic responsible for overriding the toolchain paths on
Windows. This resulted in a hard-coded path to a directory that likely
doesn't exist on the user's system (#18550).
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/0be8e746b820662a09bf9e406bb7e86da3b548e6">0be8e746</a></strong>
<div>
<span>by Benjamin Maurer</span>
<i>at 2020-09-04T22:27:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Documented the as of yet undocumented '--print-*'  GHC flags,
as well as `-split-objs`, since that is related to
`--print-object-splitting-supported`.
See #18641
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4813486f8756fde7889b214e6e41ae63465f7ad7">4813486f</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-09-04T22:27:44-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Move Hadrian's wiki pages in tree (fix #16165)

Only the debugging page contains interesting stuff. Some of this stuff
looks old (e.g. recommending "cabal install")...
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7980ae23696f2406c65ee498155b26c09d3d4394">7980ae23</a></strong>
<div>
<span>by GHC GitLab CI</span>
<i>at 2020-09-05T14:50:52-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts: Consistently use stgMallocBytes instead of malloc

This can help in debugging RTS memory leaks since all allocations go
through the same interface.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/67059893a232e682aa5eca7a3d13042b1c884d55">67059893</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-09-05T14:51:27-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">configure: Fix whitespace
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/be2cc0ad2109894d2f576c73e3f037b6b79a6bdc">be2cc0ad</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-09-05T14:51:27-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">gitlab-ci: More intelligent detection of locale availability

Previously ci.sh would unconditionally use C.UTF-8. However, this fails
on Centos 7, which appears not to provide this locale. Now we first try
C.UTF-8, then try en_US.UTF-8, then fail.

Works around #18607.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/15dca84793d5ec4ff922726477923e40caa075eb">15dca847</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-09-05T14:51:27-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">gitlab-ci: Rename RELEASE variable to RELEASE_JOB

This interfered with the autoconf variable of the same name, breaking
pre-release builds.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/bec0d1701673a80d9517acabf559738613ba4e9c">bec0d170</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-09-05T14:51:27-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">gitlab-ci: Bump Windows toolchain version

This should have been done when we bumped the bootstrap compiler to
8.8.4.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9fbaee212ff527c3a91c350c7e54c75c1484d778">9fbaee21</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-09-05T14:51:27-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">gitlab-ci: Drop Windows make job

These are a significant burden on our CI resources and end up failing
quite often due to #18274. Here I drop the make jobs during
validaion; it is now run only during the nightly builds.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/869f6e193d302c566ff0fbd530e8427440d0d2e3">869f6e19</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-09-05T14:51:27-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite: Drop Windows-specific output for parseTree

The normalise_slashes normaliser should handle this.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2c9f743c0d034b1a99b22d48e4ff7a3b6670aaa5">2c9f743c</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-09-05T14:51:28-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite: Mark T5975[ab] as broken on Windows

Due to #7305.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/643785e3835de2de6c575e6418db0d4598b72a7d">643785e3</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-09-05T14:51:28-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">gitlab-ci: Fix typo

A small typo in a rule regular expression.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c5413fc62342f05d48e62f92c81a7f8a3259d3d7">c5413fc6</a></strong>
<div>
<span>by Wander Hillen</span>
<i>at 2020-09-07T09:33:54-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add clarification regarding poll/kqueue flags
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/10434d60c62fee7212f08bffde624702f81e93cf">10434d60</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-09-07T09:34:32-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">gitlab-ci: Configure bignum backend in Hadrian builds
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d4bc9f0de7992f60bce403731019829f6248cc2c">d4bc9f0d</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-09-07T09:34:32-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">gitlab-ci: Use hadrian builds for Windows release artifacts
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4ff93292243888545da452ea4d4c1987f2343591">4ff93292</a></strong>
<div>
<span>by Moritz Angermann</span>
<i>at 2020-09-07T21:18:39-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">[macOS] improved runpath handling

In b592bd98ff25730bbe3c13d6f62a427df8c78e28 we started using
-dead_strip_dylib on macOS when lining dynamic libraries and binaries.
The underlying reason being the Load Command Size Limit in macOS
Sierra (10.14) and later.

GHC will produce @rpath/libHS... dependency entries together with a
corresponding RPATH entry pointing to the location of the libHS...
library. Thus for every library we produce two Load Commands.  One to
specify the dependent library, and one with the path where to find it.
This makes relocating libraries and binaries easier, as we just need to
update the RPATH entry with the install_name_tool. The dynamic linker
will then subsitute each @rpath with the RPATH entries it finds in the
libraries load commands or the environement, when looking up @rpath
relative libraries.

-dead_strip_dylibs intructs the linker to drop unused libraries. This in
turn help us reduce the number of referenced libraries, and subsequently
the size of the load commands.  This however does not remove the RPATH
entries.  Subsequently we can end up (in extreme cases) with only a
single @rpath/libHS... entry, but 100s or more RPATH entries in the Load
Commands.

This patch rectifies this (slighly unorthodox) by passing *no* -rpath
arguments to the linker at link time, but -headerpad 8000.  The
headerpad argument is in hexadecimal and the maxium 32k of the load
command size.  This tells the linker to pad the load command section
enough for us to inject the RPATHs later.  We then proceed to link the
library or binary with -dead_strip_dylibs, and *after* the linking
inspect the library to find the left over (non-dead-stripped)
dependencies (using otool).  We find the corresponding RPATHs for each
@rpath relative dependency, and inject them into the library or binary
using the install_name_tool.  Thus achieving a deadstripped dylib (and
rpaths) build product.

We can not do this in GHC, without starting to reimplement a dynamic
linker as we do not know which symbols and subsequently libraries are
necessary.

Commissioned-by: Mercury Technologies, Inc. (mercury.com)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/df04b81e12dac85292aa18c07e6afac7a8bd2fd5">df04b81e</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-09-07T21:19:20-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Move DynFlags test into updateModDetailsIdInfos's caller (#17957)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ea1cbb8f2ac9e077ed19530911c3a35c5f46ee8a">ea1cbb8f</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-09-08T15:42:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts: Add stg_copyArray_barrier to RtsSymbols list

It's incredible that this wasn't noticed until now.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d7b2f799469a969ad7a2535be57f105186946c40">d7b2f799</a></strong>
<div>
<span>by Daishi Nakajima</span>
<i>at 2020-09-08T15:42:41-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite: Output performance test results in tabular format
this was suggested in #18417.

Change the print format of the values.
* Shorten commit hash
* Reduce precision of the "Value" field
* Shorten metrics name
  * e.g. runtime/bytes allocated -> run/alloc
* Shorten "MetricsChange"
  * e.g. unchanged -> unch, increased -> incr

And, print the baseline environment if there are baselines that were
measured in a different environment than the current environment.

If all "Baseline commit" are the same, print it once.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/44472daf500bf862921e89ad45c9741a07a64f61">44472daf</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-09-08T15:43:16-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Make the forall-or-nothing rule only apply to invisible foralls (#18660)

This fixes #18660 by changing `isLHsForAllTy` to
`isLHsInvisForAllTy`, which is sufficient to make the
`forall`-or-nothing rule only apply to invisible `forall`s. I also
updated some related documentation and Notes while I was in the
neighborhood.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/0c61cbfff985723240671b54d6f80075e4907e85">0c61cbff</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-09-08T15:43:54-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">gitlab-ci: Handle distributions without locales

Previously we would assume that the `locale` utility exists. However,
this is not so on Alpine as musl's locale support is essentially
non-existent.

(cherry picked from commit 17cdb7ac3b557a245fee1686e066f9f770ddc21e)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d989c84225090f850591e9f4f82adffbf8c96cac">d989c842</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-09-08T15:43:55-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">gitlab-ci: Accept Centos 7 C.utf8 locale

Centos apparently has C.utf8 rather than C.UTF-8.

(cherry picked from commit d9f85dd25a26a04d3485470afb3395ee2dec6464)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e5a2899ce8e06b8645946fbb67041807cd3a4fe5">e5a2899c</a></strong>
<div>
<span>by John Ericson</span>
<i>at 2020-09-09T00:46:05-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Use "to" instead of "2" in internal names of conversion ops

Change the constructors for the primop union, and also names of the
literal conversion functions.

"2" runs into trouble when we need to do conversions from fixed-width
types, and end up with thing like "Int642Word".

Only the names internal to GHC are changed, as I don't want to worry
about breaking changes ATM.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/822f10575d207a2a47b21ac853dcf28c655041c4">822f1057</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-09-09T00:46:41-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Postpone associated tyfam default checks until after typechecking

Previously, associated type family defaults were validity-checked
during typechecking. Unfortunately, the error messages that these
checks produce run the risk of printing knot-tied type constructors,
which will cause GHC to diverge. In order to preserve the current
error message's descriptiveness, this patch postpones these validity
checks until after typechecking, which are now located in the new
function `GHC.Tc.Validity.checkValidAssocTyFamDeflt`.

Fixes #18648.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8c892689058912c35ed36e07b5a9ed0df86abc03">8c892689</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-09-09T11:19:24-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">DynFlags: add OptCoercionOpts

Use OptCoercionOpts to avoid threading DynFlags all the way down to
GHC.Core.Coercion.Opt
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/3f32a9c0f4ddceab14a381bfd3732bcad6be43f7">3f32a9c0</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-09-09T11:19:24-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">DynFlags: add UnfoldingOpts and SimpleOpts

Milestone: after this patch, we only use 'unsafeGlobalDynFlags' for the
state hack and for debug in Outputable.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b3df72a699727b00d5dd8212fcbe46cbbec05f9b">b3df72a6</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-09-09T11:19:24-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">DynFlags: add sm_pre_inline field into SimplMode (#17957)

It avoids passing and querying DynFlags down in the simplifier.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ffae57921168365272bf7ce8aaa645917bfdf218">ffae5792</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-09-09T11:19:24-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add comments about sm_dflags and simpleOptExpr
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7911d0d983a68eb0d54d7c1ba51326d6be737aae">7911d0d9</a></strong>
<div>
<span>by Alan Zimmerman</span>
<i>at 2020-09-09T11:20:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove GENERATED pragma, as it is not being used

@alanz pointed out on ghc-devs that the payload of this pragma does
not appear to be used anywhere.

I (@bgamari) did some digging and traced the pragma's addition back to
d386e0d2 (way back in 2006!).

It appears that it was intended to be used by code generators for use
in informing the code coveraging checker about generated code
provenance. When it was added it used the pragma's "payload" fields as
source location information to build an "ExternalBox". However, it
looks like this was dropped a year later in 55a5d8d9.  At this point
it seems like the pragma serves no useful purpose.

Given that it also is not documented, I think we should remove it.

Updates haddock submodule

Closes #18639
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/5aae5b325ccef857800f1840665a0e1b152e9b88">5aae5b32</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-09-09T18:31:40-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">gitlab-ci: Bump Docker images

We now generate our Docker images via Dhall definitions, as described in
ghc/ci-images!52. Additionally, we are far more careful about where tools
come from, using the ALEX, HAPPY, HSCOLOR, and GHC environment variables
(set in the Dockerfiles) to find bootstrapping tools.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4ce9fe88e7e98178d5fd6b18ac9cba666a1f8306">4ce9fe88</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-09-09T18:31:40-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">hadrian: Fix leakage of GHC in PATH into build

Previously hadrian would use GHC on PATH when configuring packages (or
fail if there is no such GHC). Fix this. Unfortunately this runs into
another bug in Cabal which we workaround.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/291a15dd8dfc03d493c0db36a9cb62fd4867db10">291a15dd</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-09-09T18:31:40-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">utils: Bump cabal-version of hp2ps and unlit
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4798caa0fefd7adf4c5b85fa84a6f28fcc6b350b">4798caa0</a></strong>
<div>
<span>by David Himmelstrup</span>
<i>at 2020-09-09T18:32:16-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts comment: RTS_TICKY_SYMBOLS moved from rts/Linker.c to rts/RtsSymbols.c
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/67ce72da1689058cb689ffbb6fcbd5cd12af56df">67ce72da</a></strong>
<div>
<span>by Sebastian Graf</span>
<i>at 2020-09-10T10:35:33-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add long-distance info for pattern bindings (#18572)

We didn't consider the RHS of a pattern-binding before, which led to
surprising warnings listed in #18572.

As can be seen from the regression test T18572, we get the expected
output now.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/1207576ac0cfdd3fe1ea00b5505f7c874613451e">1207576a</a></strong>
<div>
<span>by Sebastian Graf</span>
<i>at 2020-09-10T10:35:33-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">PmCheck: Big refactor using guard tree variants more closely following source syntax (#18565)

Previously, we desugared and coverage checked plain guard trees as
described in Lower Your Guards. That caused (in !3849) quite a bit of
pain when we need to partially recover tree structure of the input
syntax to return covered sets for long-distance information, for
example.

In this refactor, I introduced a guard tree variant for each relevant
source syntax component of a pattern-match (mainly match groups, match,
GRHS, empty case, pattern binding). I made sure to share as much
coverage checking code as possible, so that the syntax-specific checking
functions are just wrappers around the more substantial checking
functions for the LYG primitives (`checkSequence`, `checkGrds`).

The refactoring payed off in clearer code and elimination of all panics
related to assumed guard tree structure and thus fixes #18565.

I also took the liberty to rename and re-arrange the order of functions
and comments in the module, deleted some dead and irrelevant Notes,
wrote some new ones and gave an overview module haddock.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/95455982df1ef15c6d4585a7d3e93b5e75146a07">95455982</a></strong>
<div>
<span>by GHC GitLab CI</span>
<i>at 2020-09-10T10:36:09-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">hadrian: Don't include -fdiagnostics-color in argument hash

Otherwise the input hash will vary with whether colors are requested,
which changed with `isatty`.

Fixes #18672.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6abe4a1c427a511aa698424055639ea789fccf97">6abe4a1c</a></strong>
<div>
<span>by Sebastian Graf</span>
<i>at 2020-09-10T17:02:00+02:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">.gitignore *.hiedb files
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/3777be14e104f040b826762f5ab42a8b898d85ae">3777be14</a></strong>
<div>
<span>by Sebastian Graf</span>
<i>at 2020-09-10T17:03:12+02:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">PmCheck: Handle ⊥ and strict fields correctly (#18341)

In #18341, we discovered an incorrect digression from Lower Your Guards.
This MR changes what's necessary to support properly fixing #18341.

In particular, bottomness constraints are now properly tracked in the
oracle/inhabitation testing, as an additional field
`vi_bot :: Maybe Bool` in `VarInfo`. That in turn allows us to
model newtypes as advertised in the Appendix of LYG and fix #17725.
Proper handling of ⊥ also fixes #17977 (once again) and fixes #18670.

For some reason I couldn't follow, this also fixes #18273.

I also added a couple of regression tests that were missing. Most of
them were already fixed before.

In summary, this patch fixes #18341, #17725, #18273, #17977 and #18670.

Metric Decrease:
    T12227
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/1bd28931903c2fbc10a4b2ecbf9dffd0a3585ac8">1bd28931</a></strong>
<div>
<span>by David Himmelstrup</span>
<i>at 2020-09-11T09:59:43-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Define TICKY_TICKY when compiling cmm RTS files.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/15e67801ee72b94c6c826f641464c6be511685cc">15e67801</a></strong>
<div>
<span>by David Himmelstrup</span>
<i>at 2020-09-11T09:59:43-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix typos in TICKY_TICKY symbol names.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8a5a91cb67e8c4e2558031c04efccf3c378ba254">8a5a91cb</a></strong>
<div>
<span>by David Himmelstrup</span>
<i>at 2020-09-11T09:59:43-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Enable TICKY_TICKY for debug builds when building with makefiles.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/fc965c0910757410d624229419f36f0829cf73f6">fc965c09</a></strong>
<div>
<span>by Sandy Maguire</span>
<i>at 2020-09-12T00:31:36-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add clamp function to Data.Ord
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/fb6e29e8d19deaf7581fdef14adc88a02573c83e">fb6e29e8</a></strong>
<div>
<span>by Sandy Maguire</span>
<i>at 2020-09-12T00:31:37-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add tests
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2a9422859e0c079aaa38bb9a760034f887501fce">2a942285</a></strong>
<div>
<span>by Sebastian Graf</span>
<i>at 2020-09-12T00:32:13-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">PmCheck: Disattach COMPLETE pragma lookup from TyCons

By not attaching COMPLETE pragmas with a particular TyCon and instead
assume that every COMPLETE pragma is applicable everywhere, we can
drastically simplify the logic that tries to initialise available
COMPLETE sets of a variable during the pattern-match checking process,
as well as fixing a few bugs.

Of course, we have to make sure not to report any of the
ill-typed/unrelated COMPLETE sets, which came up in a few regression
tests.

In doing so, we fix #17207, #18277 and #14422.

There was a metric decrease in #18478 by ~20%.

Metric Decrease:
    T18478
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/389a668343c0d4f5fa095112ff98d0da6998e99d">389a6683</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-09-12T00:32:49-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">hadrian: Pass input file to makeindex

Strangely I find that on Alpine (and apparently only on Alpine) the
latex makeindex command expects to be given a filename, lest it reads
from stdin.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/853d121acfcdae208e852edacac65a1b3e8cab83">853d121a</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-09-12T00:33:25-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Don't quote argument to Hadrian's test-env flag (#18656)

Doing so causes the name of the test environment to gain an extra
set of double quotes, which changes the name entirely.

Fixes #18656.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8440b5fa1397940f2f293935927e690b34110a73">8440b5fa</a></strong>
<div>
<span>by Krzysztof Gogolewski</span>
<i>at 2020-09-12T00:33:25-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Make sure we can read past perf notes

See #18656.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2157be52cd454353582b04d89492b239b90f91f7">2157be52</a></strong>
<div>
<span>by theobat</span>
<i>at 2020-09-12T21:27:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Avoid iterating twice in `zipTyEnv` (#18535)

zipToUFM is a new function to replace `listToUFM (zipEqual ks vs)`.
An explicit recursion is preferred due to the sensible nature of fusion.

    T12227 -6.0%
    T12545 -12.3%
    T5030  -9.0%
    T9872a -1.6%
    T9872b -1.6%
    T9872c -2.0%

 -------------------------
Metric Decrease:
    T12227
    T12545
    T5030
    T9872a
    T9872b
    T9872c
-------------------------
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/69ea2fee35b4bcfd9253ee608f7135024186aeed">69ea2fee</a></strong>
<div>
<span>by Sebastian Graf</span>
<i>at 2020-09-12T21:27:40-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Make `tcCheckSatisfiability` incremental (#18645)

By taking and returning an `InertSet`.
Every new `TcS` session can then pick up where a prior session left with
`setTcSInerts`.

Since we don't want to unflatten the Givens (and because it leads to
infinite loops, see !3971), we introduced a new variant of `runTcS`,
`runTcSInerts`, that takes and returns the `InertSet` and makes
sure not to unflatten the Givens after running the `TcS` action.

Fixes #18645 and #17836.

Metric Decrease:
    T17977
    T18478
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a77e48d291b35a92731f106d79ea75117ec380e1">a77e48d2</a></strong>
<div>
<span>by Sebastian Graf</span>
<i>at 2020-09-12T21:27:40-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Extract definition of DsM into GHC.HsToCore.Types

`DsM` was previously defined in `GHC.Tc.Types`, along with `TcM`. But
`GHC.Tc.Types` is in the set of transitive dependencies of `GHC.Parser`,
a set which we aim to minimise. Test case `CountParserDeps` checks for
that.

Having `DsM` in that set means the parser also depends on the innards of
the pattern-match checker in `GHC.HsToCore.PmCheck.Types`, which is the
reason we have that module in the first place.

In the previous commit, we represented the `TyState` by an `InertSet`,
but that pulls the constraint solver as well as 250 more modules into
the set of dependencies, triggering failure of `CountParserDeps`.
Clearly, we want to evolve the pattern-match checker (and the desugarer)
without being concerned by this test, so this patch includes a small
refactor that puts `DsM` into its own module.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/fd5d622a5ee283d3c1f1ccd28b4f73aab30d7d9f">fd5d622a</a></strong>
<div>
<span>by Sebastian Graf</span>
<i>at 2020-09-12T21:27:40-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Hackily decouple the parser from the desugarer

In a hopefully temporary hack, I re-used the idea from !1957 of using a
nullary type family to break the dependency from GHC.Driver.Hooks on the
definition of DsM ("Abstract Data").
This in turn broke the last dependency from the parser to the desugarer.
More details in `Note [The Decoupling Abstract Data Hack]`.

In the future, we hope to undo this hack again in favour of breaking the
dependency from the parser to DynFlags altogether.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/35a7b7ecabeba39e53d6dea78ecc2d3eca8b1b24">35a7b7ec</a></strong>
<div>
<span>by Adam Sandberg Eriksson</span>
<i>at 2020-09-14T17:46:16-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">docs: -B rts option sounds the bell on every GC (#18351)</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/5ae8212c3d2f284bc18a562625be3f4640984497">5ae8212c</a></strong>
<div>
<span>by Wander Hillen</span>
<i>at 2020-09-14T17:46:54-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Populate gitlab cache after building
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a5ffb39afc386729c821b924dd2c6a93917e1b5f">a5ffb39a</a></strong>
<div>
<span>by Wander Hillen</span>
<i>at 2020-09-14T17:46:54-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Move ahead cabal cache restoration to before use of cabal
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e8b37c21fdcb9ca515e3dd2fab1661b7792fb728">e8b37c21</a></strong>
<div>
<span>by Wander Hillen</span>
<i>at 2020-09-14T17:46:54-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Do the hadrian rebuild multicore
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/07762eb5cfe735e131a7f017939a6b0ccfb28389">07762eb5</a></strong>
<div>
<span>by Wander Hillen</span>
<i>at 2020-09-14T17:46:54-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Also cache other hadrian builds
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8610bcbeb11b898f85f228b755fa8421b5ae3e34">8610bcbe</a></strong>
<div>
<span>by DenisFrezzato</span>
<i>at 2020-09-15T15:19:08-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix rtsopts documentation
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c7182a5c67fe8b5bd256cb8eb805562636853ea2">c7182a5c</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-09-15T15:19:44-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Care with implicit-parameter superclasses

Two bugs, #18627 and #18649, had the same cause: we were not
account for the fact that a constaint tuple might hide an implicit
parameter.

The solution is not hard: look for implicit parameters in
superclasses.  See Note [Local implicit parameters] in
GHC.Core.Predicate.

Then we use this new function in two places

* The "short-cut solver" in GHC.Tc.Solver.Interact.shortCutSolver
  which simply didn't handle implicit parameters properly at all.
  This fixes #18627

* The specialiser, which should not specialise on implicit parameters
  This fixes #18649

There are some lingering worries (see Note [Local implicit
parameters]) but things are much better.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/0f3884b0b72fb1e4641450e68f63580c0e86f515">0f3884b0</a></strong>
<div>
<span>by Zubin Duggal</span>
<i>at 2020-09-15T15:20:23-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Export enrichHie from GHC.Iface.Ext.Ast

This is useful for `ghcide`
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b3143f5a0827b640840ef241a30933dc23b69d91">b3143f5a</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-09-15T15:21:06-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Enhance metrics output
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4283feaa9e0826211f7a71d543054c989ea32965">4283feaa</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-09-15T15:21:43-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Introduce and use DerivClauseTys (#18662)

This switches `deriv_clause_tys` so that instead of using a list of
`LHsSigType`s to represent the types in a `deriving` clause, it now
uses a sum type. `DctSingle` represents a `deriving` clause with no
enclosing parentheses, while `DctMulti` represents a clause with
enclosing parentheses. This makes pretty-printing easier and avoids
confusion between `HsParTy` and the enclosing parentheses in
`deriving` clauses, which are different semantically.

Fixes #18662.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/90229c4b781184d0e59ac67afda90ed316f62bcd">90229c4b</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-09-16T04:53:22-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Include -f{write,validate}-ide-info in the User's Guide flag reference

Previously, these were omitted from the flag reference due to a
layout oversight in `docs/users_guide/flags.{rst,py}`.

Fixes #18426.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ce42e187ebfc81174ed477f247f023ae094c9b24">ce42e187</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-09-16T04:53:59-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts: Fix erroneous usage of vsnprintf

As pointed out in #18685, this should be snprintf not vsnprintf. This
appears to be due to a cut-and-paste error.

Fixes #18658.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b695e7d73617ab19170d37b383315e8ede289c5e">b695e7d7</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-09-16T04:54:38-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Rename ghci flag into internal-interpreter

"ghci" as a flag name was confusing because it really enables the
internal-interpreter. Even the ghci library had a "ghci" flag...
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8af954d202de1de0671062c3f55e43fc783f8192">8af954d2</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-09-16T04:55:17-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Make ghc-boot reexport modules from ghc-boot-th

Packages don't have to import both ghc-boot and ghc-boot-th. It makes
the dependency graph easier to understand and to refactor.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6baa67f5500da6ca74272016ec8fd62a4b5b5050">6baa67f5</a></strong>
<div>
<span>by Adam Sandberg Eriksson</span>
<i>at 2020-09-16T07:45:47-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">docs: correct haddock reference

[skip ci]</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7cf09ab013778227caa07b5d7ec9acd5dedd1817">7cf09ab0</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-09-17T01:27:25-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Do absence analysis on stable unfoldings

Ticket #18638 showed that Very Bad Things happen if we fail
to do absence analysis on stable unfoldings.  It's all described
in Note [Absence analysis for stable unfoldings and RULES].

I'm a bit surprised this hasn't bitten us before. Fortunately
the fix is pretty simple.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/76d3bcbcef61ac71677855d6f90754ef019b9b4f">76d3bcbc</a></strong>
<div>
<span>by Leif Metcalf</span>
<i>at 2020-09-17T01:28:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Replace deprecated git --recursive

The --recursive flag of git-clone has been replaced by the
--recurse-submodules flag since git 1.7.4, released in 2011.</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/da8f4ddd76bac18c721aeaa247725953604206d3">da8f4ddd</a></strong>
<div>
<span>by Richard Eisenberg</span>
<i>at 2020-09-17T01:28:38-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Document IfaceTupleTy
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/3c94c81629ac9159775b8b70baf2c635f0331708">3c94c816</a></strong>
<div>
<span>by HaskellMouse</span>
<i>at 2020-09-17T08:49:51-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Added explicit fixity to (~).

Solves #18252
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b612e396ed1141dadfabc8486876abb713628f06">b612e396</a></strong>
<div>
<span>by Cary Robbins</span>
<i>at 2020-09-17T08:50:30-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Make the 'IsString (Const a b)' instance polykinded on 'b'
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8d0c26c463fc1512ad90788345b002b23e53555a">8d0c26c4</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-09-17T08:51:08-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts/win32: Fix missing #include's

These slipped through CI.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/76009ec84652f9b5c085f320ad9476e3693549f1">76009ec8</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-09-17T08:51:08-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Bump Win32 submodule to 2.9.0.0

Also bumps Cabal, directory
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/147bb59826087300f989addfcf79e3956f6ed66b">147bb598</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-09-17T08:51:08-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Bump version to 9.0

Bumps haskeline and haddock submodules.

(cherry picked from commit f218cfc92f7b1a1e01190851972bb9a0e0f3c682)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/5c7387f6f8896a34af25f8a28a78095e22287752">5c7387f6</a></strong>
<div>
<span>by Leif Metcalf</span>
<i>at 2020-09-17T08:51:43-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Make Z-encoding comment into a note
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c12b3041e533962b8d0ac9ee44e928f874c11671">c12b3041</a></strong>
<div>
<span>by Leif Metcalf</span>
<i>at 2020-09-17T08:51:43-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Cosmetic
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4f461e1a31263f052effd03738b11ea123512cb0">4f461e1a</a></strong>
<div>
<span>by Vladislav Zavialov</span>
<i>at 2020-09-17T08:52:19-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Parser.y: clarify treatment of @{-# UNPACK #-}

Before this patch, we had this parser production:

        ftype : ...
              | ftype PREFIX_AT tyarg  { ... }

And 'tyarg' is defined as follows:

        tyarg : atype              { ... }
              | unpackedness atype { ... }

So one might get the (false) impression that that parser production is
intended to parse things like:

        F @{-# UNPACK #-} X

However, the lexer wouldn't produce PREFIX_AT followed by 'unpackedness',
as the '@' operator followed by '{-' is not considered prefix.

Thus there's no point using 'tyarg' after PREFIX_AT,
and a simple 'atype' will suffice:

        ftype : ...
              | ftype PREFIX_AT atype  { ... }

This change has no user-facing consequences. It just makes the grammar a
bit more clear.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9dec8600ad4734607bea2b4dc3b40a5af788996b">9dec8600</a></strong>
<div>
<span>by Benjamin Maurer</span>
<i>at 2020-09-17T08:52:56-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Documented '-m' flags for machine specific instruction extensions.
See #18641 'Documenting the Expected Undocumented Flags'
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ca48076ae866665913b9c81cbc0c76f0afef7a00">ca48076a</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-09-17T20:04:08-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Introduce OutputableP

Some types need a Platform value to be pretty-printed: CLabel, Cmm
types, instructions, etc.

Before this patch they had an Outputable instance and the Platform value
was obtained via sdocWithDynFlags. It meant that the *renderer* of the
SDoc was responsible of passing the appropriate Platform value (e.g. via
the DynFlags given to showSDoc).  It put the burden of passing the
Platform value on the renderer while the generator of the SDoc knows the
Platform it is generating the SDoc for and there is no point passing a
different Platform at rendering time.

With this patch, we introduce a new OutputableP class:

   class OutputableP a where
      pdoc :: Platform -> a -> SDoc

With this class we still have some polymorphism as we have with `ppr`
(i.e. we can use `pdoc` on a variety of types instead of having a
dedicated `pprXXX` function for each XXX type).

One step closer removing `sdocWithDynFlags` (#10143) and supporting
several platforms (#14335).
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e45c85446de7589e17acf5654c2b33f766043eb1">e45c8544</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-09-17T20:04:08-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Generalize OutputableP

Add a type parameter for the environment required by OutputableP. It
avoids tying Platform with OutputableP.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/37aa224ad5b1cfb17d472c7b88c5c76bf22a52f3">37aa224a</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-09-17T20:04:08-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add note about OutputableP
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7f2785f2d6c6947d22d4d8b71d205c7c4b025680">7f2785f2</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-09-17T20:04:08-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove pprPrec from Outputable (unused)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b689f3db0229ac58af5383796fb13c6d40e358ce">b689f3db</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-09-17T20:04:46-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Bignum: add clamping naturalToWord (fix #18697)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/0799b3de3e3462224bddc0e4b6a3156d04a06361">0799b3de</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-09-18T15:55:50-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts/nonmoving: Add missing STM write barrier

When updating a TRec for a TVar already part of a transaction we
previously neglected to add the old value to the update remembered set.
I suspect this was the cause of #18587.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c492134912e5270180881b7345ee86dc32756bdd">c4921349</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-09-18T15:56:25-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts: Refactor foreign export tracking

This avoids calling `libc` in the initializers which are responsible for
registering foreign exports. We believe this should avoid the corruption
observed in #18548.

See Note [Tracking foreign exports] in rts/ForeignExports.c for an
overview of the new scheme.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/40dc91069d15bfc1d81f1722b39e06cac8fdddd1">40dc9106</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-09-18T15:56:25-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts: Refactor unloading of foreign export StablePtrs

Previously we would allocate a linked list cell for each foreign export.
Now we can avoid this by taking advantage of the fact that they are
already broken into groups.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/45fa82182bc61e3966fd51496c35130cd067a5df">45fa8218</a></strong>
<div>
<span>by Simon Jakobi</span>
<i>at 2020-09-19T06:57:36-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Deprecate Data.Semigroup.Option

Libraries email: https://mail.haskell.org/pipermail/libraries/2018-April/028724.html

GHC issue: https://gitlab.haskell.org/ghc/ghc/issues/15028

Corresponding PRs for deepseq:
* https://github.com/haskell/deepseq/pull/55
* https://github.com/haskell/deepseq/pull/57

Bumps the deepseq submodule.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2229d570fc78867190febb4f13c799b258a41f6d">2229d570</a></strong>
<div>
<span>by Vladislav Zavialov</span>
<i>at 2020-09-19T15:47:24-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Require happy >=1.20
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a89c2fbab9bcf7d769e9d27262ab29f93342f114">a89c2fba</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-09-19T15:47:24-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">ci.sh: Enforce minimum happy/alex versions

Also, always invoke cabal-install to ensure that happy/alex symlinks are
up-to-date.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2f7ef2fb3234cdfb89b3da1298fc9c1b7381e418">2f7ef2fb</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-09-19T15:47:24-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">gitlab-ci: Ensure that cabal-install overwrites existing executables

Previously cabal-install wouldn't overwrite toolchain executables if
they already existed (as they likely would due to caching).
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ac213d267140e747a391f68bc9f060e117395547">ac213d26</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-09-19T15:48:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Wire in constraint tuples

This wires in the definitions of the constraint tuple classes. The
key changes are in:

* `GHC.Builtin.Types`, where the `mk_ctuple` function is used to
  define constraint tuple type constructors, data constructors, and
  superclass selector functions, and
* `GHC.Builtin.Uniques`. In addition to wiring in the `Unique`s for
  constraint tuple type and data constructors, we now must wire in
  the superclass selector functions. Luckily, this proves to be not
  that challenging. See the newly added comments.

Historical note: constraint tuples used to be wired-in until about
five years ago, when commit 130e93aab220bdf14d08028771f83df210da340b
turned them into known-key names. This was done as part of a larger
refactor to reduce the number of special cases for constraint tuples,
but the commit message notes that the main reason that constraint
tuples were made known-key (as opposed to boxed/unboxed tuples, which
are wired in) is because it was awkward to wire in the superclass
selectors. This commit solves the problem of wiring in superclass
selectors.

Fixes #18635.

-------------------------
Metric Decrease:
    T10421
    T12150
    T12227
    T12234
    T12425
    T13056
    T13253-spj
    T18282
    T18304
    T5321FD
    T5321Fun
    T5837
    T9961
Metric Decrease (test_env='x86_64-linux-deb9-unreg-hadrian'):
    T12707
Metric Decrease (test_env='x86_64-darwin'):
    T4029
-------------------------
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e195dae6d959e2a9b1a22a2ca78db5955e1d7dea">e195dae6</a></strong>
<div>
<span>by Wander Hillen</span>
<i>at 2020-09-19T15:48:41-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Export singleton function from Data.List

Data.OldList exports a monomorphized singleton function but
it is not re-exported by Data.List. Adding the export to
Data.List causes a conflict with a 14-year old function of the
same name and type by SPJ in GHC.Utils.Misc. We can't just remove
this function because that leads to a problems when building
GHC with a stage0 compiler that does not have singleton in
Data.List yet. We also can't hide the function in GHC.Utils.Misc
since it is not possible to hide a function from a module if the
module does not export the function. To work around this, all
places where the Utils.Misc singleton was used now use a qualified
version like Utils.singleton and in GHC.Utils.Misc we are very
specific about which version we export.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9c1b8ad931e7bfabe521bc17e74ac9869b21a748">9c1b8ad9</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-09-19T15:49:19-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Bump Stack resolver
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d05d13ce6b5be54f3aa1c23f4377920a4965fc50">d05d13ce</a></strong>
<div>
<span>by John Ericson</span>
<i>at 2020-09-19T15:49:57-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Cinch -fno-warn-name-shadowing down to specific GHCi module
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/f1accd00969e0b2993f14ee4ed858cea0c13357e">f1accd00</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-09-19T15:49:57-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add quick-validate Hadrian flavour (quick + -Werror)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8f8d51f137ffcdbc4432febc5d1a11a564807b1b">8f8d51f1</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-09-19T15:50:33-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix docs who misstated how the RTS treats size suffixes.

They are parsed as multiples of 1024. Not 1000. The docs
used to imply otherwise.

See decodeSize in rts/RtsFlags.c for the logic for this.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2ae0edbdfaf920d0c4da4edf721b947e11eb054c">2ae0edbd</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-09-19T15:50:33-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix a codeblock in ghci.rst
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4df3aa956260e3d84232f43546e297cf425081dd">4df3aa95</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-09-19T15:51:07-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">users guide: Fix various documentation issues
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/885ecd18e084e4e2b15fbc5de0aa5222f2573387">885ecd18</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-09-19T15:51:07-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">hadrian: Fail on Sphinx syntax errors

Specifically the "Inline literal start-string without end-string"
warning, which typically means that the user neglected to separate
an inline code block from suffix text with a backslash.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b26cd86795d86850bfa97aa020d0a46b8ac043da">b26cd867</a></strong>
<div>
<span>by David Feuer</span>
<i>at 2020-09-19T15:51:44-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Unpack the MVar in Compact

The `MVar` lock in `Compact` was unnecessarily lazy, creating an extra indirection and wasting two words. Make it strict.</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/760307cf5511d970dfddf7fa4b502b4e3394b197">760307cf</a></strong>
<div>
<span>by Artyom Kuznetsov</span>
<i>at 2020-09-19T15:52:21-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove GADT self-reference check (#11554, #12081, #12174, fixes #15942)

Reverts 430f5c84dac1eab550110d543831a70516b5cac8
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/057db94ce038970b14df1599fe83097c284b9c1f">057db94c</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-09-19T15:52:56-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts: Drop field initializer on thread_basic_info_data_t

This struct has a number of fields and we only care that the value is
initialized with zeros. This eliminates the warnings noted in #17905.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/87e2e2b17afed82d30841d5b44c977123b93ecc4">87e2e2b1</a></strong>
<div>
<span>by Vladislav Zavialov</span>
<i>at 2020-09-19T23:55:30+03:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Resolve shift/reduce conflicts with %shift (#17232)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/66cba46e7049d907fe5c8614bddb60288421d358">66cba46e</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-09-20T20:30:57-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite: Unmark T12971 as broken on Windows

It's unclear why, but this no longer seems to fail.

Closes #17945.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/816811d45897afec3543ade30c63dcddf56828a8">816811d4</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-09-20T20:30:57-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite: Unmark T5975[ab] as broken on Windows

Sadly it's unclear *why* they have suddenly started working.

Closes #7305.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/43a43d396e30931c1fa68b054ae032d2bd1daa98">43a43d39</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-09-20T20:30:57-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">base/testsuite: Add missing LANGUAGE pragma in ThreadDelay001

Only affected the Windows codepath.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ced8f113cc6421dfc36dd322ea85a78bfa3ff37e">ced8f113</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-09-20T20:30:57-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite: Update expected output for outofmem on Windows

The error originates from osCommitMemory rather than getMBlocks.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ea08aead19087d21c5f7334e192cd4016ae57462">ea08aead</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-09-20T20:30:57-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite: Mark some GHCi/Makefile tests as broken on Windows

See #18718.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/caf6a5a30291d80660d6ff73efc35c04eaced789">caf6a5a3</a></strong>
<div>
<span>by GHC GitLab CI</span>
<i>at 2020-09-20T20:30:57-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite: Fix WinIO error message normalization

This wasn't being applied to stderr.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/93ab3e8d235610b2cb339a5bad9ad2848eab18d4">93ab3e8d</a></strong>
<div>
<span>by GHC GitLab CI</span>
<i>at 2020-09-20T20:30:57-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite: Mark tempfiles as broken on Win32 without WinIO

The old POSIX emulation appears to ignore the user-requested prefix.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9df77fed8918bb335874a584a829ee32325cefb5">9df77fed</a></strong>
<div>
<span>by GHC GitLab CI</span>
<i>at 2020-09-20T20:30:57-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite: Mark TH_spliceE5_prof as broken on Windows

Due to #18721.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/1a0f8243efc9873a949bb6f082b4dfdf563fc1ea">1a0f8243</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-09-21T16:45:47-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove unused ThBrackCtxt and ResSigCtxt

Fixes #18715.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2f222b120e48df1b3d78f5501612d21c2a2dc470">2f222b12</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-09-21T16:45:47-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Disallow constraints in KindSigCtxt

This patch cleans up how `GHC.Tc.Validity` classifies `UserTypeCtxt`s
that can only refer to kind-level positions, which is important for
rejecting certain classes of programs. In particular, this patch:

* Introduces a new `TypeOrKindCtxt` data type and
  `typeOrKindCtxt :: UserTypeCtxt -> TypeOrKindCtxt` function, which
  determines whether a `UserTypeCtxt` can refer to type-level
  contexts, kind-level contexts, or both.
* Defines the existing `allConstraintsAllowed` and `vdqAllowed`
  functions in terms of `typeOrKindCtxt`, which avoids code
  duplication and ensures that they stay in sync in the future.

The net effect of this patch is that it fixes #18714, in which it was
discovered that `allConstraintsAllowed` incorrectly returned `True`
for `KindSigCtxt`. Because `typeOrKindCtxt` now correctly classifies
`KindSigCtxt` as a kind-level context, this bug no longer occurs.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/aaa51dcfdb729f130aeefeaeac15029b62096a74">aaa51dcf</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-09-21T16:46:22-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">hadrian: Add extra-deps: happy-1.20 to stack.yaml

GHC now requires happy-1.20, which isn't available in LTS-16.14.

Fixes #18726.</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6de40f83c53c3b1899f7b4912badbe98e4fbde88">6de40f83</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-09-22T05:37:24-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Better eta-expansion (again) and don't specilise DFuns

This patch fixes #18223, which made GHC generate an exponential
amount of code.  There are three quite separate changes in here

1.  Re-engineer eta-expansion (again).  The eta-expander was
    generating lots of intermediate stuff, which could be optimised
    away, but which choked the simplifier meanwhile.  Relatively
    easy to kill it off at source.

    See Note [The EtaInfo mechanism] in GHC.Core.Opt.Arity.
    The main new thing is the use of pushCoArg in getArg_maybe.

2.  Stop Specialise specalising DFuns.  This is the cause of a huge
    (and utterly unnecessary) blowup in program size in #18223.
    See Note [Do not specialise DFuns] in GHC.Core.Opt.Specialise.

    I also refactored the Specialise monad a bit... it was silly,
    because it passed on unchanging values as if they were mutable
    state.

3.  Do an extra Simplifer run, after SpecConstra and before
    late-Specialise.  I found (investigating perf/compiler/T16473)
    that failing to do this was crippling *both* SpecConstr *and*
    Specialise.  See Note [Simplify after SpecConstr] in
    GHC.Core.Opt.Pipeline.

    This change does mean an extra run of the Simplifier, but only
    with -O2, and I think that's acceptable.

    T16473 allocates *three* times less with this change.  (I changed
    it to check runtime rather than compile time.)

Some smaller consequences

* I moved pushCoercion, pushCoArg and friends from SimpleOpt
  to Arity, because it was needed by the new etaInfoApp.

  And pushCoValArg now returns a MCoercion rather than Coercion for
  the argument Coercion.

* A minor, incidental improvement to Core pretty-printing

This does fix #18223, (which was otherwise uncompilable. Hooray.  But
there is still a big intermediate because there are some very deeply
nested types in that program.

Modest reductions in compile-time allocation on a couple of benchmarks
    T12425     -2.0%
    T13253    -10.3%

Metric increase with -O2, due to extra simplifier run
    T9233     +5.8%
    T12227    +1.8%
    T15630    +5.0%

There is a spurious apparent increase on heap residency on T9630,
on some architectures at least.  I tried it with -G1 and the residency
is essentially unchanged.

Metric Increase
    T9233
    T12227
    T9630

Metric Decrease
    T12425
    T13253
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/416bd50e58b23ad70813b18a913ca77a3ab6e936">416bd50e</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-09-22T05:37:59-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix the occurrence analyser

Ticket #18603 demonstrated that the occurrence analyser's
handling of

  local RULES for imported Ids

(which I now call IMP-RULES) was inadequate.  It led the simplifier
into an infnite loop by failing to label a binder as a loop breaker.

The main change in this commit is to treat IMP-RULES in a simple and
uniform way: as extra rules for the local binder.  See
  Note [IMP-RULES: local rules for imported functions]

This led to quite a bit of refactoring.  The result is still tricky,
but it's much better than before, and better documented I think.

Oh, and it fixes the bug.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6fe8a0c756f8b12df5cf192ea9b0c33feb150843">6fe8a0c7</a></strong>
<div>
<span>by Sebastian Graf</span>
<i>at 2020-09-22T05:38:35-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">PmCheck - Comments only: Replace /~ by ≁
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e9501547a8be6af97bcbf38a7ed66dadf02ea27b">e9501547</a></strong>
<div>
<span>by Sebastian Graf</span>
<i>at 2020-09-22T05:38:35-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">PmCheck: Rewrite inhabitation test

We used to produce inhabitants of a pattern-match refinement type Nabla
in the checker in at least two different and mostly redundant ways:

  1. There was `provideEvidence` (now called
     `generateInhabitingPatterns`) which is used by
     `GHC.HsToCore.PmCheck` to produce non-exhaustive patterns, which
     produces inhabitants of a Nabla as a sub-refinement type where all
     match variables are instantiated.
  2. There also was `ensure{,All}Inhabited` (now called
     `inhabitationTest`) which worked slightly different, but was
     whenever new type constraints or negative term constraints were
     added. See below why `provideEvidence` and `ensureAllInhabited`
     can't be the same function, the main reason being performance.
  3. And last but not least there was the `nonVoid` test, which tested
     that a given type was inhabited. We did use this for strict fields
     and -XEmptyCase in the past.

The overlap of (3) with (2) was always a major pet peeve of mine. The
latter was quite efficient and proven to work for recursive data types,
etc, but could not handle negative constraints well (e.g. we often want
to know if a *refined* type is empty, such as `{ x:[a] | x /= [] }`).

Lower Your Guards suggested that we could get by with just one, by
replacing both functions with `inhabitationTest` in this patch.
That was only possible by implementing the structure of φ constraints
as in the paper, namely the semantics of φ constructor constraints.

This has a number of benefits:

  a. Proper handling of unlifted types and strict fields, fixing #18249,
     without any code duplication between
     `GHC.HsToCore.PmCheck.Oracle.instCon` (was `mkOneConFull`) and
     `GHC.HsToCore.PmCheck.checkGrd`.
  b. `instCon` can perform the `nonVoid` test (3) simply by emitting
     unliftedness constraints for strict fields.
  c. `nonVoid` (3) is thus simply expressed by a call to
     `inhabitationTest`.
  d. Similarly, `ensureAllInhabited` (2), which we called after adding
     type info, now can similarly be expressed as the fuel-based
     `inhabitationTest`.

See the new `Note [Why inhabitationTest doesn't call generateInhabitingPatterns]`
why we still have tests (1) and (2).

Fixes #18249 and brings nice metric decreases for `T17836` (-76%) and
`T17836b` (-46%), as well as `T18478` (-8%) at the cost of a few very
minor regressions (< +2%), potentially due to the fact that
`generateInhabitingPatterns` does more work to suggest the minimal
COMPLETE set.

Metric Decrease:
    T17836
    T17836b
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/086ef01813069fad84cafe81cab37527d41c8568">086ef018</a></strong>
<div>
<span>by Hécate</span>
<i>at 2020-09-23T06:52:08-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove the list of loaded modules from the ghci prompt
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d7385f7077c6258c2a76ae51b4ea80f6fa9c7015">d7385f70</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-09-23T06:52:44-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Bump submodules

* Bump bytestring to 0.10.12.0
* Bump Cabal to 3.4.0.0-rc3
* Bump Win32 to 2.10.0.0
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/667d63558a694e12974ace723b553950f6080365">667d6355</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-09-23T20:43:48-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Refactor CLabel pretty-printing

* Don't depend on the selected backend to know if we print Asm or C
  labels: we already have PprStyle to determine this. Moreover even when
  a native backend is used (NCG, LLVM) we may want to C headers
  containing pretty-printed labels, so it wasn't a good predicate
  anyway.

* Make pretty-printing code clearer and avoid partiality
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a584366b1d363039247f73f6dcdd3514994ad600">a584366b</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-09-23T20:43:48-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove sdocWithDynFlags (fix #10143)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a997fa01d907fc1992dc8c3ebc73f98e7a1486f7">a997fa01</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-09-23T20:43:48-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Preliminary work towards removing DynFlags -> Driver.Ppr dependency
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/31fea307499009977fdf3dadedc98cfef986077a">31fea307</a></strong>
<div>
<span>by Hécate</span>
<i>at 2020-09-23T20:44:24-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove redundant "do", "return" and language extensions from base
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/04d6433158d95658684cf419c4ba5725d2aa539e">04d64331</a></strong>
<div>
<span>by syd@cs-syd.eu</span>
<i>at 2020-09-24T13:15:54-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Update Lock.hs with more documentation to make sure that the Boolean return value is clear.

[skip ci]
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/97cff9190d346c3b51c32c88fd145fcf1e6678f1">97cff919</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-09-24T13:16:32-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Implement Quick Look impredicativity

This patch implements Quick Look impredicativity (#18126), sticking
very closely to the design in
    A quick look at impredicativity, Serrano et al, ICFP 2020

The main change is that a big chunk of GHC.Tc.Gen.Expr has been
extracted to two new modules
    GHC.Tc.Gen.App
    GHC.Tc.Gen.Head
which deal with typechecking n-ary applications, and the head of
such applications, respectively.  Both contain a good deal of
documentation.

Three other loosely-related changes are in this patch:

* I implemented (partly by accident) points (2,3)) of the accepted GHC
  proposal "Clean up printing of foralls", namely
  https://github.com/ghc-proposals/ghc-proposals/blob/
        master/proposals/0179-printing-foralls.rst
  (see #16320).

  In particular, see Note [TcRnExprMode] in GHC.Tc.Module
  - :type instantiates /inferred/, but not /specified/, quantifiers
  - :type +d instantiates /all/ quantifiers
  - :type +v is killed off

  That completes the implementation of the proposal,
  since point (1) was done in
    commit df08468113ab46832b7ac0a7311b608d1b418c4d
    Author: Krzysztof Gogolewski <krzysztof.gogolewski@tweag.io>
    Date:   Mon Feb 3 21:17:11 2020 +0100
    Always display inferred variables using braces

* HsRecFld (which the renamer introduces for record field selectors),
  is now preserved by the typechecker, rather than being rewritten
  back to HsVar.  This is more uniform, and turned out to be more
  convenient in the new scheme of things.

* The GHCi debugger uses a non-standard unification that allows the
  unification variables to unify with polytypes.  We used to hack
  this by using ImpredicativeTypes, but that doesn't work anymore
  so I introduces RuntimeUnkTv.  See Note [RuntimeUnkTv] in
  GHC.Runtime.Heap.Inspect

Updates haddock submodule.

WARNING: this patch won't validate on its own.  It was too
hard to fully disentangle it from the following patch, on
type errors and kind generalisation.

Changes to tests

* Fixes #9730 (test added)

* Fixes #7026 (test added)

* Fixes most of #8808, except function `g2'` which uses a
  section (which doesn't play with QL yet -- see #18126)
  Test added

* Fixes #1330. NB Church1.hs subsumes Church2.hs, which is now deleted

* Fixes #17332 (test added)

* Fixes #4295

* This patch makes typecheck/should_run/T7861 fail.
  But that turns out to be a pre-existing bug: #18467.
  So I have just made T7861 into expect_broken(18467)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9fa26aa16f9eee0b56b5d9e65c16367d7b789996">9fa26aa1</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-09-24T13:16:32-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Improve kind generalisation, error messages

This patch does two things:

* It refactors GHC.Tc.Errors a bit.  In debugging Quick Look I was
  forced to look in detail at error messages, and ended up doing a bit
  of refactoring, esp in mkTyVarEqErr'.  It's still quite a mess, but
  a bit better, I think.

* It makes a significant improvement to the kind checking of type and
  class declarations. Specifically, we now ensure that if kind
  checking fails with an unsolved constraint, all the skolems are in
  scope.  That wasn't the case before, which led to some obscure error
  messages; and occasional failures with "no skolem info" (eg #16245).

Both of these, and the main Quick Look patch itself, affect a /lot/ of
error messages, as you can see from the number of files changed.  I've
checked them all; I think they are as good or better than before.

Smaller things

* I documented the various instances of VarBndr better.
  See Note [The VarBndr tyep and its uses] in GHC.Types.Var

* Renamed GHC.Tc.Solver.simpl_top to simplifyTopWanteds

* A bit of refactoring in bindExplicitTKTele, to avoid the
  footwork with Either.  Simpler now.

* Move promoteTyVar from GHC.Tc.Solver to GHC.Tc.Utils.TcMType

Fixes #16245 (comment 211369), memorialised as
  typecheck/polykinds/T16245a
Also fixes the three bugs in #18640
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6d0ce0eb772bf69c57e14f30c16c606ab5035816">6d0ce0eb</a></strong>
<div>
<span>by Sebastian Graf</span>
<i>at 2020-09-24T13:17:07-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">PmCheck: Desugar string literal patterns with -XRebindableSyntax correctly (#18708)

Fixes #18708.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/007940d2fa1ac4f8046989d4af1d088914612a78">007940d2</a></strong>
<div>
<span>by Hécate</span>
<i>at 2020-09-24T13:17:44-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Namespace the Hadrian linting rule for base
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/5b72718953c289b6827e877e14d9f0f3f5c64267">5b727189</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-09-25T21:10:20-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Make sizeExpr strict in the size threshold to facilitate WW.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/dd6640316865d84075b00013b8b97076705e5c44">dd664031</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-09-25T21:10:56-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">ci.sh: Factor out common utilities
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/5b78e8658c3f5042967cbe9d30a5a630946c4fd7">5b78e865</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-09-25T21:10:56-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">ci: Add ad-hoc performance testing rule
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/29885f076219d878d2c976e78b7960a1a5938a96">29885f07</a></strong>
<div>
<span>by Zubin Duggal</span>
<i>at 2020-09-25T21:11:32-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Stop removing definitions of record fields in GHC.Iface.Ext.Ast
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/0d6519d9e8604d067f4a4f760e4bc3403727a498">0d6519d9</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-09-25T21:12:08-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">gitlab-ci: Drop Darwin cleanup job

We now have a proper periodic clean-up script installed on the runners.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/277d20af1ce54c7e2c76dfe3b96c54babceeea41">277d20af</a></strong>
<div>
<span>by Sebastian Graf</span>
<i>at 2020-09-25T21:12:44-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add regression tests for #18371

They have been fixed by !3959, I believe.
Fixes #18371.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8edf60562720b91613a6ad6b949ae08416f81c9a">8edf6056</a></strong>
<div>
<span>by Sebastian Graf</span>
<i>at 2020-09-25T21:12:44-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add a regression test for #18609

The egregious performance hits are gone since !4050.
So we fix #18609.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4a1b89a40d553213c9722207608a07f8a4c07545">4a1b89a4</a></strong>
<div>
<span>by Sebastian Graf</span>
<i>at 2020-09-25T21:12:44-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Accept new test output for #17218

The expected test output was plain wrong.
It has been fixed for a long time.
Thus we can close #17218.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/516062366ed1957e499f27dfc6b685a073a18400">51606236</a></strong>
<div>
<span>by Sven Tennie</span>
<i>at 2020-09-25T21:13:19-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Print RET_BIG stack closures

A RET_BIG closure has a large bitmap that describes it's payload and can
be printed with printLargeBitmap().

Additionally, the output for payload closures of small and big bitmaps is
changed: printObj() is used to print a bit more information about what's
on the stack.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2707c4eae4cf99e6da2709e128f560d91e468357">2707c4ea</a></strong>
<div>
<span>by Arnaud Spiwack</span>
<i>at 2020-09-25T21:13:58-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Pattern guards BindStmt always use multiplicity Many

Fixes #18439 .

The rhs of the pattern guard was consumed with multiplicity one, while
the pattern assumed it was Many. We use Many everywhere instead.

This is behaviour consistent with that of `case` expression. See #18738.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/92daad241bf136a10346ecbf520d62921c82bf7d">92daad24</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-09-25T21:14:36-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Bignum: refactor backend modules

* move backends into GHC.Num.Backend.*
* split backend selection into GHC.Num.Backend and
  GHC.Num.Backend.Selected to avoid duplication with the Check backend
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/04bc50b3c8e40387a0d0f090ea23cd68923f1834">04bc50b3</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-09-25T21:14:36-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Bignum: implement extended GCD (#18427)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6a7dae4badcea5b3519005cf4e5fbf15f7e5df59">6a7dae4b</a></strong>
<div>
<span>by Krzysztof Gogolewski</span>
<i>at 2020-09-25T21:15:14-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix typed holes causing linearity errors (#18491)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/83407ffc7acc00cc025b9f6ed063add9ab9f9bcc">83407ffc</a></strong>
<div>
<span>by Krzysztof Gogolewski</span>
<i>at 2020-09-25T21:15:53-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Various documentation fixes

* Remove UnliftedFFITypes from conf. Some time ago, this extension
  was undocumented and we had to silence a warning.
  This is no longer needed.
* Use r'' in conf.py. This fixes a Sphinx warning:
  WARNING: Support for evaluating Python 2 syntax is deprecated and will be removed in Sphinx 4.0. Convert docs/users_guide/conf.py to Python 3 syntax.
* Mark GHCForeignImportPrim as documented
* Fix formatting in template_haskell.rst
* Remove 'recursive do' from the list of unsupported items in TH
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/af1e84e794591e09e20c661fa1d3df59f5b56e4a">af1e84e7</a></strong>
<div>
<span>by Sebastian Graf</span>
<i>at 2020-09-26T05:36:46-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">PmCheck: Big refactor of module structure

  * Move everything from `GHC.HsToCore.PmCheck.*` to
    `GHC.HsToCore.Pmc.*` in analogy to `GHC.Tc`, rename exported
    `covCheck*` functions to `pmc*`
  * Rename `Pmc.Oracle` to `Pmc.Solver`
  * Split off the LYG desugaring and checking steps into their own
    modules (`Pmc.Desugar` and `Pmc.Check` respectively)
  * Split off a `Pmc.Utils` module with stuff shared by
    `Pmc.{,Desugar,Check,Solver}`
  * Move `Pmc.Types` to `Pmc.Solver.Types`, add a new `Pmc.Types` module
    with all the LYG types, which form the interfaces between
    `Pmc.{Desugar,Check,Solver,}`.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/f08f98e821bc4b755a7b6ad3bad39ce1099c5405">f08f98e8</a></strong>
<div>
<span>by Sebastian Graf</span>
<i>at 2020-09-26T05:36:46-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Extract SharedIdEnv into its own module

It's now named `GHC.Types.Unique.SDFM.UniqSDFM`.
The implementation is more clear about its stated goals and supported
operations.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/1cde295c543e209c3b81256b50e77f3c5132a4ad">1cde295c</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-09-26T05:37:23-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Bignum: add bigNatFromWordArray

Reimplementation of integer-gmp's byteArrayToBigNat#
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/bda55fa0444310079ab89f2d28ddb8982975b646">bda55fa0</a></strong>
<div>
<span>by Krzysztof Gogolewski</span>
<i>at 2020-09-26T13:18:22-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Make 'undefined x' linear in 'x' (#18731)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/160fba4aa306c0649c72a6dcd7c98d9782a0e74b">160fba4a</a></strong>
<div>
<span>by Krzysztof Gogolewski</span>
<i>at 2020-09-26T13:19:00-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Disallow linear types in FFI (#18472)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e124f2a7d9a5932a4c2383fd3f9dd772b2059885">e124f2a7</a></strong>
<div>
<span>by Krzysztof Gogolewski</span>
<i>at 2020-09-26T13:19:36-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix handling of function coercions (#18747)

This was broken when we added multiplicity to the function type.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7ff433824ea4d265fca09de9c26f3fd77a34bb22">7ff43382</a></strong>
<div>
<span>by Vladislav Zavialov</span>
<i>at 2020-09-27T03:01:31+03:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Comments: change outdated reference to mergeOps

As of 686e06c59c3aa6b66895e8a501c7afb019b09e36,
GHC.Parser.PostProcess.mergeOps no longer exists.

[ci skip]
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4edf5527dbdd9781260e8822cb11a3f758fc7e91">4edf5527</a></strong>
<div>
<span>by Vladislav Zavialov</span>
<i>at 2020-09-27T10:04:12-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Don't rearrange (->) in the renamer

The parser produces an AST where the (->)
is already associated correctly:

  1. (->) has the least possible precedence
  2. (->) is right-associative

Thus we don't need to handle it in mkHsOpTyRn.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a9ce159ba58ca7e8946b46e19b1361588b677a26">a9ce159b</a></strong>
<div>
<span>by Vladislav Zavialov</span>
<i>at 2020-09-27T10:04:12-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove outdated comment in rnHsTyKi

This comment dates back to 3df40b7b78044206bbcffe3e2c0a57d901baf5e8
and does not seem relevant anymore.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/583a2070f1ad9162a365b034b27c3b80daafb8df">583a2070</a></strong>
<div>
<span>by Richard Eisenberg</span>
<i>at 2020-09-29T00:31:27-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Optimize NthCo (FunCo ...) in coercion opt

We were missing this case previously.

Close #18528.

Metric Decrease:
    T18223
    T5321Fun
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b31a3360e2ef12f3ec7eaf66b3600247c1eb36c3">b31a3360</a></strong>
<div>
<span>by Krzysztof Gogolewski</span>
<i>at 2020-09-29T00:32:05-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Linear types: fix kind inference when checking datacons
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/5830a12c46e7227c276a8a71213057595ee4fc04">5830a12c</a></strong>
<div>
<span>by Vladislav Zavialov</span>
<i>at 2020-09-29T00:32:05-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">New linear types syntax: a %p -> b (#18459)

Implements GHC Proposal #356

Updates the haddock submodule.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/bca4d36dd835c1c31c8f3364113586e1aedc6787">bca4d36d</a></strong>
<div>
<span>by Vladislav Zavialov</span>
<i>at 2020-09-29T00:32:05-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Improve error messages for (a %m) without LinearTypes

Detect when the user forgets to enable the LinearTypes
extension and produce a better error message.

Steals the (a %m) syntax from TypeOperators, the workaround
is to write (a % m) instead.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b9635d0a9bbb7f659c376b68cdc87223c864243c">b9635d0a</a></strong>
<div>
<span>by Benjamin Maurer</span>
<i>at 2020-09-29T00:32:43-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Description of flag `-H` was in 'verbosity options', moved to 'misc'.
Fixes #18699
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/74c797f6b72c4d01f5e0092dfac1461f3f3dd7a2">74c797f6</a></strong>
<div>
<span>by Benjamin Maurer</span>
<i>at 2020-09-29T00:33:20-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Workaround for #18623: GHC crashes bc. under rlimit for vmem it will reserve
_all_ of it, leaving nothing for, e.g., thread stacks.
Fix will only allocate 2/3rds and check whether remainder is at least large
enough for minimum amount of thread stacks.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4365d77a0b306ada61654c3648b844cfa0f4fdcf">4365d77a</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-09-29T00:33:57-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add regression test #18501

ghc/ghc!3220 ended up fixing #18501. This patch adds a regression
test for #18501 to ensure that it stays fixed.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8e3f00dd24936b6674d0a2322f8410125968583e">8e3f00dd</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-09-29T17:24:03+02:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Make the parser module less dependent on DynFlags

Bump haddock submodule
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/3ab0d8f77ec67676de40ebe6ff7e86756e5c761e">3ab0d8f7</a></strong>
<div>
<span>by Sebastian Graf</span>
<i>at 2020-09-30T02:48:27-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">PmCheck: Long-distance information for LocalBinds (#18626)

Now `desugarLocalBind` (formerly `desugarLet`) reasons about

  * `FunBind`s that
    * Have no pattern matches (so which aren't functions)
    * Have a singleton match group with a single GRHS
    * (which may have guards)
  * and looks through trivial post-typechecking `AbsBinds` in doing so
    to pick up the introduced renamings.

And desugars to `PmLet` LYG-style guards. Since GRHSs are no longer
denoted simply by `NonEmpty PmGRHS`, but also need to carry a `[PmGrd]`
for the `PmLet`s from `LocalBind`s, I added `PmGRHSs` to capture that.

Since we call out to the desugarer more often, I found that there were
superfluous warnings emitted when desugaring e.g. case expressions.
Thus, I made sure that we deactivate any warnings in the LYG desugaring
steps by the new wrapper function `noCheckDs`.

There's a regression test in `T18626`. Fixes #18626.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/f8f60efc831c6adb5bfee8449b76238ba6d582db">f8f60efc</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-09-30T02:49:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite: Mark T12971 as broken on Windows

Due to #17945.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6527fc57b8e099703f5bdb5ec7f1dfd421651972">6527fc57</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-09-30T02:49:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Bump Cabal, hsc2hs, directory, process submodules

Necessary for recent Win32 bump.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/df3f58807580bc2762086e063e3823b05de6fd64">df3f5880</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-09-30T02:49:41-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove unsafeGlobalDynFlags (#17957, #14597)

There are still global variables but only 3 booleans instead of a single
DynFlags.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9befd94d79a78fd53a28a4ce051a91d2215d069c">9befd94d</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-09-30T02:49:41-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove unused global variables

Some removed globals variables were still declared in the RTS.

They were removed in the following commits:

* 4fc6524a2a4a0003495a96c8b84783286f65c198
* 0dc7985663efa1739aafb480759e2e2e7fca2a36
* bbd3c399939311ec3e308721ab87ca6b9443f358
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7c98699f685d8c53fd594b6de22b425ed951174f">7c98699f</a></strong>
<div>
<span>by Richard Eisenberg</span>
<i>at 2020-09-30T02:50:17-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Omit redundant kind equality check in solver

See updated Note [Use loose types in inert set] in
GHC.Tc.Solver.Monad.

Close #18753.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/395498260ab444f5e1ec82d716bea3cc3ad887f7">39549826</a></strong>
<div>
<span>by Sebastian Graf</span>
<i>at 2020-09-30T02:50:54-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Pmc: Don't call exprType on type arguments (#18767)

Fixes #18767.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/235e410f63a4725bbc4466dbdef7d5f661793e84">235e410f</a></strong>
<div>
<span>by Richard Eisenberg</span>
<i>at 2020-09-30T02:51:29-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Regression test for #10709.

Close #10709
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e38c63ec52545d1f7336bf9e95200badcc661809">e38c63ec</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-09-30T14:02:10+02:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Enable strict dicts by default at -O2.

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

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

Increasing the inlining threshold can help to avoid this
which is documented in the user guide.
</pre>
</li>
</ul>
<h4>24 changed files:</h4>
<ul>
<li class="file-stats">
<a href="#a5cc2925ca8258af241be7e5b0381edf30266302">
.gitignore
</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="#e3912a2eb40cf45e3dc98ea1b0275653264428e6">
<span class="new-file">
+
.gitlab/common.sh
</span>
</a>
</li>
<li class="file-stats">
<a href="#412267f7d5ed866deae5ac2ca598ff8092b826b6">
.gitlab/linters/check-cpp.py
</a>
</li>
<li class="file-stats">
<a href="#f656107cc03a27946448887125380c358788500e">
.gitlab/test-metrics.sh
</a>
</li>
<li class="file-stats">
<a href="#abe895765c4ce08c5dfbc95e5e3c5db67ff92ded">
CODEOWNERS
</a>
</li>
<li class="file-stats">
<a href="#8ec9a00bfd09b3190ac6b22251dbb1aa95a0579d">
README.md
</a>
</li>
<li class="file-stats">
<a href="#9ab3868b23ed5d5a6e12ef902049902556fa4009">
aclocal.m4
</a>
</li>
<li class="file-stats">
<a href="#d0d96a6d03668aeab20ebe05e2c4ccb798c7e64c">
compiler/GHC.hs
</a>
</li>
<li class="file-stats">
<a href="#0887cf39c5cdf9cf8d6758f410d7dab3023c0d77">
compiler/GHC/Builtin/Names.hs
</a>
</li>
<li class="file-stats">
<a href="#06764eb0158306b83ab1998d18316392a51838c2">
compiler/GHC/Builtin/Names/TH.hs
</a>
</li>
<li class="file-stats">
<a href="#a1519b7fe8a0d4b42e4aaa927fb6ab5b5da0fcdd">
compiler/GHC/Builtin/PrimOps.hs
</a>
</li>
<li class="file-stats">
<a href="#377cfd14c1f92357465df995ec6537b074051322">
compiler/GHC/Builtin/Types.hs
</a>
</li>
<li class="file-stats">
<a href="#be7a5c9dc04ecfe7bedb2a2afcc2a51be6719577">
compiler/GHC/Builtin/Types.hs-boot
</a>
</li>
<li class="file-stats">
<a href="#02362b473a022fb921814e97a6beba08107d38b1">
compiler/GHC/Builtin/Types/Literals.hs
</a>
</li>
<li class="file-stats">
<a href="#8a5cd068459120cddf3814e7b9e02003b87647ba">
compiler/GHC/Builtin/Types/Prim.hs
</a>
</li>
<li class="file-stats">
<a href="#8dc7109003a77f8a82e987dc1de31466aa956174">
compiler/GHC/Builtin/Uniques.hs
</a>
</li>
<li class="file-stats">
<a href="#6bcb866fdb5388db4ecc395e443a3af4888d9dd5">
compiler/GHC/Builtin/Uniques.hs-boot
</a>
</li>
<li class="file-stats">
<a href="#d95fdf6575459444666f72b2281534e0558a4ba0">
compiler/GHC/Builtin/Utils.hs
</a>
</li>
<li class="file-stats">
<a href="#451725cc4e5d443a3b7c2adcdf224840f953b7e2">
compiler/GHC/Builtin/primops.txt.pp
</a>
</li>
<li class="file-stats">
<a href="#2f6f8d6d05acc04b08fff94df4b3996c65b87892">
compiler/GHC/ByteCode/Asm.hs
</a>
</li>
<li class="file-stats">
<a href="#16db773e94d0938489b415eb3231cadb2565b84d">
compiler/GHC/ByteCode/InfoTable.hs
</a>
</li>
<li class="file-stats">
<a href="#f73a4fa90a8eb153bccdcfcc9f63c15edcd66785">
compiler/GHC/Cmm.hs
</a>
</li>
</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/b8c212b98fe949feccbc4788cabedd3562fec842...e38c63ec52545d1f7336bf9e95200badcc661809">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>