[Git][ghc/ghc][wip/T17775] 18 commits: Don't override proc CafInfos in ticky builds

Simon Peyton Jones gitlab at gitlab.haskell.org
Mon Apr 13 09:26:03 UTC 2020



Simon Peyton Jones pushed to branch wip/T17775 at Glasgow Haskell Compiler / GHC


Commits:
dcfe29c8 by Ömer Sinan Ağacan at 2020-04-06T13:16:08-04:00
Don't override proc CafInfos in ticky builds

Fixes #17947

When we have a ticky label for a proc, IdLabels for the ticky counter
and proc entry share the same Name. This caused overriding proc CafInfos
with the ticky CafInfos (i.e. NoCafRefs) during SRT analysis.

We now ignore the ticky labels when building SRTMaps. This makes sense
because:

- When building the current module they don't need to be in SRTMaps as
  they're initialized as non-CAFFY (see mkRednCountsLabel), so they
  don't take part in the dependency analysis and they're never added to
  SRTs.

  (Reminder: a "dependency" in the SRT analysis is a CAFFY dependency,
  non-CAFFY uses are not considered as dependencies for the algorithm)

- They don't appear in the interfaces as they're not exported, so it
  doesn't matter for cross-module concerns whether they're in the SRTMap
  or not.

See also the new Note [Ticky labels in SRT analysis].

- - - - -
cec2c71f by Simon Peyton Jones at 2020-04-06T13:16:44-04:00
Fix an tricky specialiser loop

Issue #17151 was a very tricky example of a bug in which the
specialiser accidentally constructs a recurive dictionary,
so that everything turns into bottom.

I have fixed variants of this bug at least twice before:
see Note [Avoiding loops].  It was a bit of a struggle
to isolate the problem, greatly aided by the work that
Alexey Kuleshevich did in distilling a test case.

Once I'd understood the problem, it was not difficult to fix,
though it did lead me a bit of refactoring in specImports.

- - - - -
e850d14f by Simon Peyton Jones at 2020-04-06T13:16:44-04:00
Refactoring only

This refactors DictBinds into a data type rather than a pair.
No change in behaviour, just better code

- - - - -
f38e8d61 by Daniel Gröber at 2020-04-07T02:00:05-04:00
rts: ProfHeap: Fix memory leak when not compiled with profiling

If we're doing heap profiling on an unprofiled executable we keep
allocating new space in initEra via nextEra on each profiler run but we
don't have a corresponding freeEra call.

We do free the last era in endHeapProfiling but previous eras will have
been overwritten by initEra and will never get free()ed.

Metric Decrease:
    space_leak_001

- - - - -
bcd66859 by Sebastian Graf at 2020-04-07T02:00:41-04:00
Re-export GHC.Magic.noinline from base

- - - - -
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.

- - - - -
14132e97 by Simon Peyton Jones at 2020-04-09T16:09:04+01:00
Simplify subsumption

This patch implements GHC Proposal 287: Simplify subsumption
and ticket #17775.

The highlights are:

* No deeplyInstantiate or deeplySkolemise
* No tcSubTypeDS

Everything else is a knock-on effect.

I did a bit of renaming to make things consistent

* tcPolyExpr becomes tcCheckPolyExpr
  ditto tcPolyExprNC

* Add new function
    tcCheckMonoExpr e ty = tcMon0Expr expr (mkCheckExpType ty)
  and use it

This all comopiles, but needs some eta-expansion in haskeline, and
doubtless other packages.

- - - - -
7feb5df9 by Simon Peyton Jones at 2020-04-09T16:13:14+01:00
Further refactoring and simplification

Reviewed the main changes with Richard

I had to do eta-expansion in a number of tests:
   T10283
   T10390
   T14488
   T1634
   T4284
   T9569a
   T9834
   tc145
   tc160
   tc208
   tc210
   twins

- - - - -
548d8f22 by Ben Gamari at 2020-04-09T16:13:14+01:00
Bump haskeline submodule

- - - - -
e9c0333b by Simon Peyton Jones at 2020-04-09T16:13:18+01:00
Delete commented-out code

- - - - -
4cbf8fc5 by Simon Peyton Jones at 2020-04-09T16:13:20+01:00
Fix (breaking) typo

- - - - -
9a92286c by Simon Peyton Jones at 2020-04-09T16:13:22+01:00
Improve decomposition for FunTys

This just improves error messages, avoiding
  Couldn't match type ‘Char’ with ‘Show a -> Char’

- - - - -
c61810f6 by Ryan Scott at 2020-04-09T16:13:22+01:00
Bump Cabal submodule

As well as some miscellaneous fixes needed to make GHC itself
compile under simplified subsumption.

- - - - -
279b173a by Simon Peyton Jones at 2020-04-09T16:15:51+01:00
Wibbles

* Get expected/actual the right way round
* Relevant-bindings fixes

- - - - -
474331ac by Simon Peyton Jones at 2020-04-13T10:11:04+01:00
A lot more wibbles

* Made String wired-in, so that
    "foo" :: String   rather than
    "foo" :: [Char]

* isTauTy: account for =>

* Bring dicts into scope when desugaring HsWrappers:
  addTyCsDs and hsWrapDictBinders

* Improve reporting for occurs checks where
  skolems are involved e.g. 10715b, mc19, tcfail193, T13674,
    T4272, T3169, T7758, 7148
  Payload is in the first case of mkTyVarEqErr

* solveLocalEqualitesX: fail faster.
    we want to fail fast in T11142
  Another example: T15629
  And keep all equalities in dropMisleading.  This gives better
  reporting in T12593 for example.

* Move checkDataKindSig after the solveEqualities and zonk,
  obviously!

* Move ic_telescope into ForAllSkol; a nice win.

* Pretty-printing AbsBinds

We are now very close to green

- - - - -


30 changed files:

- CODEOWNERS
- compiler/GHC.hs
- compiler/GHC/Cmm/CLabel.hs
- compiler/GHC/Cmm/Expr.hs
- compiler/GHC/Cmm/Info/Build.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/FamInstEnv.hs
- compiler/GHC/Core/InstEnv.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Op/CSE.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/CoreToStg/Prep.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/bd8eda7c22e8ccf88c2bf30de3edb69ba5519e2c...474331ace3eed36e398b76ce08c958fff3a9051d

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/bd8eda7c22e8ccf88c2bf30de3edb69ba5519e2c...474331ace3eed36e398b76ce08c958fff3a9051d
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/20200413/a474c5bb/attachment-0001.html>


More information about the ghc-commits mailing list