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

GHC.Stg.Lift.Monad

Description

Hides away distracting bookkeeping while lambda lifting into a LiftM monad.

Synopsis

Documentation

data Env Source #

Environment threaded around in a scoped, Reader-like fashion.

Constructors

Env 

Fields

  • e_dflags :: !DynFlags

    Read-only.

  • e_subst :: !Subst

    We need to track the renamings of local InIds to their lifted OutId, because shadowing might make a closure's free variables unavailable at its call sites. Consider: let f y = x + y in let x = 4 in f x Here, f can't be lifted to top-level, because its free variable x isn't available at its call site.

  • e_expansions :: !(IdEnv DIdSet)

    Lifted Ids don't occur as free variables in any closure anymore, because they are bound at the top-level. Every occurrence must supply the formerly free variables of the lifted Id, so they in turn become free variables of the call sites. This environment tracks this expansion from lifted Ids to their free variables.

    InIds to OutIds.

    Invariant: Ids not present in this map won't be substituted.

Handling floats

Consider the following expression:

    f x =
      let g y = ... f y ...
      in g x

What happens when we want to lift g? Normally, we'd put the lifted l_g binding above the binding for f:

    g f y = ... f y ...
    f x = g f x

But this very unnecessarily turns a known call to f into an unknown one, in addition to complicating matters for the analysis. Instead, we'd really like to put both functions in the same recursive group, thereby preserving the known call:

    Rec {
      g y = ... f y ...
      f x = g x
    }

But we don't want this to happen for just any binding. That would create possibly huge recursive groups in the process, calling for an occurrence analyser on STG. So, we need to track when we lift a binding out of a recursive RHS and add the binding to the same recursive group as the enclosing recursive binding (which must have either already been at the top-level or decided to be lifted itself in order to preserve the known call).

This is done by expressing this kind of nesting structure as a Writer over [FloatLang] and flattening this expression in runLiftM by a call to collectFloats. API-wise, the analysis will not need to know about the whole FloatLang business and will just manipulate it indirectly through actions in LiftM.

data FloatLang Source #

We need to detect when we are lifting something out of the RHS of a recursive binding (c.f. GHC.Stg.Lift.Monad), in which case that binding needs to be added to the same top-level recursive group. This requires we detect a certain nesting structure, which is encoded by StartBindingGroup and EndBindingGroup.

Although collectFloats will only ever care if the current binding to be lifted (through LiftedBinding) will occur inside such a binding group or not, e.g. doesn't care about the nesting level as long as its greater than 0.

Instances

Instances details
Outputable FloatLang Source # 
Instance details

Defined in GHC.Stg.Lift.Monad

Methods

ppr :: FloatLang -> SDoc Source #

collectFloats :: [FloatLang] -> [OutStgTopBinding] Source #

Flattens an expression in [FloatLang] into an STG program, see GHC.Stg.Lift.Monad. Important pre-conditions: The nesting of opening StartBindinGroups and closing EndBindinGroups is balanced. Also, it is crucial that every binding group has at least one recursive binding inside. Otherwise there's no point in announcing the binding group in the first place and an ASSERT will trigger.

Transformation monad

data LiftM a Source #

The analysis monad consists of the following RWST components:

  • Env: Reader-like context. Contains a substitution, info about how how lifted identifiers are to be expanded into applications and details such as DynFlags.
  • OrdList FloatLang: Writer output for the resulting STG program.
  • No pure state component
  • But wrapping around UniqSM for generating fresh lifted binders. (The uniqAway approach could give the same name to two different lifted binders, so this is necessary.)

Instances

Instances details
Applicative LiftM Source # 
Instance details

Defined in GHC.Stg.Lift.Monad

Methods

pure :: a -> LiftM a Source #

(<*>) :: LiftM (a -> b) -> LiftM a -> LiftM b Source #

liftA2 :: (a -> b -> c) -> LiftM a -> LiftM b -> LiftM c Source #

(*>) :: LiftM a -> LiftM b -> LiftM b Source #

(<*) :: LiftM a -> LiftM b -> LiftM a Source #

Functor LiftM Source # 
Instance details

Defined in GHC.Stg.Lift.Monad

Methods

fmap :: (a -> b) -> LiftM a -> LiftM b Source #

(<$) :: a -> LiftM b -> LiftM a Source #

Monad LiftM Source # 
Instance details

Defined in GHC.Stg.Lift.Monad

Methods

(>>=) :: LiftM a -> (a -> LiftM b) -> LiftM b Source #

(>>) :: LiftM a -> LiftM b -> LiftM b Source #

return :: a -> LiftM a Source #

HasDynFlags LiftM Source # 
Instance details

Defined in GHC.Stg.Lift.Monad

MonadUnique LiftM Source # 
Instance details

Defined in GHC.Stg.Lift.Monad

Adding bindings

startBindingGroup :: LiftM () Source #

Starts a recursive binding group. See GHC.Stg.Lift.Monad and collectFloats.

endBindingGroup :: LiftM () Source #

Ends a recursive binding group. See GHC.Stg.Lift.Monad and collectFloats.

addTopStringLit :: OutId -> ByteString -> LiftM () Source #

Writes a plain StgTopStringLit to the output.

addLiftedBinding :: OutStgBinding -> LiftM () Source #

Lifts a binding to top-level. Depending on whether it's declared inside a recursive RHS (see GHC.Stg.Lift.Monad and collectFloats), this might be added to an existing recursive top-level binding group.

Substitution and binders

withSubstBndr :: Id -> (Id -> LiftM a) -> LiftM a Source #

Takes a binder and a continuation which is called with the substituted binder. The continuation will be evaluated in a LiftM context in which that binder is deemed in scope. Think of it as a local computation: After the continuation finishes, the new binding won't be in scope anymore.

withLiftedBndr :: DIdSet -> Id -> (Id -> LiftM a) -> LiftM a Source #

Similarly to withSubstBndr, this function takes a set of variables to abstract over, the binder to lift (and generate a fresh, substituted name for) and a continuation in which that fresh, lifted binder is in scope.

It takes care of all the details involved with copying and adjusting the binder and fresh name generation.

Occurrences

substOcc :: Id -> LiftM Id Source #

Substitutes a binder occurrence, which was brought in scope earlier by withSubstBndr / withLiftedBndr.

isLifted :: InId -> LiftM Bool Source #

Whether the given binding was decided to be lambda lifted.

formerFreeVars :: InId -> LiftM [OutId] Source #

Returns an empty list for a binding that was not lifted and the list of all local variables the binding abstracts over (so, exactly the additional arguments at adjusted call sites) otherwise.

liftedIdsExpander :: LiftM (DIdSet -> DIdSet) Source #

Creates an expander function for the current set of lifted binders. This expander function will replace any InId by their corresponding OutId and, in addition, will expand any lifted binders by the former free variables it abstracts over.