Skip to content

Improve eta reduction

Simon Peyton Jones requested to merge wip/T18993a into master

This patch set implements a bunch of changes relate to eta reduction and expansion.

I have been working on them for a ridiculously long time, playing whack-a-mole. It has been a painful journey, but finally the moles are whacked. CI numbers look good. (I will add them to the main commit message before finally pulling the trigger.)

So this is ready for final review esp @sgraf812

commit d708ca487808b7df2892c9ce8a3d309299d755b0
Author: Simon Peyton Jones <simonpj@microsoft.com>
Date:   Fri Jul 23 23:57:01 2021 +0100

    A bunch of changes related to eta reduction
    
    This is a large collection of changes all relating to eta
    reduction, originally triggered by #18993, but there followed
    a long saga.
    
    Specifics:
    
    * Move state-hack stuff from GHC.Types.Id (where it never belonged)
      to GHC.Core.Opt.Arity (which seems much more appropriate).
    
    * Add a crucial mkCast in the Cast case of
      GHC.Core.Opt.Arity.eta_expand; helps with T18223
    
    * Add clarifying notes about eta-reducing to PAPs.
      See Note [Do not eta reduce PAPs]
    
    * I moved tryEtaReduce from GHC.Core.Utils to GHC.Core.Opt.Arity,
      where it properly belongs.  See Note [Eta reduce PAPs]
    
    * In GHC.Core.Opt.Simplify.Utils.tryEtaExpandRhs, pull out the code for
      when eta-expansion is wanted, to make wantEtaExpansion, and all that
      same function in GHC.Core.Opt.Simplify.simplStableUnfolding.  It was
      previously inconsistent, but it's doing the same thing.
    
    * I did a substantial refactor of ArityType; see Note [ArityType].
      This allowed me to do away with the somewhat mysterious takeOneShots;
      more generally it allows arityType to describe the function, leaving
      its clients to decide how to use that information.
    
      I made ArityType abstract, so that clients have to use functions
      to access it.
    
    * Make GHC.Core.Opt.Simplify.Utils.rebuildLam (was stupidly called
      mkLam before) aware of the floats that the simplifier builds up, so
      that it can still do eta-reduction even if there are some floats.
      (Previously that would not happen.)  That means passing the floats
      to rebuildLam, and an extra check when eta-reducting (etaFloatOk).
    
    * In GHC.Core.Opt.Simplify.Utils.tryEtaExpandRhs, make use of call-info
      in the idDemandInfo of the binder, as well as the CallArity info. The
      occurrence analyser did this but we were failing to take advantage here.
    
      In the end I moved the heavy lifting to GHC.Core.Opt.Arity.findRhsArity;
      see Note [Combining arityType with demand info], and functions
      idDemandOneShots and combineWithDemandOneShots.
    
      (These changes partly drove my refactoring of ArityType.)
    
    * In GHC.Core.Opt.Arity.findRhsArity
      * I'm now taking account of the demand on the binder to give
        extra one-shot info.  E.g. if the fn is always called with two
        args, we can give better one-shot info on the binders
        than if we just look at the RHS.
    
      * Don't do any fixpointing in the non-recursive
        case -- simple short cut.
    
      * Trim arity inside the loop. See Note [Trim arity inside the loop]
    
    * Make SimpleOpt respect the eta-reduction flag
      (Some associated refactoring here.)
    
    * I made the CallCtxt which the Simplifier uses distinguish between
      recursive and non-recursive right-hand sides.
         data CallCtxt = ... | RhsCtxt RecFlag | ...
      It affects two things:
         - We call an RHS context interesting only if it is non-recursive
           see Note [RHS of lets] in GHC.Core.Unfold
         - We only eta-reduce non-recursive RHS, rather than eta-reducing
           every lambda. I'm not sure about the "non-recursive" bit; ToDo.
    
    * Remove eta-reduction in GHC.CoreToStg.Prep, a welcome simplification.
      See Note [No eta reduction needed in rhsToBody] in GHC.CoreToStg.Prep.
    
    Other incidental changes
    
    * Fix a fairly long-standing outright bug in the ApplyToVal case of
      GHC.Core.Opt.Simplify.mkDupableContWithDmds. I was failing to take the
      tail of 'dmds' in the recursive call, which meant the demands were All
      Wrong.  I have no idea why this has not caused problems before now.
    
    * Delete dead function GHC.Core.Opt.Simplify.Utils.contIsRhsOrArg

commit fa434c3f9508c79c8039d661a7d0b9c046983c01
Author: Simon Peyton Jones <simonpj@microsoft.com>
Date:   Fri Jul 23 23:35:21 2021 +0100

    Make PrimOpId record levity
    
    This patch concerns #20155, part (1)
    
    The general idea is that since primops have curried bindings
    (currently in PrimOpWrappers.hs) we don't need to eta-expand
    them.  But we /do/ need to eta-expand the levity-polymorphic ones,
    because they /don't/ have bindings.
    
    This patch makes a start in that direction, by identifying the
    levity-polymophic primops in the PrimOpId IdDetails constructor.
    
    For the moment, I'm still eta-expanding all primops (by saying
    that hasNoBinding returns True for all primops), because of the
    bug reported in #20155.  But I hope that before long we can
    tidy that up too, and remove the TEMPORARILY stuff in hasNoBinding.

commit 71bddf6e9f4c24a6225aa71e83a18d75aaa44694
Author: Simon Peyton Jones <simonpj@microsoft.com>
Date:   Fri Jul 23 23:33:10 2021 +0100

    Comments and white space

commit bc56af18b5a26d6535295e5c9ff31bd7b9363b11
Author: Simon Peyton Jones <simonpj@microsoft.com>
Date:   Wed Jun 23 20:53:27 2021 +0100

    Make findRhsArity take RecFlag
    
    This avoids a fixpoint iteration for the common case of
    non-recursive bindings.

commit 4d64bb05639b6209cb6111a9f82dfb08dcebea01
Author: Simon Peyton Jones <simonpj@microsoft.com>
Date:   Tue Jun 15 22:49:40 2021 +0100

    Do arity trimming at bindings, rather than in exprArity
    
    Sometimes there are very large casts, and coercionRKind
    can be slow.

commit 1ab020b3de798c7c9f56f09f7207303a9d17f271
Author: Simon Peyton Jones <simonpj@microsoft.com>
Date:   Sat May 29 22:49:34 2021 +0100

    Eta reduction with casted function
    
    We want to be able to eta-reduce
       \x y. ((f x) |> co) y
    by pushing 'co' inwards.  A very small change accommodates this
    See Note [Eta reduction with casted function]
Edited by Simon Peyton Jones

Merge request reports