<!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>
Simon Peyton Jones pushed to branch wip/T18300
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/03a708ba8e8c323b07d8d2e0115d6eb59987cc02">03a708ba</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-06-25T03:54:37-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Enable large address space optimization on windows.

Starting with Win 8.1/Server 2012 windows no longer preallocates
page tables for reserverd memory eagerly, which prevented us from
using this approach in the past.

We also try to allocate the heap high in the memory space.
Hopefully this makes it easier to allocate things in the low
4GB of memory that need to be there. Like jump islands for the
linker.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7e6d3d09d983337df30d12e5aaa96bae9b81b324">7e6d3d09</a></strong>
<div>
<span>by Roland Senn</span>
<i>at 2020-06-25T03:54:38-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">In `:break ident` allow out of scope and nested identifiers (Fix #3000)

This patch fixes the bug and implements the feature request of #3000.

1. If `Module` is a real module name and `identifier` a name of a
top-level function in `Module` then `:break Module.identifer` works
also for an `identifier` that is out of scope.

2. Extend the syntax for `:break identifier` to:

    :break [ModQual.]topLevelIdent[.nestedIdent]...[.nestedIdent]

`ModQual` is optional and is either the effective name of a module or
the local alias of a qualified import statement.

`topLevelIdent` is the name of a top level function in the module
referenced by `ModQual`.

`nestedIdent` is optional and the name of a function nested in a let or
where clause inside the previously mentioned function `nestedIdent` or
`topLevelIdent`.

If `ModQual` is a module name, then `topLevelIdent` can be any top level
identifier in this module. If `ModQual` is missing or a local alias of a
qualified import, then `topLevelIdent` must be in scope.

Breakpoints can be set on arbitrarily deeply nested functions, but the
whole chain of nested function names must be specified.

3. To support the new functionality rewrite the code to tab complete `:break`.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/30e42652ed895c3ed086e7834be46f93ba1cc61b">30e42652</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-06-25T03:54:39-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">make: Respect XELATEX variable

Previously we simply ignored the XELATEX variable when building
PDF documentation.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4acc2934952f4849c2082015d9bebef446d46545">4acc2934</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-06-25T03:54:39-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">hadrian/make: Detect makeindex

Previously we would simply assume that makeindex was available.
Now we correctly detect it in `configure` and respect this conclusion in
hadrian and make.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/0d61f866b43d3385be3a8521ba24503c13e8d404">0d61f866</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-06-25T03:54:40-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Expunge GhcTcId

GHC.Hs.Extension had

  type GhcPs   = GhcPass 'Parsed
  type GhcRn   = GhcPass 'Renamed
  type GhcTc   = GhcPass 'Typechecked
  type GhcTcId = GhcTc

The last of these, GhcTcId, is a vestige of the past.

This patch expunges it from GHC.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8ddbed4ad1772ac7dfc96b352a3dc35d958a5f9b">8ddbed4a</a></strong>
<div>
<span>by Adam Wespiser</span>
<i>at 2020-06-25T03:54:40-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">add examples to Data.Traversable
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/284001d00995c82a1f2b38f696138ad683b5364b">284001d0</a></strong>
<div>
<span>by Oleg Grenrus</span>
<i>at 2020-06-25T03:54:42-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Export readBinIface_
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/90f438724dbc1ef9e4b371034d44170738fe3224">90f43872</a></strong>
<div>
<span>by Zubin Duggal</span>
<i>at 2020-06-25T03:54:43-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Export everything from HsToCore.

This lets us reuse these functions in haddock, avoiding synchronization bugs.

Also fixed some divergences with haddock in that file

Updates haddock submodule
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c7dd6da7e066872a949be7c914cc700182307cd2">c7dd6da7</a></strong>
<div>
<span>by Takenobu Tani</span>
<i>at 2020-06-25T03:54:44-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Clean up haddock hyperlinks of GHC.* (part1)

This updates haddock comments only.

This patch focuses to update for hyperlinks in GHC API's haddock comments,
because broken links especially discourage newcomers.

