ghc-9.0.2: The GHC API
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.Stg.Lift.Analysis

Description

Provides the heuristics for when it's beneficial to lambda lift bindings. Most significantly, this employs a cost model to estimate impact on heap allocations, by looking at an STG expression's Skeleton.

Synopsis

When to lift

The analysis proceeds in two steps:

  1. It tags the syntax tree with analysis information in the form of BinderInfo at each binder and Skeletons at each let-binding by tagSkeletonTopBind and friends.
  2. The resulting syntax tree is treated by the GHC.Stg.Lift module, calling out to goodToLift to decide if a binding is worthwhile to lift. goodToLift consults argument occurrence information in BinderInfo and estimates closureGrowth, for which it needs the Skeleton.

So the annotations from tagSkeletonTopBind ultimately fuel goodToLift, which employs a number of heuristics to identify and exclude lambda lifting opportunities deemed non-beneficial:

Top-level bindings
can't be lifted.
Thunks
and data constructors shouldn't be lifted in order not to destroy sharing.
Argument occurrences
of binders prohibit them to be lifted. Doing the lift would re-introduce the very allocation at call sites that we tried to get rid off in the first place. We capture analysis information in BinderInfo. Note that we also consider a nullary application as argument occurrence, because it would turn into an n-ary partial application created by a generic apply function. This occurs in CPS-heavy code like the CS benchmark.
Join points
should not be lifted, simply because there's no reduction in allocation to be had.
Abstracting over join points
destroys join points, because they end up as arguments to the lifted function.
Abstracting over known local functions
turns a known call into an unknown call (e.g. some stg_ap_*), which is generally slower. Can be turned off with -fstg-lift-lams-known.
Calling convention
Don't lift when the resulting function would have a higher arity than available argument registers for the calling convention. Can be influenced with -fstg-lift-(non)rec-args(-any).
Closure growth
introduced when former free variables have to be available at call sites may actually lead to an increase in overall allocations resulting from a lift. Estimating closure growth is described in GHC.Stg.Lift.Analysis and is what most of this module is ultimately concerned with.

There's a wiki page with some more background and history.

Estimating closure growth

We estimate closure growth by abstracting the syntax tree into a Skeleton, capturing only syntactic details relevant to closureGrowth, such as

  • ClosureSk, representing closure allocation.
  • RhsSk, representing a RHS of a binding and how many times it's called by an appropriate DmdShell.
  • AltSk, BothSk and NilSk for choice, sequence and empty element.

This abstraction is mostly so that the main analysis function closureGrowth can stay simple and focused. Also, skeletons tend to be much smaller than the syntax tree they abstract, so it makes sense to construct them once and and operate on them instead of the actual syntax tree.

A more detailed treatment of computing closure growth, including examples, can be found in the paper referenced from the wiki page.

AST annotation

data Skeleton Source #

Captures details of the syntax tree relevant to the cost model, such as closures, multi-shot lambdas and case expressions.

Constructors

ClosureSk 

Fields

RhsSk 

Fields

AltSk !Skeleton !Skeleton 
BothSk !Skeleton !Skeleton 
NilSk 

Instances

Instances details
Outputable Skeleton Source # 
Instance details

Defined in GHC.Stg.Lift.Analysis

data BinderInfo Source #

The type used in binder positions in GenStgExprs.

Constructors

BindsClosure !Id !Bool

Let(-no-escape)-bound thing with a flag indicating whether it occurs as an argument or in a nullary application (see GHC.Stg.Lift.Analysis).

BoringBinder !Id

Every other kind of binder

binderInfoBndr :: BinderInfo -> Id Source #

Gets the bound Id out a BinderInfo.

tagSkeletonTopBind :: CgStgBinding -> LlStgBinding Source #

Tags every binder with its BinderInfo and let bindings with their Skeletons.

Lifting decision

goodToLift Source #

Arguments

:: DynFlags 
-> TopLevelFlag 
-> RecFlag 
-> (DIdSet -> DIdSet)

An expander function, turning InIds into OutIds. See liftedIdsExpander.

-> [(BinderInfo, LlStgRhs)] 
-> Skeleton 
-> Maybe DIdSet

Just abs_ids = This binding is beneficial to lift and abs_ids are the variables it would abstract over

Combines several heuristics to decide whether to lambda-lift a given let-binding to top-level. See GHC.Stg.Lift.Analysis for details.

closureGrowth Source #

Arguments

:: (DIdSet -> DIdSet)

Expands outer free ids that were lifted to their free vars

-> (Id -> Int)

Computes the closure footprint of an identifier

-> IdSet

Binding group for which lifting is to be decided

-> DIdSet

Free vars of the whole binding group prior to lifting it. These must be available at call sites if we decide to lift the binding group.

-> Skeleton

Abstraction of the scope of the function

-> IntWithInf

Closure growth. infinity indicates there was growth under a (multi-shot) lambda.

closureGrowth expander sizer f fvs computes the closure growth in words as a result of lifting f to top-level. If there was any growing closure under a multi-shot lambda, the result will be infinity. Also see GHC.Stg.Lift.Analysis.