Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Hides away distracting bookkeeping while lambda lifting into a LiftM
monad.
Synopsis
- decomposeStgBinding :: GenStgBinding pass -> (RecFlag, [(BinderP pass, GenStgRhs pass)])
- mkStgBinding :: RecFlag -> [(BinderP pass, GenStgRhs pass)] -> GenStgBinding pass
- data Env = Env {
- e_config :: StgLiftConfig
- e_subst :: !Subst
- e_expansions :: !(IdEnv DIdSet)
- data FloatLang
- collectFloats :: [FloatLang] -> [OutStgTopBinding]
- data LiftM a
- runLiftM :: StgLiftConfig -> UniqSupply -> LiftM () -> [OutStgTopBinding]
- getConfig :: LiftM StgLiftConfig
- startBindingGroup :: LiftM ()
- endBindingGroup :: LiftM ()
- addTopStringLit :: OutId -> ByteString -> LiftM ()
- addLiftedBinding :: OutStgBinding -> LiftM ()
- withSubstBndr :: Id -> (Id -> LiftM a) -> LiftM a
- withSubstBndrs :: Traversable f => f Id -> (f Id -> LiftM a) -> LiftM a
- withLiftedBndr :: DIdSet -> Id -> (Id -> LiftM a) -> LiftM a
- withLiftedBndrs :: Traversable f => DIdSet -> f Id -> (f Id -> LiftM a) -> LiftM a
- substOcc :: Id -> LiftM Id
- isLifted :: InId -> LiftM Bool
- formerFreeVars :: InId -> LiftM [OutId]
- liftedIdsExpander :: LiftM (DIdSet -> DIdSet)
Documentation
decomposeStgBinding :: GenStgBinding pass -> (RecFlag, [(BinderP pass, GenStgRhs pass)]) Source #
uncurrymkStgBinding
.decomposeStgBinding
= id
mkStgBinding :: RecFlag -> [(BinderP pass, GenStgRhs pass)] -> GenStgBinding pass Source #
Environment threaded around in a scoped, Reader
-like fashion.
Env | |
|
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
[
and flattening this expression in FloatLang
]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
.
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
collectFloats :: [FloatLang] -> [OutStgTopBinding] Source #
Flattens an expression in [
into an STG program, see GHC.Stg.Lift.Monad.
Important pre-conditions: The nesting of opening FloatLang
]StartBindinGroup
s and
closing EndBindinGroup
s 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
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 configuration options.
: Writer output for the resulting STG program.OrdList
FloatLang
- No pure state component
- But wrapping around
UniqSM
for generating fresh lifted binders. (TheuniqAway
approach could give the same name to two different lifted binders, so this is necessary.)
runLiftM :: StgLiftConfig -> UniqSupply -> LiftM () -> [OutStgTopBinding] Source #
Get config
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
withSubstBndrs :: Traversable f => f Id -> (f Id -> LiftM a) -> LiftM a Source #
See withSubstBndr
.
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.
withLiftedBndrs :: Traversable f => DIdSet -> f Id -> (f Id -> LiftM a) -> LiftM a Source #
See withLiftedBndr
.
Occurrences
substOcc :: Id -> LiftM Id Source #
Substitutes a binder occurrence, which was brought in scope earlier by
withSubstBndr
/ withLiftedBndr
.