<!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>
Ben Gamari pushed to branch wip/bump-win32
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/750a1595ef31cdc335f3bab045b2f19a9c43ff93">750a1595</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-07-18T07:26:41-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts: Add --copying-gc flag to reverse effect of --nonmoving-gc

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

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

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

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

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

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

See the new Note [fillInferResult] in TcMType

Other refactoring:

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

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

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

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

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

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

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

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

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

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

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

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

This reverts commit cdfeb3f24f76e8fd30452016676e56fbc827789a.

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

This reverts commit 7abffced01f5680efafe44f6be2733eab321b039.

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

This reverts commit 3f60b94de1f460ca3f689152860b108a19ce193e.

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

This reverts commit 686e72253aed3880268dd6858eadd8c320f09e97.

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

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

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

There are three problems with the current API:

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

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

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

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

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

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

   ::

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

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

      type Env = MapF Ident (Code Q)

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

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

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

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

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

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

This patch implements the following:

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

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

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

There are multiple reasons we want this:

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

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

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

Metric Increase:
    ManyConstructors

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

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

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

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

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

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

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

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

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

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

Metric Decrease:
    T3064

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Fixes #17587 and #18408

Updates haddock submodule

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

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

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

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

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

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

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

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

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

Otherwise the Windows builds hang forever waiting for the process to
terminate.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8236925fc8cc2e6e3fed61a0676fa65270a4a538">8236925f</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-26T13:24:35-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: remove dead argument to stg_newIOPortzh
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ce0a1d678fbc8efa5fd384fd0227b7b3dc97cadd">ce0a1d67</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-26T13:25:11-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: fix detection of tty terminals
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/52685cf7c077c51e3719e3c4dd5ca8257a99c4ea">52685cf7</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-26T13:25:48-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: update codeowners
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/f314afd7006118885ea7c7d1991f89812f67e3e3">f314afd7</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-07-26T15:41:17-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Bump Win32 and process submodules
</pre>
</li>
</ul>
<h4>30 changed files:</h4>
<ul>
<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="#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="#377cfd14c1f92357465df995ec6537b074051322">
compiler/GHC/Builtin/Types.hs
</a>
</li>
<li class="file-stats">
<a href="#8a5cd068459120cddf3814e7b9e02003b87647ba">
compiler/GHC/Builtin/Types/Prim.hs
</a>
</li>
<li class="file-stats">
<a href="#451725cc4e5d443a3b7c2adcdf224840f953b7e2">
compiler/GHC/Builtin/primops.txt.pp
</a>
</li>
<li class="file-stats">
<a href="#16db773e94d0938489b415eb3231cadb2565b84d">
compiler/GHC/ByteCode/InfoTable.hs
</a>
</li>
<li class="file-stats">
<a href="#db697f6aea9f93f1583f1d5c62d25570a1e07f73">
compiler/GHC/Cmm/CLabel.hs
</a>
</li>
<li class="file-stats">
<a href="#d088ba20f051734394bf7ca283f33ed8127bc8ab">
compiler/GHC/Cmm/CallConv.hs
</a>
</li>
<li class="file-stats">
<a href="#29368208fbfcaee57ce84000cdccaba639e85a75">
compiler/GHC/Cmm/Graph.hs
</a>
</li>
<li class="file-stats">
<a href="#47cba74ae8965f1665cd11bf2b023760ea27594e">
compiler/GHC/Cmm/Info.hs
</a>
</li>
<li class="file-stats">
<a href="#2d3721ad8de95e1144493ca545db846672cb109f">
compiler/GHC/Cmm/Info/Build.hs
</a>
</li>
<li class="file-stats">
<a href="#066085df29cc928ac539d8feae6e5215cbbf1e14">
compiler/GHC/Cmm/LayoutStack.hs
</a>
</li>
<li class="file-stats">
<a href="#6fbb543d5fcea725882dd3b8d4dcd9b02022a4be">
compiler/GHC/Cmm/Monad.hs
</a>
</li>
<li class="file-stats">
<a href="#71e696f452eb493722d70306c6f304fc9b2f6a95">
compiler/GHC/Cmm/Parser.y
</a>
</li>
<li class="file-stats">
<a href="#d40f34584a7f4c0fa7587fb41f94a34bca0d1064">
compiler/GHC/Cmm/Pipeline.hs
</a>
</li>
<li class="file-stats">
<a href="#072618a3250e1148569c2d2e0c05e313c2f529e3">
compiler/GHC/Cmm/Switch.hs
</a>
</li>
<li class="file-stats">
<a href="#f8bd883e3d3136150937961aaca9b45779a06100">
compiler/GHC/Cmm/Switch/Implement.hs
</a>
</li>
<li class="file-stats">
<a href="#7296b8b156359e17fb0fad7b82eaee2db3294144">
compiler/GHC/Cmm/Type.hs
</a>
</li>
<li class="file-stats">
<a href="#f9f29a5a64a0b66967f0a7c538dbf8ad06a9f5bb">
compiler/GHC/Cmm/Utils.hs
</a>
</li>
<li class="file-stats">
<a href="#10b61652f9817945bb54ccf8fc40f8a664ca3c30">
compiler/GHC/CmmToAsm.hs
</a>
</li>
<li class="file-stats">
<a href="#7223682bb3d11ed5bc80db47627d3d9ef7fa2ac7">
compiler/GHC/CmmToAsm/Config.hs
</a>
</li>
<li class="file-stats">
<a href="#ea29061dab1b843e0ea9294afc614998f3a8d08f">
compiler/GHC/CmmToAsm/Monad.hs
</a>
</li>
<li class="file-stats">
<a href="#76664ab267df4fc0bec2465efd78bf0afacfe3a7">
compiler/GHC/CmmToC.hs
</a>
</li>
<li class="file-stats">
<a href="#1aff3a222f2ec5c5498930c3d145b401cc300028">
compiler/GHC/CmmToLlvm.hs
</a>
</li>
<li class="file-stats">
<a href="#182d6a315e784018aa9c8b2ad736036b97bd5d48">
compiler/GHC/Core.hs
</a>
</li>
<li class="file-stats">
<a href="#6fcf64907fb5bdd93082d2d1eb94e4566e735865">
compiler/GHC/Core/DataCon.hs
</a>
</li>
<li class="file-stats">
<a href="#36a42448a83a9d1f6df8475f03ead2eed199dd8e">
compiler/GHC/Core/Lint.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/cdfc18918cc93970795dee7741e41400efe89cba...f314afd7006118885ea7c7d1991f89812f67e3e3">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>