[Git][ghc/ghc][wip/T13253] 56 commits: Reject nested foralls/contexts in instance types more consistently

Ben Gamari gitlab at gitlab.haskell.org
Mon Jul 13 07:42:44 UTC 2020



Ben Gamari pushed to branch wip/T13253 at Glasgow Haskell Compiler / GHC


Commits:
71006532 by Ryan Scott at 2020-06-30T07:10:42-04:00
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.

- - - - -
bccf3351 by Sylvain Henry at 2020-06-30T07:10:46-04:00
Add ghc-bignum to 8.12 release notes

- - - - -
81704a6f by David Eichmann at 2020-06-30T07:10:48-04:00
Update ssh keys in CI performance metrics upload script

- - - - -
85310fb8 by Joshua Price at 2020-06-30T07:10:49-04:00
Add missing Ix instances for tuples of size 6 through 15 (#16643)

- - - - -
cbb6b62f by Vladislav Zavialov at 2020-07-01T15:41:38-04:00
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.

- - - - -
fb5a0d01 by Martin Handley at 2020-07-01T15:42:14-04:00
#17169: Clarify Fixed's Enum instance.

- - - - -
b316804d by Simon Peyton Jones at 2020-07-01T15:42:49-04:00
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

- - - - -
5c9fabb8 by Hécate at 2020-07-01T15:43:25-04:00
Add most common return values for `os` and `arch`

- - - - -
76d8cc74 by Ryan Scott at 2020-07-01T15:44:01-04:00
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.

- - - - -
44d6a335 by Andreas Klebinger at 2020-07-02T02:54:54-04:00
T16012: Be verbose on failure.

- - - - -
f9853330 by Ryan Scott at 2020-07-02T02:55:29-04:00
Bump ghc-prim version to 0.7.0

Fixes #18279. Bumps the `text` submodule.

- - - - -
23e4e047 by Sylvain Henry at 2020-07-02T10:46:31-04:00
Hadrian: fix PowerPC64le support (#17601)

[ci skip]

- - - - -
3cdd8d69 by Sylvain Henry at 2020-07-02T10:47:08-04:00
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.

- - - - -
4d90b3ff by Gabor Greif at 2020-07-02T20:07:59-04:00
No need for CURSES_INCLUDE_DIRS

This is a leftover from ef63ff27251a20ff11e58c9303677fa31e609a88
- - - - -
f08d6316 by Sylvain Henry at 2020-07-02T20:08:36-04:00
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.

- - - - -
8cc7274b by Ben Gamari at 2020-07-03T02:49:27-04:00
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.

- - - - -
b835112c by Ben Gamari at 2020-07-03T02:49:27-04:00
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.

- - - - -
34be6523 by Valery Tolstov at 2020-07-03T02:50:03-04:00
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

- - - - -
edc8d22b by Sylvain Henry at 2020-07-03T02:50:40-04:00
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.

- - - - -
4bf18646 by Simon Peyton Jones at 2020-07-03T08:37:42+01:00
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.

- - - - -
41d26492 by Sylvain Henry at 2020-07-03T17:33:59-04:00
DynFlags: avoid the use of sdocWithDynFlags in GHC.Core.Rules (#17957)

- - - - -
7aa6ef11 by Hécate at 2020-07-03T17:34:36-04:00
Add the __GHC_FULL_VERSION__ CPP macro to expose the full GHC version

- - - - -
e61d5395 by Chaitanya Koparkar at 2020-07-07T13:55:59-04:00
ghc-prim: Turn some comments into haddocks

[ci skip]

- - - - -
37743f91 by John Ericson at 2020-07-07T13:56:00-04:00
Support `timesInt2#` in LLVM backend

- - - - -
46397e53 by John Ericson at 2020-07-07T13:56:00-04:00
`genericIntMul2Op`: Call `genericWordMul2Op` directly

This unblocks a refactor, and removes partiality. It might be a PowerPC
regression but that should be fixable.

- - - - -
8a1c0584 by John Ericson at 2020-07-07T13:56:00-04:00
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.

- - - - -
6607f203 by John Ericson at 2020-07-07T13:56:00-04:00
`opAllDone` -> `opIntoRegs`

The old name was and terrible and became worse after the previous
commit's refactor moved non-trivial funcationlity into its body.

- - - - -
fdcc53ba by Sylvain Henry at 2020-07-07T13:56:00-04:00
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!

- - - - -
686e7225 by Moritz Angermann at 2020-07-07T13:56:01-04:00
[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

- - - - -
3f60b94d by Moritz Angermann at 2020-07-07T13:56:01-04:00
better if guards.

- - - - -
7abffced by Moritz Angermann at 2020-07-07T13:56:01-04:00
Fix (1)

- - - - -
cdfeb3f2 by Moritz Angermann at 2020-07-07T13:56:01-04:00
AArch32 symbols only on aarch32.

- - - - -
f496c955 by Adam Sandberg Ericsson at 2020-07-07T13:56:02-04:00
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.

- - - - -
c59faf67 by Stefan Schulze Frielinghaus at 2020-07-07T13:56:04-04:00
hadrian: link check-ppr against debugging RTS if ghcDebugged

- - - - -
0effc57d by Adam Sandberg Ericsson at 2020-07-07T13:56:05-04:00
rts linker: teach the linker about GLIBC's special handling of *stat, mknod and atexit functions #7072

- - - - -
96153433 by Adam Sandberg Ericsson at 2020-07-07T13:56:06-04:00
hadrian: make hadrian/ghci use the bootstrap compiler from configure #18190

- - - - -
4d24f886 by Adam Sandberg Ericsson at 2020-07-07T13:56:07-04:00
hadrian: ignore cabal configure verbosity related flags #18131

- - - - -
7332bbff by Ben Gamari at 2020-07-07T13:56:08-04:00
testsuite: Widen T12234 acceptance window to 2%

Previously it wasn't uncommon to see +/-1% fluctuations in compiler
allocations on this test.

- - - - -
180b6313 by Gabor Greif at 2020-07-07T13:56:08-04:00
When running libtool, report it as such
- - - - -
d3bd6897 by Sylvain Henry at 2020-07-07T13:56:11-04:00
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.

- - - - -
929d26db by Sylvain Henry at 2020-07-07T13:56:12-04:00
Bignum: don't build ghc-bignum with stage0

Noticed by @Ericson2314

- - - - -
d25b6851 by Sylvain Henry at 2020-07-07T13:56:12-04:00
Hadrian: ghc-gmp.h shouldn't be a compiler dependency

- - - - -
0ddae2ba by Sylvain Henry at 2020-07-07T13:56:14-04:00
DynFlags: factor out pprUnitId from "Outputable UnitId" instance

- - - - -
204f3f5d by Krzysztof Gogolewski at 2020-07-07T13:56:18-04:00
Remove unused function pprHsForAllExtra (#18423)

The function `pprHsForAllExtra` was called only on `Nothing`
since 2015 (1e041b7382b6aa).

- - - - -
3033e0e4 by Adam Sandberg Ericsson at 2020-07-08T20:36:49-04:00
hadrian: add flag to skip rebuilding dependency information #17636

- - - - -
b7de4b96 by Stefan Schulze Frielinghaus at 2020-07-09T09:49:22-04:00
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

- - - - -
3656dff8 by Sylvain Henry at 2020-07-09T09:50:01-04:00
LLVM: fix MO_S_Mul2 support (#18434)

The value indicating if the carry is useful wasn't taken into account.

- - - - -
d9f09506 by Simon Peyton Jones at 2020-07-10T10:33:44-04:00
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.

- - - - -
bce695cc by Simon Peyton Jones at 2020-07-10T10:33:44-04:00
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.

- - - - -
2b7c71cb by Simon Peyton Jones at 2020-07-11T12:17:02-04:00
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

- - - - -
de139cc4 by Artem Pelenitsyn at 2020-07-12T02:53:20-04:00
add reproducer for #15630

- - - - -
c4de6a7a by Andreas Klebinger at 2020-07-12T02:53:55-04:00
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.

- - - - -
d2927dbc by Simon Peyton Jones at 2020-07-13T03:41:42-04:00
Use dumpStyle when printing inlinings

This just makes debug-printing consistent,
and more informative.

- - - - -
c23021cf by Simon Peyton Jones at 2020-07-13T03:41:42-04:00
Comments only

- - - - -
a5ca69c2 by Simon Peyton Jones at 2020-07-13T03:41:42-04:00
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

- - - - -
818aba30 by Simon Peyton Jones at 2020-07-13T03:42:34-04:00
This patch addresses the exponential blow-up in the simplifier.

Specifically:
  #13253 exponential inlining
  #10421 ditto
  #18140 strict constructors
  #18282 another nested-function call case

This patch makes two significant changes:

1. For Ids that are used at most once in each branch of a case,
   make the occurrence analyser record the total number of
   syntactic occurrences.  Then in postInlineUnconditionally
   use that info to avoid inling something many many times.

   Actual changes:
     * See the occ_n_br field of OneOcc.
     * postInlineUnconditionally
   See Note [Suppress exponential blowup] in GHC.Core.Opt.Simplify.Utils

2. Change the way that mkDupableCont handles StrictArg.
   The details are explained in GHC.Core.Opt.Simplify
      Note [Duplicating StrictArg]

Current nofib run

        Program           Size    Allocs   Runtime   Elapsed  TotalMem
--------------------------------------------------------------------------------
             VS          -0.3%   +115.9%    +12.1%    +11.2%      0.0%
         boyer2          -0.3%    +10.0%     +3.5%     +4.0%      0.0%
   cryptarithm2          -0.3%    +39.0%    +16.6%    +16.1%      0.0%
         gamteb          -0.3%     +4.1%     -0.0%     +0.4%      0.0%
     last-piece          -0.3%     +1.4%     -1.1%     -0.4%      0.0%
           mate          -0.4%    -11.1%     -8.5%     -9.0%      0.0%
     multiplier          -0.3%     -2.2%     -1.5%     -1.5%      0.0%
      transform          -0.3%     +3.4%     +0.5%     +0.8%      0.0%
--------------------------------------------------------------------------------
            Min          -0.8%    -11.1%     -8.5%     -9.0%      0.0%
            Max          -0.3%   +115.9%    +30.1%    +26.4%      0.0%
 Geometric Mean          -0.3%     +1.0%     +1.0%     +1.0%     -0.0%

Should investigate these numbers.

But the tickets are indeed cured, I think.

- - - - -


30 changed files:

- .gitlab/test-metrics.sh
- aclocal.m4
- compiler/GHC.hs
- compiler/GHC/Builtin/PrimOps.hs
- compiler/GHC/Builtin/Utils.hs
- compiler/GHC/Cmm/Info.hs
- compiler/GHC/Cmm/LayoutStack.hs
- compiler/GHC/Cmm/Parser.y
- compiler/GHC/Cmm/Sink.hs
- compiler/GHC/CmmToAsm.hs
- compiler/GHC/CmmToAsm/BlockLayout.hs
- compiler/GHC/CmmToAsm/Monad.hs
- compiler/GHC/CmmToAsm/Reg/Graph.hs
- compiler/GHC/CmmToAsm/Reg/Graph/Coalesce.hs
- compiler/GHC/CmmToAsm/Reg/Graph/Spill.hs
- compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs
- compiler/GHC/CmmToAsm/Reg/Graph/SpillCost.hs
- compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs
- compiler/GHC/CmmToAsm/Reg/Linear.hs
- compiler/GHC/CmmToAsm/Reg/Linear/Base.hs
- compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs
- compiler/GHC/CmmToAsm/Reg/Linear/StackMap.hs
- compiler/GHC/CmmToAsm/Reg/Linear/Stats.hs
- compiler/GHC/CmmToAsm/Reg/Liveness.hs
- + compiler/GHC/CmmToAsm/Reg/Utils.hs
- compiler/GHC/CmmToAsm/X86/CodeGen.hs
- compiler/GHC/CmmToAsm/X86/RegInfo.hs
- compiler/GHC/CmmToLlvm/Base.hs
- compiler/GHC/CmmToLlvm/CodeGen.hs
- compiler/GHC/CmmToLlvm/Regs.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/35bcb5fa41963d3a144a0792a7383dd168a27945...818aba30cc10ea959afa405bd7c67e1b765239b7

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/35bcb5fa41963d3a144a0792a7383dd168a27945...818aba30cc10ea959afa405bd7c67e1b765239b7
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20200713/c43bb9af/attachment-0001.html>


More information about the ghc-commits mailing list