This includes the following hierarchies:
  - GHC.Hs.*
  - GHC.Core.*
  - GHC.Stg.*
  - GHC.Cmm.*
  - GHC.Types.*
  - GHC.Data.*
  - GHC.Builtin.*
  - GHC.Parser.*
  - GHC.Driver.*
  - GHC top
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/1eb997a84669f158de9dd16a9e54d279cec22293">1eb997a8</a></strong>
<div>
<span>by Takenobu Tani</span>
<i>at 2020-06-25T03:54:44-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Clean up haddock hyperlinks of GHC.* (part2)

This updates haddock comments only.

This patch focuses to update for hyperlinks in GHC API's haddock comments,
because broken links especially discourage newcomers.

This includes the following hierarchies:

  - GHC.Iface.*
  - GHC.Llvm.*

  - GHC.Rename.*
  - GHC.Tc.*

  - GHC.HsToCore.*
  - GHC.StgToCmm.*
  - GHC.CmmToAsm.*

  - GHC.Runtime.*

  - GHC.Unit.*
  - GHC.Utils.*
  - GHC.SysTools.*
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/67a86b4d4d21954bae7aaddec7617228025a8270">67a86b4d</a></strong>
<div>
<span>by Oleg Grenrus</span>
<i>at 2020-06-25T03:54:46-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add MonadZip and MonadFix instances for Complex

These instances are taken from
https://hackage.haskell.org/package/linear-1.21/docs/Linear-Instances.html

