<!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/win32-missing-tarball
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/cb5c31b51b021ce86890bba73276fe6f7405f5d3">cb5c31b5</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-06-03T17:55:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">gitlab-ci: Allow ARMv7 job to fail
Due to #18298.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/32a4ae90b50cc56f2955f489ad0cf8c7ff5e131a">32a4ae90</a></strong>
<div>
<span>by John Ericson</span>
<i>at 2020-06-04T04:34:42-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Clean up boot vs non-boot disambiguating types
We often have (ModuleName, Bool) or (Module, Bool) pairs for "extended"
module names (without or with a unit id) disambiguating boot and normal
modules. We think this is important enough across the compiler that it
deserves a new nominal product type. We do this with synnoyms and a
functor named with a `Gen` prefix, matching other newly created
definitions.
It was also requested that we keep custom `IsBoot` / `NotBoot` sum type.
So we have it too. This means changing many the many bools to use that
instead.
Updates `haddock` submodule.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c05756cdef800f1d8e92114222bcc480bce758b9">c05756cd</a></strong>
<div>
<span>by Niklas Hambüchen</span>
<i>at 2020-06-04T04:35:24-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">docs: Add more details on InterruptibleFFI.
Details from https://gitlab.haskell.org/ghc/ghc/issues/8684
and https://github.com/takano-akio/filelock/pull/7#discussion_r280332430
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/1b975aedb1b74b8694d14ba8fdc5955497f8f31c">1b975aed</a></strong>
<div>
<span>by Andrew Martin</span>
<i>at 2020-06-04T04:36:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Allow finalizeForeignPtr to be called on FinalPtr/PlainPtr.
MR 2165 (commit 49301ad6226d9a83d110bee8c419615dd94f5ded) regressed
finalizeForeignPtr by throwing exceptions when PlainPtr was encounterd.
This regression did not make it into a release of GHC. Here, the
original behavior is restored, and FinalPtr is given the same treatment
as PlainPtr.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2bd3929ad1b06b01c1d22d513902507eefadc131">2bd3929a</a></strong>
<div>
<span>by Luke Lau</span>
<i>at 2020-06-04T04:36:41-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix documentation on type families not being extracted
It looks like the location of the Names used for CoAxioms on type
families are now located at their type constructors. Previously, Docs.hs
thought the Names were located in the RHS, so the RealSrcSpan in the
instanceMap and getInstLoc didn't match up. Fixes #18241
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6735b9d94605b4c7f75e70339bfaa4207f23e52b">6735b9d9</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-06-04T04:37:21-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">GHC.Hs.Instances: Compile with -O0
This module contains exclusively Data instances, which are going to be
slow no matter what we do. Furthermore, they are incredibly slow to
compile with optimisation (see #9557). Consequently we compile this with
-O0. See #18254.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c330331adc0a686f24b94844d0eb3a0711b928d7">c330331a</a></strong>
<div>
<span>by nineonine</span>
<i>at 2020-06-04T04:37:59-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add test for #17669
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/cab684f0857c71c40996201d6fb3ba93eb38a701">cab684f0</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-06-04T04:38:36-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts: Add Windows-specific implementation of rtsSleep
Previously we would use the POSIX path, which uses `nanosleep`. However,
it turns out that `nanosleep` is provided by `libpthread` on Windows. In
general we don't want to incur such a dependency. Avoid this by simply
using `Sleep` on Windows.
Fixes #18272.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ad44b50484f27beceab8213a061aa60c7a03f7ca">ad44b504</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-06-04T04:38:36-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">compiler: Disable use of process jobs with process < 1.6.9
Due to #17926.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6a4098a4bb89b3d30cca26d82b82724913062536">6a4098a4</a></strong>
<div>
<span>by Moritz Angermann</span>
<i>at 2020-06-04T04:55:51-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">[linker] Adds void printLoadedObjects(void);
This allows us to dump in-memory object code locations for debugging.
Fixup printLoadedObjects prototype
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/af5e3a885ddd09dd5f550552c535af3661ff3dbf">af5e3a88</a></strong>
<div>
<span>by Artem Pelenitsyn</span>
<i>at 2020-06-05T03:18:49-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">base: fix sign confusion in log1mexp implementation (fix #17125)
author: claude (https://gitlab.haskell.org/trac-claude)
The correct threshold for log1mexp is -(log 2) with the current specification
of log1mexp. This change improves accuracy for large negative inputs.
To avoid code duplication, a small helper function is added;
it isn't the default implementation in Floating because it needs Ord.
This patch does nothing to address that the Haskell specification is
different from that in common use in other languages.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2b792facab46f7cdd09d12e79499f4e0dcd4293f">2b792fac</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-06-05T09:27:50-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Simple subsumption
This patch simplifies GHC to use simple subsumption.
Ticket #17775
Implements GHC proposal #287
https://github.com/ghc-proposals/ghc-proposals/blob/master/
proposals/0287-simplify-subsumption.rst
All the motivation is described there; I will not repeat it here.
The implementation payload:
* tcSubType and friends become noticably simpler, because it no
longer uses eta-expansion when checking subsumption.
* No deeplyInstantiate or deeplySkolemise
That in turn means that some tests fail, by design; they can all
be fixed by eta expansion. There is a list of such changes below.
Implementing the patch led me into a variety of sticky corners, so
the patch includes several othe changes, some quite significant:
* I made String wired-in, so that
"foo" :: String rather than
"foo" :: [Char]
This improves error messages, and fixes #15679
* The pattern match checker relies on knowing about in-scope equality
constraints, andd adds them to the desugarer's environment using
addTyCsDs. But the co_fn in a FunBind was missed, and for some reason
simple-subsumption ends up with dictionaries there. So I added a
call to addTyCsDs. This is really part of #18049.
* I moved the ic_telescope field out of Implication and into
ForAllSkol instead. This is a nice win; just expresses the code
much better.
* There was a bug in GHC.Tc.TyCl.Instance.tcDataFamInstHeader.
We called checkDataKindSig inside tc_kind_sig, /before/
solveEqualities and zonking. Obviously wrong, easily fixed.
* solveLocalEqualitiesX: there was a whole mess in here, around
failing fast enough. I discovered a bad latent bug where we
could successfully kind-check a type signature, and use it,
but have unsolved constraints that could fill in coercion
holes in that signature -- aargh.
It's all explained in Note [Failure in local type signatures]
in GHC.Tc.Solver. Much better now.
* I fixed a serious bug in anonymous type holes. IN
f :: Int -> (forall a. a -> _) -> Int
that "_" should be a unification variable at the /outer/
level; it cannot be instantiated to 'a'. This was plain
wrong. New fields mode_lvl and mode_holes in TcTyMode,
and auxiliary data type GHC.Tc.Gen.HsType.HoleMode.
This fixes #16292, but makes no progress towards the more
ambitious #16082
* I got sucked into an enormous refactoring of the reporting of
equality errors in GHC.Tc.Errors, especially in
mkEqErr1
mkTyVarEqErr
misMatchMsg
misMatchMsgOrCND
In particular, the very tricky mkExpectedActualMsg function
is gone.
It took me a full day. But the result is far easier to understand.
(Still not easy!) This led to various minor improvements in error
output, and an enormous number of test-case error wibbles.
One particular point: for occurs-check errors I now just say
Can't match 'a' against '[a]'
rather than using the intimidating language of "occurs check".
* Pretty-printing AbsBinds
Tests review
* Eta expansions
T11305: one eta expansion
T12082: one eta expansion (undefined)
T13585a: one eta expansion
T3102: one eta expansion
T3692: two eta expansions (tricky)
T2239: two eta expansions
T16473: one eta
determ004: two eta expansions (undefined)
annfail06: two eta (undefined)
T17923: four eta expansions (a strange program indeed!)
tcrun035: one eta expansion
* Ambiguity check at higher rank. Now that we have simple
subsumption, a type like
f :: (forall a. Eq a => Int) -> Int
is no longer ambiguous, because we could write
g :: (forall a. Eq a => Int) -> Int
g = f
and it'd typecheck just fine. But f's type is a bit
suspicious, and we might want to consider making the
ambiguity check do a check on each sub-term. Meanwhile,
these tests are accepted, whereas they were previously
rejected as ambiguous:
T7220a
T15438
T10503
T9222
* Some more interesting error message wibbles
T13381: Fine: one error (Int ~ Exp Int)
rather than two (Int ~ Exp Int, Exp Int ~ Int)
T9834: Small change in error (improvement)
T10619: Improved
T2414: Small change, due to order of unification, fine
T2534: A very simple case in which a change of unification order
means we get tow unsolved constraints instead of one
tc211: bizarre impredicative tests; just accept this for now
Updates Cabal and haddock submodules.
Metric Increase:
T12150
T12234
T5837
haddock.base
Metric Decrease:
haddock.compiler
haddock.Cabal
haddock.base
Merge note: This appears to break the
`UnliftedNewtypesDifficultUnification` test. It has been marked as
broken in the interest of merging.
(cherry picked from commit 66b7b195cb3dce93ed5078b80bf568efae904cc5)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2dff814158e08aed53036bf6ebd7c3c8394af438">2dff8141</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-06-05T14:21:24-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Simplify bindLHsTyVarBndrs and bindHsQTyVars
Both `bindLHsTyVarBndrs` and `bindHsQTyVars` take two separate
`Maybe` arguments, which I find terribly confusing. Thankfully, it's
possible to remove one `Maybe` argument from each of these functions,
which this patch accomplishes:
* `bindHsQTyVars` takes a `Maybe SDoc` argument, which is `Just` if
GHC should warn about any of the quantified type variables going
unused. However, every call site uses `Nothing` in practice. This
makes sense, since it doesn't really make sense to warn about
unused type variables bound by an `LHsQTyVars`. For instance, you
wouldn't warn about the `a` in `data Proxy a = Proxy` going unused.
As a result, I simply remove this `Maybe SDoc` argument altogether.
* `bindLHsTyVarBndrs` also takes a `Maybe SDoc` argument for the same
reasons that `bindHsQTyVars` took one. To make things more
confusing, however, `bindLHsTyVarBndrs` also takes a separate
`HsDocContext` argument, which is pretty-printed (to an `SDoc`) in
warnings and error messages.
In practice, the `Maybe SDoc` and the `HsDocContext` often contain
the same text. See the call sites for `bindLHsTyVarBndrs` in
`rnFamInstEqn` and `rnConDecl`, for instance. There are only a
handful of call sites where the text differs between the
`Maybe SDoc` and `HsDocContext` arguments:
* In `rnHsRuleDecl`, where the `Maybe SDoc` says "`In the rule`"
and the `HsDocContext` says "`In the transformation rule`".
* In `rnHsTyKi`/`rn_ty`, where the `Maybe SDoc` says
"`In the type`" but the `HsDocContext` is inhereted from the
surrounding context (e.g., if `rnHsTyKi` were called on a
top-level type signature, the `HsDocContext` would be
"`In the type signature`" instead)
In both cases, warnings/error messages arguably _improve_ by
unifying making the `Maybe SDoc`'s text match that of the
`HsDocContext`. As a result, I decided to remove the `Maybe SDoc`
argument to `bindLHsTyVarBndrs` entirely and simply reuse the text
from the `HsDocContext`. (I decided to change the phrase
"transformation rule" to "rewrite rule" while I was in the area.)
The `Maybe SDoc` argument has one other purpose: signaling when to
emit "`Unused quantified type variable`" warnings. To recover this
functionality, I replaced the `Maybe SDoc` argument with a
boolean-like `WarnUnusedForalls` argument. The only
`bindLHsTyVarBndrs` call site that chooses _not_ to emit these
warnings in `bindHsQTyVars`.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e372331b3212e5d8eddfa6f8d2c3840b7e95c2b3">e372331b</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-06-07T08:46:41-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">hadrian: Add missing deriveConstants dependency on ghcplatform.h
deriveConstants wants to compile C sources which #include PosixSource.h,
which itself #includes ghcplatform.h. Make sure that Hadrian knows
about this dependency.
Fixes #18290.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b022051a50d30e39d86ee21e565e899e7e98255f">b022051a</a></strong>
<div>
<span>by Moritz Angermann</span>
<i>at 2020-06-07T08:46:42-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">ghc-prim needs to depend on libc and libm
libm is just an empty shell on musl, and all the math functions are contained in
libc.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6dae65484f9552239652f743e2303fa17aae953b">6dae6548</a></strong>
<div>
<span>by Moritz Angermann</span>
<i>at 2020-06-07T08:46:42-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Disable DLL loading if without system linker
Some platforms (musl, aarch64) do not have a working dynamic linker
implemented in the libc, even though we might see dlopen. It will
ultimately just return that this is not supported. Hence we'll add
a flag to the compiler to flat our disable loading dlls. This is
needed as we will otherwise try to load the shared library even
if this will subsequently fail. At that point we have given up
looking for static options though.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4a158ffc4e0ac250897aefaf6caf03eb5f688182">4a158ffc</a></strong>
<div>
<span>by Moritz Angermann</span>
<i>at 2020-06-07T08:46:43-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Range is actually +/-2^32, not +/-2^31
See also: https://static.docs.arm.com/ihi0056/g/aaelf64.pdf
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/f1bfb806683b3092fc5ead84e7ecff928c55fbc4">f1bfb806</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-06-07T10:49:30-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">OccurAnal: Avoid exponential behavior due to where clauses
Previously the `Var` case of `occAnalApp` could in some cases (namely
in the case of `runRW#` applications) call `occAnalRhs` two. In the case
of nested `runRW#`s this results in exponential complexity. In some
cases the compilation time that resulted would be very long indeed
(see #18296).
Fixes #18296.
Metric Decrease:
T9961
T12150
T12234
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9b607671b9158c60470b2bd57804a7684d3ea33f">9b607671</a></strong>
<div>
<span>by Takenobu Tani</span>
<i>at 2020-06-09T08:05:46-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add link to GHC's wiki in the GHC API header
This adds a URL to point to GHC's wiki in the GHC API header.
Newcomers could easily find more information from the GHC API's
web like [1].
[1]: Current version, https://ghc.gitlab.haskell.org/ghc/doc/libraries/ghc-8.11.0.20200604/index.html
[skip ci]
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/72c7fe9a1e147dfeaf043f6d591d724a126cce45">72c7fe9a</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-06-09T08:06:24-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Make GADT constructors adhere to the forall-or-nothing rule properly
Issue #18191 revealed that the types of GADT constructors don't quite
adhere to the `forall`-or-nothing rule. This patch serves to clean up
this sad state of affairs somewhat. The main change is not in the
code itself, but in the documentation, as this patch introduces two
sections to the GHC User's Guide:
* A "Formal syntax for GADTs" section that presents a BNF-style
grammar for what is and isn't allowed in GADT constructor types.
This mostly exists to codify GHC's existing behavior, but it also
imposes a new restriction that addresses #18191: the outermost
`forall` and/or context in a GADT constructor is not allowed to be
surrounded by parentheses. Doing so would make these
`forall`s/contexts nested, and GADTs do not support nested
`forall`s/contexts at present.
* A "`forall`-or-nothing rule" section that describes exactly what
the `forall`-or-nothing rule is all about. Surprisingly, there was
no mention of this anywhere in the User's Guide up until now!
To adhere the new specification in the "Formal syntax for GADTs"
section of the User's Guide, the following code changes were made:
* A new function, `GHC.Hs.Type.splitLHsGADTPrefixTy`, was introduced.
This is very much like `splitLHsSigmaTy`, except that it avoids
splitting apart any parentheses, which can be syntactically
significant for GADT types. See
`Note [No nested foralls or contexts in GADT constructors]` in
`GHC.Hs.Type`.
* `ConDeclGADTPrefixPs`, an extension constructor for `XConDecl`, was
introduced so that `GHC.Parser.PostProcess.mkGadtDecl` can return
it when given a prefix GADT constructor. Unlike `ConDeclGADT`,
`ConDeclGADTPrefixPs` does not split the GADT type into its argument
and result types, as this cannot be done until after the type is
renamed (see `Note [GADT abstract syntax]` in `GHC.Hs.Decls` for why
this is the case).
* `GHC.Renamer.Module.rnConDecl` now has an additional case for
`ConDeclGADTPrefixPs` that (1) splits apart the full `LHsType` into
its `forall`s, context, argument types, and result type, and
(2) checks for nested `forall`s/contexts. Step (2) used to be
performed the typechecker (in `GHC.Tc.TyCl.badDataConTyCon`) rather
than the renamer, but now the relevant code from the typechecker
can simply be deleted.
One nice side effect of this change is that we are able to give a
more accurate error message for GADT constructors that use visible
dependent quantification (e.g., `MkFoo :: forall a -> a -> Foo a`),
which improves the stderr in the `T16326_Fail6` test case.
Fixes #18191. Bumps the Haddock submodule.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a47e6442bc4be4a33339499d876792ba109e8d32">a47e6442</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-06-10T03:39:12-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Always use rnImplicitBndrs to bring implicit tyvars into scope
This implements a first step towards #16762 by changing the renamer
to always use `rnImplicitBndrs` to bring implicitly bound type
variables into scope. The main change is in `rnFamInstEqn` and
`bindHsQTyVars`, which previously used _ad hoc_ methods of binding
their implicit tyvars.
There are a number of knock-on consequences:
* One of the reasons that `rnFamInstEqn` used an _ad hoc_ binding
mechanism was to give more precise source locations in
`-Wunused-type-patterns` warnings. (See
https://gitlab.haskell.org/ghc/ghc/issues/16762#note_273343 for an
example of this.) However, these warnings are actually a little
_too_ precise, since implicitly bound type variables don't have
exact binding sites like explicitly bound type variables do.
A similar problem existed for
"`Different names for the same type variable`" errors involving
implicit tyvars bound by `bindHsQTyVars`.
Therefore, we simply accept the less precise (but more accurate)
source locations from `rnImplicitBndrs` in `rnFamInstEqn` and
`bindHsQTyVars`. See
`Note [Source locations for implicitly bound type variables]` in
`GHC.Rename.HsType` for the full story.
* In order for `rnImplicitBndrs` to work in `rnFamInstEqn`, it needs
to be able to look up names from the parent class (in the event
that we are renaming an associated type family instance). As a
result, `rnImplicitBndrs` now takes an argument of type
`Maybe assoc`, which is `Just` in the event that a type family
instance is associated with a class.
* Previously, GHC kept track of three type synonyms for free type
variables in the renamer: `FreeKiTyVars`, `FreeKiTyVarsDups`
(which are allowed to contain duplicates), and
`FreeKiTyVarsNoDups` (which contain no duplicates). However, making
is a distinction between `-Dups` and `-NoDups` is now pointless, as
all code that returns `FreeKiTyVars{,Dups,NoDups}` will eventually
end up being passed to `rnImplicitBndrs`, which removes duplicates.
As a result, I decided to just get rid of `FreeKiTyVarsDups` and
`FreeKiTyVarsNoDups`, leaving only `FreeKiTyVars`.
* The `bindLRdrNames` and `deleteBys` functions are now dead code, so
I took the liberty of removing them.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2487912938f188cb264e4a11d21bf750adccc5e7">24879129</a></strong>
<div>
<span>by Takenobu Tani</span>
<i>at 2020-06-10T03:39:59-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Clarify leaf module names for new module hierarchy
This updates comments only.
This patch replaces leaf module names according to new module
hierarchy [1][2] as followings:
* Expand leaf names to easily find the module path:
for instance, `Id.hs` to `GHC.Types.Id`.
* Modify leaf names according to new module hierarchy:
for instance, `Convert.hs` to `GHC.ThToHs`.
* Fix typo:
for instance, `GHC.Core.TyCo.Rep.hs` to `GHC.Core.TyCo.Rep`
See also !3375
[1]: https://gitlab.haskell.org/ghc/ghc/-/wikis/Make-GHC-codebase-more-modular
[2]: https://gitlab.haskell.org/ghc/ghc/issues/13009
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/92de9e25aa1a6f7aa73154868521bcf4f0dc9d1e">92de9e25</a></strong>
<div>
<span>by Ömer Sinan Ağacan</span>
<i>at 2020-06-10T03:41:07-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts: Remove unused GET_ENTRY closure macro
This macro is not used and got broken in the meantime, as ENTRY_CODE was
deleted.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/87102928cce33d9029ca4cc449dde6efc802b8ec">87102928</a></strong>
<div>
<span>by Ömer Sinan Ağacan</span>
<i>at 2020-06-10T03:41:50-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix -fkeep-cafs flag name in users guide
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ccd6843d4a39920b4fa02badbe82e529390d4a74">ccd6843d</a></strong>
<div>
<span>by Shayne Fletcher</span>
<i>at 2020-06-10T04:14:57-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Expose impliedGFlags, impledOffGFlags, impliedXFlags
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7a737e898014d92bdbeed2e1cf5c35fc0a91a547">7a737e89</a></strong>
<div>
<span>by Ömer Sinan Ağacan</span>
<i>at 2020-06-10T04:14:58-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Cross-module LambdaFormInfo passing
- Store LambdaFormInfos of exported Ids in interface files
- Use them in importing modules
This is for optimization purposes: if we know LambdaFormInfo of imported
Ids we can generate more efficient calling code, see `getCallMethod`.
Exporting (putting them in interface files or in ModDetails) and
importing (reading them from interface files) are both optional. We
don't assume known LambdaFormInfos anywhere and do not change how we
call Ids with unknown LambdaFormInfos.
Runtime, allocation, and residency numbers when building
Cabal-the-library (commit 0d4ee7ba3):
(Log and .hp files are in the MR: !2842)
| | GHC HEAD | This patch | Diff |
|-----|----------|------------|----------------|
| -O0 | 0:35.89 | 0:34.10 | -1.78s, -4.98% |
| -O1 | 2:24.01 | 2:23.62 | -0.39s, -0.27% |
| -O2 | 2:52.23 | 2:51.35 | -0.88s, -0.51% |
| | GHC HEAD | This patch | Diff |
|-----|-----------------|-----------------|----------------------------|
| -O0 | 54,843,608,416 | 54,878,769,544 | +35,161,128 bytes, +0.06% |
| -O1 | 227,136,076,400 | 227,569,045,168 | +432,968,768 bytes, +0.19% |
| -O2 | 266,147,063,296 | 266,749,643,440 | +602,580,144 bytes, +0.22% |
NOTE: Residency is measured with extra runtime args: `-i0 -h` which effectively
turn all GCs into major GCs, and do GC more often.
| | GHC HEAD | This patch | Diff |
|-----|----------------------------|------------------------------|----------------------------|
| -O0 | 410,284,000 (910 samples) | 411,745,008 (906 samples) | +1,461,008 bytes, +0.35% |
| -O1 | 928,580,856 (2109 samples) | 943,506,552 (2103 samples) | +14,925,696 bytes, +1.60% |
| -O2 | 993,951,352 (2549 samples) | 1,010,156,328 (2545 samples) | +16,204,9760 bytes, +1.63% |
NoFib results:
--------------------------------------------------------------------------------
Program Size Allocs Instrs Reads Writes
--------------------------------------------------------------------------------
CS 0.0% 0.0% +0.0% +0.0% +0.0%
CSD 0.0% 0.0% 0.0% +0.0% +0.0%
FS 0.0% 0.0% +0.0% +0.0% +0.0%
S 0.0% 0.0% +0.0% +0.0% +0.0%
VS 0.0% 0.0% +0.0% +0.0% +0.0%
VSD 0.0% 0.0% +0.0% +0.0% +0.1%
VSM 0.0% 0.0% +0.0% +0.0% +0.0%
anna 0.0% 0.0% -0.3% -0.8% -0.0%
ansi 0.0% 0.0% -0.0% -0.0% 0.0%
atom 0.0% 0.0% -0.0% -0.0% 0.0%
awards 0.0% 0.0% -0.1% -0.3% 0.0%
banner 0.0% 0.0% -0.0% -0.0% -0.0%
bernouilli 0.0% 0.0% -0.0% -0.0% -0.0%
binary-trees 0.0% 0.0% -0.0% -0.0% +0.0%
boyer 0.0% 0.0% -0.0% -0.0% 0.0%
boyer2 0.0% 0.0% -0.0% -0.0% 0.0%
bspt 0.0% 0.0% -0.0% -0.2% 0.0%
cacheprof 0.0% 0.0% -0.1% -0.4% +0.0%
calendar 0.0% 0.0% -0.0% -0.0% 0.0%
cichelli 0.0% 0.0% -0.9% -2.4% 0.0%
circsim 0.0% 0.0% -0.0% -0.0% 0.0%
clausify 0.0% 0.0% -0.1% -0.3% 0.0%
comp_lab_zift 0.0% 0.0% -0.0% -0.0% +0.0%
compress 0.0% 0.0% -0.0% -0.0% -0.0%
compress2 0.0% 0.0% -0.0% -0.0% 0.0%
constraints 0.0% 0.0% -0.1% -0.2% -0.0%
cryptarithm1 0.0% 0.0% -0.0% -0.0% 0.0%
cryptarithm2 0.0% 0.0% -1.4% -4.1% -0.0%
cse 0.0% 0.0% -0.0% -0.0% -0.0%
digits-of-e1 0.0% 0.0% -0.0% -0.0% -0.0%
digits-of-e2 0.0% 0.0% -0.0% -0.0% -0.0%
dom-lt 0.0% 0.0% -0.1% -0.2% 0.0%
eliza 0.0% 0.0% -0.5% -1.5% 0.0%
event 0.0% 0.0% -0.0% -0.0% -0.0%
exact-reals 0.0% 0.0% -0.1% -0.3% +0.0%
exp3_8 0.0% 0.0% -0.0% -0.0% -0.0%
expert 0.0% 0.0% -0.3% -1.0% -0.0%
fannkuch-redux 0.0% 0.0% +0.0% +0.0% +0.0%
fasta 0.0% 0.0% -0.0% -0.0% +0.0%
fem 0.0% 0.0% -0.0% -0.0% 0.0%
fft 0.0% 0.0% -0.0% -0.0% 0.0%
fft2 0.0% 0.0% -0.0% -0.0% 0.0%
fibheaps 0.0% 0.0% -0.0% -0.0% +0.0%
fish 0.0% 0.0% 0.0% -0.0% +0.0%
fluid 0.0% 0.0% -0.4% -1.2% +0.0%
fulsom 0.0% 0.0% -0.0% -0.0% 0.0%
gamteb 0.0% 0.0% -0.1% -0.3% 0.0%
gcd 0.0% 0.0% -0.0% -0.0% 0.0%
gen_regexps 0.0% 0.0% -0.0% -0.0% -0.0%
genfft 0.0% 0.0% -0.0% -0.0% 0.0%
gg 0.0% 0.0% -0.0% -0.0% +0.0%
grep 0.0% 0.0% -0.0% -0.0% -0.0%
hidden 0.0% 0.0% -0.1% -0.4% -0.0%
hpg 0.0% 0.0% -0.2% -0.5% +0.0%
ida 0.0% 0.0% -0.0% -0.0% +0.0%
infer 0.0% 0.0% -0.3% -0.8% -0.0%
integer 0.0% 0.0% -0.0% -0.0% +0.0%
integrate 0.0% 0.0% -0.0% -0.0% 0.0%
k-nucleotide 0.0% 0.0% -0.0% -0.0% +0.0%
kahan 0.0% 0.0% -0.0% -0.0% +0.0%
knights 0.0% 0.0% -2.2% -5.4% 0.0%
lambda 0.0% 0.0% -0.6% -1.8% 0.0%
last-piece 0.0% 0.0% -0.0% -0.0% 0.0%
lcss 0.0% 0.0% -0.0% -0.1% 0.0%
life 0.0% 0.0% -0.0% -0.1% 0.0%
lift 0.0% 0.0% -0.2% -0.6% +0.0%
linear 0.0% 0.0% -0.0% -0.0% -0.0%
listcompr 0.0% 0.0% -0.0% -0.0% 0.0%
listcopy 0.0% 0.0% -0.0% -0.0% 0.0%
maillist 0.0% 0.0% -0.1% -0.3% +0.0%
mandel 0.0% 0.0% -0.0% -0.0% 0.0%
mandel2 0.0% 0.0% -0.0% -0.0% -0.0%
mate +0.0% 0.0% -0.0% -0.0% -0.0%
minimax 0.0% 0.0% -0.2% -1.0% 0.0%
mkhprog 0.0% 0.0% -0.1% -0.2% -0.0%
multiplier 0.0% 0.0% -0.0% -0.0% -0.0%
n-body 0.0% 0.0% -0.0% -0.0% +0.0%
nucleic2 0.0% 0.0% -0.1% -0.2% 0.0%
para 0.0% 0.0% -0.0% -0.0% -0.0%
paraffins 0.0% 0.0% -0.0% -0.0% 0.0%
parser 0.0% 0.0% -0.2% -0.7% 0.0%
parstof 0.0% 0.0% -0.0% -0.0% +0.0%
pic 0.0% 0.0% -0.0% -0.0% 0.0%
pidigits 0.0% 0.0% +0.0% +0.0% +0.0%
power 0.0% 0.0% -0.2% -0.6% +0.0%
pretty 0.0% 0.0% -0.0% -0.0% -0.0%
primes 0.0% 0.0% -0.0% -0.0% 0.0%
primetest 0.0% 0.0% -0.0% -0.0% -0.0%
prolog 0.0% 0.0% -0.3% -1.1% 0.0%
puzzle 0.0% 0.0% -0.0% -0.0% 0.0%
queens 0.0% 0.0% -0.0% -0.0% +0.0%
reptile 0.0% 0.0% -0.0% -0.0% 0.0%
reverse-complem 0.0% 0.0% -0.0% -0.0% +0.0%
rewrite 0.0% 0.0% -0.7% -2.5% -0.0%
rfib 0.0% 0.0% -0.0% -0.0% 0.0%
rsa 0.0% 0.0% -0.0% -0.0% 0.0%
scc 0.0% 0.0% -0.1% -0.2% -0.0%
sched 0.0% 0.0% -0.0% -0.0% -0.0%
scs 0.0% 0.0% -1.0% -2.6% +0.0%
simple 0.0% 0.0% +0.0% -0.0% +0.0%
solid 0.0% 0.0% -0.0% -0.0% 0.0%
sorting 0.0% 0.0% -0.6% -1.6% 0.0%
spectral-norm 0.0% 0.0% +0.0% 0.0% +0.0%
sphere 0.0% 0.0% -0.0% -0.0% -0.0%
symalg 0.0% 0.0% -0.0% -0.0% +0.0%
tak 0.0% 0.0% -0.0% -0.0% 0.0%
transform 0.0% 0.0% -0.0% -0.0% 0.0%
treejoin 0.0% 0.0% -0.0% -0.0% 0.0%
typecheck 0.0% 0.0% -0.0% -0.0% +0.0%
veritas +0.0% 0.0% -0.2% -0.4% +0.0%
wang 0.0% 0.0% -0.0% -0.0% 0.0%
wave4main 0.0% 0.0% -0.0% -0.0% -0.0%
wheel-sieve1 0.0% 0.0% -0.0% -0.0% -0.0%
wheel-sieve2 0.0% 0.0% -0.0% -0.0% +0.0%
x2n1 0.0% 0.0% -0.0% -0.0% -0.0%
--------------------------------------------------------------------------------
Min 0.0% 0.0% -2.2% -5.4% -0.0%
Max +0.0% 0.0% +0.0% +0.0% +0.1%
Geometric Mean -0.0% -0.0% -0.1% -0.3% +0.0%
Metric increases micro benchmarks tracked in #17686:
Metric Increase:
T12150
T12234
T12425
T13035
T5837
T6048
T9233
Co-authored-by: Andreas Klebinger <klebinger.andreas@gmx.at>
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/3b22b14a7a1c1819fc8682fc127acf7448c5630c">3b22b14a</a></strong>
<div>
<span>by Shayne Fletcher</span>
<i>at 2020-06-10T04:15:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Give Language a Bounded instance
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9454511b0bdfcd79a1899d7f24bf65a3eb0d06e3">9454511b</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-06-10T04:17:06-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Optimisation in Unique.Supply
This patch switches on -fno-state-hack in GHC.Types.Unique.Supply.
It turned out that my fixes for #18078 (coercion floating) changed the
optimisation pathway for mkSplitUniqSupply in such a way that we had
an extra allocation inside the inner loop. Adding -fno-state-hack
fixed that -- and indeed the loop in mkSplitUniqSupply is a classic
example of the way in which -fno-state-hack can be bad; see #18238.
Moreover, the new code is better than the old. They allocate
the same, but the old code ends up with a partial application.
The net effect is that the test
perf/should_run/UniqLoop
runs 20% faster! From 2.5s down to 2.0s. The allocation numbers
are the same -- but elapsed time falls. Good!
The bad thing about this is that it's terribly delicate. But
at least it's a good example of such delicacy in action.
There is a long Note [Optimising the unique supply] which now
explains all this.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6d49d5be904c0c01788fa7aae1b112d5b4dfaf1c">6d49d5be</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-06-10T04:17:06-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Implement cast worker/wrapper properly
The cast worker/wrapper transformation transforms
x = e |> co
into
y = e
x = y |> co
This is done by the simplifier, but we were being
careless about transferring IdInfo from x to y,
and about what to do if x is a NOINLNE function.
This resulted in a series of bugs:
#17673, #18093, #18078.
This patch fixes all that:
* Main change is in GHC.Core.Opt.Simplify, and
the new prepareBinding function, which does this
cast worker/wrapper transform.
See Note [Cast worker/wrappers].
* There is quite a bit of refactoring around
prepareRhs, makeTrivial etc. It's nicer now.
* Some wrappers from strictness and cast w/w, notably those for
a function with a NOINLINE, should inline very late. There
wasn't really a mechanism for that, which was an existing bug
really; so I invented a new finalPhase = Phase (-1). It's used
for all simplifier runs after the user-visible phase 2,1,0 have
run. (No new runs of the simplifier are introduced thereby.)
See new Note [Compiler phases] in GHC.Types.Basic;
the main changes are in GHC.Core.Opt.Driver
* Doing this made me trip over two places where the AnonArgFlag on a
FunTy was being lost so we could end up with (Num a -> ty)
rather than (Num a => ty)
- In coercionLKind/coercionRKind
- In contHoleType in the Simplifier
I fixed the former by defining mkFunctionType and using it in
coercionLKind/RKind.
I could have done the same for the latter, but the information
is almost to hand. So I fixed the latter by
- adding sc_hole_ty to ApplyToVal (like ApplyToTy),
- adding as_hole_ty to ValArg (like TyArg)
- adding sc_fun_ty to StrictArg
Turned out I could then remove ai_type from ArgInfo. This is
just moving the deck chairs around, but it worked out nicely.
See the new Note [AnonArgFlag] in GHC.Types.Var
* When looking at the 'arity decrease' thing (#18093) I discovered
that stable unfoldings had a much lower arity than the actual
optimised function. That's what led to the arity-decrease
message. Simple solution: eta-expand.
It's described in Note [Eta-expand stable unfoldings]
in GHC.Core.Opt.Simplify
* I also discovered that unsafeCoerce wasn't being inlined if
the context was boring. So (\x. f (unsafeCoerce x)) would
create a thunk -- yikes! I fixed that by making inlineBoringOK
a bit cleverer: see Note [Inline unsafeCoerce] in GHC.Core.Unfold.
I also found that unsafeCoerceName was unused, so I removed it.
I made a test case for #18078, and a very similar one for #17673.
The net effect of all this on nofib is very modest, but positive:
--------------------------------------------------------------------------------
Program Size Allocs Runtime Elapsed TotalMem
--------------------------------------------------------------------------------
anna -0.4% -0.1% -3.1% -3.1% 0.0%
fannkuch-redux -0.4% -0.3% -0.1% -0.1% 0.0%
maillist -0.4% -0.1% -7.8% -1.0% -14.3%
primetest -0.4% -15.6% -7.1% -6.6% 0.0%
--------------------------------------------------------------------------------
Min -0.9% -15.6% -13.3% -14.2% -14.3%
Max -0.3% 0.0% +12.1% +12.4% 0.0%
Geometric Mean -0.4% -0.2% -2.3% -2.2% -0.1%
All following metric decreases are compile-time allocation decreases
between -1% and -3%:
Metric Decrease:
T5631
T13701
T14697
T15164
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/32fd37f5e1e6dc6e3b664ae41e0041ed8a19ae21">32fd37f5</a></strong>
<div>
<span>by Luke Lau</span>
<i>at 2020-06-10T04:17:22-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix lookupGlobalOccRn_maybe sometimes reporting an error
In some cases it was possible for lookupGlobalOccRn_maybe to return an
error, when it should be returning a Nothing. If it called
lookupExactOcc_either when there were no matching GlobalRdrElts in the
otherwise case, it would return an error message. This could be caused
when lookupThName_maybe in Template Haskell was looking in different
namespaces (thRdrNameGuesses), guessing different namespaces that the
name wasn't guaranteed to be found in.
However, by addressing this some more accurate errors were being lost in
the conversion to Maybes. So some of the lookup* functions have been
shuffled about so that errors should always be ignored in
lookup*_maybes, and propagated otherwise.
This fixes #18263
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9b283e1b2a46af614d89b0e3a0dfd23871511c17">9b283e1b</a></strong>
<div>
<span>by Roland Senn</span>
<i>at 2020-06-10T04:17:34-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Initialize the allocation counter in GHCi to 0 (Fixes #16012)
According to the documentation for the function `getAllocationCounter` in
[System.Mem](http://hackage.haskell.org/package/base-4.14.0.0/docs/System-Mem.html)
initialize the allocationCounter also in GHCi to 0.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8d07c48ce3fde32a3c08c84764e0859b84eee461">8d07c48c</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-10T04:17:36-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">test: fix conc038
We had spurious failures of conc038 test on CI with stdout:
```
newThread started
-mainThread
-Haskell: 2
newThread back again
+mainThread
1 sec later
shutting down
+Haskell: 2
```
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4c7e9689f6fcc3eb974f0a76ae8078abda30026d">4c7e9689</a></strong>
<div>
<span>by Sebastian Graf</span>
<i>at 2020-06-11T10:37:38+02:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Release Notes: Add news from the pattern-match checker [skip ci]
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/3445b9652671280920755ee3d2b49780eeb3a991">3445b965</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Only test T16190 with the NCG
T16190 is meant to test a NCG feature. It has already caused spurious
failures in other MRs (e.g. !2165) when LLVM is used.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2517a51c0f949c1021de9f7c16f67345c6ab78a9">2517a51c</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">DynFlags refactoring VIII (#17957)
* Remove several uses of `sdocWithDynFlags`, especially in GHC.Llvm.*
* Add LlvmOpts datatype to store Llvm backend options
* Remove Outputable instances (for LlvmVar, LlvmLit, LlvmStatic and
Llvm.MetaExpr) which require LlvmOpts.
* Rename ppMetaExpr into ppMetaAnnotExpr (pprMetaExpr is now used in place of `ppr :: MetaExpr -> SDoc`)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7a02599afe836ac32c2e732671415d0afdfbf7fb">7a02599a</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove unused code
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/72d086106d49bc18277f3a066e671e87e9b37a1b">72d08610</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Refactor homeUnit
* rename thisPackage into homeUnit
* document and refactor several Backpack things
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8dc71f5577a541168951371bd55b51a588b57813">8dc71f55</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Rename unsafeGetUnitInfo into unsafeLookupUnit
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/f6be6e432e53108075905c1fc7785d8b1f18a33f">f6be6e43</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add allowVirtualUnits field in PackageState
Instead of always querying DynFlags to know whether we are allowed to
use virtual units (i.e. instantiated on-the-fly, cf Note [About units]
in GHC.Unit), we store it once for all in
`PackageState.allowVirtualUnits`.
This avoids using DynFlags too much (cf #17957) and is preliminary work
for #14335.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e7272d53e67e72580caceae40e766c4bfeb1c398">e7272d53</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Enhance UnitId use
* use UnitId instead of String to identify wired-in units
* use UnitId instead of Unit in the backend (Unit are only use by
Backpack to produce type-checked interfaces, not real code)
* rename lookup functions for consistency
* documentation
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9c5572cd29924dcc6effd8e102c9bb30d7b39bec">9c5572cd</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove LinkerUnitId type alias
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d345edfe96a3fdf35b8e953c1a4aacc325ca948e">d345edfe</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Refactor WiredMap
* Remove WiredInUnitId and WiredUnitId type aliases
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/3d171cd6d5cfbc8eae12cd1b152541d4f285b245">3d171cd6</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Document and refactor `mkUnit` and `mkUnitInfoMap`
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d2109b4f10ddbe09ac3397486922142f0cadaacc">d2109b4f</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove PreloadUnitId type alias
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/f50c19b8a78da9252cb39f49c1c66db4a684cc3b">f50c19b8</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Rename listUnitInfoMap into listUnitInfo
There is no Map involved
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ed533ec217667423e4fce30040f24053dbcc7de4">ed533ec2</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Rename Package into Unit
The terminology changed over time and now package databases contain
"units" (there can be several units compiled from a single Cabal
package: one per-component, one for each option set, one per
instantiation, etc.). We should try to be consistent internally and use
"units": that's what this renaming does. Maybe one day we'll fix the UI
too (e.g. replace -package-id with -unit-id, we already have
-this-unit-id and ghc-pkg has -unit-id...) but it's not done in this
patch.
* rename getPkgFrameworkOpts into getUnitFrameworkOpts
* rename UnitInfoMap into ClosureUnitInfoMap
* rename InstalledPackageIndex into UnitInfoMap
* rename UnusablePackages into UnusableUnits
* rename PackagePrecedenceIndex into UnitPrecedenceMap
* rename PackageDatabase into UnitDatabase
* rename pkgDatabase into unitDatabases
* rename pkgState into unitState
* rename initPackages into initUnits
* rename renamePackage into renameUnitInfo
* rename UnusablePackageReason into UnusableUnitReason
* rename getPackage* into getUnit*
* etc.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/202728e529f2faa88731b9f4b34b2ac567eb7c95">202728e5</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Make ClosureUnitInfoMap uses UnitInfoMap
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/55b4263e1a53cc27b1da9227249bdcd20139ddc9">55b4263e</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove ClosureUnitInfoMap
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/653d17bdd57ec8ca9b11b19e45860982bd1e7c9e">653d17bd</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Rename Package into Unit (2)
* rename PackageState into UnitState
* rename findWiredInPackages into findWiredInUnits
* rename lookupModuleInAll[Packages,Units]
* etc.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ae900605c4860684c51584dac271956635eb60cc">ae900605</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Move dump_mod_map into initUnits
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/598cc1dde543807902fd502b5e2f8050ebac1fa5">598cc1dd</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Move wiring of homeUnitInstantiations outside of mkUnitState
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/437265eb26b45a2de3ac537b6bc9a81986d4f7ae">437265eb</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Avoid timing module map dump in initUnits
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9400aa934880695b83201e192998de2576cfdf92">9400aa93</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove preload parameter of mkUnitState
* Remove preload parameter (unused)
* Don't explicitly return preloaded units: redundant because already
returned as "preloadUnits" field of UnitState
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/266bc3d9c3735620598ab18ff6ac9c44134cbbff">266bc3d9</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">DynFlags: refactor unwireUnit
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9e715c1b84702dc60fe31fd19dacf85335d59b27">9e715c1b</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Document getPreloadUnitsAnd
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/bd5810dc4e23331ca4f73ec3b1818c3350b5bbd7">bd5810dc</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">DynFlags: remove useless add_package parameter
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/36e1daf0a604d98a34d9a066a01dd4f5439b4aca">36e1daf0</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">DynFlags: make listVisibleModuleNames take a UnitState
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/5226da37845ae82bff0e3e6b16be7453e3d9370d">5226da37</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Refactor and document add_package
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4b53aac1e2128fa9baa5fd4623fcb3afd2602870">4b53aac1</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Refactor and document closeUnitDeps
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/42c054f6cd7a9890c3e9d2d0c444252abe08a8d5">42c054f6</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">DynFlags: findWiredInUnits
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a444d01bc97be99b7743b752a33ca9982de4c0f1">a444d01b</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">DynFlags: reportCycles, reportUnusable
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8408d521a67e2af4012d886d6a7e2af02ce42add">8408d521</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">DynFlags: merge_databases
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/fca2d25ff76d442d0825847643ed7448492e0e55">fca2d25f</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">DynFlags: add UnitConfig datatype
Avoid directly querying flags from DynFlags to build the UnitState.
Instead go via UnitConfig so that we could reuse this to make another
UnitState for plugins.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4274688a6333abffdfe7c7bda252c566f947afdf">4274688a</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Move distrustAll into mkUnitState
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/28d804e1e12a6be9bcd94b4667e27ba73beade38">28d804e1</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Create helper upd_wired_in_home_instantiations
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ac964c8350ba41082e9dca9cf1b7ff02aea2a636">ac964c83</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Put database cache in UnitConfig
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/bfd0a78cdd0287c26998a4d9419174e4dc305c6f">bfd0a78c</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Don't return preload units when we set DyNFlags
Preload units can be retrieved in UnitState when needed (i.e. in GHCi)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/1fbb4bf5f3d31f115e5a824588efc529cebf3185">1fbb4bf5</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">NCGConfig: remove useless ncgUnitId field
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c10ff7e7e5e5bd687938b5a4256e980cf58fcad1">c10ff7e7</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Doc: fix some comments
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/456e17f035238984e487870fe8007f5fb5f726cf">456e17f0</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Bump haddock submodule and allow metric decrease
Metric Decrease:
T12150
T12234
T5837
Metric Increase:
T16190
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/429539025450757e30124fa9ee33206deeb951a2">42953902</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-06-13T02:13:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Trim the demand for recursive product types
Ticket #18304 showed that we need to be very careful
when exploring the demand (esp usage demand) on recursive
product types.
This patch solves the problem by trimming the demand on such types --
in effect, a form of "widening".
See the Note [Trimming a demand to a type] in DmdAnal, which explains
how I did this by piggy-backing on an existing mechansim for trimming
demands becuase of GADTs. The significant payload of this patch is
very small indeed:
* Make GHC.Core.Opt.WorkWrap.Utils.typeShape use RecTcChecker to
avoid looking through recursive types.
But on the way
* I found that ae_rec_tc was entirely inoperative and did nothing.
So I removed it altogether from DmdAnal.
* I moved some code around in DmdAnal and Demand.
(There are no actual changes in dmdFix.)
* I changed the API of DmsAnal.dmdAnalRhsLetDown to return
a StrictSig rather than a decorated Id
* I removed the dead function peelTsFuns from Demand
Performance effects:
Nofib: 0.0% changes. Not surprising, because they don't
use recursive products
Perf tests
T12227:
1% increase in compiler allocation, becuase $cto gets w/w'd.
It did not w/w before because it takes a deeply nested
argument, so the worker gets too many args, so we abandon w/w
altogether (see GHC.Core.Opt.WorkWrap.Utils.isWorkerSmallEnough)
With this patch we trim the demands. That is not strictly
necessary (since these Generic type constructors are like
tuples -- they can't cause a loop) but the net result is that
we now w/w $cto which is fine.
UniqLoop:
16% decrease in /runtime/ allocation. The UniqSupply is a
recursive product, so currently we abandon all strictness on
'churn'. With this patch 'churn' gets useful strictness, and
we w/w it. Hooray
Metric Decrease:
UniqLoop
Metric Increase:
T12227
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/87d504f475471c61305b29578da2656f9ff9653e">87d504f4</a></strong>
<div>
<span>by Viktor Dukhovni</span>
<i>at 2020-06-13T02:13:05-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add introductory prose for Data.Traversable
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9f09b608eecf07ad6c27729f7b6f74aca4e17e6c">9f09b608</a></strong>
<div>
<span>by Oleg Grenrus</span>
<i>at 2020-06-13T02:13:07-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix #12073: Add MonadFix Q instance
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/220c2d34a34727d696cc4b44a1b87aba83231ce4">220c2d34</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-06-13T02:13:07-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite: Increase size of T12150
As noted in #18319, this test was previously very fragile. Increase its
size to make it more likely that its fails with its newly-increased
acceptance threshold.
Metric Increase:
T12150
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8bba1c26193e704d2d6bb2be9a2fac668b0ea54c">8bba1c26</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-06-13T04:59:06-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">gitlab-ci: Always push perf notes
Previously we ci.sh would run with `set -e` implying that we wouldn't
push perf notes if the testsuite were to fail, even if it *only* failed
due to perf notes. This rendered the whole performance testing story
quite fragile as a single regressing commit would cause every successive
commit to fail since a new baseline would not be uploaded.
Fix this by ensuring that we always push performance notes.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7a773f169cfe072c7b29924c53075e4dfa4e2adb">7a773f16</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-06-13T15:10:55-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">gitlab-ci: Eliminate redundant push of CI metrics
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a31218f7737a65b6333ec7905e88dc094703f025">a31218f7</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-06-13T15:58:37-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Use HsForAllTelescope to avoid inferred, visible foralls
Currently, `HsForAllTy` permits the combination of `ForallVis` and
`Inferred`, but you can't actually typecheck code that uses it
(e.g., `forall {a} ->`). This patch refactors `HsForAllTy` to use a
new `HsForAllTelescope` data type that makes a type-level distinction
between visible and invisible `forall`s such that visible `forall`s
do not track `Specificity`. That part of the patch is actually quite
small; the rest is simply changing consumers of `HsType` to
accommodate this new type.
Fixes #18235. Bumps the `haddock` submodule.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c0e6dee99242eff08420176a36d77b715972f1f2">c0e6dee9</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-06-14T09:07:44-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Add Atomic Exchange PrimOp and implement Atomic Ptr exchanges.
The initial version was rewritten by Tamar Christina.
It was rewritten in large parts by Andreas Klebinger.
Co-authored-by: Andreas Klebinger <klebinger.andreas@gmx.at>
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9a7462fb6b8bdd6326a607bbd7b9453eb588193b">9a7462fb</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-06-14T15:35:23-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">codeGen: Don't discard live case binders in unsafeEqualityProof logic
Previously CoreToStg would unconditionally discard cases of the form:
case unsafeEqualityProof of wild { _ -> rhs }
and rather replace the whole thing with `rhs`. However, in some cases
(see #18227) the case binder is still live, resulting in unbound
occurrences in `rhs`. Fix this by only discarding the case if the case
binder is dead.
Fixes #18227.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e4137c486a3df66b49395beea7efc6e200cc9bac">e4137c48</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-06-14T15:35:23-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite: Add tests for #18227
T18227A is the original issue which gave rise to the ticket and depends
upon bytestring. T18227B is a minimized reproducer.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8bab9ff1e09c1566a4105146bd636634a24928b9">8bab9ff1</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-06-14T15:35:59-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">hadrian: Fix rts include and library paths
Fixes two bugs:
* (?) and (<>) associated in a surprising way
* We neglected to include libdw paths in the rts configure flags
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/bd761185561747fe0b3adc22602f75d7b50cd248">bd761185</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-06-14T15:35:59-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">hadrian: Drop redundant GHC arguments
Cabal should already be passing this arguments to GHC.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/01f7052cc182c0ced85522dc775ebc490bf094ce">01f7052c</a></strong>
<div>
<span>by Peter Trommler</span>
<i>at 2020-06-14T15:36:38-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">FFI: Fix pass small ints in foreign call wrappers
The Haskell calling convention requires integer parameters smaller
than wordsize to be promoted to wordsize (where the upper bits are
don't care). To access such small integer parameter read a word from
the parameter array and then cast that word to the small integer
target type.
Fixes #15933
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/502647f7583be626319482adf4ea3d905db0006d">502647f7</a></strong>
<div>
<span>by Krzysztof Gogolewski</span>
<i>at 2020-06-14T15:37:14-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix "ndecreasingIndentation" in manual (#18116)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9a9cc0897b676ffd6612562a46600ea98c53a58d">9a9cc089</a></strong>
<div>
<span>by Simon Jakobi</span>
<i>at 2020-06-15T13:10:00-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Use foldl' in unionManyUniqDSets
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/761dcb84cd4c50c6fbb361eb26fb429af87392a3">761dcb84</a></strong>
<div>
<span>by Moritz Angermann</span>
<i>at 2020-06-15T13:10:36-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Load .lo as well.
Some archives contain so called linker objects, with the affectionate
.lo suffic. For example the musl libc.a will come in that form. We
still want to load those objects, hence we should not discard them and
look for .lo as well. Ultimately we might want to fix this proerly by
looking at the file magic.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/cf01477f03da13caaf78caacc5b001cb46a86685">cf01477f</a></strong>
<div>
<span>by Vladislav Zavialov</span>
<i>at 2020-06-15T13:11:20-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">User's Guide: KnownNat evidence is Natural
This bit of documentation got outdated after commit
1fcede43d2b30f33b7505e25eb6b1f321be0407f
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d0dcbfe646e52d0a1ef6d6e59a059323485775eb">d0dcbfe6</a></strong>
<div>
<span>by Jan Hrček</span>
<i>at 2020-06-16T20:36:38+02:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix typos and formatting in user guide
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/56a9e95fd6c2f213d676c9a2bd0a6cf93c531dbb">56a9e95f</a></strong>
<div>
<span>by Jan Hrček</span>
<i>at 2020-06-16T20:36:38+02:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Resolve TODO
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/3e884d14102948ad49d75611da247beff25911a4">3e884d14</a></strong>
<div>
<span>by Jan Hrček</span>
<i>at 2020-06-16T20:36:38+02:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Rename TcHoleErrors to GHC.Tc.Errors.Hole
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d23fc67847a27222ad8a0c193e6a10b5a4c0cf48">d23fc678</a></strong>
<div>
<span>by Stefan Schulze Frielinghaus</span>
<i>at 2020-06-17T15:31:09-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">hadrian: Build with threaded runtime if available
See #16873.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/0639dc10e214280a90dd6b75ce86cf43d1eb2286">0639dc10</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-17T15:31:53-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">T16190: only measure bytes_allocated
Just adding `{-# LANGUAGE BangPatterns #-}` makes the two other metrics
fluctuate by 13%.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4cab68974dba3e674016514c939946ce60e58273">4cab6897</a></strong>
<div>
<span>by Adam Sandberg Ericsson</span>
<i>at 2020-06-17T15:32:44-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">docs: fix formatting in users guide
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/eb8115a8c4cbc842b66798480fefc7ab64d31931">eb8115a8</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-17T15:33:23-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Move CLabel assertions into smart constructors (#17957)
It avoids using DynFlags in the Outputable instance of Clabel to check
assertions at pretty-printing time.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7faa4509cd7dbc6e2f873e4997e8888bd6ec3507">7faa4509</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-06-17T15:43:31-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">base: Bump to 4.15.0.0
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/20616959a7f4821034e14a64c3c9bf288c9bc956">20616959</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-06-17T15:43:31-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">configure: Use grep -q instead of --quiet
The latter is apparently not supported by busybox.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/40fa237e1daab7a76b9871bb6c50b953a1addf23">40fa237e</a></strong>
<div>
<span>by Krzysztof Gogolewski</span>
<i>at 2020-06-17T16:21:58-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Linear types (#15981)
This is the first step towards implementation of the linear types proposal
(https://github.com/ghc-proposals/ghc-proposals/pull/111).
It features
* A language extension -XLinearTypes
* Syntax for linear functions in the surface language
* Linearity checking in Core Lint, enabled with -dlinear-core-lint
* Core-to-core passes are mostly compatible with linearity
* Fields in a data type can be linear or unrestricted; linear fields
have multiplicity-polymorphic constructors.
If -XLinearTypes is disabled, the GADT syntax defaults to linear fields
The following items are not yet supported:
* a # m -> b syntax (only prefix FUN is supported for now)
* Full multiplicity inference (multiplicities are really only checked)
* Decent linearity error messages
* Linear let, where, and case expressions in the surface language
(each of these currently introduce the unrestricted variant)
* Multiplicity-parametric fields
* Syntax for annotating lambda-bound or let-bound with a multiplicity
* Syntax for non-linear/multiple-field-multiplicity records
* Linear projections for records with a single linear field
* Linear pattern synonyms
* Multiplicity coercions (test LinearPolyType)
A high-level description can be found at
https://ghc.haskell.org/trac/ghc/wiki/LinearTypes/Implementation
Following the link above you will find a description of the changes made to Core.
This commit has been authored by
* Richard Eisenberg
* Krzysztof Gogolewski
* Matthew Pickering
* Arnaud Spiwack
With contributions from:
* Mark Barbone
* Alexander Vershilov
Updates haddock submodule.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6cb84c469bf1ab6b03e099f5d100e78800ca09e0">6cb84c46</a></strong>
<div>
<span>by Krzysztof Gogolewski</span>
<i>at 2020-06-17T16:22:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Various performance improvements
This implements several general performance improvements to GHC,
to offset the effect of the linear types change.
General optimisations:
- Add a `coreFullView` function which iterates `coreView` on the
head. This avoids making function recursive solely because the
iterate `coreView` themselves. As a consequence, this functions can
be inlined, and trigger case-of-known constructor (_e.g._
`kindRep_maybe`, `isLiftedRuntimeRep`, `isMultiplicityTy`,
`getTyVar_maybe`, `splitAppTy_maybe`, `splitFunType_maybe`,
`tyConAppTyCon_maybe`). The common pattern about all these functions
is that they are almost always used as views, and immediately
consumed by a case expression. This commit also mark them asx `INLINE`.
- In `subst_ty` add a special case for nullary `TyConApp`, which avoid
allocations altogether.
- Use `mkTyConApp` in `subst_ty` for the general `TyConApp`. This
required quite a bit of module shuffling.
case. `myTyConApp` enforces crucial sharing, which was lost during
substitution. See also !2952 .
- Make `subst_ty` stricter.
- In `eqType` (specifically, in `nonDetCmpType`), add a special case,
tested first, for the very common case of nullary `TyConApp`.
`nonDetCmpType` has been made `INLINE` otherwise it is actually a
regression. This is similar to the optimisations in !2952.
Linear-type specific optimisations:
- Use `tyConAppTyCon_maybe` instead of the more complex `eqType` in
the definition of the pattern synonyms `One` and `Many`.
- Break the `hs-boot` cycles between `Multiplicity.hs` and `Type.hs`:
`Multiplicity` now import `Type` normally, rather than from the
`hs-boot`. This way `tyConAppTyCon_maybe` can inline properly in the
`One` and `Many` pattern synonyms.
- Make `updateIdTypeAndMult` strict in its type and multiplicity
- The `scaleIdBy` gets a specialised definition rather than being an
alias to `scaleVarBy`
- `splitFunTy_maybe` is given the type `Type -> Maybe (Mult, Type,
Type)` instead of `Type -> Maybe (Scaled Type, Type)`
- Remove the `MultMul` pattern synonym in favour of a view `isMultMul`
because pattern synonyms appear not to inline well.
- in `eqType`, in a `FunTy`, compare multiplicities last: they are
almost always both `Many`, so it helps failing faster.
- Cache `manyDataConTy` in `mkTyConApp`, to make sure that all the
instances of `TyConApp ManyDataConTy []` are physically the same.
This commit has been authored by
* Richard Eisenberg
* Krzysztof Gogolewski
* Arnaud Spiwack
Metric Decrease:
haddock.base
T12227
T12545
T12990
T1969
T3064
T5030
T9872b
Metric Increase:
haddock.base
haddock.Cabal
haddock.compiler
T12150
T12234
T12425
T12707
T13035
T13056
T15164
T16190
T18304
T1969
T3064
T3294
T5631
T5642
T5837
T6048
T9020
T9233
T9675
T9872a
T9961
WWRec
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/57db91d8ee501c7cf176c4bb1e2101d3092fd0f6">57db91d8</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-17T16:22:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove integer-simple
integer-simple uses lists of words (`[Word]`) to represent big numbers
instead of ByteArray#:
* it is less efficient than the newer ghc-bignum native backend
* it isn't compatible with the big number representation that is now
shared by all the ghc-bignum backends (based on the one that was
used only in integer-gmp before).
As a consequence, we simply drop integer-simple
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9f96bc127d6231b5e76bbab442244eb303b08867">9f96bc12</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-17T16:22:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">ghc-bignum library
ghc-bignum is a newer package that aims to replace the legacy
integer-simple and integer-gmp packages.
* it supports several backends. In particular GMP is still supported and
most of the code from integer-gmp has been merged in the "gmp"
backend.
* the pure Haskell "native" backend is new and is much faster than the
previous pure Haskell implementation provided by integer-simple
* new backends are easier to write because they only have to provide a
few well defined functions. All the other code is common to all
backends. In particular they all share the efficient small/big number
distinction previously used only in integer-gmp.
* backends can all be tested against the "native" backend with a simple
Cabal flag. Backends are only allowed to differ in performance, their
results should be the same.
* Add `integer-gmp` compat package: provide some pattern synonyms and
function aliases for those in `ghc-bignum`. It is intended to avoid
breaking packages that depend on `integer-gmp` internals.
Update submodules: text, bytestring
Metric Decrease:
Conversions
ManyAlternatives
ManyConstructors
Naperian
T10359
T10547
T10678
T12150
T12227
T12234
T12425
T13035
T13719
T14936
T1969
T4801
T4830
T5237
T5549
T5837
T8766
T9020
parsing001
space_leak_001
T16190
haddock.base
On ARM and i386, T17499 regresses (+6% > 5%).
On x86_64 unregistered, T13701 sometimes regresses (+2.2% > 2%).
Metric Increase:
T17499
T13701
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/96aa57878fd6e6a7b92e841a0df8b5255a559c97">96aa5787</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-17T16:22:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Update compiler
Thanks to ghc-bignum, the compiler can be simplified:
* Types and constructors of Integer and Natural can be wired-in. It
means that we don't have to query them from interfaces. It also means
that numeric literals don't have to carry their type with them.
* The same code is used whatever ghc-bignum backend is enabled. In
particular, conversion of bignum literals into final Core expressions
is now much more straightforward. Bignum closure inspection too.
* GHC itself doesn't depend on any integer-* package anymore
* The `integerLibrary` setting is gone.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/0f67e3447e5a0089b5348940d404ed876fddddfc">0f67e344</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-17T16:22:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Update `base` package
* GHC.Natural isn't implemented in `base` anymore. It is provided by
ghc-bignum in GHC.Num.Natural. It means that we can safely use Natural
primitives in `base` without fearing issues with built-in rewrite
rules (cf #15286)
* `base` doesn't conditionally depend on an integer-* package anymore,
it depends on ghc-bignum
* Some duplicated code in integer-* can now be factored in GHC.Float
* ghc-bignum tries to use a uniform naming convention so most of the
other changes are renaming
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/aa9e7b7196f03f84579e3b4a09068c668cbe6ffb">aa9e7b71</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-17T16:22:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Update `make` based build system
* replace integer-* package selection with ghc-bignum backend selection
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/f817d816e60a487bca64037095c01e9956225b64">f817d816</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-17T16:22:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Update testsuite
* support detection of slow ghc-bignum backend (to replace the detection
of integer-simple use). There are still some test cases that the
native backend doesn't handle efficiently enough.
* remove tests for GMP only functions that have been removed from
ghc-bignum
* fix test results showing dependent packages (e.g. integer-gmp) or
showing suggested instances
* fix test using Integer/Natural API or showing internal names
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/dceecb093c3ee1e4dc970bb6669ff855ec37f6ac">dceecb09</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-17T16:22:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Update Hadrian
* support ghc-bignum backend selection in flavours and command-line
* support ghc-bignum "--check" flag (compare results of selected backend
against results of the native one) in flavours and command-line (e.g.
pass --bignum=check-gmp" to check the "gmp" backend)
* remove the hack to workaround #15286
* build GMP only when the gmp backend is used
* remove hacks to workaround `text` package flags about integer-*. We
fix `text` to use ghc-bignum unconditionally in another patch
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/fa4281d672e462b8421098b3506bd3c4c6a1f819">fa4281d6</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-17T16:22:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Bump bytestring and text submodules
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/1a3f6f348004a80d3d7add81b22e4217b648b145">1a3f6f34</a></strong>
<div>
<span>by Adam Sandberg Ericsson</span>
<i>at 2020-06-18T23:03:36-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">docs: mention -hiedir in docs for -outputdir
[skip ci]
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/729bcb02716593ae46d7baecce4776b3f353e3f7">729bcb02</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-18T23:04:17-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Hadrian: fix build on Mac OS Catalina (#17798)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/95e18292731cd799e024976f11c18fdf34bcb777">95e18292</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-06-18T23:04:58-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Relax allocation threshold for T12150.
This test performs little work, so the most minor allocation
changes often cause the test to fail.
Increasing the threshold to 2% should help with this.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8ce6c393888fad5d52dfe0bff9b72cd1cf9facc0">8ce6c393</a></strong>
<div>
<span>by Sebastian Graf</span>
<i>at 2020-06-18T23:05:36-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">hadrian: Bump pinned cabal.project to an existent index-state
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/08c1cb0f30770acbf366423f085f8ef92f7f6a06">08c1cb0f</a></strong>
<div>
<span>by Ömer Sinan Ağacan</span>
<i>at 2020-06-18T23:06:21-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix uninitialized field read in Linker.c
Valgrind report of the bug when running the test `linker_unload`:
==29666== Conditional jump or move depends on uninitialised value(s)
==29666== at 0x369C5B4: setOcInitialStatus (Linker.c:1305)
==29666== by 0x369C6C5: mkOc (Linker.c:1347)
==29666== by 0x36C027A: loadArchive_ (LoadArchive.c:522)
==29666== by 0x36C0600: loadArchive (LoadArchive.c:626)
==29666== by 0x2C144CD: ??? (in /home/omer/haskell/ghc_2/testsuite/tests/rts/linker/linker_unload.run/linker_unload)
==29666==
==29666== Conditional jump or move depends on uninitialised value(s)
==29666== at 0x369C5B4: setOcInitialStatus (Linker.c:1305)
==29666== by 0x369C6C5: mkOc (Linker.c:1347)
==29666== by 0x369C9F6: preloadObjectFile (Linker.c:1507)
==29666== by 0x369CA8D: loadObj_ (Linker.c:1536)
==29666== by 0x369CB17: loadObj (Linker.c:1557)
==29666== by 0x3866BC: main (linker_unload.c:33)
The problem is `mkOc` allocates a new `ObjectCode` and calls
`setOcInitialStatus` without initializing the `status` field.
`setOcInitialStatus` reads the field as first thing:
static void setOcInitialStatus(ObjectCode* oc) {
if (oc->status == OBJECT_DONT_RESOLVE)
return;
if (oc->archiveMemberName == NULL) {
oc->status = OBJECT_NEEDED;
} else {
oc->status = OBJECT_LOADED;
}
}
`setOcInitialStatus` is unsed in two places for two different purposes:
in `mkOc` where we don't have the `status` field initialized yet (`mkOc`
is supposed to initialize it), and `loadOc` where we do have `status`
field initialized and we want to update it. Instead of splitting the
function into two functions which are both called just once I inline the
functions in the use sites and remove it.
Fixes #18342
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/da18ff9935e72c7fe6127cb5d5d0c53654a204b0">da18ff99</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-06-18T23:07:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">fix windows bootstrap due to linker changes
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2af0ec9059b94e1fa6b37eda60216e0222e1a53d">2af0ec90</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-18T23:07:47-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">DynFlags: store default depth in SDocContext (#17957)
It avoids having to use DynFlags to reach for pprUserLength.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d4a0be758003f32b9d9d89cfd14b9839ac002f4d">d4a0be75</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-18T23:08:35-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Move tablesNextToCode field into Platform
tablesNextToCode is a platform setting and doesn't belong into DynFlags
(#17957). Doing this is also a prerequisite to fix #14335 where we deal
with two platforms (target and host) that may have different platform
settings.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/809caedffe489931efa8c96a60eaed6d7ff739b9">809caedf</a></strong>
<div>
<span>by John Ericson</span>
<i>at 2020-06-23T22:47:37-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Switch from HscSource to IsBootInterface for module lookup in GhcMake
We look up modules by their name, and not their contents. There is no
way to separately reference a signature vs regular module; you get what
you get. Only boot files can be referenced indepenently with `import {-#
SOURCE #-}`.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7750bd456f32c3e91b9165587fe290122b9c2444">7750bd45</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-23T22:48:18-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Cmm: introduce SAVE_REGS/RESTORE_REGS
We don't want to save both Fn and Dn register sets on x86-64 as they are
aliased to the same arch register (XMMn).
Moreover, when SAVE_STGREGS was used in conjunction with `jump foo [*]`
which makes a set of Cmm registers alive so that they cover all arch
registers used to pass parameter, we could have Fn, Dn and XMMn alive at
the same time. It made the LLVM code generator choke (see #17920).
Now `SAVE_REGS/RESTORE_REGS` and `jump foo [*]` use the same set of
registers.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2636794d1a1d0c4c2666d5afb002b0ba73600f8a">2636794d</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-23T22:48:18-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">CmmToC: don't add extern decl to parsed Cmm data
Previously, if a .cmm file *not in the RTS* contained something like:
```cmm
section "rodata" { msg : bits8[] "Test\n"; }
```
It would get compiled by CmmToC into:
```c
ERW_(msg);
const char msg[] = "Test\012";
```
and fail with:
```
/tmp/ghc32129_0/ghc_4.hc:5:12: error:
error: conflicting types for \u2018msg\u2019
const char msg[] = "Test\012";
^~~
In file included from /tmp/ghc32129_0/ghc_4.hc:3:0: error:
/tmp/ghc32129_0/ghc_4.hc:4:6: error:
note: previous declaration of \u2018msg\u2019 was here
ERW_(msg);
^
/builds/hsyl20/ghc/_build/install/lib/ghc-8.11.0.20200605/lib/../lib/x86_64-linux-ghc-8.11.0.20200605/rts-1.0/include/Stg.h:253:46: error:
note: in definition of macro \u2018ERW_\u2019
#define ERW_(X) extern StgWordArray (X)
^
```
See the rationale for this on https://gitlab.haskell.org/ghc/ghc/-/wikis/commentary/compiler/backends/ppr-c#prototypes
Now we don't generate these extern declarations (ERW_, etc.) for
top-level data. It shouldn't change anything for the RTS (the only place
we use .cmm files) as it is already special cased in
`GHC.Cmm.CLabel.needsCDecl`. And hand-written Cmm can use explicit
extern declarations when needed.
Note that it allows `cgrun069` test to pass with CmmToC (cf #15467).
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/5f6a0665512717271ac2b249d107e2a0cb18ae86">5f6a0665</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-23T22:48:18-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">LLVM: refactor and comment register padding code (#17920)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/cad62ef11972490b180fad3cd4a5c7754fa218e4">cad62ef1</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-23T22:48:18-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add tests for #17920
Metric Decrease:
T12150
T12234
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a2a9006b068ba9af9d41711307a8d597d2bb03d7">a2a9006b</a></strong>
<div>
<span>by Xavier Denis</span>
<i>at 2020-06-23T22:48:56-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix issue #18262 by zonking constraints after solving
Zonk residual constraints in checkForExistence to reveal user type
errors.
Previously when `:instances` was used with instances that have TypeError
constraints the result would look something like:
instance [safe] s0 => Err 'A -- Defined at ../Bug2.hs:8:10
whereas after zonking, `:instances` now sees the `TypeError` and
properly eliminates the constraint from the results.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/181516bcd6f18f22e1df3915bfca0c36524a725b">181516bc</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-06-23T22:49:33-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix a buglet in Simplify.simplCast
This bug, revealed by #18347, is just a missing update to
sc_hole_ty in simplCast. I'd missed a code path when I
made the recentchanges in
commit 6d49d5be904c0c01788fa7aae1b112d5b4dfaf1c
Author: Simon Peyton Jones <simonpj@microsoft.com>
Date: Thu May 21 12:53:35 2020 +0100
Implement cast worker/wrapper properly
The fix is very easy.
Two other minor changes
* Tidy up in SimpleOpt.simple_opt_expr. In fact I think this is an
outright bug, introduced in the fix to #18112: we were simplifying
the same coercion twice *with the same substitution*, which is just
wrong. It'd be a hard bug to trigger, so I just fixed it; less code
too.
* Better debug printing of ApplyToVal
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/625a7f5465d51d054c6930772412bad7d87189c5">625a7f54</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-06-23T22:50:11-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Two small tweaks to Coercion.simplifyArgsWorker
These tweaks affect the inner loop of simplifyArgsWorker, which
in turn is called from the flattener in Flatten.hs. This is
a key perf bottleneck to T9872{a,b,c,d}.
These two small changes have a modest but useful benefit.
No change in functionality whatsoever.
Relates to #18354
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b5768cce0214e20937f8e1d41ef1d9b5613b02ae">b5768cce</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-23T22:50:49-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Don't use timesInt2# with GHC < 8.11 (fix #18358)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7ad4085c22a8d5030545cc9e0fedd0784836ecbf">7ad4085c</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-23T22:51:27-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix invalid printf format
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a1f34d37b47826e86343e368a5c00f1a4b1f2bce">a1f34d37</a></strong>
<div>
<span>by Krzysztof Gogolewski</span>
<i>at 2020-06-23T22:52:09-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add missing entry to freeNamesItem (#18369)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/03a708ba8e8c323b07d8d2e0115d6eb59987cc02">03a708ba</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-06-25T03:54:37-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Enable large address space optimization on windows.
Starting with Win 8.1/Server 2012 windows no longer preallocates
page tables for reserverd memory eagerly, which prevented us from
using this approach in the past.
We also try to allocate the heap high in the memory space.
Hopefully this makes it easier to allocate things in the low
4GB of memory that need to be there. Like jump islands for the
linker.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7e6d3d09d983337df30d12e5aaa96bae9b81b324">7e6d3d09</a></strong>
<div>
<span>by Roland Senn</span>
<i>at 2020-06-25T03:54:38-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">In `:break ident` allow out of scope and nested identifiers (Fix #3000)
This patch fixes the bug and implements the feature request of #3000.
1. If `Module` is a real module name and `identifier` a name of a
top-level function in `Module` then `:break Module.identifer` works
also for an `identifier` that is out of scope.
2. Extend the syntax for `:break identifier` to:
:break [ModQual.]topLevelIdent[.nestedIdent]...[.nestedIdent]
`ModQual` is optional and is either the effective name of a module or
the local alias of a qualified import statement.
`topLevelIdent` is the name of a top level function in the module
referenced by `ModQual`.
`nestedIdent` is optional and the name of a function nested in a let or
where clause inside the previously mentioned function `nestedIdent` or
`topLevelIdent`.
If `ModQual` is a module name, then `topLevelIdent` can be any top level
identifier in this module. If `ModQual` is missing or a local alias of a
qualified import, then `topLevelIdent` must be in scope.
Breakpoints can be set on arbitrarily deeply nested functions, but the
whole chain of nested function names must be specified.
3. To support the new functionality rewrite the code to tab complete `:break`.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/30e42652ed895c3ed086e7834be46f93ba1cc61b">30e42652</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-06-25T03:54:39-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">make: Respect XELATEX variable
Previously we simply ignored the XELATEX variable when building
PDF documentation.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4acc2934952f4849c2082015d9bebef446d46545">4acc2934</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-06-25T03:54:39-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">hadrian/make: Detect makeindex
Previously we would simply assume that makeindex was available.
Now we correctly detect it in `configure` and respect this conclusion in
hadrian and make.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/0d61f866b43d3385be3a8521ba24503c13e8d404">0d61f866</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-06-25T03:54:40-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Expunge GhcTcId
GHC.Hs.Extension had
type GhcPs = GhcPass 'Parsed
type GhcRn = GhcPass 'Renamed
type GhcTc = GhcPass 'Typechecked
type GhcTcId = GhcTc
The last of these, GhcTcId, is a vestige of the past.
This patch expunges it from GHC.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8ddbed4ad1772ac7dfc96b352a3dc35d958a5f9b">8ddbed4a</a></strong>
<div>
<span>by Adam Wespiser</span>
<i>at 2020-06-25T03:54:40-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">add examples to Data.Traversable
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/284001d00995c82a1f2b38f696138ad683b5364b">284001d0</a></strong>
<div>
<span>by Oleg Grenrus</span>
<i>at 2020-06-25T03:54:42-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Export readBinIface_
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/90f438724dbc1ef9e4b371034d44170738fe3224">90f43872</a></strong>
<div>
<span>by Zubin Duggal</span>
<i>at 2020-06-25T03:54:43-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Export everything from HsToCore.
This lets us reuse these functions in haddock, avoiding synchronization bugs.
Also fixed some divergences with haddock in that file
Updates haddock submodule
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c7dd6da7e066872a949be7c914cc700182307cd2">c7dd6da7</a></strong>
<div>
<span>by Takenobu Tani</span>
<i>at 2020-06-25T03:54:44-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Clean up haddock hyperlinks of GHC.* (part1)
This updates haddock comments only.
This patch focuses to update for hyperlinks in GHC API's haddock comments,
because broken links especially discourage newcomers.
This includes the following hierarchies:
- GHC.Hs.*
- GHC.Core.*
- GHC.Stg.*
- GHC.Cmm.*
- GHC.Types.*
- GHC.Data.*
- GHC.Builtin.*
- GHC.Parser.*
- GHC.Driver.*
- GHC top
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/1eb997a84669f158de9dd16a9e54d279cec22293">1eb997a8</a></strong>
<div>
<span>by Takenobu Tani</span>
<i>at 2020-06-25T03:54:44-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Clean up haddock hyperlinks of GHC.* (part2)
This updates haddock comments only.
This patch focuses to update for hyperlinks in GHC API's haddock comments,
because broken links especially discourage newcomers.
This includes the following hierarchies:
- GHC.Iface.*
- GHC.Llvm.*
- GHC.Rename.*
- GHC.Tc.*
- GHC.HsToCore.*
- GHC.StgToCmm.*
- GHC.CmmToAsm.*
- GHC.Runtime.*
- GHC.Unit.*
- GHC.Utils.*
- GHC.SysTools.*
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/67a86b4d4d21954bae7aaddec7617228025a8270">67a86b4d</a></strong>
<div>
<span>by Oleg Grenrus</span>
<i>at 2020-06-25T03:54:46-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add MonadZip and MonadFix instances for Complex
These instances are taken from
https://hackage.haskell.org/package/linear-1.21/docs/Linear-Instances.html
They are the unique possible, so let they be in `base`.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c50ef26edaa537c0a13ac1a574632f9078c5671b">c50ef26e</a></strong>
<div>
<span>by Artem Pelenitsyn</span>
<i>at 2020-06-25T03:54:47-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">test suite: add reproducer for #17516
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/fe281b27d544920a2c2ddc00f6284006b85ab294">fe281b27</a></strong>
<div>
<span>by Roland Senn</span>
<i>at 2020-06-25T03:54:48-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Enable maxBound checks for OverloadedLists (Fixes #18172)
Consider the Literal `[256] :: [Data.Word.Word8]`
When the `OverloadedLists` extension is not active, then the `ol_ext` field
in the `OverLitTc` record that is passed to the function `getIntegralLit`
contains the type `Word8`. This is a simple type, and we can use its
type constructor immediately for the `warnAboutOverflowedLiterals` function.
When the `OverloadedLists` extension is active, then the `ol_ext` field
contains the type family `Item [Word8]`. The function `nomaliseType` is used
to convert it to the needed type `Word8`.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a788d4d17ad332dbfbe08e6822c52ae0de6ef496">a788d4d1</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-06-25T03:54:52-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts/Hash: Simplify freeing of HashListChunks
While looking at #18348 I noticed that the treatment of HashLists are a
bit more complex than necessary (which lead to some initial confusion on
my part). Specifically, we allocate HashLists in chunks. Each chunk
allocation makes two allocations: one for the chunk itself and one for a
HashListChunk to link together the chunks for the purposes of freeing.
Simplify this (and hopefully make the relationship between these
clearer) but allocating the HashLists and HashListChunk in a single
malloc. This will both make the implementation easier to follow and
reduce C heap fragmentation.
Note that even after this patch we fail to bound the size of the free
HashList pool. However, this is a separate bug.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d3c2d59bafe253dd7e4966a46564fb16acb1af5c">d3c2d59b</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-25T03:54:55-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">RTS: avoid overflow on 32-bit arch (#18375)
We're now correctly computing allocated bytes on 32-bit arch, so we get
huge increases.
Metric Increase:
haddock.Cabal
haddock.base
haddock.compiler
space_leak_001
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a3d69dc6c2134afe239caf4f881ba5542d2c2be0">a3d69dc6</a></strong>
<div>
<span>by Sebastian Graf</span>
<i>at 2020-06-25T23:06:18-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">GHC.Core.Unify: Make UM actions one-shot by default
This MR makes the UM monad in GHC.Core.Unify into a one-shot
monad. See the long Note [The one-shot state monad trick].
See also #18202 and !3309, which applies this to all Reader/State-like
monads in GHC for compile-time perf improvements. The pattern used
here enables something similar to the state-hack, but is applicable to
user-defined monads, not just `IO`.
Metric Decrease 'runtime/bytes allocated' (test_env='i386-linux-deb9'):
haddock.Cabal
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9ee58f8d900884ac8b721b6b95dbfa6500f39431">9ee58f8d</a></strong>
<div>
<span>by Matthias Pall Gissurarson</span>
<i>at 2020-06-26T17:12:45+00:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Implement the proposed -XQualifiedDo extension
Co-authored-by: Facundo Domínguez <facundo.dominguez@tweag.io>
QualifiedDo is implemented using the same placeholders for operation names in
the AST that were devised for RebindableSyntax. Whenever the renamer checks
which names to use for do syntax, it first checks if the do block is qualified
(e.g. M.do { stmts }), in which case it searches for qualified names in
the module M.
This allows users to write
{-# LANGUAGE QualifiedDo #-}
import qualified SomeModule as M
f x = M.do -- desugars to:
y <- M.return x -- M.return x M.>>= \y ->
M.return y -- M.return y M.>>
M.return y -- M.return y
See Note [QualifiedDo] and the users' guide for more details.
Issue #18214
Proposal:
https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0216-qualified-do.rst
Since we change the constructors `ITdo` and `ITmdo` to carry the new module
name, we need to bump the haddock submodule to account or the new shape of
these constructors.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ce987865d7594ecbcb3d27435eef773e95b2db85">ce987865</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-06-27T11:55:21-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Revamp the treatment of auxiliary bindings for derived instances
This started as a simple fix for #18321 that organically grew into a
much more sweeping refactor of how auxiliary bindings for derived
instances are handled. I have rewritten `Note [Auxiliary binders]`
in `GHC.Tc.Deriv.Generate` to explain all of the moving parts, but
the highlights are:
* Previously, the OccName of each auxiliary binding would be given
a suffix containing a hash of its package name, module name, and
parent data type to avoid name clashes. This was needlessly
complicated, so we take the more direct approach of generating
`Exact` `RdrName`s for each auxiliary binding with the same
`OccName`, but using an underlying `System` `Name` with a fresh
`Unique` for each binding. Unlike hashes, allocating new `Unique`s
does not require any cleverness and avoid name clashes all the
same...
* ...speaking of which, in order to convince the renamer that multiple
auxiliary bindings with the same `OccName` (but different
`Unique`s) are kosher, we now use `rnLocalValBindsLHS` instead of
`rnTopBindsLHS` to rename auxiliary bindings. Again, see
`Note [Auxiliary binders]` for the full story.
* I have removed the `DerivHsBind` constructor for
`DerivStuff`—which was only used for `Data.Data`-related
auxiliary bindings—and refactored `gen_Data_binds` to use
`DerivAuxBind` instead. This brings the treatment of
`Data.Data`-related auxiliary bindings in line with every other
form of auxiliary binding.
Fixes #18321.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a403eb917bd26caf96c29d67bfe91163b593b2c9">a403eb91</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-27T11:55:59-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">ghc-bignum: fix division by zero (#18359)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/1b3d13b68c95ef9bbeca4437028531d184abcbea">1b3d13b6</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-27T11:55:59-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix ghc-bignum exceptions
We must ensure that exceptions are not simplified. Previously we used:
case raiseDivZero of
_ -> 0## -- dummyValue
But it was wrong because the evaluation of `raiseDivZero` was removed and
the dummy value was directly returned. See new Note [ghc-bignum exceptions].
I've also removed the exception triggering primops which were fragile.
We don't need them to be primops, we can have them exported by ghc-prim.
I've also added a test for #18359 which triggered this patch.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a74ec37c9d7679a5563ab86a8759c79c3c5de6f0">a74ec37c</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-06-27T11:56:34-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Better loop detection in findTypeShape
Andreas pointed out, in !3466, that my fix for #18304 was not
quite right. This patch fixes it properly, by having just one
RecTcChecker rather than (implicitly) two nested ones, in
findTypeShape.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a04020b88d4935d675f989806aff251f459561e9">a04020b8</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-27T11:57:11-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">DynFlags: don't store buildTag
`DynFlags.buildTag` was a field created from the set of Ways in
`DynFlags.ways`. It had to be kept in sync with `DynFlags.ways` which
was fragile. We want to avoid global state like this (#17957).
Moreover in #14335 we also want to support loading units with different
ways: target units would still use `DynFlags.ways` but plugins would use
`GHC.Driver.Ways.hostFullWays`. To avoid having to deal both with build
tag and with ways, we recompute the buildTag on-the-fly (should be
pretty cheap) and we remove `DynFlags.buildTag` field.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/0e83efa24636c72811e4c79fe1c7e4f7cf3170cd">0e83efa2</a></strong>
<div>
<span>by Krzysztof Gogolewski</span>
<i>at 2020-06-27T11:57:49-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Don't generalize when typechecking a tuple section
The code is simpler and cleaner.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d8ba9e6f951a2f8c6e2429a8b2dcb035c392908f">d8ba9e6f</a></strong>
<div>
<span>by Peter Trommler</span>
<i>at 2020-06-28T09:19:11-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">RTS: Refactor Haskell-C glue for PPC 64-bit
Make sure the stack is 16 byte aligned even when reserved stack
bytes are not a multiple of 16 bytes.
Avoid saving r2 (TOC). On ELF v1 the function descriptor of StgReturn
has the same TOC as StgRun, on ELF v2 the TOC is recomputed in the
function prologue.
Use the ABI provided functions to save clobbered GPRs and FPRs.
Improve comments. Describe what the stack looks like and how it relates
to the respective ABIs.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/42f797b0ad034a92389e7081aa50ef4ab3434d01">42f797b0</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-06-28T09:19:46-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Use NHsCoreTy to embed types into GND-generated code
`GeneralizedNewtypeDeriving` is in the unique situation where it must
produce an `LHsType GhcPs` from a Core `Type`. Historically, this was
done with the `typeToLHsType` function, which walked over the entire
`Type` and attempted to construct an `LHsType` with the same overall
structure. `typeToLHsType` is quite complicated, however, and has
been the subject of numerous bugs over the years (e.g., #14579).
Luckily, there is an easier way to accomplish the same thing: the
`XHsType` constructor of `HsType`. `XHsType` bundles an `NHsCoreTy`,
which allows embedding a Core `Type` directly into an `HsType`,
avoiding the need to laboriously convert from one to another (as
`typeToLHsType` did). Moreover, renaming and typechecking an
`XHsType` is simple, since one doesn't need to do anything to a
Core `Type`...
...well, almost. For the reasons described in
`Note [Typechecking NHsCoreTys]` in `GHC.Tc.Gen.HsType`, we must
apply a substitution that we build from the local `tcl_env` type
environment. But that's a relatively modest price to pay.
Now that `GeneralizedNewtypeDeriving` uses `NHsCoreTy`, the
`typeToLHsType` function no longer has any uses in GHC, so this patch
rips it out. Some additional tweaks to `hsTypeNeedsParens` were
necessary to make the new `-ddump-deriv` output correctly
parenthesized, but other than that, this patch is quite
straightforward.
This is a mostly internal refactoring, although it is likely that
`GeneralizedNewtypeDeriving`-generated code will now need fewer
language extensions in certain situations than it did before.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/68530b1cd45629e5a353a37df80195ac54d26ade">68530b1c</a></strong>
<div>
<span>by Jan Hrček</span>
<i>at 2020-06-28T09:20:22-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix duplicated words and typos in comments and user guide
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/15b79befc246aa9c63dd084012dc7843ea93daaa">15b79bef</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-06-28T09:20:57-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add integer-gmp's ghc.mk and GNUmakefile to .gitignore
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/bfa5698b1ab0190820a2df19487d3d72d3a7924d">bfa5698b</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-06-28T09:21:32-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix a typo in Lint
This simple error in GHC.Core.Litn.lintJoinLams meant that
Lint reported bogus errors.
Fixes #18399
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/71006532abb88a53df7c7e0b3a5e2c8af99a48d1">71006532</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-06-30T07:10:42-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Reject nested foralls/contexts in instance types more consistently
GHC is very wishy-washy about rejecting instance declarations with
nested `forall`s or contexts that are surrounded by outermost
parentheses. This can even lead to some strange interactions with
`ScopedTypeVariables`, as demonstrated in #18240. This patch makes
GHC more consistently reject instance types with nested
`forall`s/contexts so as to prevent these strange interactions.
On the implementation side, this patch tweaks `splitLHsInstDeclTy`
and `getLHsInstDeclHead` to not look through parentheses, which can
be semantically significant. I've added a
`Note [No nested foralls or contexts in instance types]` in
`GHC.Hs.Type` to explain why. This also introduces a
`no_nested_foralls_contexts_err` function in `GHC.Rename.HsType` to
catch nested `forall`s/contexts in instance types. This function is
now used in `rnClsInstDecl` (for ordinary instance declarations) and
`rnSrcDerivDecl` (for standalone `deriving` declarations), the latter
of which fixes #18271.
On the documentation side, this adds a new
"Formal syntax for instance declaration types" section to the GHC
User's Guide that presents a BNF-style grammar for what is and isn't
allowed in instance types.
Fixes #18240. Fixes #18271.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/bccf3351a28638fba94953c4bb244ecfc3a1a044">bccf3351</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-06-30T07:10:46-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add ghc-bignum to 8.12 release notes
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/81704a6f3b155b0bfbc20f53cd821be3cb9006a7">81704a6f</a></strong>
<div>
<span>by David Eichmann</span>
<i>at 2020-06-30T07:10:48-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Update ssh keys in CI performance metrics upload script
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/85310fb83fdb7d7294bd453026102fc42000bf14">85310fb8</a></strong>
<div>
<span>by Joshua Price</span>
<i>at 2020-06-30T07:10:49-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add missing Ix instances for tuples of size 6 through 15 (#16643)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/cbb6b62f54c77637e29bc66e3d1214541c347753">cbb6b62f</a></strong>
<div>
<span>by Vladislav Zavialov</span>
<i>at 2020-07-01T15:41:38-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Implement -XLexicalNegation (GHC Proposal #229)
This patch introduces a new extension, -XLexicalNegation, which detects
whether the minus sign stands for negation or subtraction using the
whitespace-based rules described in GHC Proposal #229.
Updates haddock submodule.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/fb5a0d01d575cdb830918a6a0406f385de2749c2">fb5a0d01</a></strong>
<div>
<span>by Martin Handley</span>
<i>at 2020-07-01T15:42:14-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">#17169: Clarify Fixed's Enum instance.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b316804dbafe1d0287fd33f656b7ce5711ec34f7">b316804d</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-07-01T15:42:49-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Improve debug tracing for substitution
This patch improves debug tracing a bit (#18395)
* Remove the ancient SDoc argument to substitution, replacing it
with a HasDebugCallStack constraint. The latter does the same
job (indicate the call site) but much better.
* Add HasDebugCallStack to simpleOptExpr, exprIsConApp_maybe
I needed this to help nail the lookupIdSubst panic in
#18326, #17784
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/5c9fabb82b39aed9e61c6b78c72312b20a568c68">5c9fabb8</a></strong>
<div>
<span>by Hécate</span>
<i>at 2020-07-01T15:43:25-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add most common return values for `os` and `arch`
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/76d8cc744977d98f6a427b1816198709e2d2e856">76d8cc74</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-07-01T15:44:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Desugar quoted uses of DerivingVia and expression type signatures properly
The way that `GHC.HsToCore.Quote` desugared quoted `via` types (e.g.,
`deriving via forall a. [a] instance Eq a => Eq (List a)`) and
explicit type annotations in signatures (e.g.,
`f = id @a :: forall a. a -> a`) was completely wrong, as it did not
implement the scoping guidelines laid out in
`Note [Scoped type variables in bindings]`. This is easily fixed.
While I was in town, I did some minor cleanup of related Notes:
* `Note [Scoped type variables in bindings]` and
`Note [Scoped type variables in class and instance declarations]`
say very nearly the same thing. I decided to just consolidate the
two Notes into `Note [Scoped type variables in quotes]`.
* `Note [Don't quantify implicit type variables in quotes]` is
somewhat outdated, as it predates GHC 8.10, where the
`forall`-or-nothing rule requires kind variables to be explicitly
quantified in the presence of an explicit `forall`. As a result,
the running example in that Note doesn't even compile. I have
changed the example to something simpler that illustrates the
same point that the original Note was making.
Fixes #18388.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/44d6a3352d708785b75aeb616bfc7efff839184e">44d6a335</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-02T02:54:54-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">T16012: Be verbose on failure.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/f985333002c1690bf49debcc64fc65ed1d1de244">f9853330</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-07-02T02:55:29-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Bump ghc-prim version to 0.7.0
Fixes #18279. Bumps the `text` submodule.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/23e4e04700f840e3c4e75ccb2085aea05bfb5318">23e4e047</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-07-02T10:46:31-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Hadrian: fix PowerPC64le support (#17601)
[ci skip]
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/3cdd8d69f5c1d63137b9b56992bb9b74a6785459">3cdd8d69</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-07-02T10:47:08-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">NCG: correctly handle addresses with huge offsets (#15570)
Before this patch we could generate addresses of this form:
movzbl cP0_str+-9223372036854775808,%eax
The linker can't handle them because the offset is too large:
ld.lld: error: Main.o:(.text+0xB3): relocation R_X86_64_32S out of range: -9223372036852653050 is not in [-2147483648, 2147483647]
With this patch we detect those cases and generate:
movq $-9223372036854775808,%rax
addq $cP0_str,%rax
movzbl (%rax),%eax
I've also refactored `getAmode` a little bit to make it easier to
understand and to trace.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4d90b3ff02002ea25460d087dde56f69a9641096">4d90b3ff</a></strong>
<div>
<span>by Gabor Greif</span>
<i>at 2020-07-02T20:07:59-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">No need for CURSES_INCLUDE_DIRS
This is a leftover from ef63ff27251a20ff11e58c9303677fa31e609a88</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/f08d6316d3d19b627550d99b4364e9bf0b45c329">f08d6316</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-07-02T20:08:36-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Replace Opt_SccProfilingOn flag with sccProfilingEnabled helper function
SCC profiling was enabled in a convoluted way: if WayProf was enabled,
Opt_SccProfilingOn general flag was set (in
`GHC.Driver.Ways.wayGeneralFlags`), and then this flag was queried in
various places.
There is no need to go via general flags, so this patch defines a
`sccProfilingEnabled :: DynFlags -> Bool` helper function that just
checks whether WayProf is enabled.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8cc7274b8de254c7266b61fadbc6795dc37bd1e9">8cc7274b</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-07-03T02:49:27-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts/ProfHeap: Only allocate the Censuses that we need
When not LDV profiling there is no reason to allocate 32 Censuses; one
will do. This is a very small memory footprint optimisation, but it
comes for free.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b835112cbeaa6e34a8bae7b7697bdf2826edaa9a">b835112c</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-07-03T02:49:27-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts/ProfHeap: Free old allocations when reinitialising Censuses
Previously when not LDV profiling we would repeatedly reinitialise
`censuses[0]` with `initEra`. This failed to free the `Arena` and
`HashTable` from the old census, resulting in a memory leak.
Fixes #18348.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/34be6523a220b2be972b391d8ad26b75f7c26eb1">34be6523</a></strong>
<div>
<span>by Valery Tolstov</span>
<i>at 2020-07-03T02:50:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Mention flags that are not enabled by -Wall (#18372)
* Mention missing flags that are not actually enabled by -Wall (docs/users_guide/using-warnings.rst)
* Additionally remove -Wmissing-monadfail-instances from the list of flags enabled by -Wcompat, as it is not the case since 8.8
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/edc8d22b2eea5d43dd6c3d0e4b2f85fc02ffa5ce">edc8d22b</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-07-03T02:50:40-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">LLVM: support R9 and R10 registers
d535ef006d85dbdb7cda2b09c5bc35cb80108909 allowed the use of up to 10
vanilla registers but didn't update LLVM backend to support them. This
patch fixes it.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4bf18646acbb5a59ad8716aedc32acfe2ead0f58">4bf18646</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-07-03T08:37:42+01:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Improve handling of data type return kinds
Following a long conversation with Richard, this patch tidies up the
handling of return kinds for data/newtype declarations (vanilla,
family, and instance).
I have substantially edited the Notes in TyCl, so they would
bear careful reading.
Fixes #18300, #18357
In GHC.Tc.Instance.Family.newFamInst we were checking some Lint-like
properties with ASSSERT. Instead Richard and I have added
a proper linter for axioms, and called it from lintGblEnv, which in
turn is called in tcRnModuleTcRnM
New tests (T18300, T18357) cause an ASSERT failure in HEAD.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/41d2649288a5debcb4c8003e54b7d3072ab951c5">41d26492</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-07-03T17:33:59-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">DynFlags: avoid the use of sdocWithDynFlags in GHC.Core.Rules (#17957)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7aa6ef110d8cc6626b1cf18d85a37cbac53e2795">7aa6ef11</a></strong>
<div>
<span>by Hécate</span>
<i>at 2020-07-03T17:34:36-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add the __GHC_FULL_VERSION__ CPP macro to expose the full GHC version
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e61d539527a7398017f759c67621ba18a15878f7">e61d5395</a></strong>
<div>
<span>by Chaitanya Koparkar</span>
<i>at 2020-07-07T13:55:59-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">ghc-prim: Turn some comments into haddocks
[ci skip]
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/37743f91a3f5018a8894ca6d35e8b423e4e08b50">37743f91</a></strong>
<div>
<span>by John Ericson</span>
<i>at 2020-07-07T13:56:00-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Support `timesInt2#` in LLVM backend
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/46397e530e1b107c6b8932f7ca79ebab53a3249a">46397e53</a></strong>
<div>
<span>by John Ericson</span>
<i>at 2020-07-07T13:56:00-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">`genericIntMul2Op`: Call `genericWordMul2Op` directly
This unblocks a refactor, and removes partiality. It might be a PowerPC
regression but that should be fixable.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8a1c0584da40d0f8d1ffd01796efcce3b3d0820d">8a1c0584</a></strong>
<div>
<span>by John Ericson</span>
<i>at 2020-07-07T13:56:00-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Simplify `PrimopCmmEmit`
Follow @simonpj's suggestion of pushing the "into regs" logic into
`emitPrimOp`. With the previous commit getting rid of the recursion in
`genericIntMul2Op`, this is now an easy refactor.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6607f203fb9ad11af1463145810e1bd3c6c4f2c8">6607f203</a></strong>
<div>
<span>by John Ericson</span>
<i>at 2020-07-07T13:56:00-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">`opAllDone` -> `opIntoRegs`
The old name was and terrible and became worse after the previous
commit's refactor moved non-trivial funcationlity into its body.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/fdcc53babbd6c878344d2a3395bbd619428bd2dd">fdcc53ba</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-07-07T13:56:00-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Optimise genericIntMul2Op
We shouldn't directly call 'genericWordMul2Op' in genericIntMul2Op
because a target may provide a faster primop for 'WordMul2Op': we'd
better use it!
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/686e72253aed3880268dd6858eadd8c320f09e97">686e7225</a></strong>
<div>
<span>by Moritz Angermann</span>
<i>at 2020-07-07T13:56:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">[linker/rtsSymbols] More linker symbols
Mostly symbols needed for aarch64/armv7l
and in combination with musl, where we have
to rely on loading *all* objects/archives
- __stack_chk_* only when not DYNAMIC
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/3f60b94de1f460ca3f689152860b108a19ce193e">3f60b94d</a></strong>
<div>
<span>by Moritz Angermann</span>
<i>at 2020-07-07T13:56:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">better if guards.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7abffced01f5680efafe44f6be2733eab321b039">7abffced</a></strong>
<div>
<span>by Moritz Angermann</span>
<i>at 2020-07-07T13:56:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix (1)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/cdfeb3f24f76e8fd30452016676e56fbc827789a">cdfeb3f2</a></strong>
<div>
<span>by Moritz Angermann</span>
<i>at 2020-07-07T13:56:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">AArch32 symbols only on aarch32.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/f496c9550098ffaa3bf25a3447c138626d79bae0">f496c955</a></strong>
<div>
<span>by Adam Sandberg Ericsson</span>
<i>at 2020-07-07T13:56:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">add -flink-rts flag to link the rts when linking a shared or static library #18072
By default we don't link the RTS when linking shared libraries because in the
most usual mode a shared library is an intermediary product, for example a
Haskell library, that will be linked into some executable in the end. So we
wish to defer the RTS flavour to link to the final link.
However sometimes the final product is the shared library, for example when
writing a plugin for some other system, so we do wish the shared library to
link the RTS.
For consistency we also make -staticlib honor this flag and its inversion.
-staticlib currently implies -flink-shared.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c59faf67fec83c98ffd1b65f1be0775b34f36595">c59faf67</a></strong>
<div>
<span>by Stefan Schulze Frielinghaus</span>
<i>at 2020-07-07T13:56:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">hadrian: link check-ppr against debugging RTS if ghcDebugged
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/0effc57d48ace6b719a9f4cbeac67c95ad55010b">0effc57d</a></strong>
<div>
<span>by Adam Sandberg Ericsson</span>
<i>at 2020-07-07T13:56:05-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts linker: teach the linker about GLIBC's special handling of *stat, mknod and atexit functions #7072
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9615343363a68313c4bfdb068696002ecca7786e">96153433</a></strong>
<div>
<span>by Adam Sandberg Ericsson</span>
<i>at 2020-07-07T13:56:06-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">hadrian: make hadrian/ghci use the bootstrap compiler from configure #18190
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4d24f886a428e95eb5e962294c77b12bffa40a52">4d24f886</a></strong>
<div>
<span>by Adam Sandberg Ericsson</span>
<i>at 2020-07-07T13:56:07-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">hadrian: ignore cabal configure verbosity related flags #18131
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7332bbffee9e2a712508540200eb52ed3d227426">7332bbff</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-07-07T13:56:08-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite: Widen T12234 acceptance window to 2%
Previously it wasn't uncommon to see +/-1% fluctuations in compiler
allocations on this test.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/180b63136f25d9fedb764cb9bc23637e7781ed4e">180b6313</a></strong>
<div>
<span>by Gabor Greif</span>
<i>at 2020-07-07T13:56:08-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">When running libtool, report it as such</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d3bd68978476487591fc60f7feb7cfb36b8fc3a3">d3bd6897</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-07-07T13:56:11-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">BigNum: rename BigNat types
Before this patch BigNat names were confusing because we had:
* GHC.Num.BigNat.BigNat: unlifted type used everywhere else
* GHC.Num.BigNat.BigNatW: lifted type only used to share static constants
* GHC.Natural.BigNat: lifted type only used for backward compatibility
After this patch we have:
* GHC.Num.BigNat.BigNat#: unlifted type
* GHC.Num.BigNat.BigNat: lifted type (reexported from GHC.Natural)
Thanks to @RyanGlScott for spotting this.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/929d26db3080ec49ab67690952a316fc082b479f">929d26db</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-07-07T13:56:12-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Bignum: don't build ghc-bignum with stage0
Noticed by @Ericson2314
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d25b6851bbd63b6a65fb7cd08b37c6bc74df9855">d25b6851</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-07-07T13:56:12-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Hadrian: ghc-gmp.h shouldn't be a compiler dependency
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/0ddae2ba979ac2e01d7d9f6b79a9559fbfde46ea">0ddae2ba</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-07-07T13:56:14-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">DynFlags: factor out pprUnitId from "Outputable UnitId" instance
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/204f3f5ddec56403bfb12e74291b3b1d14824138">204f3f5d</a></strong>
<div>
<span>by Krzysztof Gogolewski</span>
<i>at 2020-07-07T13:56:18-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove unused function pprHsForAllExtra (#18423)
The function `pprHsForAllExtra` was called only on `Nothing`
since 2015 (1e041b7382b6aa).
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/3033e0e4940e6ecc43f478f1dcfbd0c3cb1e3ef8">3033e0e4</a></strong>
<div>
<span>by Adam Sandberg Ericsson</span>
<i>at 2020-07-08T20:36:49-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">hadrian: add flag to skip rebuilding dependency information #17636
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b7de4b960a1024adcd0bded6bd320a90979d7ab8">b7de4b96</a></strong>
<div>
<span>by Stefan Schulze Frielinghaus</span>
<i>at 2020-07-09T09:49:22-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix GHCi :print on big-endian platforms
On big-endian platforms executing
import GHC.Exts
data Foo = Foo Float# deriving Show
foo = Foo 42.0#
foo
:print foo
results in an arithmetic overflow exception which is caused by function
index where moveBytes equals
word_size - (r + item_size_b) * 8
Here we have a mixture of units. Both, word_size and item_size_b have
unit bytes whereas r has unit bits. On 64-bit platforms moveBytes
equals then
8 - (0 + 4) * 8
which results in a negative and therefore invalid second parameter for a
shiftL operation.
In order to make things more clear the expression
(word .&. (mask `shiftL` moveBytes)) `shiftR` moveBytes
is equivalent to
(word `shiftR` moveBytes) .&. mask
On big-endian platforms the shift must be a left shift instead of a
right shift. For symmetry reasons not a mask is used but two shifts in
order to zero out bits. Thus the fixed version equals
case endian of
BigEndian -> (word `shiftL` moveBits) `shiftR` zeroOutBits `shiftL` zeroOutBits
LittleEndian -> (word `shiftR` moveBits) `shiftL` zeroOutBits `shiftR` zeroOutBits
Fixes #16548 and #14455
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/3656dff8259199d0dab2d1a1f1b887c252a9c1a3">3656dff8</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-07-09T09:50:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">LLVM: fix MO_S_Mul2 support (#18434)
The value indicating if the carry is useful wasn't taken into account.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d9f095060b0f00d7140f8b0858b7a5dcbffea9ef">d9f09506</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-07-10T10:33:44-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Define multiShotIO and use it in mkSplitUniqueSupply
This patch is part of the ongoing eta-expansion saga;
see #18238.
It implements a neat trick (suggested by Sebastian Graf)
that allows the programmer to disable the default one-shot behaviour
of IO (the "state hack"). The trick is to use a new multiShotIO
function; see Note [multiShotIO]. For now, multiShotIO is defined
here in Unique.Supply; but it should ultimately be moved to the IO
library.
The change is necessary to get good code for GHC's unique supply;
see Note [Optimising the unique supply].
However it makes no difference to GHC as-is. Rather, it makes
a difference when a subsequent commit
Improve eta-expansion using ArityType
lands.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/bce695cc97cadbc3eced5b53efaaa0ecfd201d61">bce695cc</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-07-10T10:33:44-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Make arityType deal with join points
As Note [Eta-expansion and join points] describes,
this patch makes arityType deal correctly with join points.
What was there before was not wrong, but yielded lower
arities than it could.
Fixes #18328
In base GHC this makes no difference to nofib.
Program Size Allocs Runtime Elapsed TotalMem
--------------------------------------------------------------------------------
n-body -0.1% -0.1% -1.2% -1.1% 0.0%
--------------------------------------------------------------------------------
Min -0.1% -0.1% -55.0% -56.5% 0.0%
Max -0.0% 0.0% +16.1% +13.4% 0.0%
Geometric Mean -0.0% -0.0% -30.1% -31.0% -0.0%
But it starts to make real difference when we land the change to the
way mkDupableAlts handles StrictArg, in fixing #13253 and friends.
I think this is because we then get more non-inlined join points.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2b7c71cb79095a10b9a5964a5a0676a2a196e92d">2b7c71cb</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-07-11T12:17:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Improve eta-expansion using ArityType
As #18355 shows, we were failing to preserve one-shot info when
eta-expanding. It's rather easy to fix, by using ArityType more,
rather than just Arity.
This patch is important to suport the one-shot monad trick;
see #18202. But the extra tracking of one-shot-ness requires
the patch
Define multiShotIO and use it in mkSplitUniqueSupply
If that patch is missing, ths patch makes things worse in
GHC.Types.Uniq.Supply. With it, however, we see these improvements
T3064 compiler bytes allocated -2.2%
T3294 compiler bytes allocated -1.3%
T12707 compiler bytes allocated -1.3%
T13056 compiler bytes allocated -2.2%
Metric Decrease:
T3064
T3294
T12707
T13056
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/de139cc496c0e0110e252a1208ae346f47f8061e">de139cc4</a></strong>
<div>
<span>by Artem Pelenitsyn</span>
<i>at 2020-07-12T02:53:20-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">add reproducer for #15630
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c4de6a7a5c6433ae8c4df8a9fa09fbd9f3bbd0bf">c4de6a7a</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-12T02:53:55-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Give Uniq[D]FM a phantom type for its key.
This fixes #17667 and should help to avoid such issues going forward.
The changes are mostly mechanical in nature. With two notable
exceptions.
* The register allocator.
The register allocator references registers by distinct uniques.
However they come from the types of VirtualReg, Reg or Unique in
various places. As a result we sometimes cast the key type of the
map and use functions which operate on the now typed map but take
a raw Unique as actual key. The logic itself has not changed it
just becomes obvious where we do so now.
* <Type>Env Modules.
As an example a ClassEnv is currently queried using the types `Class`,
`Name`, and `TyCon`. This is safe since for a distinct class value all
these expressions give the same unique.
getUnique cls
getUnique (classTyCon cls)
getUnique (className cls)
getUnique (tcName $ classTyCon cls)
This is for the most part contained within the modules defining the
interface. However it requires us to play dirty when we are given a
`Name` to lookup in a `UniqFM Class a` map. But again the logic did
not change and it's for the most part hidden behind the Env Module.
Some of these cases could be avoided by refactoring but this is left
for future work.
We also bump the haddock submodule as it uses UniqFM.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c2cfdfde20d0d6c0e16aa7a84d8ebe51501bcfa8">c2cfdfde</a></strong>
<div>
<span>by Aaron Allen</span>
<i>at 2020-07-13T09:00:33-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Warn about empty Char enumerations (#18402)
Currently the "Enumeration is empty" warning (-Wempty-enumerations)
only fires for numeric literals. This patch adds support for `Char`
literals so that enumerating an empty list of `Char`s will also
trigger the warning.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c3ac87ece2716b83ad886e81c20f4161e8ec0efd">c3ac87ec</a></strong>
<div>
<span>by Stefan Schulze Frielinghaus</span>
<i>at 2020-07-13T09:01:10-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">hadrian: build check-ppr dynamic if GHC is build dynamic
Fixes #18361
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9ad072b487fe528947f817b0417933a6cd1941b7">9ad072b4</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-07-13T14:52:49-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Use dumpStyle when printing inlinings
This just makes debug-printing consistent,
and more informative.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e78c4efb8735eb97f17e7b4ca35e305b0766f78a">e78c4efb</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-07-13T14:52:49-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Comments only
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7ccb760b1a8034b28171d7540712fd195f65d1fd">7ccb760b</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-07-13T14:52:49-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Reduce result discount in conSize
Ticket #18282 showed that the result discount given by conSize
was massively too large. This patch reduces that discount to
a constant 10, which just balances the cost of the constructor
application itself.
Note [Constructor size and result discount] elaborates, as
does the ticket #18282.
Reducing result discount reduces inlining, which affects perf. I
found that I could increase the unfoldingUseThrehold from 80 to 90 in
compensation; in combination with the result discount change I get
these overall nofib numbers:
Program Size Allocs Runtime Elapsed TotalMem
--------------------------------------------------------------------------------
boyer -0.2% +5.4% -3.2% -3.4% 0.0%
cichelli -0.1% +5.9% -11.2% -11.7% 0.0%
compress2 -0.2% +9.6% -6.0% -6.8% 0.0%
cryptarithm2 -0.1% -3.9% -6.0% -5.7% 0.0%
gamteb -0.2% +2.6% -13.8% -14.4% 0.0%
genfft -0.1% -1.6% -29.5% -29.9% 0.0%
gg -0.0% -2.2% -17.2% -17.8% -20.0%
life -0.1% -2.2% -62.3% -63.4% 0.0%
mate +0.0% +1.4% -5.1% -5.1% -14.3%
parser -0.2% -2.1% +7.4% +6.7% 0.0%
primetest -0.2% -12.8% -14.3% -14.2% 0.0%
puzzle -0.2% +2.1% -10.0% -10.4% 0.0%
rsa -0.2% -11.7% -3.7% -3.8% 0.0%
simple -0.2% +2.8% -36.7% -38.3% -2.2%
wheel-sieve2 -0.1% -19.2% -48.8% -49.2% -42.9%
--------------------------------------------------------------------------------
Min -0.4% -19.2% -62.3% -63.4% -42.9%
Max +0.3% +9.6% +7.4% +11.0% +16.7%
Geometric Mean -0.1% -0.3% -17.6% -18.0% -0.7%
I'm ok with these numbers, remembering that this change removes
an *exponential* increase in code size in some in-the-wild cases.
I investigated compress2. The difference is entirely caused by this
function no longer inlining
WriteRoutines.$woutputCodes
= \ (w :: [CodeEvent]) ->
let result_s1Sr
= case WriteRoutines.outputCodes_$s$woutput w 0# 0# 8# 9# of
(# ww1, ww2 #) -> (ww1, ww2)
in (# case result_s1Sr of (x, _) ->
map @Int @Char WriteRoutines.outputCodes1 x
, case result_s1Sr of { (_, y) -> y } #)
It was right on the cusp before, driven by the excessive result
discount. Too bad!
Happily, the compiler/perf tests show a number of improvements:
T12227 compiler bytes-alloc -6.6%
T12545 compiler bytes-alloc -4.7%
T13056 compiler bytes-alloc -3.3%
T15263 runtime bytes-alloc -13.1%
T17499 runtime bytes-alloc -14.3%
T3294 compiler bytes-alloc -1.1%
T5030 compiler bytes-alloc -11.7%
T9872a compiler bytes-alloc -2.0%
T9872b compiler bytes-alloc -1.2%
T9872c compiler bytes-alloc -1.5%
Metric Decrease:
T12227
T12545
T13056
T15263
T17499
T3294
T5030
T9872a
T9872b
T9872c
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7f0b671ee8a65913891c07f157b21d77d6c63036">7f0b671e</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-07-13T14:52:49-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite: Widen acceptance threshold on T5837
This test is positively tiny and consequently the bytes allocated
measurement will be relatively noisy. Consequently I have seen this
fail spuriously quite often.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/118e1c3da622f17c67b4e0fbc12ed7c7084055dc">118e1c3d</a></strong>
<div>
<span>by Alp Mestanogullari</span>
<i>at 2020-07-14T21:30:52-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">compiler: re-engineer the treatment of rebindable if
Executing on the plan described in #17582, this patch changes the way if expressions
are handled in the compiler in the presence of rebindable syntax. We get rid of the
SyntaxExpr field of HsIf and instead, when rebindable syntax is on, we rewrite the HsIf
node to the appropriate sequence of applications of the local `ifThenElse` function.
In order to be able to report good error messages, with expressions as they were
written by the user (and not as desugared by the renamer), we make use of TTG
extensions to extend GhcRn expression ASTs with an `HsExpansion` construct, which
keeps track of a source (GhcPs) expression and the desugared (GhcRn) expression that
it gives rise to. This way, we can typecheck the latter while reporting the former in
error messages.
In order to discard the error context lines that arise from typechecking the desugared
expressions (because they talk about expressions that the user has not written), we
carefully give a special treatment to the nodes fabricated by this new renaming-time
transformation when typechecking them. See Note [Rebindable syntax and HsExpansion]
for more details. The note also includes a recipe to apply the same treatment to
other rebindable constructs.
Tests 'rebindable11' and 'rebindable12' have been added to make sure we report
identical error messages as before this patch under various circumstances.
We also now disable rebindable syntax when processing untyped TH quotes, as per
the discussion in #18102 and document the interaction of rebindable syntax and
Template Haskell, both in Note [Template Haskell quotes and Rebindable Syntax]
and in the user guide, adding a test to make sure that we do not regress in
that regard.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/64c774b043a2d9be3b98e445990c795f070dab3f">64c774b0</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-14T21:31:27-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Explain why keeping DynFlags in AnalEnv saves allocation.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/254245d01e3c1d4f9072abc4372fd3fb0a6ece9f">254245d0</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-07-14T21:32:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">docs/users-guide: Update default -funfolding-use-threshold value
This was changed in 3d2991f8 but I neglected to update the
documentation. Fixes #18419.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4c259f86938f4016f4bd4fde7a300fa83591036f">4c259f86</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-14T21:32:41-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Escape backslashes in json profiling reports properly.
I also took the liberty to do away the fixed buffer size for escaping.
Using a fixed size here can only lead to issues down the line.
Fixes #18438.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2379722438cb551210c4899119ade05989c17166">23797224</a></strong>
<div>
<span>by Sergei Trofimovich</span>
<i>at 2020-07-14T21:33:19-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">.gitlab: re-enable integer-simple substitute (BIGNUM_BACKEND)
Recently build system migrated from INTEGER_LIBRARY to BIGNUM_BACKEND.
But gitlab CI was never updated. Let's enable BIGNUM_BACKEND=native.
Bug: https://gitlab.haskell.org/ghc/ghc/-/issues/18437
Signed-off-by: Sergei Trofimovich <slyfox@gentoo.org>
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e0db878a789e58c2a1aba2e73d42857008174124">e0db878a</a></strong>
<div>
<span>by Sergei Trofimovich</span>
<i>at 2020-07-14T21:33:19-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">ghc-bignum: bring in sync .hs-boot files with module declarations
Before this change `BIGNUM_BACKEND=native` build was failing as:
```
libraries/ghc-bignum/src/GHC/Num/BigNat/Native.hs:708:16: error:
* Variable not in scope: naturalFromBigNat# :: WordArray# -> t
* Perhaps you meant one of these:
`naturalFromBigNat' (imported from GHC.Num.Natural),
`naturalToBigNat' (imported from GHC.Num.Natural)
|
708 | m' = naturalFromBigNat# m
|
```
This happens because `.hs-boot` files are slightly out of date.
This change brings in data and function types in sync.
Bug: https://gitlab.haskell.org/ghc/ghc/-/issues/18437
Signed-off-by: Sergei Trofimovich <slyfox@gentoo.org>
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c9f65c369a60467dcaf2b37d5f41f00565b4fe25">c9f65c36</a></strong>
<div>
<span>by Stefan Schulze Frielinghaus</span>
<i>at 2020-07-14T21:33:57-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">rts/Disassembler.c: Use FMT_HexWord for printing values in hex format
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/58ae62ebb5750e4dfbdb171efde8e3064b7afea8">58ae62eb</a></strong>
<div>
<span>by Matthias Andreas Benkard</span>
<i>at 2020-07-14T21:34:35-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">macOS: Load frameworks without stating them first.
macOS Big Sur makes the following change to how frameworks are shipped
with the OS:
> New in macOS Big Sur 11 beta, the system ships with a built-in
> dynamic linker cache of all system-provided libraries. As part of
> this change, copies of dynamic libraries are no longer present on
> the filesystem. Code that attempts to check for dynamic library
> presence by looking for a file at a path or enumerating a directory
> will fail. Instead, check for library presence by attempting to
> dlopen() the path, which will correctly check for the library in the
> cache. (62986286)
https://developer.apple.com/documentation/macos-release-notes/macos-big-sur-11-beta-release-notes/
Therefore, the previous method of checking whether a library exists
before attempting to load it makes GHC.Runtime.Linker.loadFramework
fail to find frameworks installed at /System/Library/Frameworks.
GHC.Runtime.Linker.loadFramework now opportunistically loads the
framework libraries without checking for their existence first,
failing only if all attempts to load a given framework from any of the
various possible locations fail.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/cdc4a6b0f71bbd16a11f23e455b28c0c15720b38">cdc4a6b0</a></strong>
<div>
<span>by Matthias Andreas Benkard</span>
<i>at 2020-07-14T21:34:35-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">loadFramework: Output the errors collected in all loading attempts.
With the recent change away from first finding and then loading a
framework, loadFramework had no way of communicating the real reason
why loadDLL failed if it was any reason other than the framework
missing from the file system. It now collects all loading attempt
errors into a list and concatenates them into a string to return to
the caller.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/51dbfa52df483822b99bb191d2ffc0943954e1d3">51dbfa52</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-07-15T04:05:34-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">StgToCmm: Use CmmRegOff smart constructor
Previously we would generate expressions of the form
`CmmRegOff BaseReg 0`. This should do no harm (and really should be
handled by the NCG anyways) but it's better to just generate a plain
`CmmReg`.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ae11bdfd98a10266bfc7de9e16b500be220307ac">ae11bdfd</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-07-15T04:06:08-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite: Add regression test for #17744
Test due to @monoidal.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/0e3c277a6c82c5ab529771c1c493d86e7eda0a98">0e3c277a</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-07-15T16:41:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Bump Cabal submodule
Updates a variety of tests as Cabal is now more strict about Cabal file
form.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ceed994acd07259ef3a780ab440185dbb26fff09">ceed994a</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Drop Windows Vista support, require Windows 7
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/00a23bfda4840546075ec2b2e18f61380b360dfc">00a23bfd</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Update Windows FileSystem wrapper utilities.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/459e1c5f7c71e37ed8bb239c57bdec441d278fff">459e1c5f</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Use SlimReaderLocks and ConditonalVariables provided by the OS instead of emulated ones
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/763088fc3c14c8687685fe811eac13d216971840">763088fc</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Small linker comment and ifdef cleanups
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/1a228ff9e04c91bc9b6f62942dc18bf1985a58a4">1a228ff9</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Flush event logs eagerly.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e9e04ddae1bf89902803d86282f41a586620c58f">e9e04dda</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Refactor Buffer structures to be able to track async operations
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/356dc3feae967b1c361130f1f356ef9ad6a693e4">356dc3fe</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Implement new Console API
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/90e69f779b6da755fac472337535a1321cbb7917">90e69f77</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Add IOPort synchronization primitive
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/71245fcce24723910f12f934fbc4c700658b727a">71245fcc</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Add new io-manager cmdline options
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d548a3b3058232cbfd588f6a2c2b9108bbe8d190">d548a3b3</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Init Windows console Codepage to UTF-8.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/58ef63668ec395aa7a2b250d9930641305d646e2">58ef6366</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Add unsafeSplat to GHC.Event.Array
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d660725edbdaeef9be5da4c032e687276dd09b13">d660725e</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Add size and iterate to GHC.Event.IntTable.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/050da6dd42d0cb293c7fce4a5ccdeb5abe1aadb4">050da6dd</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Switch Testsuite to test winio by default
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4bf542bf1cdf2fa468457fc0af21333478293476">4bf542bf</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:01-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Multiple refactorings and support changes.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4489af6bad11a198e9e6c192f41e17020f28d0c1">4489af6b</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: core threaded I/O manager
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/64d8f2fe2d27743e2986d2176b1aa934e5484d7a">64d8f2fe</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: core non-threaded I/O manager
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8da15a09955926c4617d3468b84b3f3ca414d48a">8da15a09</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Fix a scheduler bug with the threaded-runtime.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/84ea3d1492127442e2d416f1f576a5921186ada4">84ea3d14</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Relaxing some constraints in io-manager.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ccf0d1073969e3b73fed82cd421d74800f552953">ccf0d107</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Fix issues with non-threaded I/O manager after split.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b492fe6e4bde56341abbdb55d19fdf6e02ff70e9">b492fe6e</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Remove some barf statements that are a bit strict.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/01423fd205809e884fd9b7b69286108ca06a0d98">01423fd2</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Expand comments describing non-threaded loop
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4b69004f3c9518f59a8f0b6f7f77aa92bea85adf">4b69004f</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: fix FileSize unstat-able handles
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9b38427045b8f1621f607fa7ab9c6353aa479ac5">9b384270</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Implement new tempfile routines for winio
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/f1e0be824523c6687e3d8588c46a57b2cd22ecc1">f1e0be82</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Fix input truncation when reading from handle.
This was caused by not upholding the read buffer invariant
that bufR == bufL == 0 for empty read buffers.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e176b625689563d2ccfbfec46e664d17824f1968">e176b625</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Fix output truncation for writes larger than buffer size
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a831ce0e7f0bbd8d81e96074e981fe1972fde6dd">a831ce0e</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Rewrite bufWrite.
I think it's far easier to follow the code now.
It's also correct now as I had still missed a spot
where we didn't update the offset.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6aefdf62b767b7828698c3ec5bf6a15e6e20eddb">6aefdf62</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Fix offset set by bufReadEmpty.
bufReadEmpty returns the bytes read *including* content that
was already buffered,
But for calculating the offset we only care about the number
of bytes read into the new buffer.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/750ebaeec06d7ee118abfbb29142c12fb31730cc">750ebaee</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Clean up code surrounding IOPort primitives.
According to phyx these should only be read and written once per
object. Not neccesarily in that order.
To strengthen that guarantee the primitives will now throw an
exception if we violate this invariant.
As a consequence we can eliminate some code from their primops.
In particular code dealing with multiple queued readers/writers
now simply checks the invariant and throws an exception if it
was violated. That is in contrast to mvars which will do things
like wake up all readers, queue multi writers etc.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ffd31db99f6fb8958900147035ddac9a47b7a764">ffd31db9</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Fix multi threaded threadDelay and a few other small changes.
Multithreaded threadDelay suffered from a race condition
based on the ioManagerStatus. Since the status isn't needed
for WIO I removed it completely.
This resulted in a light refactoring, as consequence we will always
wake up the IO manager using interruptSystemManager, which uses
`postQueuedCompletionStatus` internally.
I also added a few comments which hopefully makes the code easier to
dive into for the next person diving in.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6ec26df241d80e8e5cf39a02757c274067c8078d">6ec26df2</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">wionio: Make IO subsystem check a no-op on non-windows platforms.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/29bcd9363f2712524f7720377f19cb885adf2825">29bcd936</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Set handle offset when opening files in Append mode.
Otherwise we would truncate the file.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/55c29700fba3f35a80acd366b2f05b66464d8258">55c29700</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Remove debug event log trace
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9acb9f40d90b79da9e587022d73f8afb26a46463">9acb9f40</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Fix sqrt and openFile009 test cases
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/57017cb7454cbfaa1b011693e7fb141fbf519ccf">57017cb7</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Allow hp2ps to build with -DDEBUG
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b8cd99951c8e21f82c3a95940de10128b78ab4ab">b8cd9995</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Update output of T9681 since we now actually run it.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/10af5b1418554860e377b0df79026c2ea3669ab4">10af5b14</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: A few more improvements to the IOPort primitives.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/39afc4a785a37f238a9004b2f6882d1951953c07">39afc4a7</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Fix expected tempfiles output.
Tempfiles now works properly on windows, as such we can
delete the win32 specific output.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/99db46e09c50681e35de75d8bfec6cfb9ac3f9fc">99db46e0</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Assign thread labels to IOManager threads.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/be6af7324bcd918c61172f6814b8a70a6cfdd58e">be6af732</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Properly check for the tso of an incall to be zero.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e2c6dac783d6cb15217a3be196abeba6c6105588">e2c6dac7</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Mark FD instances as unsupported under WINIO.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/fd02ceed5661e1c2fa85ec5c663697a3b0cf3e04">fd02ceed</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Fix threadDelay maxBound invocations.
Instead of letting the ns timer overflow now clamp it at
(maxBound :: Word64) ns. That still gives a few hundred
years.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/bc79f9f180b3fc73fe25439faf9cc5f19622acb3">bc79f9f1</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Add comments/cleanup an import in base
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/1d197f4bbe5bf6d7189c329a742917db3f67ad34">1d197f4b</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Mark outstanding_service_requests volatile.
As far as I know C(99) gives no guarantees for code like
bool condition;
...
while(condition)
sleep();
that condition will be updated if it's changed by another thread.
So we are explicit here and mark it as volatile, this will force
a reload from memory on each iteration.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/dc4381869748ec25ac9560bf7e89641b560b6862">dc438186</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Make last_event a local variable
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2fc957c52270d93073b7ed9fe42ac51fcd749a45">2fc957c5</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Add comment about thread safety of processCompletion.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4c026b6cf5eb25651f656833e4d312621866330d">4c026b6c</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: nonthreaded: Create io processing threads in main thread.
We now set a flag in the IO thread. The scheduler when looking for work
will check the flag and create/queue threads accordingly.
We used to create these in the IO thread. This improved performance
but caused frequent segfaults. Thread creation/allocation is only safe to
do if nothing currently accesses the storeagemanager. However without
locks in the non-threaded runtime this can't be guaranteed.
This shouldn't change performance all too much.
In the past we had:
* IO: Create/Queue thread.
* Scheduler: Runs a few times. Eventually picks up IO processing thread.
Now it's:
* IO: Set flag to queue thread.
* Scheduler: Pick up flag, if set create/queue thread. Eventually picks up IO processing thread.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/f47c7208c31bdd695ba46e6bdf4a349ae46c79bc">f47c7208</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Add an exported isHeapAlloced function to the RTS
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/cc5d7bb1dcf5603ac47320e83e4fc9ef53e409e9">cc5d7bb1</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Queue IO processing threads at the front of the queue.
This will unblock the IO thread sooner hopefully leading to higher
throughput in some situations.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e763011596ccafccdd476e1cac0ee6088d439e3b">e7630115</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: ThreadDelay001: Use higher resolution timer.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/451b5f96c8a3366584a62034747c8b78fc3b0486">451b5f96</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Update T9681 output, disable T4808 on windows.
T4808 tests functionality of the FD interface which won't be supported
under WINIO.
T9681 just has it's expected output tweaked.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/dd06f930a3228ef7ae8ea5c7225552d6df21f662">dd06f930</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:02-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Wake io manager once per registerTimeout.
Which is implicitly done in editTimeouts, so need to wake it
up twice.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e87d0bf9a430bf52a0068b9b53dcc4592c8da930">e87d0bf9</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Update placeholder comment with actual function name.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/fc9025db55345d6b427489b942878d781f70a039">fc9025db</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Always lock win32 event queue
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c24c9a1f2a10e044a31b7d89586f4a19ff61e137">c24c9a1f</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Display thread labels when tracing scheduler events.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/06542b033116bfc4b47c80bdeab44ed1d99005bb">06542b03</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Refactor non-threaded runner thread and scheduler interface.
Only use a single communication point (registerAlertableWait) to inform
the C side aobut both timeouts to use as well as outstanding requests.
Also queue a haskell processing thread after each return from alertable
waits. This way there is no risk of us missing a timer event.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/256299b13e17044d6904a85043130d13bc592a62">256299b1</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Remove outstanding_requests from runner.
We used a variable to keep track of situations where we got
entries from the IO port, but all of them had already been
canceled. While we can avoid some work that way this case
seems quite rare.
So we give up on tracking this and instead always assume at
least one of the returned entries is valid.
If that's not the case no harm is done, we just perform some
additional work. But it makes the runner easier to reason about.
In particular we don't need to care if another thread modifies
oustanding_requests after we return from waiting on the IO Port.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/3ebd8ad9b1f7f77a928f2ff0d3e61ddfae068dd3">3ebd8ad9</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Various fixes related to rebase and testdriver
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6be6bcbac0e39537f3a40c615d1568a3d6391f9b">6be6bcba</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Fix rebase artifacts
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2c649dc3ba7b08817352eb24d9888651290b6eb6">2c649dc3</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Rename unsafeSplat to unsafeCopyFromBuffer
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a18b73f34dc3d177e76259bd65326a94824d97e0">a18b73f3</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Remove unused size/iterate operations from IntTable
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/16bab48ef69866725d2ab20ca7bd1da5f5a70000">16bab48e</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Detect running IO Backend via peeking at RtsConfig
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8b8405a0dd45c16ec305884cadda992327733621">8b8405a0</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: update temp path so GCC etc can handle it.
Also fix PIPE support, clean up error casting, fix memory leaks
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2092bc542516461eeb06d855dfbe9b04438767bc">2092bc54</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Minor comments/renamings
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a5b5b6c0de4e9ea2923beeff488e852aa247000a">a5b5b6c0</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Checking if an error code indicates completion is now a function.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/362176fd9189e73083fd2a2012c9b5be1e3fd05b">362176fd</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Small refactor in withOverlappedEx
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/32e20597b2fe5864b578c732501fe20d899e8f9c">32e20597</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: A few comments and commented out dbxIO
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a4bfc1d9ae59adc58a0df3b25f85873533481e94">a4bfc1d9</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Don't drop buffer offset in byteView/cwcharView
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b3ad2a54bf775e1ca110b501894891d4ccff3d8f">b3ad2a54</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: revert BHandle changes.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/3dcd87e2fd6d03028d18bf1a61e526142ee9b8a1">3dcd87e2</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Fix imports
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/5a3718909e8eb214d4a70082b7fee8d6f3efc975">5a371890</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: update ghc-cabal to handle new Cabal submodule bump
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d07ebe0df6df32bbffbf77ea09e39b6da2e8cbb3">d07ebe0d</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Only compile sources on Windows
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/dcb423937a052496af73e34a315e3d15882b9f19">dcb42393</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Actually return Nothing on EOF for non-blocking read
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/895a3beb26de69f5611ea496dddb2b121c1dd5c1">895a3beb</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Deduplicate logic in encodeMultiByte[Raw]IO.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e06e6734a4d5c49c625605a2675c47fd93f834b2">e06e6734</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Deduplicate openFile logic
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b59430c00f41e18386bc44540180451169f6b9d7">b59430c0</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: fix -werror issue in encoding file
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/f8d39a510c563271e26ec7175b8e538d0b6809da">f8d39a51</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Don't mention windows specific functions when building on Linux.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6a533d2afaab8b8ca0026c9af1a8ed9ff09c4462">6a533d2a</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: add a note about file locking in the RTS.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/cf37ce3499a0367faf7fcaf014d8350e5864fe7a">cf37ce34</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Add version to @since annotation
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/0fafa2eb45d9283526c79f810476a369af21bf3b">0fafa2eb</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Rename GHC.Conc.IOCP -> GHC.Conc.WinIO
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/1854fc23489baa39cb37f8d49ff74b7ee78d7de1">1854fc23</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Expand GHC.Conc.POSIX description
It now explains users may not use these functions when
using the old IO manager.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/fcc7ba414e1dfab70136a824775421b26ce1b81a">fcc7ba41</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Fix potential spaceleak in __createUUIDTempFileErrNo
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/6b3fd9fa15e75f646ac6eaa384f54afe853029f4">6b3fd9fa</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Remove redundant -Wno-missing-signatures pragmas
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/916fc861520615149c66c1069f6cb661bc8b8483">916fc861</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Make it explicit that we only create one IO manager
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/f260a7218f71398ad2dbca0f47feaf31c21081b3">f260a721</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Note why we don't use blocking waits.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/aa0a4bbfbae0244313fa99862b97f71c15f9bd81">aa0a4bbf</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Remove commented out pragma
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d679b544e14ad912fddc97b1b735d3c2838a2c4b">d679b544</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Remove redundant buffer write in Handle/Text.hs:bufReadEmpty
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d3f94368cc27e124c07f9c3f90e3f9563a7fc55d">d3f94368</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Rename SmartHandles to StdHandles
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/bd6b8ec1e775441fc943702e93d48ce75f155e9e">bd6b8ec1</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: add comment stating failure behaviour for getUniqueFileInfo.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/12846b85a94b2b73f456e4c441c7890d685deb67">12846b85</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:03-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Update IOPort haddocks.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9f39fb14997f1aa3768c89bb8e83c6addc705d92">9f39fb14</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Add a note cross reference
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/62dd5a7309f273b5bb7d6ab44a1d2745010c13a0">62dd5a73</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Name Haskell/OS I/O Manager explicitly in Note
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/fa80782864895fe614e1b83416736014e68c8b35">fa807828</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Expand BlockedOnIOCompletion description.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/f0880a1daea4f3c9fa6fa4624914081f29736ea2">f0880a1d</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Remove historical todos
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/8e58e714e9a4b5fe77c4e71802cc4b9ad1998af3">8e58e714</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Update note, remove debugging pragma.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/aa4d84d556b39715ebc1a7860a620ec5a7d9beeb">aa4d84d5</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: flushCharReadBuffer shouldn't need to adjust offsets.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e580893ab8b76ff4b6582b1fb2ed55cc9742d5a2">e580893a</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Remove obsolete comment about cond. variables
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/d54e9d7911901ee5bfcba43b2e4e1a4df11c670e">d54e9d79</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: fix initial linux validate build
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/3cd4de46c1f31e2f044c671a4474126fc0d5a8da">3cd4de46</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Fix ThreadDelay001 CPP
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c88b1b9fde4eedcd1b62c51b1a53201ec3cf29c8">c88b1b9f</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Fix openFile009 merge conflict leftover
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/849e8889fe9586bf9e1bf37885537f25743383f2">849e8889</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Accept T9681 output.
GHC now reports String instead of [Char].
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/e7701818e75b66957724f48c4aafac146699b667">e7701818</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Fix cabal006 after upgrading cabal submodule
Demand cabal 2.0 syntax instead of >= 1.20 as required by newer cabal versions.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a44f037372feac67793deb919d988468809ce470">a44f0373</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Fix stderr output for ghci/linking/dyn tests.
We used to filter rtsopts, i opted to instead just accept the warning of it having no effect.
This works both for -rtsopts, as well as -with-rtsopts which winio adds.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/515d98960d3cdcdd7d78a9f28d1b0ad39865c67f">515d9896</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Adjust T15261b stdout for --io-manager flag.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/949aaaccf34ef7e28a745081775b01627590fc46">949aaacc</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Adjust T5435_dyn_asm stderr
The warning about rtsopts having no consequences is expected.
So accept new stderr.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7d424e1e31a8f16e614947460e0e4e4b52f8b5cf">7d424e1e</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Also accept T7037 stderr
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/1f0097683f65ee3cd917af843621ed73b5348e68">1f009768</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: fix cabal04 by filtering rts args
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/981a9f2e57728cdf39de9fc173b11be4084997d3">981a9f2e</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: fix cabal01 by accepting expected stderr
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b7b0464eb7a5510fde4a804402491ecad2f1092b">b7b0464e</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: fix safePkg01 by accepting expected stderr
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/32734b29cbe0450d27fa6b4ea67b05aff2c4919d">32734b29</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: fix T5435_dyn_gcc by accepting expected stderr
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/acc5cebf42e38c2b0869117329811c03c4e3f545">acc5cebf</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: fix tempfiles test on linux
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c577b789e8f76f81a99f1731700c27796effb598">c577b789</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Accept accepted stderr for T3807
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c108c52779a6423871ea372be82b94f5274e57da">c108c527</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Accept accepted stderr for linker_unload
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2b0b9a08a3412114f568fb26e3d684ccb7092f88">2b0b9a08</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: Accept accepted stderr for linker_unload_multiple_objs
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/67afb03c45cf8a8dc9e51413cf187f36768a5a0b">67afb03c</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: clarify wording on conditional variables.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/3bd415721672da9aa88c4528df8ba15bc616f3be">3bd41572</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: clarify comment on cooked mode.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ded58a037774147073366ff2dfdc8965e02a96e5">ded58a03</a></strong>
<div>
<span>by Tamar Christina</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">winio: update lockfile signature and remove mistaken symbol in rts.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/2143c49273d7d87ee2f3ef1211856d60b1427af1">2143c492</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-07-15T16:41:04-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">testsuite: Add winio and winio_threaded ways
Reverts many of the testsuite changes
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/c0979cc53442b3a6202acab9cf164f0a4beea0b7">c0979cc5</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-07-16T10:56:54-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Merge remote-tracking branch 'origin/wip/winio'
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/08b9ece7275f27d64ecd2d2a9efa69c9e6b6385b">08b9ece7</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-07-16T13:42:59-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">get-win32-tarballs: Fix detection of missing tarballs
This fixes the error message given by configure when the user
attempts to configure without first download the win32 tarballs.
</pre>
</li>
</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="#f656107cc03a27946448887125380c358788500e">
.gitlab/test-metrics.sh
</a>
</li>
<li class="file-stats">
<a href="#7445606fbf8f3683cd42bdc54b05d7a0bc2dfc44">
.gitmodules
</a>
</li>
<li class="file-stats">
<a href="#836efb6e25a091dcb4ff8e1dbb2f0be6a5cbf14c">
Makefile
</a>
</li>
<li class="file-stats">
<a href="#9ab3868b23ed5d5a6e12ef902049902556fa4009">
aclocal.m4
</a>
</li>
<li class="file-stats">
<a href="#d0d96a6d03668aeab20ebe05e2c4ccb798c7e64c">
compiler/GHC.hs
</a>
</li>
<li class="file-stats">
<a href="#0887cf39c5cdf9cf8d6758f410d7dab3023c0d77">
compiler/GHC/Builtin/Names.hs
</a>
</li>
<li class="file-stats">
<a href="#06764eb0158306b83ab1998d18316392a51838c2">
compiler/GHC/Builtin/Names/TH.hs
</a>
</li>
<li class="file-stats">
<a href="#a1519b7fe8a0d4b42e4aaa927fb6ab5b5da0fcdd">
compiler/GHC/Builtin/PrimOps.hs
</a>
</li>
<li class="file-stats">
<a href="#5f4b3cf094f6e2fc46805a6c447613ae13a08942">
<span class="new-file">
+
compiler/GHC/Builtin/RebindableNames.hs
</span>
</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="#d95fdf6575459444666f72b2281534e0558a4ba0">
compiler/GHC/Builtin/Utils.hs
</a>
</li>
<li class="file-stats">
<a href="#451725cc4e5d443a3b7c2adcdf224840f953b7e2">
compiler/GHC/Builtin/primops.txt.pp
</a>
</li>
<li class="file-stats">
<a href="#2f6f8d6d05acc04b08fff94df4b3996c65b87892">
compiler/GHC/ByteCode/Asm.hs
</a>
</li>
<li class="file-stats">
<a href="#16db773e94d0938489b415eb3231cadb2565b84d">
compiler/GHC/ByteCode/InfoTable.hs
</a>
</li>
<li class="file-stats">
<a href="#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="#db697f6aea9f93f1583f1d5c62d25570a1e07f73">
compiler/GHC/Cmm/CLabel.hs
</a>
</li>
<li class="file-stats">
<a href="#d088ba20f051734394bf7ca283f33ed8127bc8ab">
compiler/GHC/Cmm/CallConv.hs
</a>
</li>
<li class="file-stats">
<a href="#eae45922f6e633780395508f44c14a5ed7959e7a">
compiler/GHC/Cmm/Dataflow/Block.hs
</a>
</li>
<li class="file-stats">
<a href="#92b713d88390e6ea489e24b6cff8a3960384c0d0">
compiler/GHC/Cmm/DebugBlock.hs
</a>
</li>
<li class="file-stats">
<a href="#47cba74ae8965f1665cd11bf2b023760ea27594e">
compiler/GHC/Cmm/Info.hs
</a>
</li>
<li class="file-stats">
<a href="#2d3721ad8de95e1144493ca545db846672cb109f">
compiler/GHC/Cmm/Info/Build.hs
</a>
</li>
<li class="file-stats">
<a href="#066085df29cc928ac539d8feae6e5215cbbf1e14">
compiler/GHC/Cmm/LayoutStack.hs
</a>
</li>
<li class="file-stats">
<a href="#c898e00d01234ab22d3b485be68db3645f52f220">
compiler/GHC/Cmm/MachOp.hs
</a>
</li>
<li class="file-stats">
<a href="#6fbb543d5fcea725882dd3b8d4dcd9b02022a4be">
compiler/GHC/Cmm/Monad.hs
</a>
</li>
<li class="file-stats">
<a href="#90378e83c3a00a78bc0b3c01da111e0a787de451">
compiler/GHC/Cmm/Node.hs
</a>
</li>
</ul>
<h5>The diff was not included because it is too large.</h5>
</div>
<div class="footer" style="margin-top: 10px;">
<p style="font-size: small; color: #777;">
—
<br>
<a href="https://gitlab.haskell.org/ghc/ghc/-/compare/62c3f42b66d39fdad0c8c12c373765fa4ff2606e...08b9ece7275f27d64ecd2d2a9efa69c9e6b6385b">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>