[Git][ghc/ghc][wip/osa1/lfinfo] 13 commits: simplifier: Kill off ufKeenessFactor

Ömer Sinan Ağacan gitlab at gitlab.haskell.org
Fri Apr 10 11:45:24 UTC 2020



Ömer Sinan Ağacan pushed to branch wip/osa1/lfinfo at Glasgow Haskell Compiler / GHC


Commits:
3d2991f8 by Ben Gamari at 2020-04-07T18:36:09-04:00
simplifier: Kill off ufKeenessFactor

We used to have another factor, ufKeenessFactor, which would scale the
discounts before they were subtracted from the size. This was justified
with the following comment:

  -- We multiple the raw discounts (args_discount and result_discount)
  -- ty opt_UnfoldingKeenessFactor because the former have to do with
  --  *size* whereas the discounts imply that there's some extra
  --  *efficiency* to be gained (e.g. beta reductions, case reductions)
  -- by inlining.

However, this is highly suspect since it means that we subtract a
*scaled* size from an absolute size, resulting in crazy (e.g. negative)
scores in some cases (#15304). We consequently killed off
ufKeenessFactor and bumped up the ufUseThreshold to compensate.

Adjustment of unfolding use threshold
=====================================

Since this removes a discount from our inlining heuristic, I revisited our
default choice of -funfolding-use-threshold to minimize the change in
overall inlining behavior. Specifically, I measured runtime allocations
and executable size of nofib and the testsuite performance tests built
using compilers (and core libraries) built with several values of
-funfolding-use-threshold.

This comes as a result of a quantitative comparison of testsuite
performance and code size as a function of ufUseThreshold, comparing
GHC trees using values of 50, 60, 70, 80, 90, and 100. The test set
consisted of nofib and the testsuite performance tests.
A full summary of these measurements are found in the description of
!2608

Comparing executable sizes (relative to the base commit) across all
nofib tests, we see that sizes are similar to the baseline:

            gmean      min      max   median
thresh
50         -6.36%   -7.04%   -4.82%   -6.46%
60         -5.04%   -5.97%   -3.83%   -5.11%
70         -2.90%   -3.84%   -2.31%   -2.92%
80         -0.75%   -2.16%   -0.42%   -0.73%
90         +0.24%   -0.41%   +0.55%   +0.26%
100        +1.36%   +0.80%   +1.64%   +1.37%
baseline   +0.00%   +0.00%   +0.00%   +0.00%

Likewise, looking at runtime allocations we see that 80 gives slightly
better optimisation than the baseline:

            gmean      min      max   median
thresh
50         +0.16%   -0.16%   +4.43%   +0.00%
60         +0.09%   -0.00%   +3.10%   +0.00%
70         +0.04%   -0.09%   +2.29%   +0.00%
80         +0.02%   -1.17%   +2.29%   +0.00%
90         -0.02%   -2.59%   +1.86%   +0.00%
100        +0.00%   -2.59%   +7.51%   -0.00%
baseline   +0.00%   +0.00%   +0.00%   +0.00%

Finally, I had to add a NOINLINE in T4306 to ensure that `upd` is
worker-wrappered as the test expects. This makes me wonder whether the
inlining heuristic is now too liberal as `upd` is quite a large
function. The same measure was taken in T12600.

             Wall clock time compiling Cabal with -O0
thresh       50     60     70     80     90      100    baseline
build-Cabal  93.88  89.58  92.59  90.09  100.26  94.81  89.13

Also, this change happens to avoid the spurious test output in
`plugin-recomp-change` and `plugin-recomp-change-prof` (see #17308).

Metric Decrease:
    hie002
    T12234
    T13035
    T13719
    T14683
    T4801
    T5631
    T5642
    T9020
    T9872d
    T9961
Metric Increase:
    T12150
    T12425
    T13701
    T14697
    T15426
    T1969
    T3064
    T5837
    T6048
    T9203
    T9872a
    T9872b
    T9872c
    T9872d
    haddock.Cabal
    haddock.base
    haddock.compiler

- - - - -
255418da by Sylvain Henry at 2020-04-07T18:36:49-04:00
Modules: type-checker (#13009)

Update Haddock submodule

- - - - -
04b6cf94 by Ryan Scott at 2020-04-07T19:43:20-04:00
Make NoExtCon fields strict

This changes every unused TTG extension constructor to be strict in
its field so that the pattern-match coverage checker is smart enough
any such constructors are unreachable in pattern matches. This lets
us remove nearly every use of `noExtCon` in the GHC API. The only
ones we cannot remove are ones underneath uses of `ghcPass`, but that
is only because GHC 8.8's and 8.10's coverage checkers weren't smart
enough to perform this kind of reasoning. GHC HEAD's coverage
checker, on the other hand, _is_ smart enough, so we guard these uses
of `noExtCon` with CPP for now.

Bumps the `haddock` submodule.

Fixes #17992.

- - - - -
7802fa17 by Ryan Scott at 2020-04-08T16:43:44-04:00
Handle promoted data constructors in typeToLHsType correctly

Instead of using `nlHsTyVar`, which hardcodes `NotPromoted`, have
`typeToLHsType` pick between `Promoted` and `NotPromoted` by checking
if a type constructor is promoted using `isPromotedDataCon`.

Fixes #18020.

- - - - -
ce481361 by Ben Gamari at 2020-04-09T16:17:21-04:00
hadrian: Use --export-dynamic when linking iserv

As noticed in #17962, the make build system currently does this (see
3ce0e0ba) but the change was never ported to Hadrian.

- - - - -
fa66f143 by Ben Gamari at 2020-04-09T16:17:21-04:00
iserv: Don't pass --export-dynamic on FreeBSD

This is definitely a hack but it's probably the best we can do for now.
Hadrian does the right thing here by passing --export-dynamic only to
the linker.

- - - - -
39075176 by Ömer Sinan Ağacan at 2020-04-09T16:18:00-04:00
Fix CNF handling in compacting GC

Fixes #17937

Previously compacting GC simply ignored CNFs. This is mostly fine as
most (see "What about small compacts?" below) CNF objects don't have
outgoing pointers, and are "large" (allocated in large blocks) and large
objects are not moved or compacted.

However if we do GC *during* sharing-preserving compaction then the CNF
will have a hash table mapping objects that have been moved to the CNF
to their location in the CNF, to be able to preserve sharing.

This case is handled in the copying collector, in `scavenge_compact`,
where we evacuate hash table entries and then rehash the table.

Compacting GC ignored this case.

We now visit CNFs in all generations when threading pointers to the
compacted heap and thread hash table keys. A visited CNF is added to the
list `nfdata_chain`. After compaction is done, we re-visit the CNFs in
that list and rehash the tables.

The overhead is minimal: the list is static in `Compact.c`, and link
field is added to `StgCompactNFData` closure. Programs that don't use
CNFs should not be affected.

To test this CNF tests are now also run in a new way 'compacting_gc',
which just passes `-c` to the RTS, enabling compacting GC for the oldest
generation. Before this patch the result would be:

    Unexpected failures:
       compact_gc.run          compact_gc [bad exit code (139)] (compacting_gc)
       compact_huge_array.run  compact_huge_array [bad exit code (1)] (compacting_gc)

With this patch all tests pass. I can also pass `-c -DS` without any
failures.

What about small compacts? Small CNFs are still not handled by the
compacting GC. However so far I'm unable to write a test that triggers a
runtime panic ("update_fwd: unknown/strange object") by allocating a
small CNF in a compated heap. It's possible that I'm missing something
and it's not possible to have a small CNF.

NoFib Results:

--------------------------------------------------------------------------------
        Program           Size    Allocs    Instrs     Reads    Writes
--------------------------------------------------------------------------------
             CS          +0.1%      0.0%      0.0%     +0.0%     +0.0%
            CSD          +0.1%      0.0%      0.0%      0.0%      0.0%
             FS          +0.1%      0.0%      0.0%      0.0%      0.0%
              S          +0.1%      0.0%      0.0%      0.0%      0.0%
             VS          +0.1%      0.0%      0.0%      0.0%      0.0%
            VSD          +0.1%      0.0%     +0.0%     +0.0%     -0.0%
            VSM          +0.1%      0.0%     +0.0%     -0.0%      0.0%
           anna          +0.0%      0.0%     -0.0%     -0.0%     -0.0%
           ansi          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
           atom          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
         awards          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
         banner          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
     bernouilli          +0.1%      0.0%      0.0%     -0.0%     +0.0%
   binary-trees          +0.1%      0.0%     -0.0%     -0.0%      0.0%
          boyer          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
         boyer2          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
           bspt          +0.1%      0.0%     -0.0%     -0.0%     -0.0%
      cacheprof          +0.1%      0.0%     -0.0%     -0.0%     -0.0%
       calendar          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
       cichelli          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
        circsim          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
       clausify          +0.1%      0.0%     -0.0%     +0.0%     +0.0%
  comp_lab_zift          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
       compress          +0.1%      0.0%     +0.0%     +0.0%      0.0%
      compress2          +0.1%      0.0%     -0.0%      0.0%      0.0%
    constraints          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
   cryptarithm1          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
   cryptarithm2          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
            cse          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
   digits-of-e1          +0.1%      0.0%     +0.0%     -0.0%     -0.0%
   digits-of-e2          +0.1%      0.0%     -0.0%     -0.0%     -0.0%
         dom-lt          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
          eliza          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
          event          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
    exact-reals          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
         exp3_8          +0.1%      0.0%     +0.0%     -0.0%      0.0%
         expert          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
 fannkuch-redux          +0.1%      0.0%     -0.0%      0.0%      0.0%
          fasta          +0.1%      0.0%     -0.0%     +0.0%     +0.0%
            fem          +0.1%      0.0%     -0.0%     +0.0%      0.0%
            fft          +0.1%      0.0%     -0.0%     +0.0%     +0.0%
           fft2          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
       fibheaps          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
           fish          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
          fluid          +0.0%      0.0%     +0.0%     +0.0%     +0.0%
         fulsom          +0.1%      0.0%     -0.0%     +0.0%      0.0%
         gamteb          +0.1%      0.0%     +0.0%     +0.0%      0.0%
            gcd          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
    gen_regexps          +0.1%      0.0%     -0.0%     +0.0%      0.0%
         genfft          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
             gg          +0.1%      0.0%      0.0%     +0.0%     +0.0%
           grep          +0.1%      0.0%     -0.0%     +0.0%     +0.0%
         hidden          +0.1%      0.0%     +0.0%     -0.0%      0.0%
            hpg          +0.1%      0.0%     -0.0%     -0.0%     -0.0%
            ida          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
          infer          +0.1%      0.0%     +0.0%      0.0%     -0.0%
        integer          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
      integrate          +0.1%      0.0%     -0.0%     -0.0%     -0.0%
   k-nucleotide          +0.1%      0.0%     +0.0%     +0.0%      0.0%
          kahan          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
        knights          +0.1%      0.0%     -0.0%     -0.0%     -0.0%
         lambda          +0.1%      0.0%     +0.0%     +0.0%     -0.0%
     last-piece          +0.1%      0.0%     +0.0%      0.0%      0.0%
           lcss          +0.1%      0.0%     +0.0%     +0.0%      0.0%
           life          +0.1%      0.0%     -0.0%     +0.0%     +0.0%
           lift          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
         linear          +0.1%      0.0%     -0.0%     +0.0%      0.0%
      listcompr          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
       listcopy          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
       maillist          +0.1%      0.0%     +0.0%     -0.0%     -0.0%
         mandel          +0.1%      0.0%     +0.0%     +0.0%      0.0%
        mandel2          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
           mate          +0.1%      0.0%     +0.0%      0.0%     +0.0%
        minimax          +0.1%      0.0%     -0.0%      0.0%     -0.0%
        mkhprog          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
     multiplier          +0.1%      0.0%     +0.0%      0.0%      0.0%
         n-body          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
       nucleic2          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
           para          +0.1%      0.0%      0.0%     +0.0%     +0.0%
      paraffins          +0.1%      0.0%     +0.0%     -0.0%      0.0%
         parser          +0.1%      0.0%     -0.0%     -0.0%     -0.0%
        parstof          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
            pic          +0.1%      0.0%     -0.0%     -0.0%      0.0%
       pidigits          +0.1%      0.0%     +0.0%     -0.0%     -0.0%
          power          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
         pretty          +0.1%      0.0%     -0.0%     -0.0%     -0.1%
         primes          +0.1%      0.0%     -0.0%     -0.0%     -0.0%
      primetest          +0.1%      0.0%     -0.0%     -0.0%     -0.0%
         prolog          +0.1%      0.0%     -0.0%     -0.0%     -0.0%
         puzzle          +0.1%      0.0%     -0.0%     -0.0%     -0.0%
         queens          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
        reptile          +0.1%      0.0%     -0.0%     -0.0%     +0.0%
reverse-complem          +0.1%      0.0%     +0.0%      0.0%     -0.0%
        rewrite          +0.1%      0.0%     -0.0%     -0.0%     -0.0%
           rfib          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
            rsa          +0.1%      0.0%     -0.0%     +0.0%     -0.0%
            scc          +0.1%      0.0%     -0.0%     -0.0%     -0.1%
          sched          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
            scs          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
         simple          +0.1%      0.0%     -0.0%     -0.0%     -0.0%
          solid          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
        sorting          +0.1%      0.0%     -0.0%     -0.0%     -0.0%
  spectral-norm          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
         sphere          +0.1%      0.0%     -0.0%     -0.0%     -0.0%
         symalg          +0.1%      0.0%     -0.0%     -0.0%     -0.0%
            tak          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
      transform          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
       treejoin          +0.1%      0.0%     +0.0%     -0.0%     -0.0%
      typecheck          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
        veritas          +0.0%      0.0%     +0.0%     +0.0%     +0.0%
           wang          +0.1%      0.0%      0.0%     +0.0%     +0.0%
      wave4main          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
   wheel-sieve1          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
   wheel-sieve2          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
           x2n1          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
--------------------------------------------------------------------------------
            Min          +0.0%      0.0%     -0.0%     -0.0%     -0.1%
            Max          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
 Geometric Mean          +0.1%     -0.0%     -0.0%     -0.0%     -0.0%

Bumping numbers of nonsensical perf tests:

Metric Increase:
    T12150
    T12234
    T12425
    T13035
    T5837
    T6048

It's simply not possible for this patch to increase allocations, and
I've wasted enough time on these test in the past (see #17686). I think
these tests should not be perf tests, but for now I'll bump the numbers.

- - - - -
dce50062 by Sylvain Henry at 2020-04-09T16:18:44-04:00
Rts: show errno on failure (#18033)

- - - - -
045139f4 by Hécate at 2020-04-09T23:10:44-04:00
Add an example to liftIO and explain its purpose

- - - - -
101fab6e by Sebastian Graf at 2020-04-09T23:11:21-04:00
Special case `isConstraintKindCon` on `AlgTyCon`

Previously, the `tyConUnique` record selector would unfold into a huge
case expression that would be inlined in all call sites, such as the
`INLINE`-annotated `coreView`, see #18026. `constraintKindTyConKey` only
occurs as the `Unique` of an `AlgTyCon` anyway, so we can make the code
a lot more compact, but have to move it to GHC.Core.TyCon.

Metric Decrease:
    T12150
    T12234

- - - - -
f5212dfc by Sebastian Graf at 2020-04-09T23:11:57-04:00
DmdAnal: No need to attach a StrictSig to DataCon workers

In GHC.Types.Id.Make we were giving a strictness signature to every data
constructor wrapper Id that we weren't looking at in demand analysis
anyway. We used to use its CPR info, but that has its own CPR signature
now.

`Note [Data-con worker strictness]` then felt very out of place, so I
moved it to GHC.Core.DataCon.

- - - - -
75a185dc by Sylvain Henry at 2020-04-09T23:12:37-04:00
Hadrian: fix --summary

- - - - -
33f9a555 by Ömer Sinan Ağacan at 2020-04-10T13:02:10+03:00
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.

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%

- - - - -


30 changed files:

- CODEOWNERS
- compiler/GHC.hs
- compiler/GHC/Cmm/Expr.hs
- compiler/GHC/Cmm/Node.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Arity.hs
- compiler/GHC/Core/Class.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/Coercion/Axiom.hs
- compiler/GHC/Core/Coercion/Opt.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/FamInstEnv.hs
- compiler/GHC/Core/InstEnv.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Op/CSE.hs
- compiler/GHC/Core/Op/DmdAnal.hs
- compiler/GHC/Core/Op/OccurAnal.hs
- compiler/GHC/Core/Op/Simplify.hs
- compiler/GHC/Core/Op/Specialise.hs
- compiler/GHC/Core/PatSyn.hs
- compiler/GHC/Core/Predicate.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/TyCo/FVs.hs
- compiler/GHC/Core/TyCo/Ppr.hs
- compiler/GHC/Core/TyCo/Rep.hs
- compiler/GHC/Core/TyCon.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Unfold.hs
- compiler/GHC/Core/Unify.hs
- compiler/GHC/CoreToIface.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9a32ab1abbe3eb1b6f6e9f83bbf928ee04d316f9...33f9a555bf9c968908124fc6c5143d9a758d6fb8

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9a32ab1abbe3eb1b6f6e9f83bbf928ee04d316f9...33f9a555bf9c968908124fc6c5143d9a758d6fb8
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/20200410/c7793dcf/attachment-0001.html>


More information about the ghc-commits mailing list