Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data Subst = Subst InScopeSet IdSubstEnv TvSubstEnv CvSubstEnv
- type TvSubstEnv = TyVarEnv Type
- type IdSubstEnv = IdEnv CoreExpr
- data InScopeSet
- deShadowBinds :: CoreProgram -> CoreProgram
- substRuleInfo :: Subst -> Id -> RuleInfo -> RuleInfo
- substRulesForImportedIds :: Subst -> [CoreRule] -> [CoreRule]
- substTyUnchecked :: Subst -> Type -> Type
- substCo :: HasDebugCallStack => Subst -> Coercion -> Coercion
- substExpr :: HasDebugCallStack => Subst -> CoreExpr -> CoreExpr
- substExprSC :: HasDebugCallStack => Subst -> CoreExpr -> CoreExpr
- substBind :: HasDebugCallStack => Subst -> CoreBind -> (Subst, CoreBind)
- substBindSC :: HasDebugCallStack => Subst -> CoreBind -> (Subst, CoreBind)
- substUnfolding :: Subst -> Unfolding -> Unfolding
- substUnfoldingSC :: Subst -> Unfolding -> Unfolding
- lookupIdSubst :: HasDebugCallStack => Subst -> Id -> CoreExpr
- lookupIdSubst_maybe :: HasDebugCallStack => Subst -> Id -> Maybe CoreExpr
- substIdType :: Subst -> Id -> Id
- substIdOcc :: Subst -> Id -> Id
- substTickish :: Subst -> CoreTickish -> CoreTickish
- substDVarSet :: HasDebugCallStack => 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
- isEmptySubst :: Subst -> Bool
- extendIdSubst :: Subst -> Id -> CoreExpr -> Subst
- extendIdSubstList :: Subst -> [(Id, CoreExpr)] -> Subst
- extendTCvSubst :: Subst -> TyCoVar -> Type -> Subst
- extendTvSubstList :: Subst -> [(TyVar, Type)] -> Subst
- extendIdSubstWithClone :: Subst -> Id -> Id -> Subst
- extendSubst :: Subst -> Var -> CoreArg -> Subst
- extendSubstList :: Subst -> [(Var, CoreArg)] -> Subst
- extendSubstWithVar :: Subst -> Var -> Var -> Subst
- extendSubstInScope :: Subst -> Var -> Subst
- extendSubstInScopeList :: Subst -> [Var] -> Subst
- extendSubstInScopeSet :: Subst -> VarSet -> Subst
- isInScope :: Var -> Subst -> Bool
- setInScope :: Subst -> InScopeSet -> Subst
- getSubstInScope :: Subst -> InScopeSet
- extendTvSubst :: Subst -> TyVar -> Type -> Subst
- extendCvSubst :: Subst -> CoVar -> Coercion -> Subst
- delBndr :: Subst -> Var -> Subst
- delBndrs :: Subst -> [Var] -> Subst
- zapSubst :: Subst -> Subst
- substBndr :: Subst -> Var -> (Subst, Var)
- substBndrs :: Traversable f => Subst -> f Var -> (Subst, f Var)
- substRecBndrs :: Traversable f => Subst -> f Id -> (Subst, f Id)
- substTyVarBndr :: HasDebugCallStack => Subst -> TyVar -> (Subst, TyVar)
- substCoVarBndr :: HasDebugCallStack => Subst -> CoVar -> (Subst, CoVar)
- 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
Type & coercion & id substitution
The Subst data type defined in this module contains substitution for tyvar, covar and id. However, operations on IdSubstEnv (mapping from Id to CoreExpr) that require the definition of the Expr data type are defined in GHC.Core.Subst to avoid circular module dependency.
Instances
data InScopeSet Source #
A set of variables that are in scope at some point.
Note that this is a superset of the variables that are currently in scope. See Note [The InScopeSet invariant].
"Secrets of the Glasgow Haskell Compiler inliner" Section 3.2 provides the motivation for this abstraction.
Instances
Outputable InScopeSet Source # | |
Defined in GHC.Types.Var.Env ppr :: InScopeSet -> SDoc Source # |
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
substTyUnchecked :: Subst -> Type -> Type Source #
Substitute within a Type
disabling the sanity checks.
The problems that the sanity checks in substTy catch are described in
Note [The substitution invariant].
The goal of #11371 is to migrate all the calls of substTyUnchecked to
substTy and remove this function. Please don't use in new code.
substCo :: HasDebugCallStack => Subst -> Coercion -> Coercion Source #
Substitute within a Coercion
The substitution has to satisfy the invariants described in
Note [The substitution invariant].
substExpr :: HasDebugCallStack => Subst -> CoreExpr -> CoreExpr Source #
substExpr applies a substitution to an entire CoreExpr
. Remember,
you may only apply the substitution once:
See Note [Substitutions apply only once] in GHC.Core.TyCo.Subst
Do *not* attempt to short-cut in the case of an empty substitution! See Note [Extending the IdSubstEnv]
substExprSC :: HasDebugCallStack => Subst -> CoreExpr -> CoreExpr Source #
substBindSC :: HasDebugCallStack => Subst -> CoreBind -> (Subst, CoreBind) Source #
substUnfolding :: Subst -> Unfolding -> Unfolding Source #
Substitutes for the Id
s within an unfolding
NB: substUnfolding discards any unfolding without
without a Stable source. This is usually what we want,
but it may be a bit unexpected
substUnfoldingSC :: Subst -> Unfolding -> Unfolding Source #
Substitutes for the Id
s within an unfolding
NB: substUnfolding discards any unfolding without
without a Stable source. This is usually what we want,
but it may be a bit unexpected
lookupIdSubst :: HasDebugCallStack => Subst -> Id -> CoreExpr Source #
lookupIdSubst_maybe :: HasDebugCallStack => Subst -> Id -> Maybe CoreExpr Source #
substTickish :: Subst -> CoreTickish -> CoreTickish Source #
substDVarSet :: HasDebugCallStack => Subst -> DVarSet -> DVarSet Source #
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
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
.
extendSubstInScopeList :: Subst -> [Var] -> Subst Source #
Add the Var
s to the in-scope set: see also extendInScope
extendSubstInScopeSet :: Subst -> VarSet -> Subst Source #
Add the Var
s to the in-scope set: see also extendInScope
setInScope :: Subst -> InScopeSet -> Subst Source #
getSubstInScope :: Subst -> InScopeSet Source #
Find the in-scope set: see Note [The substitution invariant]
zapSubst :: Subst -> Subst Source #
Remove all substitutions that might have been built up while preserving the in-scope set originally called zapSubstEnv
Substituting and cloning binders
substBndrs :: Traversable f => Subst -> f Var -> (Subst, f Var) Source #
substRecBndrs :: Traversable f => Subst -> f Id -> (Subst, f Id) Source #
Substitute in a mutually recursive group of Id
s
substTyVarBndr :: HasDebugCallStack => Subst -> TyVar -> (Subst, TyVar) Source #
substCoVarBndr :: HasDebugCallStack => Subst -> CoVar -> (Subst, CoVar) Source #
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
Discards non-Stable unfoldings
cloneRecIdBndrs :: Subst -> UniqSupply -> [Id] -> (Subst, [Id]) Source #
Clone a mutually recursive group of Id
s