<!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>
Alan Zimmerman pushed to branch wip/az/exactprint
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/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/4653a82677fdf9d2c7093333d4ec432f3a98cd91">4653a826</a></strong>
<div>
<span>by Alan Zimmerman</span>
<i>at 2020-06-23T17:47:58+01:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Proof of Concept implementation of in-tree API Annotations

This MR introduces a possible machinery to introduce API Annotations
into the TTG extension points.

It is intended to be a concrete example for discussion.

It still needs to process comments.

----

Work in progress, adding more TTG extensions for annotations.

And fixing ppr round-trip tests by being able to blank out in-tree
annotations, as done with SrcSpans.

This is needed for the case of

  class Foo a where

for which current ppr does not print the "where".

Rename AA to AddApiAnn and AA to AddAnn

Add XConPatIn and XConPatOut

Rebase

----

First pass at bringing in LocatedA for API anns in locations

Treatment of ECP in parsing is provisional at this stage, leads to some
horribly stuff in Parser.y and RdrHsSyn.

It is an extensive but not invasive change. I think (AZ).

Locally it reports some parsing tests using less memory.

Add ApiAnns to the HsExpr data structure.

rebase.

Change HsMatchContext and HsStmtContext to use an id, not a GhcPass
parameter.

Add ApiAnns to Hs/Types

Rebase

Rebased 2020-03-25

WIP on in-tree annotations

Includes updating HsModule

Imports

LocateA ImportDecl so we can hang AnnSemi off it

A whole bunch of stuff more

InjectivityAnn and FamEqn now have annotations in them

Add annotations to context srcspan

----

In-tree annotations: LHsDecl and LHsBind LocatedA

----

WIP on in-tree annotations

----

in-tree annotations: LHsType is now LocatedA

----

FunDeps is now also a HS data type

----

WIP.  Added LocatedA to Pat, Expr, Decl

And worked some more through Parser.y

----

LStmt now Located

----

Finished working through Parser.y, tests seem ok

failures relate to annotations.

Adding test infrastructure for check-exact

Like check-ppr, but checking for an exact reproduction of the parsed
source file.

Starting to work on actual exact printer

Bring in ApiAnnName

As an alternative for LocatedA, to be used for names only.

Carrying extra name adornments, such as locations of backticks,
parens, etc.

Working on changing ApiAnnName to accurately reflect actual usage

Get rid of AnnApiName in favour of LocatedN

Working on check-exact. Making progress

Working on the ghc-exact bit

Progress, can reproduce the first Test.hs file.

