Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Subst = Subst InScopeSet IdSubstEnv TvSubstEnv CvSubstEnv
- type TvSubstEnv = TyVarEnv Type
- type IdSubstEnv = IdEnv CoreExpr
- data InScopeSet
- deShadowBinds :: CoreProgram -> CoreProgram
- substSpec :: Subst -> Id -> RuleInfo -> RuleInfo
- substRulesForImportedIds :: Subst -> [CoreRule] -> [CoreRule]
- substTy :: Subst -> Type -> Type
- substCo :: HasCallStack => Subst -> Coercion -> Coercion
- substExpr :: SDoc -> Subst -> CoreExpr -> CoreExpr
- substExprSC :: SDoc -> Subst -> CoreExpr -> CoreExpr
- substBind :: Subst -> CoreBind -> (Subst, CoreBind)
- substBindSC :: Subst -> CoreBind -> (Subst, CoreBind)
- substUnfolding :: Subst -> Unfolding -> Unfolding
- substUnfoldingSC :: Subst -> Unfolding -> Unfolding
- lookupIdSubst :: SDoc -> Subst -> Id -> CoreExpr
- lookupTCvSubst :: Subst -> TyVar -> Type
- substIdOcc :: Subst -> Id -> Id
- substTickish :: Subst -> Tickish Id -> Tickish Id
- substDVarSet :: Subst -> DVarSet -> DVarSet
- substIdInfo :: Subst -> Id -> IdInfo -> Maybe IdInfo
- emptySubst :: Subst
- mkEmptySubst :: InScopeSet -> Subst
- mkSubst :: InScopeSet -> TvSubstEnv -> CvSubstEnv -> IdSubstEnv -> Subst
- mkOpenSubst :: InScopeSet -> [(Var, CoreArg)] -> Subst
- substInScope :: Subst -> InScopeSet
- isEmptySubst :: Subst -> Bool
- extendIdSubst :: Subst -> Id -> CoreExpr -> Subst
- extendIdSubstList :: Subst -> [(Id, CoreExpr)] -> Subst
- extendTCvSubst :: TCvSubst -> TyCoVar -> Type -> TCvSubst
- extendTvSubstList :: Subst -> [(TyVar, Type)] -> Subst
- extendSubst :: Subst -> Var -> CoreArg -> Subst
- extendSubstList :: Subst -> [(Var, CoreArg)] -> Subst
- extendSubstWithVar :: Subst -> Var -> Var -> Subst
- zapSubstEnv :: Subst -> Subst
- addInScopeSet :: Subst -> VarSet -> Subst
- extendInScope :: Subst -> Var -> Subst
- extendInScopeList :: Subst -> [Var] -> Subst
- extendInScopeIds :: Subst -> [Id] -> Subst
- isInScope :: Var -> Subst -> Bool
- setInScope :: Subst -> InScopeSet -> Subst
- getTCvSubst :: Subst -> TCvSubst
- extendTvSubst :: Subst -> TyVar -> Type -> Subst
- extendCvSubst :: Subst -> CoVar -> Coercion -> Subst
- delBndr :: Subst -> Var -> Subst
- delBndrs :: Subst -> [Var] -> Subst
- substBndr :: Subst -> Var -> (Subst, Var)
- substBndrs :: Subst -> [Var] -> (Subst, [Var])
- substRecBndrs :: Subst -> [Id] -> (Subst, [Id])
- substTyVarBndr :: Subst -> TyVar -> (Subst, TyVar)
- substCoVarBndr :: Subst -> TyVar -> (Subst, TyVar)
- cloneBndr :: Subst -> Unique -> Var -> (Subst, Var)
- cloneBndrs :: Subst -> UniqSupply -> [Var] -> (Subst, [Var])
- cloneIdBndr :: Subst -> UniqSupply -> Id -> (Subst, Id)
- cloneIdBndrs :: Subst -> UniqSupply -> [Id] -> (Subst, [Id])
- cloneRecIdBndrs :: Subst -> UniqSupply -> [Id] -> (Subst, [Id])
Main data types
data InScopeSet Source #
A set of variables that are in scope at some point "Secrets of the Glasgow Haskell Compiler inliner" Section 3.2 provides the motivation for this abstraction.
Instances
Substituting into expressions and related types
deShadowBinds :: CoreProgram -> CoreProgram Source #
De-shadowing the program is sometimes a useful pre-pass. It can be done simply by running over the bindings with an empty substitution, because substitution returns a result that has no-shadowing guaranteed.
(Actually, within a single type there might still be shadowing, because
substTy
is a no-op for the empty substitution, but that's probably OK.)
- Aug 09
- This function is not used in GHC at the moment, but seems so short and simple that I'm going to leave it here
substExprSC :: SDoc -> Subst -> CoreExpr -> CoreExpr Source #
Apply a substitution to an entire CoreExpr
. Remember, you may only
apply the substitution once:
See Note [Substitutions apply only once] in TyCoSubst
Do *not* attempt to short-cut in the case of an empty substitution! See Note [Extending the Subst]
substUnfolding :: Subst -> Unfolding -> Unfolding Source #
Substitutes for the Id
s within an unfolding
substUnfoldingSC :: Subst -> Unfolding -> Unfolding Source #
Substitutes for the Id
s within an unfolding
Operations on substitutions
emptySubst :: Subst Source #
mkEmptySubst :: InScopeSet -> Subst Source #
mkSubst :: InScopeSet -> TvSubstEnv -> CvSubstEnv -> IdSubstEnv -> Subst Source #
mkOpenSubst :: InScopeSet -> [(Var, CoreArg)] -> Subst Source #
Simultaneously substitute for a bunch of variables No left-right shadowing ie the substitution for (x y. e) a1 a2 so neither x nor y scope over a1 a2
substInScope :: Subst -> InScopeSet Source #
Find the in-scope set: see TyCoSubst Note [The substitution invariant]
isEmptySubst :: Subst -> Bool Source #
extendIdSubstList :: Subst -> [(Id, CoreExpr)] -> Subst Source #
Adds multiple Id
substitutions to the Subst
: see also extendIdSubst
extendTvSubstList :: Subst -> [(TyVar, Type)] -> Subst Source #
Adds multiple TyVar
substitutions to the Subst
: see also extendTvSubst
extendSubst :: Subst -> Var -> CoreArg -> Subst Source #
Add a substitution appropriate to the thing being substituted
(whether an expression, type, or coercion). See also
extendIdSubst
, extendTvSubst
, extendCvSubst
extendSubstList :: Subst -> [(Var, CoreArg)] -> Subst Source #
Add a substitution as appropriate to each of the terms being
substituted (whether expressions, types, or coercions). See also
extendSubst
.
zapSubstEnv :: Subst -> Subst Source #
addInScopeSet :: Subst -> VarSet -> Subst Source #
Add the Var
to the in-scope set, but do not remove
any existing substitutions for it
extendInScope :: Subst -> Var -> Subst Source #
Add the Var
to the in-scope set: as a side effect,
and remove any existing substitutions for it
extendInScopeList :: Subst -> [Var] -> Subst Source #
Add the Var
s to the in-scope set: see also extendInScope
extendInScopeIds :: Subst -> [Id] -> Subst Source #
Optimized version of extendInScopeList
that can be used if you are certain
all the things being added are Id
s and hence none are TyVar
s or CoVar
s
setInScope :: Subst -> InScopeSet -> Subst Source #
getTCvSubst :: Subst -> TCvSubst Source #
Substituting and cloning binders
substRecBndrs :: Subst -> [Id] -> (Subst, [Id]) Source #
Substitute in a mutually recursive group of Id
s
cloneBndrs :: Subst -> UniqSupply -> [Var] -> (Subst, [Var]) Source #
cloneIdBndr :: Subst -> UniqSupply -> Id -> (Subst, Id) Source #
cloneIdBndrs :: Subst -> UniqSupply -> [Id] -> (Subst, [Id]) Source #
Applies cloneIdBndr
to a number of Id
s, accumulating a final
substitution from left to right
cloneRecIdBndrs :: Subst -> UniqSupply -> [Id] -> (Subst, [Id]) Source #
Clone a mutually recursive group of Id
s