They are the unique possible, so let they be in `base`.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c50ef26edaa537c0a13ac1a574632f9078c5671b">c50ef26e</a></strong>
<div>
<span>by Artem Pelenitsyn</span>
<i>at 2020-06-25T03:54:47-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">test suite: add reproducer for #17516
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/fe281b27d544920a2c2ddc00f6284006b85ab294">fe281b27</a></strong>
<div>
<span>by Roland Senn</span>
<i>at 2020-06-25T03:54:48-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Enable maxBound checks for OverloadedLists (Fixes #18172)

Consider the Literal `[256] :: [Data.Word.Word8]`

When the `OverloadedLists` extension is not active, then the `ol_ext` field
in the `OverLitTc` record that is passed to the function `getIntegralLit`
contains the type `Word8`. This is a simple type, and we can use its
type constructor immediately for the `warnAboutOverflowedLiterals` function.

When the `OverloadedLists` extension is active, then the `ol_ext` field
contains the type family `Item [Word8]`. The function `nomaliseType` is used
to convert it to the needed type `Word8`.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a788d4d17ad332dbfbe08e6822c52ae0de6ef496">a788d4d1</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-06-25T03:54:52-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts/Hash: Simplify freeing of HashListChunks

While looking at #18348 I noticed that the treatment of HashLists are a
bit more complex than necessary (which lead to some initial confusion on
my part). Specifically, we allocate HashLists in chunks. Each chunk
allocation makes two allocations: one for the chunk itself and one for a
HashListChunk to link together the chunks for the purposes of freeing.

Simplify this (and hopefully make the relationship between these
clearer) but allocating the HashLists and HashListChunk in a single
malloc. This will both make the implementation easier to follow and
reduce C heap fragmentation.

Note that even after this patch we fail to bound the size of the free
HashList pool. However, this is a separate bug.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d3c2d59bafe253dd7e4966a46564fb16acb1af5c">d3c2d59b</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-25T03:54:55-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">RTS: avoid overflow on 32-bit arch (#18375)

We're now correctly computing allocated bytes on 32-bit arch, so we get
huge increases.

Metric Increase:
    haddock.Cabal
    haddock.base
    haddock.compiler
    space_leak_001
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a3d69dc6c2134afe239caf4f881ba5542d2c2be0">a3d69dc6</a></strong>
<div>
<span>by Sebastian Graf</span>
<i>at 2020-06-25T23:06:18-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">GHC.Core.Unify: Make UM actions one-shot by default

This MR makes the UM monad in GHC.Core.Unify into a one-shot
monad.  See the long Note [The one-shot state monad trick].

See also #18202 and !3309, which applies this to all Reader/State-like
monads in GHC for compile-time perf improvements. The pattern used
here enables something similar to the state-hack, but is applicable to
user-defined monads, not just `IO`.

Metric Decrease 'runtime/bytes allocated' (test_env='i386-linux-deb9'):
    haddock.Cabal
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9ee58f8d900884ac8b721b6b95dbfa6500f39431">9ee58f8d</a></strong>
<div>
<span>by Matthias Pall Gissurarson</span>
<i>at 2020-06-26T17:12:45+00:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Implement the proposed -XQualifiedDo extension

Co-authored-by: Facundo Domínguez <facundo.dominguez@tweag.io>

QualifiedDo is implemented using the same placeholders for operation names in
the AST that were devised for RebindableSyntax. Whenever the renamer checks
which names to use for do syntax, it first checks if the do block is qualified
(e.g. M.do { stmts }), in which case it searches for qualified names in
the module M.

This allows users to write

    {-# LANGUAGE QualifiedDo #-}
    import qualified SomeModule as M

    f x = M.do           -- desugars to:
      y <- M.return x    -- M.return x M.>>= \y ->
      M.return y         -- M.return y M.>>
      M.return y         -- M.return y

See Note [QualifiedDo] and the users' guide for more details.

Issue #18214

Proposal:
https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0216-qualified-do.rst

Since we change the constructors `ITdo` and `ITmdo` to carry the new module
name, we need to bump the haddock submodule to account or the new shape of
these constructors.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ce987865d7594ecbcb3d27435eef773e95b2db85">ce987865</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-06-27T11:55:21-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Revamp the treatment of auxiliary bindings for derived instances

This started as a simple fix for #18321 that organically grew into a
much more sweeping refactor of how auxiliary bindings for derived
instances are handled. I have rewritten `Note [Auxiliary binders]`
in `GHC.Tc.Deriv.Generate` to explain all of the moving parts, but
the highlights are:

* Previously, the OccName of each auxiliary binding would be given
  a suffix containing a hash of its package name, module name, and
  parent data type to avoid name clashes. This was needlessly
  complicated, so we take the more direct approach of generating
  `Exact` `RdrName`s for each auxiliary binding with the same
  `OccName`, but using an underlying `System` `Name` with a fresh
  `Unique` for each binding. Unlike hashes, allocating new `Unique`s
  does not require any cleverness and avoid name clashes all the
  same...
* ...speaking of which, in order to convince the renamer that multiple
  auxiliary bindings with the same `OccName` (but different
  `Unique`s) are kosher, we now use `rnLocalValBindsLHS` instead of
  `rnTopBindsLHS` to rename auxiliary bindings. Again, see
  `Note [Auxiliary binders]` for the full story.
* I have removed the `DerivHsBind` constructor for
  `DerivStuff`—which was only used for `Data.Data`-related
  auxiliary bindings—and refactored `gen_Data_binds` to use
  `DerivAuxBind` instead. This brings the treatment of
  `Data.Data`-related auxiliary bindings in line with every other
  form of auxiliary binding.

Fixes #18321.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a403eb917bd26caf96c29d67bfe91163b593b2c9">a403eb91</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-27T11:55:59-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">ghc-bignum: fix division by zero (#18359)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/1b3d13b68c95ef9bbeca4437028531d184abcbea">1b3d13b6</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-27T11:55:59-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix ghc-bignum exceptions

We must ensure that exceptions are not simplified. Previously we used:

   case raiseDivZero of
      _ -> 0## -- dummyValue

But it was wrong because the evaluation of `raiseDivZero` was removed and
the dummy value was directly returned. See new Note [ghc-bignum exceptions].

I've also removed the exception triggering primops which were fragile.
We don't need them to be primops, we can have them exported by ghc-prim.

I've also added a test for #18359 which triggered this patch.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a74ec37c9d7679a5563ab86a8759c79c3c5de6f0">a74ec37c</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-06-27T11:56:34-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Better loop detection in findTypeShape

Andreas pointed out, in !3466, that my fix for #18304 was not
quite right.  This patch fixes it properly, by having just one
RecTcChecker rather than (implicitly) two nested ones, in
findTypeShape.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a04020b88d4935d675f989806aff251f459561e9">a04020b8</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-27T11:57:11-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">DynFlags: don't store buildTag

`DynFlags.buildTag` was a field created from the set of Ways in
`DynFlags.ways`. It had to be kept in sync with `DynFlags.ways` which
was fragile. We want to avoid global state like this (#17957).

Moreover in #14335 we also want to support loading units with different
ways: target units would still use `DynFlags.ways` but plugins would use
`GHC.Driver.Ways.hostFullWays`. To avoid having to deal both with build
tag and with ways, we recompute the buildTag on-the-fly (should be
pretty cheap) and we remove `DynFlags.buildTag` field.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/0e83efa24636c72811e4c79fe1c7e4f7cf3170cd">0e83efa2</a></strong>
<div>
<span>by Krzysztof Gogolewski</span>
<i>at 2020-06-27T11:57:49-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Don't generalize when typechecking a tuple section

The code is simpler and cleaner.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d8ba9e6f951a2f8c6e2429a8b2dcb035c392908f">d8ba9e6f</a></strong>
<div>
<span>by Peter Trommler</span>
<i>at 2020-06-28T09:19:11-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">RTS: Refactor Haskell-C glue for PPC 64-bit

Make sure the stack is 16 byte aligned even when reserved stack
bytes are not a multiple of 16 bytes.

Avoid saving r2 (TOC). On ELF v1 the function descriptor of StgReturn
has the same TOC as StgRun, on ELF v2 the TOC is recomputed in the
function prologue.

Use the ABI provided functions to save clobbered GPRs and FPRs.

Improve comments. Describe what the stack looks like and how it relates
to the respective ABIs.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/42f797b0ad034a92389e7081aa50ef4ab3434d01">42f797b0</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-06-28T09:19:46-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Use NHsCoreTy to embed types into GND-generated code

`GeneralizedNewtypeDeriving` is in the unique situation where it must
produce an `LHsType GhcPs` from a Core `Type`. Historically, this was
done with the `typeToLHsType` function, which walked over the entire
`Type` and attempted to construct an `LHsType` with the same overall
structure. `typeToLHsType` is quite complicated, however, and has
been the subject of numerous bugs over the years (e.g., #14579).

Luckily, there is an easier way to accomplish the same thing: the
`XHsType` constructor of `HsType`. `XHsType` bundles an `NHsCoreTy`,
which allows embedding a Core `Type` directly into an `HsType`,
avoiding the need to laboriously convert from one to another (as
`typeToLHsType` did). Moreover, renaming and typechecking an
`XHsType` is simple, since one doesn't need to do anything to a
Core `Type`...

...well, almost. For the reasons described in
`Note [Typechecking NHsCoreTys]` in `GHC.Tc.Gen.HsType`, we must
apply a substitution that we build from the local `tcl_env` type
environment. But that's a relatively modest price to pay.

Now that `GeneralizedNewtypeDeriving` uses `NHsCoreTy`, the
`typeToLHsType` function no longer has any uses in GHC, so this patch
rips it out. Some additional tweaks to `hsTypeNeedsParens` were
necessary to make the new `-ddump-deriv` output correctly
parenthesized, but other than that, this patch is quite
straightforward.

This is a mostly internal refactoring, although it is likely that
`GeneralizedNewtypeDeriving`-generated code will now need fewer
language extensions in certain situations than it did before.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/68530b1cd45629e5a353a37df80195ac54d26ade">68530b1c</a></strong>
<div>
<span>by Jan Hrček</span>
<i>at 2020-06-28T09:20:22-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix duplicated words and typos in comments and user guide
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/15b79befc246aa9c63dd084012dc7843ea93daaa">15b79bef</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-06-28T09:20:57-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add integer-gmp's ghc.mk and GNUmakefile to .gitignore
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/bfa5698b1ab0190820a2df19487d3d72d3a7924d">bfa5698b</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-06-28T09:21:32-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix a typo in Lint

This simple error in GHC.Core.Litn.lintJoinLams meant that
Lint reported bogus errors.

Fixes #18399
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/71006532abb88a53df7c7e0b3a5e2c8af99a48d1">71006532</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-06-30T07:10:42-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Reject nested foralls/contexts in instance types more consistently

GHC is very wishy-washy about rejecting instance declarations with
nested `forall`s or contexts that are surrounded by outermost
parentheses. This can even lead to some strange interactions with
`ScopedTypeVariables`, as demonstrated in #18240. This patch makes
GHC more consistently reject instance types with nested
`forall`s/contexts so as to prevent these strange interactions.

On the implementation side, this patch tweaks `splitLHsInstDeclTy`
and `getLHsInstDeclHead` to not look through parentheses, which can
be semantically significant. I've added a
`Note [No nested foralls or contexts in instance types]` in
`GHC.Hs.Type` to explain why. This also introduces a
`no_nested_foralls_contexts_err` function in `GHC.Rename.HsType` to
catch nested `forall`s/contexts in instance types. This function is
now used in `rnClsInstDecl` (for ordinary instance declarations) and
`rnSrcDerivDecl` (for standalone `deriving` declarations), the latter
of which fixes #18271.

On the documentation side, this adds a new
"Formal syntax for instance declaration types" section to the GHC
User's Guide that presents a BNF-style grammar for what is and isn't
allowed in instance types.

Fixes #18240. Fixes #18271.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/bccf3351a28638fba94953c4bb244ecfc3a1a044">bccf3351</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-30T07:10:46-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add ghc-bignum to 8.12 release notes
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/81704a6f3b155b0bfbc20f53cd821be3cb9006a7">81704a6f</a></strong>
<div>
<span>by David Eichmann</span>
<i>at 2020-06-30T07:10:48-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Update ssh keys in CI performance metrics upload script
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/85310fb83fdb7d7294bd453026102fc42000bf14">85310fb8</a></strong>
<div>
<span>by Joshua Price</span>
<i>at 2020-06-30T07:10:49-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add missing Ix instances for tuples of size 6 through 15 (#16643)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/cbb6b62f54c77637e29bc66e3d1214541c347753">cbb6b62f</a></strong>
<div>
<span>by Vladislav Zavialov</span>
<i>at 2020-07-01T15:41:38-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Implement -XLexicalNegation (GHC Proposal #229)

This patch introduces a new extension, -XLexicalNegation, which detects
whether the minus sign stands for negation or subtraction using the
whitespace-based rules described in GHC Proposal #229.

Updates haddock submodule.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/fb5a0d01d575cdb830918a6a0406f385de2749c2">fb5a0d01</a></strong>
<div>
<span>by Martin Handley</span>
<i>at 2020-07-01T15:42:14-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">#17169: Clarify Fixed's Enum instance.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b316804dbafe1d0287fd33f656b7ce5711ec34f7">b316804d</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-07-01T15:42:49-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Improve debug tracing for substitution

This patch improves debug tracing a bit (#18395)

* Remove the ancient SDoc argument to substitution, replacing it
  with a HasDebugCallStack constraint. The latter does the same
  job (indicate the call site) but much better.

* Add HasDebugCallStack to simpleOptExpr, exprIsConApp_maybe
  I needed this to help nail the lookupIdSubst panic in
  #18326, #17784
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/5c9fabb82b39aed9e61c6b78c72312b20a568c68">5c9fabb8</a></strong>
<div>
<span>by Hécate</span>
<i>at 2020-07-01T15:43:25-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add most common return values for `os` and `arch`
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/76d8cc744977d98f6a427b1816198709e2d2e856">76d8cc74</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-07-01T15:44:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Desugar quoted uses of DerivingVia and expression type signatures properly

The way that `GHC.HsToCore.Quote` desugared quoted `via` types (e.g.,
`deriving via forall a. [a] instance Eq a => Eq (List a)`) and
explicit type annotations in signatures (e.g.,
`f = id @a :: forall a. a -> a`) was completely wrong, as it did not
implement the scoping guidelines laid out in
`Note [Scoped type variables in bindings]`. This is easily fixed.

While I was in town, I did some minor cleanup of related Notes:

* `Note [Scoped type variables in bindings]` and
  `Note [Scoped type variables in class and instance declarations]`
  say very nearly the same thing. I decided to just consolidate the
  two Notes into `Note [Scoped type variables in quotes]`.
* `Note [Don't quantify implicit type variables in quotes]` is
  somewhat outdated, as it predates GHC 8.10, where the
  `forall`-or-nothing rule requires kind variables to be explicitly
  quantified in the presence of an explicit `forall`. As a result,
  the running example in that Note doesn't even compile. I have
  changed the example to something simpler that illustrates the
  same point that the original Note was making.

Fixes #18388.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/44d6a3352d708785b75aeb616bfc7efff839184e">44d6a335</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-02T02:54:54-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">T16012: Be verbose on failure.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/f985333002c1690bf49debcc64fc65ed1d1de244">f9853330</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-07-02T02:55:29-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Bump ghc-prim version to 0.7.0

Fixes #18279. Bumps the `text` submodule.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/23e4e04700f840e3c4e75ccb2085aea05bfb5318">23e4e047</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-07-02T10:46:31-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Hadrian: fix PowerPC64le support (#17601)

[ci skip]
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/3cdd8d69f5c1d63137b9b56992bb9b74a6785459">3cdd8d69</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-07-02T10:47:08-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">NCG: correctly handle addresses with huge offsets (#15570)

Before this patch we could generate addresses of this form:

   movzbl cP0_str+-9223372036854775808,%eax

The linker can't handle them because the offset is too large:

   ld.lld: error: Main.o:(.text+0xB3): relocation R_X86_64_32S out of range: -9223372036852653050 is not in [-2147483648, 2147483647]

With this patch we detect those cases and generate:

   movq $-9223372036854775808,%rax
   addq $cP0_str,%rax
   movzbl (%rax),%eax

I've also refactored `getAmode` a little bit to make it easier to
understand and to trace.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4d90b3ff02002ea25460d087dde56f69a9641096">4d90b3ff</a></strong>
<div>
<span>by Gabor Greif</span>
<i>at 2020-07-02T20:07:59-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">No need for CURSES_INCLUDE_DIRS

This is a leftover from ef63ff27251a20ff11e58c9303677fa31e609a88</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/f08d6316d3d19b627550d99b4364e9bf0b45c329">f08d6316</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-07-02T20:08:36-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Replace Opt_SccProfilingOn flag with sccProfilingEnabled helper function

SCC profiling was enabled in a convoluted way: if WayProf was enabled,
Opt_SccProfilingOn general flag was set (in
`GHC.Driver.Ways.wayGeneralFlags`), and then this flag was queried in
various places.

There is no need to go via general flags, so this patch defines a
`sccProfilingEnabled :: DynFlags -> Bool` helper function that just
checks whether WayProf is enabled.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8cc7274b8de254c7266b61fadbc6795dc37bd1e9">8cc7274b</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-07-03T02:49:27-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts/ProfHeap: Only allocate the Censuses that we need

When not LDV profiling there is no reason to allocate 32 Censuses; one
will do. This is a very small memory footprint optimisation, but it
comes for free.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b835112cbeaa6e34a8bae7b7697bdf2826edaa9a">b835112c</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-07-03T02:49:27-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts/ProfHeap: Free old allocations when reinitialising Censuses

Previously when not LDV profiling we would repeatedly reinitialise
`censuses[0]` with `initEra`. This failed to free the `Arena` and
`HashTable` from the old census, resulting in a memory leak.

Fixes #18348.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/34be6523a220b2be972b391d8ad26b75f7c26eb1">34be6523</a></strong>
<div>
<span>by Valery Tolstov</span>
<i>at 2020-07-03T02:50:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Mention flags that are not enabled by -Wall (#18372)

* Mention missing flags that are not actually enabled by -Wall (docs/users_guide/using-warnings.rst)
* Additionally remove -Wmissing-monadfail-instances from the list of flags enabled by -Wcompat, as it is not the case since 8.8
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/edc8d22b2eea5d43dd6c3d0e4b2f85fc02ffa5ce">edc8d22b</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-07-03T02:50:40-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">LLVM: support R9 and R10 registers

d535ef006d85dbdb7cda2b09c5bc35cb80108909 allowed the use of up to 10
vanilla registers but didn't update LLVM backend to support them. This
patch fixes it.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d7c1ba52036c9796faac8db6da80133d31888622">d7c1ba52</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-07-03T08:32:49+01:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Improve handling of data type return kinds

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

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

Fixes #18300, #18357

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

New tests (T18300, T18357) cause an ASSERT failure in HEAD.
</pre>
</li>
</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="#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="#8a5cd068459120cddf3814e7b9e02003b87647ba">
compiler/GHC/Builtin/Types/Prim.hs
</a>
</li>
<li class="file-stats">
<a href="#d95fdf6575459444666f72b2281534e0558a4ba0">
compiler/GHC/Builtin/Utils.hs
</a>
</li>
<li class="file-stats">
<a href="#451725cc4e5d443a3b7c2adcdf224840f953b7e2">
compiler/GHC/Builtin/primops.txt.pp
</a>
</li>
<li class="file-stats">
<a href="#5c66928780aaad0eb5888511dc4b0b08492c69fa">
compiler/GHC/ByteCode/Types.hs
</a>
</li>
<li class="file-stats">
<a href="#db697f6aea9f93f1583f1d5c62d25570a1e07f73">
compiler/GHC/Cmm/CLabel.hs
</a>
</li>
<li class="file-stats">
<a href="#eae45922f6e633780395508f44c14a5ed7959e7a">
compiler/GHC/Cmm/Dataflow/Block.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="#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="#5986ebaacfa99d264abfd2f7ef19d99a64db720f">
compiler/GHC/CmmToAsm/BlockLayout.hs
</a>
</li>
<li class="file-stats">
<a href="#d6e95c6ffd8955a51f59d69de7525bebd693db69">
compiler/GHC/CmmToAsm/CFG.hs
</a>
</li>
<li class="file-stats">
<a href="#31959c38fe93e481a7160526f11fa80db82d20b7">
compiler/GHC/CmmToAsm/Dwarf/Constants.hs
</a>
</li>
<li class="file-stats">
<a href="#ea29061dab1b843e0ea9294afc614998f3a8d08f">
compiler/GHC/CmmToAsm/Monad.hs
</a>
</li>
<li class="file-stats">
<a href="#3aba9ceb20d68f25343fe3a27b2b7a4f8fea68da">
compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs
</a>
</li>
<li class="file-stats">
<a href="#2892194edc6317f317205814e79ce0241e8ff8c6">
compiler/GHC/CmmToAsm/SPARC/CodeGen/Base.hs
</a>
</li>
<li class="file-stats">
<a href="#ac425fefb01f046d6c5170ebcf3962923cee32b8">
compiler/GHC/CmmToAsm/SPARC/Regs.hs
</a>
</li>
<li class="file-stats">
<a href="#2bae5947e9412f6deebf4db7dcb89d780913130f">
compiler/GHC/CmmToAsm/X86/CodeGen.hs
</a>
</li>
<li class="file-stats">
<a href="#335d279236d65dcf13f2bab3891e515cb803203c">
compiler/GHC/CmmToAsm/X86/Ppr.hs
</a>
</li>
<li class="file-stats">
<a href="#7afeacc3c3f223aef50037f68cea140093ecc04a">
compiler/GHC/CmmToLlvm/Regs.hs
</a>
</li>
<li class="file-stats">
<a href="#182d6a315e784018aa9c8b2ad736036b97bd5d48">
compiler/GHC/Core.hs
</a>
</li>
<li class="file-stats">
<a href="#e39f2416dd3b2af571ddd26dcca3476a55810c41">
compiler/GHC/Core/Class.hs
</a>
</li>
<li class="file-stats">
<a href="#783e5dae6e86931f06700fc088fb7d48c8a07386">
compiler/GHC/Core/Coercion.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/32a50de133cf859931189b8eecbe9ad9ff1271cd...d7c1ba52036c9796faac8db6da80133d31888622">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>