<!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/boxed-rep
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/fcfda909fd7fcf539ff31717ce01a56292abb92f">fcfda909</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-11-11T03:19:59-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">nativeGen: Make makeImportsDoc take an NCGConfig rather than DynFlags

It appears this was an oversight as there is no reason the full DynFlags
is necessary.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6e23695e7d84aa248e7ca20bdb8d133f9b356548">6e23695e</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-11-11T03:19:59-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Move this_module into NCGConfig

In various places in the NCG we need the Module currently being
compiled. Let's move this into the environment instead of chewing threw
another register.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c6264a2d652517954b7cd076c7bc4487ed17c97d">c6264a2d</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-11-11T03:20:00-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">codeGen: Produce local symbols for module-internal functions

It turns out that some important native debugging/profiling tools (e.g.
perf) rely only on symbol tables for function name resolution (as
opposed to using DWARF DIEs). However, previously GHC would emit
temporary symbols (e.g. `.La42b`) to identify module-internal
entities. Such symbols are dropped during linking and therefore not
visible to runtime tools (in addition to having rather un-helpful unique
names). For instance, `perf report` would often end up attributing all
cost to the libc `frame_dummy` symbol since Haskell code was no covered
by any proper symbol (see #17605).

We now rather follow the model of C compilers and emit
descriptively-named local symbols for module internal things. Since this
will increase object file size this behavior can be disabled with the
`-fno-expose-internal-symbols` flag.

With this `perf record` can finally be used against Haskell executables.
Even more, with `-g3` `perf annotate` provides inline source code.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/584058ddff71460023712a8d816b83b581e6e78f">584058dd</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-11-11T03:20:00-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Enable -fexpose-internal-symbols when debug level >=2

This seems like a reasonable default as the object file size increases
by around 5%.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c34a4b98b1f09ea3096d39a839a86f2d7185c796">c34a4b98</a></strong>
<div>
<span>by Ömer Sinan Ağacan</span>
<i>at 2020-11-11T03:20:35-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix and enable object unloading in GHCi

Fixes #16525 by tracking dependencies between object file symbols and
marking symbol liveness during garbage collection

See Note [Object unloading] in CheckUnload.c for details.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2782487f5f6ad9df4dc8725226a47f07fec77f9f">2782487f</a></strong>
<div>
<span>by Ray Shih</span>
<i>at 2020-11-11T03:20:35-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add loadNativeObj and unloadNativeObj

(This change is originally written by niteria)

This adds two functions:
* `loadNativeObj`
* `unloadNativeObj`
and implements them for Linux.

They are useful if you want to load a shared object with Haskell code
using the system linker and have GHC call dlclose() after the
code is no longer referenced from the heap.

Using the system linker allows you to load the shared object
above outside the low-mem region. It also loads the DWARF sections
in a way that `perf` understands.

`dl_iterate_phdr` is what makes this implementation Linux specific.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7a65f9e140906087273ce95f062775f18f6a708d">7a65f9e1</a></strong>
<div>
<span>by GHC GitLab CI</span>
<i>at 2020-11-11T03:20:35-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts: Introduce highMemDynamic
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e9e1b2e75de17be47ab887a26943f5517a8463ac">e9e1b2e7</a></strong>
<div>
<span>by GHC GitLab CI</span>
<i>at 2020-11-11T03:20:35-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Introduce test for dynamic library unloading

This uses the highMemDynamic flag introduced earlier to verify that
dynamic objects are properly unloaded.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/5506f1342e51bad71a7525ddad0650d1ac63afeb">5506f134</a></strong>
<div>
<span>by Krzysztof Gogolewski</span>
<i>at 2020-11-11T03:21:14-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Force argument in setIdMult (#18925)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/787e93ae141ae0f33bc36895494d48a2a5e49e08">787e93ae</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-11-11T23:14:11-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite: Add testcase for #18733
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/5353fd500b1e92636cd9d45274585fd88a915ff6">5353fd50</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-11-12T10:05:30-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">compiler: Fix recompilation checking

In ticket #18733 we noticed a rather serious deficiency in the current
fingerprinting logic for recursive groups. I have described the old
fingerprinting story and its problems in Note [Fingerprinting recursive
groups] and have reworked the story accordingly to avoid these issues.

Fixes #18733.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/63fa399726ff85a3ff4ca42a88f3d8a00921a718">63fa3997</a></strong>
<div>
<span>by Sebastian Graf</span>
<i>at 2020-11-13T14:29:39-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Arity: Rework `ArityType` to fix monotonicity (#18870)

As we found out in #18870, `andArityType` is not monotone, with
potentially severe consequences for termination of fixed-point
iteration. That showed in an abundance of "Exciting arity" DEBUG
messages that are emitted whenever we do more than one step in
fixed-point iteration.

The solution necessitates also recording `OneShotInfo` info for
`ABot` arity type. Thus we get the following definition for `ArityType`:

```
data ArityType = AT [OneShotInfo] Divergence
```

The majority of changes in this patch are the result of refactoring use
sites of `ArityType` to match the new definition.

The regression test `T18870` asserts that we indeed don't emit any DEBUG
output anymore for a function where we previously would have.
Similarly, there's a regression test `T18937` for #18937, which we
expect to be broken for now.

Fixes #18870.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/197d59facbe8f9799df47e86c99f401ced487040">197d59fa</a></strong>
<div>
<span>by Sebastian Graf</span>
<i>at 2020-11-13T14:29:39-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Arity: Emit "Exciting arity" warning only after second iteration (#18937)

See Note [Exciting arity] why we emit the warning at all and why we only
do after the second iteration now.

Fixes #18937.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/de7ec9dd2bd573d5950ae294747d2bdb45051000">de7ec9dd</a></strong>
<div>
<span>by David Eichmann</span>
<i>at 2020-11-13T14:30:16-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add rts_listThreads and rts_listMiscRoots to RtsAPI.h

These are used to find the current roots of the garbage collector.

Co-authored-by: Sven Tennie's avatarSven Tennie <sven.tennie@gmail.com>
Co-authored-by: Matthew Pickering's avatarMatthew Pickering <matthewtpickering@gmail.com>
Co-authored-by: default avatarBen Gamari <bgamari.foss@gmail.com>
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/24a86f09da3426cf1006004bc45d312725280dd5">24a86f09</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-11-13T14:30:51-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">gitlab-ci: Cache cabal store in linting job
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/0a7e592cb1883824a14639372ba284766849ff3a">0a7e592c</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-11-15T03:35:45-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">nativeGen/dwarf: Fix procedure end addresses

Previously the `.debug_aranges` and `.debug_info` (DIE) DWARF
information would claim that procedures (represented with a
`DW_TAG_subprogram` DIE) would only span the range covered by their entry
block. This omitted all of the continuation blocks (represented by
`DW_TAG_lexical_block` DIEs), confusing `perf`. Fix this by introducing
a end-of-procedure label and using this as the `DW_AT_high_pc` of
procedure `DW_TAG_subprogram` DIEs

Fixes #17605.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/1e19183d08a3312ac2331b8284d17bc17170a51e">1e19183d</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-11-15T03:35:45-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">nativeGen/dwarf: Only produce DW_AT_source_note DIEs in -g3

Standard debugging tools don't know how to understand these so let's not
produce them unless asked.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ad73370f6770480f1786aab8f2b7f5fe155152c8">ad73370f</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-11-15T03:35:45-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">nativeGen/dwarf: Use DW_AT_linkage instead of DW_AT_MIPS_linkage
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a2539650cc9c6606c6b50dd5dd96caa0209b408c">a2539650</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-11-15T03:35:45-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">gitlab-ci: Add DWARF release jobs for Debian 10, Fedora27
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d61adb3dace8f52e21f302989182145a0efa103f">d61adb3d</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-11-15T03:36:21-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Name (tc)SplitForAll- functions more consistently

There is a zoo of `splitForAll-` functions in `GHC.Core.Type` (as well as
`tcSplitForAll-` functions in `GHC.Tc.Utils.TcType`) that all do very similar
things, but vary in the particular form of type variable that they return. To
make things worse, the names of these functions are often quite misleading.
Some particularly egregious examples:

* `splitForAllTys` returns `TyCoVar`s, but `splitSomeForAllTys` returns
  `VarBndr`s.
* `splitSomeForAllTys` returns `VarBndr`s, but `tcSplitSomeForAllTys` returns
  `TyVar`s.
* `splitForAllTys` returns `TyCoVar`s, but `splitForAllTysInvis` returns
  `InvisTVBinder`s. (This in particular arose in the context of #18939, and
  this finally motivated me to bite the bullet and improve the status quo
  vis-à-vis how we name these functions.)

In an attempt to bring some sanity to how these functions are named, I have
opted to rename most of these functions en masse to use consistent suffixes
that describe the particular form of type variable that each function returns.
In concrete terms, this amounts to:

* Functions that return a `TyVar` now use the suffix `-TyVar`.
  This caused the following functions to be renamed:
  * `splitTyVarForAllTys` -> `splitForAllTyVars`
  * `splitForAllTy_ty_maybe` -> `splitForAllTyVar_maybe`
  * `tcSplitForAllTys` -> `tcSplitForAllTyVars`
  * `tcSplitSomeForAllTys` -> `tcSplitSomeForAllTyVars`
* Functions that return a `CoVar` now use the suffix `-CoVar`.
  This caused the following functions to be renamed:
  * `splitForAllTy_co_maybe` -> `splitForAllCoVar_maybe`
* Functions that return a `TyCoVar` now use the suffix `-TyCoVar`.
  This caused the following functions to be renamed:
  * `splitForAllTy` -> `splitForAllTyCoVar`
  * `splitForAllTys` -> `splitForAllTyCoVars`
  * `splitForAllTys'` -> `splitForAllTyCoVars'`
  * `splitForAllTy_maybe` -> `splitForAllTyCoVar_maybe`
* Functions that return a `VarBndr` now use the suffix corresponding to the
  most relevant type synonym. This caused the following functions to be renamed:
  * `splitForAllVarBndrs` -> `splitForAllTyCoVarBinders`
  * `splitForAllTysInvis` -> `splitForAllInvisTVBinders`
  * `splitForAllTysReq` -> `splitForAllReqTVBinders`
  * `splitSomeForAllTys` -> `splitSomeForAllTyCoVarBndrs`
  * `tcSplitForAllVarBndrs` -> `tcSplitForAllTyVarBinders`
  * `tcSplitForAllTysInvis` -> `tcSplitForAllInvisTVBinders`
  * `tcSplitForAllTysReq` -> `tcSplitForAllReqTVBinders`
  * `tcSplitForAllTy_maybe` -> `tcSplitForAllTyVarBinder_maybe`

Note that I left the following functions alone:

* Functions that split apart things besides `ForAllTy`s, such as `splitFunTys`
  or `splitPiTys`. Thankfully, there are far fewer of these functions than
  there are functions that split apart `ForAllTy`s, so there isn't much of a
  pressing need to apply the new naming convention elsewhere.
* Functions that split apart `ForAllCo`s in `Coercion`s, such as
  `GHC.Core.Coercion.splitForAllCo_maybe`. We could theoretically apply the new
  naming convention here, but then we'd have to figure out how to disambiguate
  `Type`-splitting functions from `Coercion`-splitting functions. Ultimately,
  the `Coercion`-splitting functions aren't used nearly as much as the
  `Type`-splitting functions, so I decided to leave the former alone.

This is purely refactoring and should cause no change in behavior.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/645444af9eb185684c750c95e4740d301352b2b9">645444af</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-11-15T03:36:21-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Use tcSplitForAllInvisTyVars (not tcSplitForAllTyVars) in more places

The use of `tcSplitForAllTyVars` in `tcDataFamInstHeader` was the immediate
cause of #18939, and replacing it with a new `tcSplitForAllInvisTyVars`
function (which behaves like `tcSplitForAllTyVars` but only splits invisible
type variables) fixes the issue. However, this led me to realize that _most_
uses of `tcSplitForAllTyVars` in GHC really ought to be
`tcSplitForAllInvisTyVars` instead. While I was in town, I opted to replace
most uses of `tcSplitForAllTys` with `tcSplitForAllTysInvis` to reduce the
likelihood of such bugs in the future.

I say "most uses" above since there is one notable place where we _do_ want
to use `tcSplitForAllTyVars`: in `GHC.Tc.Validity.forAllTyErr`, which produces
the "`Illegal polymorphic type`" error message if you try to use a higher-rank
`forall` without having `RankNTypes` enabled. Here, we really do want to split
all `forall`s, not just invisible ones, or we run the risk of giving an
inaccurate error message in the newly added `T18939_Fail` test case.

I debated at some length whether I wanted to name the new function
`tcSplitForAllInvisTyVars` or `tcSplitForAllTyVarsInvisible`, but in the end,
I decided that I liked the former better. For consistency's sake, I opted to
rename the existing `splitPiTysInvisible` and `splitPiTysInvisibleN` functions
to `splitInvisPiTys` and `splitPiTysInvisN`, respectively, so that they use the
same naming convention. As a consequence, this ended up requiring a `haddock`
submodule bump.

Fixes #18939.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8887102fc4ed8ed1089c1aafd19bab424ad706f3">8887102f</a></strong>
<div>
<span>by Moritz Angermann</span>
<i>at 2020-11-15T03:36:56-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">AArch64/arm64 adjustments

This addes the necessary logic to support aarch64 on elf, as well
as aarch64 on mach-o, which Apple calls arm64.

We change architecture name to AArch64, which is the official arm
naming scheme.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/fc644b1a643128041cfec25db84e417851e28bab">fc644b1a</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-11-15T03:37:31-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">ghc-bin: Build with eventlogging by default

We now have all sorts of great facilities using the
eventlog which were previously unavailable without
building a custom GHC. Fix this by linking with
`-eventlog` by default.</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/52114fa0f97805d4c4924bc3abce1a8b0fc7a5c6">52114fa0</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-11-16T11:48:47+01:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add Addr# atomic primops (#17751)

This reuses the codegen used for ByteArray#'s atomic primops.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8150f6546e6fd0006252e245d5697f13ffd8ce3e">8150f654</a></strong>
<div>
<span>by Sebastian Graf</span>
<i>at 2020-11-18T23:38:40-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">PmCheck: Print types of uncovered patterns (#18932)

In order to avoid confusion as in #18932, we display the type of the
match variables in the non-exhaustiveness warning, e.g.

```
T18932.hs:14:1: warning: [-Wincomplete-patterns]
    Pattern match(es) are non-exhaustive
    In an equation for ‘g’:
        Patterns of type  ‘T a’, ‘T a’, ‘T a’ not matched:
            (MkT2 _) (MkT1 _) (MkT1 _)
            (MkT2 _) (MkT1 _) (MkT2 _)
            (MkT2 _) (MkT2 _) (MkT1 _)
            (MkT2 _) (MkT2 _) (MkT2 _)
            ...
   |
14 | g (MkT1 x) (MkT1 _) (MkT1 _) = x
   | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
```

It also allows us to omit the type signature on wildcard matches which
we previously showed in only some situations, particularly
`-XEmptyCase`.

Fixes #18932.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/165352a2d163537afb01a835bccc7cd0a667410a">165352a2</a></strong>
<div>
<span>by Krzysztof Gogolewski</span>
<i>at 2020-11-20T02:08:36-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Export indexError from GHC.Ix (#18579)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b57845c3d80f5bed8f498f27fb7a318f2b2f8b2c">b57845c3</a></strong>
<div>
<span>by Kamil Dworakowski</span>
<i>at 2020-11-20T02:09:16-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Clarify interruptible FFI wrt masking state
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/321d1bd8a79ab39c3c9e8697fffb0107c43f83cf">321d1bd8</a></strong>
<div>
<span>by Sebastian Graf</span>
<i>at 2020-11-20T02:09:51-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix strictness signatures of `prefetchValue*#` primops

Their strictness signatures said the primops are strict in their first
argument, which is wrong: Handing it a thunk will prefetch the pointer
to the thunk, but not evaluate it. Hence not strict.

The regression test `T8256` actually tests for laziness in the first
argument, so GHC apparently never exploited the strictness signature.

See also https://gitlab.haskell.org/ghc/ghc/-/issues/8256#note_310867,
where this came up.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/0aec78b6c97cee58ba20bfcb959f1369b80c4e4c">0aec78b6</a></strong>
<div>
<span>by Sebastian Graf</span>
<i>at 2020-11-20T02:09:51-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Demand: Interleave usage and strictness demands (#18903)

As outlined in #18903, interleaving usage and strictness demands not
only means a more compact demand representation, but also allows us to
express demands that we weren't easily able to express before.

Call demands are *relative* in the sense that a call demand `Cn(cd)`
on `g` says "`g` is called `n` times. *Whenever `g` is called*, the
result is used according to `cd`". Example from #18903:

```hs
h :: Int -> Int
h m =
  let g :: Int -> (Int,Int)
      g 1 = (m, 0)
      g n = (2 * n, 2 `div` n)
      {-# NOINLINE g #-}
  in case m of
    1 -> 0
    2 -> snd (g m)
    _ -> uncurry (+) (g m)
```

Without the interleaved representation, we would just get `L` for the
strictness demand on `g`. Now we are able to express that whenever
`g` is called, its second component is used strictly in denoting `g`
by `1C1(P(1P(U),SP(U)))`. This would allow Nested CPR to unbox the
division, for example.

Fixes #18903.
While fixing regressions, I also discovered and fixed #18957.

Metric Decrease:
    T13253-spj
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/3a55b3a2574f913d046f3a6f82db48d7f6df32e3">3a55b3a2</a></strong>
<div>
<span>by Sebastian Graf</span>
<i>at 2020-11-20T02:09:51-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Update user's guide entry on demand analysis and worker/wrapper

The demand signature notation has been undocumented for a long time.
The only source to understand it, apart from reading the `Outputable`
instance, has been an outdated wiki page.

Since the previous commits have reworked the demand lattice, I took
it as an opportunity to also write some documentation about notation.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/fc963932018ccf5445613ec0932d726b51887769">fc963932</a></strong>
<div>
<span>by Greg Steuck</span>
<i>at 2020-11-20T02:10:31-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Find hadrian location more reliably in cabal-install output

Fix #18944
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9f40cf6ca9fb24dbc55f7eae43e2b89aa12bf251">9f40cf6c</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-11-20T02:11:07-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts/linker: Align bssSize to page size when mapping symbol extras

We place symbol_extras right after bss. We also need
to ensure that symbol_extras can be mprotect'd independently from the
rest of the image. To ensure this we round up the size of bss to a page
boundary, thus ensuring that symbol_extras is also page-aligned.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b739c319dd56fa2aabd8007cc200eafb3c7651a7">b739c319</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-11-20T02:11:43-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">gitlab-ci: Add usage message to ci.sh
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/802e9180dd9a9a88c4e8869f0de1048e1edd6343">802e9180</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-11-20T02:11:43-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">gitlab-ci: Add VERBOSE environment variable

And change the make build system's default behavior to V=0, greatly
reducing build log sizes.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2a8a979c24fe34a81a438ae179693ddaca12709f">2a8a979c</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-11-21T01:13:26-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">users-guide: A bit of clean-up in profiling flag documentation
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/56804e33a05729f5a5340d3680ae2849e30a9e86">56804e33</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-11-21T01:13:26-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite: Refactor CountParserDeps
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/53ad67eacacde8fde452f1a323d5886183375182">53ad67ea</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-11-21T01:13:26-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Introduce -fprof-callers flag

This introducing a new compiler flag to provide a convenient way to
introduce profiler cost-centers on all occurrences of the named
identifier.

Closes #18566.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ecfd0278cb811c93853c176fe5df60222d1a8fb5">ecfd0278</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-11-21T01:14:09-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Move Plugins into HscEnv (#17957)

Loaded plugins have nothing to do in DynFlags so this patch moves them
into HscEnv (session state).

"DynFlags plugins" become "Driver plugins" to still be able to register
static plugins.

Bump haddock submodule
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/72f2257c792e6178933f12ee3401939da11584b6">72f2257c</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-11-21T01:14:09-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Don't initialize plugins in the Core2Core pipeline

Some plugins can be added via TH (cf addCorePlugin). Initialize them in
the driver instead of in the Core2Core pipeline.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ddbeeb3c7dc7a2781801cc0e6539d2b4b0e97a20">ddbeeb3c</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-11-21T01:14:44-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add regression test for #10504

This issue was fixed at some point between GHC 8.0 and 8.2. Let's add a
regression test to ensure that it stays fixed.

Fixes #10504.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a4a6dc2a90e28c34054d0cfd4c6fd962bf4adc2e">a4a6dc2a</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-11-21T01:15:21-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">dwarf: Apply info table offset consistently

Previously we failed to apply the info table offset to the aranges and
DIEs, meaning that we often failed to unwind in gdb. For some reason
this only seemed to manifest in the RTS's Cmm closures. Nevertheless,
now we can unwind completely up to `main`
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/69bfbc216c2278c9796aa999c7815c19c12b0f2c">69bfbc21</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-11-21T01:15:56-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">hadrian: Disable stripping when debug information is enabled
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7e93ae8b2257c17d5ae5ef7832db723e897c8e8b">7e93ae8b</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-11-21T13:13:29-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts: Post ticky entry counts to the eventlog

We currently only post the entry counters, not the other global
counters as in my experience the former are more useful. We use the heap
profiler's census period to decide when to dump.

Also spruces up the documentation surrounding ticky-ticky a bit.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/bc9c3916df96a20c58b91fd383a0da77ec83c4b0">bc9c3916</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-11-22T06:28:10-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Implement -ddump-c-backend argument

To dump output of the C backend.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/901bc2208a115e0f8313b3aa9abc76fd05509aaa">901bc220</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-11-22T12:39:02-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Bump time submodule to 1.11.1

Also bumps directory, Cabal, hpc, time, and unix submodules.

Closes #18847.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/92c0afbf592e71dae3c80cec09b1596df50ff8a9">92c0afbf</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-11-22T12:39:38-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">hadrian: Dump STG when ticky is enabled

This changes the "ticky" modifier to enable dumping of final STG as this
is generally needed to make sense of the ticky profiles.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d23fef68415ce6587f77e9530cb0571bb90b31cc">d23fef68</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-11-22T12:39:38-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">hadrian: Introduce notion of flavour transformers

This extends Hadrian's notion of "flavour", as described in #18942.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/179d0becd2ddfa216f7b221df9fc520a352fdbe7">179d0bec</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-11-22T12:39:38-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">hadrian: Add a viaLlvmBackend modifier

Note that this also slightly changes the semantics of these flavours as
we only use LLVM for >= stage1 builds.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d4d95e51a463e539fceb1c6f191e84adaa337e3b">d4d95e51</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-11-22T12:39:38-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">hadrian: Add profiled_ghc and no_dynamic_ghc modifiers
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6815603f271484766425ff2e37043b78da2d073c">6815603f</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-11-22T12:39:38-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">hadrian: Drop redundant flavour definitions

Drop the profiled, LLVM, and ThreadSanitizer flavour definitions as
these can now be realized with flavour transformers.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/f88f43398217a5f4c2d326555e21fb1417a21db2">f88f4339</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-11-24T02:43:20-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts: Flush eventlog buffers from flushEventLog

As noted in #18043, flushTrace failed flush anything beyond the writer.
This means that a significant amount of data sitting in capability-local
event buffers may never get flushed, despite the users' pleads for us to
flush.

Fix this by making flushEventLog flush all of the event buffers before
flushing the writer.

Fixes #18043.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7c03cc5010999d0f0f9dfc549984023b3a1f2c8d">7c03cc50</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-11-24T02:43:55-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">gitlab-ci: Run LLVM job on appropriately-labelled MRs

Namely, those marked with the ~"LLVM backend" label
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9b95d815d718ce671e9e87b8a2eb0534ed5688dd">9b95d815</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-11-24T02:43:55-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">gitlab-ci: Run LLVM builds on Debian 10

The current Debian 9 image doesn't provide LLVM 7.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2ed3e6c0f179c06828712832d1176519cdfa82a6">2ed3e6c0</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-11-24T02:43:55-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">CmmToLlvm: Declare signature for memcmp

Otherwise `opt` fails with:

    error: use of undefined value '@memcmp$def'
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/be5d74caab64abf9d986fc7290f62731db7e73e7">be5d74ca</a></strong>
<div>
<span>by Moritz Angermann</span>
<i>at 2020-11-26T16:00:32-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">[Sized Cmm] properly retain sizes.

This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int#  with
Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us
with properly sized primitives in the codegenerator instead of pretending
they are all full machine words.

This came up when implementing darwinpcs for arm64.  The darwinpcs reqires
us to pack function argugments in excess of registers on the stack.  While
most procedure call standards (pcs) assume arguments are just passed in
8 byte slots; and thus the caller does not know the exact signature to make
the call, darwinpcs requires us to adhere to the prototype, and thus have
the correct sizes.  If we specify CInt in the FFI call, it should correspond
to the C int, and not just be Word sized, when it's only half the size.

This does change the expected output of T16402 but the new result is no
less correct as it eliminates the narrowing (instead of the `and` as was
previously done).

Bumps the array, bytestring, text, and binary submodules.

Co-Authored-By: Ben Gamari <ben@well-typed.com>

Metric Increase:
    T13701
    T14697
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a84e53f978341135355c5c82cd7af2ae2efa5e72">a84e53f9</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-11-26T16:00:32-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">RTS: Fix failed inlining of copy_tag.

On windows using gcc-10 gcc failed to inline copy_tag into evacuate.

To fix this we now set the always_inline attribute for the various
copy* functions in Evac.c. The main motivation here is not the
overhead of the function call, but rather that this allows the code
to "specialize" for the size of the closure we copy which is often
known at compile time.

An earlier commit also tried to avoid evacuate_large inlining. But
didn't quite succeed. So I also marked evacuate_large as noinline.

Fixes #12416
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/cdbd16f5450998ad27f376e97b11d3e2873b95f9">cdbd16f5</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-11-26T16:00:33-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix toArgRep to support 64-bit reps on all systems

[This is @Ericson2314 writing a commit message for @hsyl20's patch.]

(Progress towards #11953, #17377, #17375)

`Int64Rep` and `Word64Rep` are currently broken on 64-bit systems.  This
is because they should use "native arg rep" but instead use "large arg
rep" as they do on 32-bit systems, which is either a non-concept or a
128-bit rep depending on one's vantage point.

Now, these reps currently aren't used during 64-bit compilation, so the
brokenness isn't observed, but I don't think that constitutes reasons
not to fix it. Firstly, the linked issues there is a clearly expressed
desire to use explicit-bitwidth constructs in more places. Secondly, per
[1], there are other bugs that *do* manifest from not threading
explicit-bitwidth information all the way through the compilation
pipeline. One can therefore view this as one piece of the larger effort
to do that, improve ergnomics, and squash remaining bugs.

Also, this is needed for !3658. I could just merge this as part of that,
but I'm keen on merging fixes "as they are ready" so the fixes that
aren't ready are isolated and easier to debug.

[1]: https://mail.haskell.org/pipermail/ghc-devs/2020-October/019332.html
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a9378e690d79ea5fce18aad96c76c8eb34f2ebba">a9378e69</a></strong>
<div>
<span>by Tim Barnes</span>
<i>at 2020-11-26T16:00:34-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Set dynamic users-guide TOC spacing (fixes #18554)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/86a59d930fa6ab0889792c1d67b1d29ba1edec1f">86a59d93</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-11-26T16:00:34-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts: Use RTS_LIKELY in CHECK

Most compilers probably already infer that
`barf` diverges but it nevertheless doesn't
hurt to be explicit.</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/5757e82b9344a3b012cf6d71c347ad727e57f8a3">5757e82b</a></strong>
<div>
<span>by Matthew Pickering</span>
<i>at 2020-11-26T16:00:35-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove special case for GHC.ByteCode.Instr

This was added in
https://github.com/nomeata/ghc-heap-view/commit/34935206e51b9c86902481d84d2f368a6fd93423

GHC.ByteCode.Instr.BreakInfo no longer exists so the special case is dead code.

Any check like this can be easily dealt with in client code.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d9c8b5b472b6e7c4bd5a2b7eeda2bef711db9239">d9c8b5b4</a></strong>
<div>
<span>by Matthew Pickering</span>
<i>at 2020-11-26T16:00:35-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Split Up getClosureDataFromHeapRep

Motivation

1. Don't enforce the repeated decoding of an info table, when the client
can cache it (ghc-debug)
2. Allow the constructor information decoding to be overridden, this
casues segfaults in ghc-debug
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/3e3555cc9c2a9f5246895f151259fd2a81621f38">3e3555cc</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-11-26T16:00:35-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">RegAlloc: Add missing raPlatformfield to RegAllocStatsSpill

Fixes #18994

Co-Author: Benjamin Maurer <maurer.benjamin@gmail.com>
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a1a75aa9be2c133dd1372a08eeb6a92c31688df7">a1a75aa9</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-11-27T06:20:41-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts: Allocate MBlocks with MAP_TOP_DOWN on Windows

As noted in #18991, we would previously allocate heap in low memory.
Due to this the linker, which typically *needs* low memory, would end up
competing with the heap. In longer builds we end up running out of
low memory entirely, leading to linking failures.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/75fc1ed58bb9adb3f472e1529d368c0fff479353">75fc1ed5</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-11-28T15:40:23-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Hadrian: fix detection of ghc-pkg for cross-compilers
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7cb5df9617544dc3bdf85b719feaaa5d15f01c2c">7cb5df96</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-11-28T15:40:23-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">hadrian: fix ghc-pkg uses (#17601)

Make sure ghc-pkg doesn't read the compiler "settings" file by passing
--no-user-package-db.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e3fd4226a08ac6cd4abe9f25f764e518de66834a">e3fd4226</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-11-28T15:40:23-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">gitlab-ci: Introduce a nightly cross-compilation job

This adds a job to test cross-compilation from x86-64 to AArch64 with
Hadrian.

Fixes #18234
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/698d3d9648e9cb6b3757269e21ce4fa1692a1a3b">698d3d96</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-11-28T15:41:00-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">gitlab-ci: Only deploy GitLab Pages in ghc/ghc>

The deployments are quite large and yet are currently only served for
the ghc/ghc> project.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/625726f988852f5779825a954609d187d9865dc1">625726f9</a></strong>
<div>
<span>by David Eichmann</span>
<i>at 2020-11-28T15:41:37-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">ghc-heap: partial TSO/STACK decoding

Co-authored-by: Sven Tennie <sven.tennie@gmail.com>
Co-authored-by: Matthew Pickering <matthewtpickering@gmail.com>
Co-authored-by: Ben Gamari <bgamari.foss@gmail.com>
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/22ea9c296906ad3a8fed384bcf6fb35d4b6ca814">22ea9c29</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-11-28T15:42:13-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Small optimization to CmmSink.

Inside `regsUsedIn` we can avoid some thunks by specializing the
recursion. In particular we avoid the thunk for `(f e z)` in the
MachOp/Load branches, where we know this will evaluate to z.

Reduces allocations for T3294 by ~1%.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/bba42c62220a437f52e7d30cbfa67e93b4cab06e">bba42c62</a></strong>
<div>
<span>by John Ericson</span>
<i>at 2020-11-28T15:42:49-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Make primop handler indentation more consistent
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c82bc8e9d444d6d61198f3bfbcc7c5bb5f6ce13c">c82bc8e9</a></strong>
<div>
<span>by John Ericson</span>
<i>at 2020-11-28T15:42:49-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Cleanup some primop constructor names

Harmonize the internal (big sum type) names of the native vs fixed-sized
number primops a bit. (Mainly by renaming the former.)

No user-facing names are changed.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ae14f160c64d20880486ba365348ef3900c84a60">ae14f160</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-11-28T15:43:25-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite: Mark T14702 as fragile on Windows

Due to #18953.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/1bc104b029b4f043cac42253ee2387f4d574abca">1bc104b0</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-11-29T15:33:18-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">withTimings: Emit allocations counter

This will allow us to back out the allocations per compiler pass from
the eventlog. Note that we dump the allocation counter rather than the
difference since this will allow us to determine how much work is done
*between* `withTiming` blocks.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e992ea84248e2ac9f9d439cd9b25745e8c41e32d">e992ea84</a></strong>
<div>
<span>by GHC GitLab CI</span>
<i>at 2020-11-29T15:33:54-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">ThreadPaused: Don't zero slop until free vars are pushed

When threadPaused blackholes a thunk it calls `OVERWRITING_CLOSURE` to
zero the slop for the benefit of the sanity checker. Previously this was
done *before* pushing the thunk's free variables to the update
remembered set. Consequently we would pull zero'd pointers to the update
remembered set.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e82cd140e510a792031247a8f414ade48382703b">e82cd140</a></strong>
<div>
<span>by GHC GitLab CI</span>
<i>at 2020-11-29T15:33:54-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">nonmoving: Fix regression from TSAN work

The TSAN rework (specifically aad1f803) introduced a subtle regression
in GC.c, swapping `g0` in place of `gen`. Whoops!

Fixes #18997.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/35a5207e8277800b77af90d74cdd235d29a901e6">35a5207e</a></strong>
<div>
<span>by GHC GitLab CI</span>
<i>at 2020-11-29T15:33:54-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts/Messages: Add missing write barrier in THROWTO message update

After a THROWTO message has been handle the message closure is
overwritten by a NULL message. We must ensure that the original
closure's pointers continue to be visible to the nonmoving GC.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/0120829f47ed9ebd02ffd552d71e45cca3bdc9f6">0120829f</a></strong>
<div>
<span>by GHC GitLab CI</span>
<i>at 2020-11-29T15:33:54-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">nonmoving: Add missing write barrier in shrinkSmallByteArray
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8a4d8fb62abde3b79043e8915ee538aaabe2d97c">8a4d8fb6</a></strong>
<div>
<span>by GHC GitLab CI</span>
<i>at 2020-11-29T15:33:54-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Updates: Don't zero slop until closure has been pushed

Ensure that the the free variables have been pushed to the update
remembered set before we zero the slop.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2793cfdc8f7dca8461149d54882286a76f52ff84">2793cfdc</a></strong>
<div>
<span>by GHC GitLab CI</span>
<i>at 2020-11-29T15:33:54-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">OSThreads: Fix error code checking

pthread_join returns its error code and apparently doesn't set errno.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e391a16f919e5bebf75355e8dd1542cdc5656198">e391a16f</a></strong>
<div>
<span>by GHC GitLab CI</span>
<i>at 2020-11-29T15:33:54-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">nonmoving: Don't join to mark_thread on shutdown

The mark thread is not joinable as we detach from it on creation.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/60d088aba238c7265adf76840ec1d883373b0e20">60d088ab</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-11-29T15:33:54-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">nonmoving: Add reference to Ueno 2016
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/3aa603620ef5a6aae1778278aa9914f344ab526e">3aa60362</a></strong>
<div>
<span>by GHC GitLab CI</span>
<i>at 2020-11-29T15:33:54-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">nonmoving: Ensure that evacuated large objects are marked

See Note [Non-moving GC: Marking evacuated objects].
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8d304a99d2d0c17fb49c0589c0525817d515c0d0">8d304a99</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-11-30T10:15:22-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts/m32: Refactor handling of allocator seeding

Previously, in an attempt to reduce fragmentation, each new allocator
would map a region of M32_MAX_PAGES fresh pages to seed itself. However,
this ends up being extremely wasteful since it turns out that we often
use fewer than this.  Consequently, these pages end up getting freed
which, ends up fragmenting our address space more than than we would
have if we had naively allocated pages on-demand.

Here we refactor m32 to avoid this waste while achieving the
fragmentation mitigation previously desired. In particular, we move all
page allocation into the global m32_alloc_page, which will pull a page
from the free page pool. If the free page pool is empty we then refill
it by allocating a region of M32_MAP_PAGES and adding them to the pool.

Furthermore, we do away with the initial seeding entirely. That is, the
allocator starts with no active pages: pages are rather allocated on an
as-needed basis.

On the whole this ends up being a pleasingly simple change,
simultaneously making m32 more efficient, more robust, and simpler.

Fixes #18980.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b66292890d5fe0791c291f4fc427f1ab1d0f5c15">b6629289</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-11-30T10:15:58-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts: Use CHECK instead of assert

Use the GHC wrappers instead of <assert.h>.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9f4efa6a5e5d43c81d7e61b27f7cd6e3f812b1ea">9f4efa6a</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-11-30T10:15:58-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts/linker: Replace some ASSERTs with CHECK

In the past some people have confused ASSERT, which is for checking
internal invariants, which CHECK, which should be used when checking
things that might fail due to bad input (and therefore should be enabled
even in the release compiler). Change some of these cases in the linker
to use CHECK.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/0f8a4655e39bed1ca39820abdd3df9db5706b036">0f8a4655</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-11-30T10:16:34-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Allow deploy:pages job to fail

See #18973.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/49ebe369165c85ae4c2382b40e34bfa4f1e9da25">49ebe369</a></strong>
<div>
<span>by chessai</span>
<i>at 2020-11-30T19:47:40-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Optimisations in Data.Foldable (T17867)

This PR concerns the following functions from `Data.Foldable`:
* minimum
* maximum
* sum
* product
* minimumBy
* maximumBy

- Default implementations of these functions now use `foldl'` or `foldMap'`.
- All have been marked with INLINEABLE to make room for further optimisations.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4d79ef6599f44b5ab33cbd89fec96ebfac0794a1">4d79ef65</a></strong>
<div>
<span>by chessai</span>
<i>at 2020-11-30T19:47:40-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Apply suggestion to libraries/base/Data/Foldable.hs</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6af074cecdee533791943af1191541f82abc34c4">6af074ce</a></strong>
<div>
<span>by chessai</span>
<i>at 2020-11-30T19:47:40-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Apply suggestion to libraries/base/Data/Foldable.hs</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ab334262a605b0ebc228096d8af88a55aa5ea6b8">ab334262</a></strong>
<div>
<span>by Viktor Dukhovni</span>
<i>at 2020-11-30T19:48:17-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">dirty MVAR after mutating TSO queue head

While the original head and tail of the TSO queue may be in the same
generation as the MVAR, interior elements of the queue could be younger
after a GC run and may then be exposed by putMVar operation that updates
the queue head.

Resolves #18919
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/5eb163f321fdc9a3dbb5e02a157b7f8194e70fcc">5eb163f3</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-11-30T19:48:53-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts/linker: Don't allow shared libraries to be loaded multiple times
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/490aa14dbc98e4713f913c4417d454e53b8b278a">490aa14d</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-11-30T19:48:53-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts/linker: Initialise CCSs from native shared objects
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6ac3db5fefbac6bea6c8fd0ac64daf036d9a8e60">6ac3db5f</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-11-30T19:48:53-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts/linker: Move shared library loading logic into Elf.c
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b6698d73fa9811795ca37ba0b704aa430c390345">b6698d73</a></strong>
<div>
<span>by GHC GitLab CI</span>
<i>at 2020-11-30T19:48:53-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts/linker: Don't declare dynamic objects with image_mapped

This previously resulted in warnings due to spurious unmap failures.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b94a65afe1e270245cd5b9fe03d59b726dfba8c4">b94a65af</a></strong>
<div>
<span>by jneira</span>
<i>at 2020-11-30T19:49:31-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Include tried paths in findToolDir error
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/72a87fbc7a95c012be260d1a14374e2b06ed0a36">72a87fbc</a></strong>
<div>
<span>by Richard Eisenberg</span>
<i>at 2020-12-01T19:57:41-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Move core flattening algorithm to Core.Unify

This sets the stage for a later change, where this
algorithm will be needed from GHC.Core.InstEnv.

This commit also splits GHC.Core.Map into
GHC.Core.Map.Type and GHC.Core.Map.Expr,
in order to avoid module import cycles
with GHC.Core.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/0dd45d0adbade7eaae973b09b4d0ff1acb1479b8">0dd45d0a</a></strong>
<div>
<span>by Richard Eisenberg</span>
<i>at 2020-12-01T19:57:41-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Bump the # of commits searched for perf baseline

The previous value of 75 meant that a feature branch with
more than 75 commits would get spurious CI passes.

This affects #18692, but does not fix that ticket, because
if a baseline cannot be found, we should fail, not succeed.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8bb52d9186655134e3e06b4dc003e060379f5417">8bb52d91</a></strong>
<div>
<span>by Richard Eisenberg</span>
<i>at 2020-12-01T19:57:41-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove flattening variables

This patch redesigns the flattener to simplify type family applications
directly instead of using flattening meta-variables and skolems. The key new
innovation is the CanEqLHS type and the new CEqCan constraint (Ct). A CanEqLHS
is either a type variable or exactly-saturated type family application; either
can now be rewritten using a CEqCan constraint in the inert set.

Because the flattener no longer reduces all type family applications to
variables, there was some performance degradation if a lengthy type family
application is now flattened over and over (not making progress). To
compensate, this patch contains some extra optimizations in the flattener,
leading to a number of performance improvements.

Close #18875.
Close #18910.

There are many extra parts of the compiler that had to be affected in writing
this patch:

* The family-application cache (formerly the flat-cache) sometimes stores
  coercions built from Given inerts. When these inerts get kicked out, we must
  kick out from the cache as well. (This was, I believe, true previously, but
  somehow never caused trouble.) Kicking out from the cache requires adding a
  filterTM function to TrieMap.

* This patch obviates the need to distinguish "blocking" coercion holes from
  non-blocking ones (which, previously, arose from CFunEqCans). There is thus
  some simplification around coercion holes.

* Extra commentary throughout parts of the code I read through, to preserve
  the knowledge I gained while working.

* A change in the pure unifier around unifying skolems with other types.
  Unifying a skolem now leads to SurelyApart, not MaybeApart, as documented
  in Note [Binding when looking up instances] in GHC.Core.InstEnv.

* Some more use of MCoercion where appropriate.

* Previously, class-instance lookup automatically noticed that e.g. C Int was
  a "unifier" to a target [W] C (F Bool), because the F Bool was flattened to
  a variable. Now, a little more care must be taken around checking for
  unifying instances.

* Previously, tcSplitTyConApp_maybe would split (Eq a => a). This is silly,
  because (=>) is not a tycon in Haskell. Fixed now, but there are some
  knock-on changes in e.g. TrieMap code and in the canonicaliser.

* New function anyFreeVarsOf{Type,Co} to check whether a free variable
  satisfies a certain predicate.

* Type synonyms now remember whether or not they are "forgetful"; a forgetful
  synonym drops at least one argument. This is useful when flattening; see
  flattenView.

* The pattern-match completeness checker invokes the solver. This invocation
  might need to look through newtypes when checking representational equality.
  Thus, the desugarer needs to keep track of the in-scope variables to know
  what newtype constructors are in scope. I bet this bug was around before but
  never noticed.

* Extra-constraints wildcards are no longer simplified before printing.
  See Note [Do not simplify ConstraintHoles] in GHC.Tc.Solver.

* Whether or not there are Given equalities has become slightly subtler.
  See the new HasGivenEqs datatype.

* Note [Type variable cycles in Givens] in GHC.Tc.Solver.Canonical
  explains a significant new wrinkle in the new approach.

* See Note [What might match later?] in GHC.Tc.Solver.Interact, which
  explains the fix to #18910.

* The inert_count field of InertCans wasn't actually used, so I removed
  it.

Though I (Richard) did the implementation, Simon PJ was very involved
in design and review.

This updates the Haddock submodule to avoid #18932 by adding
a type signature.

-------------------------
Metric Decrease:
    T12227
    T5030
    T9872a
    T9872b
    T9872c
Metric Increase:
    T9872d
-------------------------
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d66660ba4c491f9937a1a959b009d90f08a4fbee">d66660ba</a></strong>
<div>
<span>by Richard Eisenberg</span>
<i>at 2020-12-01T19:57:41-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Rename the flattener to become the rewriter.

Now that flattening doesn't produce flattening variables,
it's not really flattening anything: it's rewriting. This
change also means that the rewriter can no longer be confused
the core flattener (in GHC.Core.Unify), which is sometimes used
during type-checking.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/add0aeaefd4d823d31315564e924ce8c018fb69e">add0aeae</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-12-01T19:58:17-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts: Introduce mmapAnonForLinker

Previously most of the uses of mmapForLinker were mapping anonymous
memory, resulting in a great deal of unnecessary repetition. Factor this
out into a new helper.

Also fixes a few places where error checking was missing or suboptimal.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/97d71646ddf3814de62573100ed0b224d1588cbc">97d71646</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-12-01T19:58:17-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts/linker: Introduce munmapForLinker

Consolidates munmap calls to ensure consistent error handling.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d8872af08d205c3067371d56200e68cf2f0c1ffc">d8872af0</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-12-01T19:58:18-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts/Linker: Introduce Windows implementations for mmapForLinker, et al.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c35d0e03514ce111ff8265426a7b911456984f50">c35d0e03</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-12-01T19:58:18-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts/m32: Introduce NEEDS_M32 macro

Instead of relying on RTS_LINKER_USE_MMAP
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/41c64eb5db50c80e110e47b7ab1c1ee18dada46b">41c64eb5</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-12-01T19:58:18-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts/linker: Use m32 to allocate symbol extras in PEi386
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e0b08c5f445f70381c854f78913489685feb224e">e0b08c5f</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-12-03T13:01:47-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">gitlab-ci: Fix copy-paste error

Also be more consistent in quoting.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/33ec3a0600fe8c009ab8ed6d86941a8fd88fb033">33ec3a06</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-12-03T23:11:31-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">gitlab-ci: Run linters through ci.sh

Ensuring that the right toolchain is used.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4a437bc19d2026845948356a932b2cac2417eb12">4a437bc1</a></strong>
<div>
<span>by Shayne Fletcher</span>
<i>at 2020-12-05T09:06:38-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix bad span calculations of post qualified imports
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8fac4b9333ef3607e75b4520d847054316cb8c2d">8fac4b93</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-12-05T09:07:13-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite: Add a test for #18923
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/62ed6957463a9c0f711ea698d7ed4371e00fb122">62ed6957</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-12-08T15:31:41-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix kind inference for data types. Again.

This patch fixes several aspects of kind inference for data type
declarations, especially data /instance/ declarations

Specifically

1. In kcConDecls/kcConDecl make it clear that the tc_res_kind argument
   is only used in the H98 case; and in that case there is no result
   kind signature; and hence no need for the disgusting splitPiTys in
   kcConDecls (now thankfully gone).

   The GADT case is a bit different to before, and much nicer.
   This is what fixes #18891.

   See Note [kcConDecls: kind-checking data type decls]

2. Do not look at the constructor decls of a data/newtype instance
   in tcDataFamInstanceHeader. See GHC.Tc.TyCl.Instance
   Note [Kind inference for data family instances].  This was a
   new realisation that arose when doing (1)

   This causes a few knock-on effects in the tests suite, because
   we require more information than before in the instance /header/.

   New user-manual material about this in "Kind inference in data type
   declarations" and "Kind inference for data/newtype instance
   declarations".

3. Minor improvement in kcTyClDecl, combining GADT and H98 cases

4. Fix #14111 and #8707 by allowing the header of a data instance
   to affect kind inferece for the the data constructor signatures;
   as described at length in Note [GADT return types] in GHC.Tc.TyCl

   This led to a modest refactoring of the arguments (and argument
   order) of tcConDecl/tcConDecls.

5. Fix #19000 by inverting the sense of the test in new_locs
   in GHC.Tc.Solver.Canonical.canDecomposableTyConAppOK.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/0abe3ddf85a915ab99ae4f87a85faf6ee5466ad3">0abe3ddf</a></strong>
<div>
<span>by Adam Sandberg Ericsson</span>
<i>at 2020-12-08T15:32:19-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">hadrian: build the _l and _thr_l rts flavours in the develN flavours

The ghc binary requires the eventlog rts since
fc644b1a643128041cfec25db84e417851e28bab
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/51e3bb6db85c20cb6b287fa5ec7cfe679a7e5259">51e3bb6d</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-12-08T22:43:21-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">CodeGen: Make folds User/DefinerOfRegs INLINEABLE.

Reduces allocation for the test case I was looking at by about 1.2%.
Mostly from avoiding allocation of some folding functions which turn
into let-no-escape bindings which just reuse their environment instead.

We also force inlining in a few key places in CmmSink which helps a bit
more.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/69ae10c39bfed1c4f90f34b42aa0630e0fda2b1b">69ae10c3</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-12-08T22:43:21-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">CmmSink: Force inlining of foldRegsDefd

Helps avoid allocating the folding function. Improves
perf for T3294 by about 1%.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6e3da80055dd7b3fc3bdc576088fdd16129bdac7">6e3da800</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-12-08T22:43:21-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Cmm: Make a few types and utility function slightly stricter.

About 0.6% reduction in allocations for the code I was looking at.

Not a huge difference but no need to throw away performance.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/aef44d7fbef92159960daf73c53dbc3c8d21ecbf">aef44d7f</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-12-08T22:43:21-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Cmm.Sink: Optimize retaining of assignments, live sets.

Sinking requires us to track live local regs after each
cmm statement. We used to do this via "Set LocalReg".

However we can replace this with a solution based on IntSet
which is overall more efficient without losing much. The thing
we lose is width of the variables, which isn't used by the sinking
pass anyway.

I also reworked how we keep assignments to regs mentioned in
skipped assignments. I put the details into
Note [Keeping assignemnts mentioned in skipped RHSs].

The gist of it is instead of keeping track of it via the use count
which is a `IntMap Int` we now use the live regs set (IntSet) which
is quite a bit faster.

I think it also matches the semantics a lot better. The skipped
(not discarded) assignment does in fact keep the regs on it's rhs
alive so keeping track of this in the live set seems like the clearer
solution as well.

Improves allocations for T3294 by yet another 1%.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/59f2249b4f4f3b1a5f2d0bc1b2923e0652b7de8f">59f2249b</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-12-08T22:43:21-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">GHC.Cmm.Opt: Be stricter in results.

Optimization either returns Nothing if nothing is to be done or
`Just <cmmExpr>` otherwise. There is no point in being lazy in
`cmmExpr`. We usually inspect this element so the thunk gets forced
not long after.

We might eliminate it as dead code once in a blue moon but that's
not a case worth optimizing for.

Overall the impact of this is rather low. As Cmm.Opt doesn't allocate
much (compared to the rest of GHC) to begin with.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/54b88eacbf9d13f2b1d070932a742ec74419c3f5">54b88eac</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-12-08T22:43:57-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Bump time submodule.

This should fix #19002.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/35e7b0c6581bb7b577e63b08770bb8f1372435aa">35e7b0c6</a></strong>
<div>
<span>by Kirill Elagin</span>
<i>at 2020-12-10T01:45:54-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">doc: Clarify the default for -fomit-yields

“Yield points enabled” is confusing (and probably wrong?
I am not 100% sure what it means). Change it to a simple “on”.

Undo this change from 2c23fff2e03e77187dc4d01f325f5f43a0e7cad2.</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/3551c554acd8d692de7948c47a27327988b3a308">3551c554</a></strong>
<div>
<span>by Kirill Elagin</span>
<i>at 2020-12-10T01:45:54-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">doc: Extra-clarify -fomit-yields

Be more clear on what this optimisation being on by default means
in terms of yields.</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6484f0d72a9110c5960b9185f239e6ce049b0c74">6484f0d7</a></strong>
<div>
<span>by Sergei Trofimovich</span>
<i>at 2020-12-10T01:46:33-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts/linker/Elf.c: add missing <dlfcn.h> include (musl support)

The change fixes build failure on musl:

```
rts/linker/Elf.c:2031:3: error:
     warning: implicit declaration of function 'dlclose'; did you mean 'close'? [-Wimplicit-function-declaration]
     2031 |   dlclose(nc->dlopen_handle);
          |   ^~~~~~~
          |   close
```

Signed-off-by: Sergei Trofimovich <slyfox@gentoo.org>
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ab24ed9bdb1d1b6967883f47eb432c08477d26a9">ab24ed9b</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-12-11T03:55:51-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">users guide: Fix syntax errors

Fixes errors introduced by 3a55b3a2574f913d046f3a6f82db48d7f6df32e3.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d3a24d3190de47044981363329337c16b5052028">d3a24d31</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-12-11T03:55:51-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">users guide: Describe GC lifecycle events

Every time I am asked about how to interpret these events I need to
figure it out from scratch. It's well past time that the users guide
properly documents these.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/741309b94e5ef312f4112c86e99b540d412dd100">741309b9</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-12-11T03:56:27-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">gitlab-ci: Fix incorrect Docker image for nightly cross job

Also refactor the job definition to eliminate the bug by construction.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/19703bc83732525cd8309b1e07815840fcc622fb">19703bc8</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-12-11T03:56:27-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">gitlab-ci: Fix name of flavour in ThreadSanitizer job

It looks like I neglected to update this after introduce flavour
transformers.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/381eb66012c2b1b9ef50008df57293fe443c2972">381eb660</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-12-11T12:57:35-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Display FFI labels (fix #18539)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4548d1f8a2356458ded83f26a728c31159b46a56">4548d1f8</a></strong>
<div>
<span>by Aaron Allen</span>
<i>at 2020-12-11T12:58:14-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Elide extraneous messages for :doc command (#15784)

Do not print `<has no documentation>` alongside a valid doc.
Additionally, if two matching symbols lack documentation then the
message will only be printed once. Hence, `<has no documentation>` will
be printed at most once and only if all matching symbols are lacking
docs.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/5eba91b629745746397ed36f25fe592d08ec667b">5eba91b6</a></strong>
<div>
<span>by Aaron Allen</span>
<i>at 2020-12-11T12:58:14-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add :doc test case for duplicate record fields

Tests that the output of the `:doc` command is correct for duplicate
record fields defined using -XDuplicateRecordFields.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/5feb9b2dad0ce609e3cfb537a6ca758a09a6898e">5feb9b2d</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-12-11T22:39:29-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Delete outdated Note [Kind-checking tyvar binders for associated types]

This Note has severely bitrotted, as it has no references anywhere in the
codebase, and none of the functions that it mentions exist anymore. Let's just
delete this. While I was in town, I deleted some outdated comments from
`checkFamPatBinders` of a similar caliber.

Fixes #19008.

[ci skip]
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/f9f9f030d77ee6fb882897246a67b527937b8f66">f9f9f030</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-12-11T22:40:08-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Arrows: correctly query arrow methods (#17423)

Consider the following code:

    proc (C x y) -> ...

Before this patch, the evidence binding for the Arrow dictionary was
attached to the C pattern:

    proc (C x y) { $dArrow = ... } -> ...

But then when we desugar this, we use arrow operations ("arr", ">>>"...)
specialised for this arrow:

    let
        arr_xy = arr $dArrow -- <-- Not in scope!
        ...
    in
        arr_xy (\(C x y) { $dArrow = ... } -> ...)

This patch allows arrow operations to be type-checked before the proc
itself, avoiding this issue.

Fix #17423
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/aaa8f00fa03dbc29511283f93fde3b627023f4fe">aaa8f00f</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-12-11T22:40:48-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Validate script: fix configure command when using stack
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b4a929a1e54272ff6ba67c1a2baba635bae93b0b">b4a929a1</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-12-11T22:41:30-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Hadrian: fix libffi tarball parsing

Fix parsing of "libffi-3.3.tar.gz".

NB: switch to a newer libffi isn't done in this patch
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/690c894616a539c59cb8e58d2bba8b9c02c5ad4c">690c8946</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-12-11T22:42:09-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Parser: move parser utils into their own module

Move code unrelated to runtime evaluation out of GHC.Runtime.Eval
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/76be0e32d6638c04521b74421a9ce2380593fb54">76be0e32</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-12-11T22:42:48-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Move SizedSeq into ghc-boot
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/3a16d764f3cf01add8c09b9ca5c071176f857fb8">3a16d764</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-12-11T22:42:48-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">ghci: don't compile unneeded modules
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2895fa60350e19016ee4babc1a1ce8bc5179364d">2895fa60</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-12-11T22:42:48-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">ghci: reuse Arch from ghc-boot
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/480a38d4ad2f6fa2137e81e9f318dda445858e9c">480a38d4</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-12-11T22:43:30-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts: don't use siginterrupt (#19019)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4af6126d1758d5e365cadf032e34c99489f13dee">4af6126d</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-12-11T22:44:11-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Use static array in zeroCount
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/5bd71bfd3a410ff2edcd29306a9824d60857f9fd">5bd71bfd</a></strong>
<div>
<span>by Sebastian Graf</span>
<i>at 2020-12-12T04:45:09-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">DmdAnal: Annotate top-level function bindings with demands (#18894)

It's useful to annotate a non-exported top-level function like `g` in

```hs
module Lib (h) where

g :: Int -> Int -> (Int,Int)
g m 1 = (m, 0)
g m n = (2 * m, 2 `div` n)
{-# NOINLINE g #-}

h :: Int -> Int
h 1 = 0
h m
  | odd m     = snd (g m 2)
  | otherwise = uncurry (+) (g 2 m)
```

with its demand `UCU(CS(P(1P(U),SP(U))`, which tells us that whenever `g` was
called, the second component of the returned pair was evaluated strictly.

Since #18903 we do so for local functions, where we can see all calls.
For top-level functions, we can assume that all *exported* functions are
demanded according to `topDmd` and thus get sound demands for
non-exported top-level functions.

The demand on `g` is crucial information for Nested CPR, which may the
go on and unbox `g` for the second pair component. That is true even if
that pair component may diverge, as is the case for the call site `g 13
0`, which throws a div-by-zero exception.

In `T18894b`, you can even see the new demand annotation enabling us to
eta-expand a function that we wouldn't be able to eta-expand without
Call Arity.

We only track bindings of function type in order not to risk huge compile-time
regressions, see `isInterestingTopLevelFn`.

There was a CoreLint check that rejected strict demand annotations on
recursive or top-level bindings, which seems completely unjustified.
All the cases I investigated were fine, so I removed it.

Fixes #18894.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/3aae036eded89603756d025e0fac2ec0642edeaf">3aae036e</a></strong>
<div>
<span>by Sebastian Graf</span>
<i>at 2020-12-12T04:45:09-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Demand: Simplify `CU(U)` to `U` (#19005)

Both sub-demands encode the same information.
This is a trivial change and already affects a few regression tests
(e.g. `T5075`), so no separate regression test is necessary.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c647763954717d9853d08ff04eece7f1ddeae15c">c6477639</a></strong>
<div>
<span>by Adam Sandberg Ericsson</span>
<i>at 2020-12-12T04:45:48-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">hadrian: correctly copy the docs dir into the bindist #18669
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e033dd0512443140dcca5b3c90b84022d8caf942">e033dd05</a></strong>
<div>
<span>by Adam Sandberg Ericsson</span>
<i>at 2020-12-12T10:52:19+00:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">mkDocs: support hadrian bindists #18973
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/78580ba3f99565b0aecb25c4206718d4c8a52317">78580ba3</a></strong>
<div>
<span>by John Ericson</span>
<i>at 2020-12-13T07:14:50-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove old .travis.yml
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c696bb2f4476e0ce4071e0d91687c1fe84405599">c696bb2f</a></strong>
<div>
<span>by Cale Gibbard</span>
<i>at 2020-12-14T13:37:09-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Implement type applications in patterns

The haddock submodule is also updated so that it understands the changes
to patterns.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7e9debd4ceb068effe8ac81892d2cabcb8f55850">7e9debd4</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-12-14T13:37:09-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Optimise nullary type constructor usage

During the compilation of programs GHC very frequently deals with
the `Type` type, which is a synonym of `TYPE 'LiftedRep`. This patch
teaches GHC to avoid expanding the `Type` synonym (and other nullary
type synonyms) during type comparisons, saving a good amount of work.
This optimisation is described in `Note [Comparing nullary type
synonyms]`.

To maximize the impact of this optimisation, we introduce a few
special-cases to reduce `TYPE 'LiftedRep` to `Type`. See
`Note [Prefer Type over TYPE 'LiftedPtrRep]`.

Closes #17958.

Metric Decrease:
   T18698b
   T1969
   T12227
   T12545
   T12707
   T14683
   T3064
   T5631
   T5642
   T9020
   T9630
   T9872a
   T13035
   haddock.Cabal
   haddock.base
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/92377c27e1a48d0d3776f65c7074dfeb122b46db">92377c27</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-12-14T13:41:58-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Revert "Optimise nullary type constructor usage"

This was inadvertently merged.

This reverts commit 7e9debd4ceb068effe8ac81892d2cabcb8f55850.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d0e8c10d587e4b9984526d0dfcfcb258b75733b8">d0e8c10d</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-12-14T19:45:13+01:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Move Unit related fields from DynFlags to HscEnv

The unit database cache, the home unit and the unit state were stored in
DynFlags while they ought to be stored in the compiler session state
(HscEnv). This patch fixes this.

It introduces a new UnitEnv type that should be used in the future to
handle separate unit environments (especially host vs target units).

Related to #17957

Bump haddock submodule
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/af855ac1d37359df3db8c48dc6c9dd2f3fe24e77">af855ac1</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-12-14T15:22:13-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Optimize dumping of consecutive whitespace.

The naive way of putting out n characters of indent would be something
like `hPutStr hdl (replicate n ' ')`. However this is quite inefficient
as we allocate an absurd number of strings consisting of simply spaces
as we don't cache them.

To improve on this we now track if we can simply write ascii spaces via
hPutBuf instead. This is the case when running with -ddump-to-file where
we force the encoding to be UTF8.

This avoids both the cost of going through encoding as well as avoiding
allocation churn from all the white space. Instead we simply use hPutBuf
on a preallocated unlifted string.

When dumping stg like this:

> nofib/spectral/simple/Main.hs -fforce-recomp -ddump-stg-final -ddump-to-file -c +RTS -s

Allocations went from 1,778 MB to 1,702MB. About a 4% reduction of
allocation! I did not measure the difference in runtime but expect it
to be similar.

Bumps the haddock submodule since the interface of GHC's Pretty
slightly changed.

-------------------------
Metric Decrease:
    T12227
-------------------------
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/dad87210efffce9cfc2d17dc088a71d9dea14535">dad87210</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-12-14T15:22:29-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Optimise nullary type constructor usage

During the compilation of programs GHC very frequently deals with
the `Type` type, which is a synonym of `TYPE 'LiftedRep`. This patch
teaches GHC to avoid expanding the `Type` synonym (and other nullary
type synonyms) during type comparisons, saving a good amount of work.
This optimisation is described in `Note [Comparing nullary type
synonyms]`.

To maximize the impact of this optimisation, we introduce a few
special-cases to reduce `TYPE 'LiftedRep` to `Type`. See
`Note [Prefer Type over TYPE 'LiftedPtrRep]`.

Closes #17958.

Metric Decrease:
   T18698b
   T1969
   T12227
   T12545
   T12707
   T14683
   T3064
   T5631
   T5642
   T9020
   T9630
   T9872a
   T13035
   haddock.Cabal
   haddock.base
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6c2eb2232b39ff4720fda0a4a009fb6afbc9dcea">6c2eb223</a></strong>
<div>
<span>by Andrew Martin</span>
<i>at 2020-12-14T18:48:51-05:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Implement BoxedRep proposal

This implements the BoxedRep proposal, refacoring the `RuntimeRep`
hierarchy from:

```haskell
data RuntimeRep = LiftedPtrRep | UnliftedPtrRep | ...
```

to

```haskell
data RuntimeRep = BoxedRep Levity | ...
data Levity = Lifted | Unlifted
```

Closes #17526.
</pre>
</li>
</ul>
<h4>30 changed files:</h4>
<ul>
<li class="file-stats">
<a href="#587d266bb27a4dc3022bbed44dfa19849df3044c">
.gitlab-ci.yml
</a>
</li>
<li class="file-stats">
<a href="#157f7634c25bc6366cb7c9c9edb48e819dce38db">
.gitlab/ci.sh
</a>
</li>
<li class="file-stats">
<a href="#dea01dd89a3b602828e630677fde5d77c06441c8">
<span class="deleted-file">

.travis.yml
</span>
</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="#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="#8a5cd068459120cddf3814e7b9e02003b87647ba">
compiler/GHC/Builtin/Types/Prim.hs
</a>
</li>
<li class="file-stats">
<a href="#26a4620a80da2cc1c44d4e84ca58cf0393140be4">
<span class="new-file">
+
compiler/GHC/Builtin/Types/Prim.hs-boot
</span>
</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="#11e6f6a348be9920cecad0893a25350137524b4f">
compiler/GHC/ByteCode/Linker.hs
</a>
</li>
<li class="file-stats">
<a href="#5c66928780aaad0eb5888511dc4b0b08492c69fa">
compiler/GHC/ByteCode/Types.hs
</a>
</li>
<li class="file-stats">
<a href="#f73a4fa90a8eb153bccdcfcc9f63c15edcd66785">
compiler/GHC/Cmm.hs
</a>
</li>
<li class="file-stats">
<a href="#db697f6aea9f93f1583f1d5c62d25570a1e07f73">
compiler/GHC/Cmm/CLabel.hs
</a>
</li>
<li class="file-stats">
<a href="#806448db91cc2906ebcc088107220a663d3d43eb">
compiler/GHC/Cmm/CommonBlockElim.hs
</a>
</li>
<li class="file-stats">
<a href="#4fbb1c5f251c38fc01fcde693420ee6d02df7e45">
compiler/GHC/Cmm/Dataflow/Label.hs
</a>
</li>
<li class="file-stats">
<a href="#56e23d78cfece2c83f03ed9b9a8ce9b20be26462">
compiler/GHC/Cmm/Expr.hs
</a>
</li>
<li class="file-stats">
<a href="#2d3721ad8de95e1144493ca545db846672cb109f">
compiler/GHC/Cmm/Info/Build.hs
</a>
</li>
<li class="file-stats">
<a href="#2d9f432ef2a75cf9ce101a5380b45e6cb06a42d0">
<span class="new-file">
+
compiler/GHC/Cmm/LRegSet.hs
</span>
</a>
</li>
<li class="file-stats">
<a href="#e9c044b79842eca94ef683d075c4bfeca3bbb931">
compiler/GHC/Cmm/Lexer.x
</a>
</li>
<li class="file-stats">
<a href="#95111d27913460e138e20c87f610b61c3745ab2b">
compiler/GHC/Cmm/Liveness.hs
</a>
</li>
<li class="file-stats">
<a href="#90378e83c3a00a78bc0b3c01da111e0a787de451">
compiler/GHC/Cmm/Node.hs
</a>
</li>
<li class="file-stats">
<a href="#00c27365316e033b00cc3ed3854ac8714d25a2b5">
compiler/GHC/Cmm/Opt.hs
</a>
</li>
<li class="file-stats">
<a href="#71e696f452eb493722d70306c6f304fc9b2f6a95">
compiler/GHC/Cmm/Parser.y
</a>
</li>
<li class="file-stats">
<a href="#c1b0959b75a7a0d23334b99aea968a34ef714ce4">
compiler/GHC/Cmm/Parser/Monad.hs
</a>
</li>
<li class="file-stats">
<a href="#b1390f6749e1a2dddcae35f88d55623ea6269f56">
compiler/GHC/Cmm/Sink.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>
</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: #666;">

<br>
<a href="https://gitlab.haskell.org/ghc/ghc/-/compare/185a01b0a2522b8197710e339b21179267d4245a...6c2eb2232b39ff4720fda0a4a009fb6afbc9dcea">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>