Move API Annotations out of the extensions to annotations
</pre>
</li>
</ul>
<h4>30 changed files:</h4>
<ul>
<li class="file-stats">
<a href="#7445606fbf8f3683cd42bdc54b05d7a0bc2dfc44">
.gitmodules
</a>
</li>
<li class="file-stats">
<a href="#9ab3868b23ed5d5a6e12ef902049902556fa4009">
aclocal.m4
</a>
</li>
<li class="file-stats">
<a href="#d0d96a6d03668aeab20ebe05e2c4ccb798c7e64c">
compiler/GHC.hs
</a>
</li>
<li class="file-stats">
<a href="#0887cf39c5cdf9cf8d6758f410d7dab3023c0d77">
compiler/GHC/Builtin/Names.hs
</a>
</li>
<li class="file-stats">
<a href="#06764eb0158306b83ab1998d18316392a51838c2">
compiler/GHC/Builtin/Names/TH.hs
</a>
</li>
<li class="file-stats">
<a href="#a1519b7fe8a0d4b42e4aaa927fb6ab5b5da0fcdd">
compiler/GHC/Builtin/PrimOps.hs
</a>
</li>
<li class="file-stats">
<a href="#377cfd14c1f92357465df995ec6537b074051322">
compiler/GHC/Builtin/Types.hs
</a>
</li>
<li class="file-stats">
<a href="#be7a5c9dc04ecfe7bedb2a2afcc2a51be6719577">
compiler/GHC/Builtin/Types.hs-boot
</a>
</li>
<li class="file-stats">
<a href="#8a5cd068459120cddf3814e7b9e02003b87647ba">
compiler/GHC/Builtin/Types/Prim.hs
</a>
</li>
<li class="file-stats">
<a href="#451725cc4e5d443a3b7c2adcdf224840f953b7e2">
compiler/GHC/Builtin/primops.txt.pp
</a>
</li>
<li class="file-stats">
<a href="#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="#db697f6aea9f93f1583f1d5c62d25570a1e07f73">
compiler/GHC/Cmm/CLabel.hs
</a>
</li>
<li class="file-stats">
<a href="#47cba74ae8965f1665cd11bf2b023760ea27594e">
compiler/GHC/Cmm/Info.hs
</a>
</li>
<li class="file-stats">
<a href="#066085df29cc928ac539d8feae6e5215cbbf1e14">
compiler/GHC/Cmm/LayoutStack.hs
</a>
</li>
<li class="file-stats">
<a href="#71e696f452eb493722d70306c6f304fc9b2f6a95">
compiler/GHC/Cmm/Parser.y
</a>
</li>
<li class="file-stats">
<a href="#d40f34584a7f4c0fa7587fb41f94a34bca0d1064">
compiler/GHC/Cmm/Pipeline.hs
</a>
</li>
<li class="file-stats">
<a href="#29a1593e7281c8a9103a19e3a7562e2365e23b47">
compiler/GHC/Cmm/ProcPoint.hs
</a>
</li>
<li class="file-stats">
<a href="#335d279236d65dcf13f2bab3891e515cb803203c">
compiler/GHC/CmmToAsm/X86/Ppr.hs
</a>
</li>
<li class="file-stats">
<a href="#182d6a315e784018aa9c8b2ad736036b97bd5d48">
compiler/GHC/Core.hs
</a>
</li>
<li class="file-stats">
<a href="#783e5dae6e86931f06700fc088fb7d48c8a07386">
compiler/GHC/Core/Coercion.hs
</a>
</li>
<li class="file-stats">
<a href="#b0ab2032bd0c006bb9cda1e5433173de35930f53">
compiler/GHC/Core/Coercion.hs-boot
</a>
</li>
<li class="file-stats">
<a href="#f10ed7a2470454dfdd8691a08beba67d8b78ee70">
compiler/GHC/Core/Coercion/Axiom.hs
</a>
</li>
<li class="file-stats">
<a href="#975dc08a8e7942b32d621f617d5a9c1b668601dd">
compiler/GHC/Core/Coercion/Opt.hs
</a>
</li>
<li class="file-stats">
<a href="#b452cc5181a4af3460c43a4e3e4b5edaa238b4e0">
compiler/GHC/Core/ConLike.hs
</a>
</li>
<li class="file-stats">
<a href="#6fcf64907fb5bdd93082d2d1eb94e4566e735865">
compiler/GHC/Core/DataCon.hs
</a>
</li>
<li class="file-stats">
<a href="#f1ee1dbd326408dee78428b876306e279a748497">
compiler/GHC/Core/DataCon.hs-boot
</a>
</li>
<li class="file-stats">
<a href="#448d7f6e0151c2014de38dead3a902f511c45b75">
compiler/GHC/Core/FVs.hs
</a>
</li>
<li class="file-stats">
<a href="#91648438362e5a35363d2bb7abb04016dedd7d7e">
compiler/GHC/Core/FamInstEnv.hs
</a>
</li>
<li class="file-stats">
<a href="#36a42448a83a9d1f6df8475f03ead2eed199dd8e">
compiler/GHC/Core/Lint.hs
</a>
</li>
</ul>
<h5>The diff was not included because it is too large.</h5>

</div>
<div class="footer" style="margin-top: 10px;">
<p style="font-size: small; color: #777;">

<br>
<a href="https://gitlab.haskell.org/ghc/ghc/-/compare/e25ea7a32a6abca778c2e30143f9bce9363742a7...4653a82677fdf9d2c7093333d4ec432f3a98cd91">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>