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

GHC.Core.Subst

Synopsis

Main data types

data Subst Source #

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

Instances details
Outputable Subst Source # 
Instance details

Defined in GHC.Core.TyCo.Subst

Methods

ppr :: Subst -> SDoc Source #

type TvSubstEnv = TyVarEnv Type Source #

A substitution of Types for TyVars and Kinds for KindVars

type IdSubstEnv = IdEnv CoreExpr Source #

A substitution of Exprs for non-coercion Ids

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

Instances details
Outputable InScopeSet Source # 
Instance details

Defined in GHC.Types.Var.Env

Methods

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

substRuleInfo :: Subst -> Id -> RuleInfo -> RuleInfo Source #

Substitutes for the Ids within the RuleInfo given the new function Id

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]

substBind :: HasDebugCallStack => Subst -> CoreBind -> (Subst, CoreBind) Source #

Apply a substitution to an entire CoreBind, additionally returning an updated Subst that should be used by subsequent substitutions.

substBindSC :: HasDebugCallStack => Subst -> CoreBind -> (Subst, CoreBind) Source #

Apply a substitution to an entire CoreBind, additionally returning an updated Subst that should be used by subsequent substitutions.

substUnfolding :: Subst -> Unfolding -> Unfolding Source #

Substitutes for the Ids 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 Ids 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 #

Find the substitution for an Id in the Subst The Id should not be a CoVar

substIdInfo :: Subst -> Id -> IdInfo -> Maybe IdInfo Source #

Substitute into some IdInfo with regard to the supplied new Id. Discards unfoldings, unless they are Stable

Operations on substitutions

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

extendIdSubst :: Subst -> Id -> CoreExpr -> Subst Source #

Add a substitution for an Id to the Subst: you must ensure that the in-scope set is such that TyCoSubst Note [The substitution invariant] holds after extending the substitution like this

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.

extendSubstInScope :: Subst -> Var -> Subst Source #

Add the Var to the in-scope set

extendSubstInScopeList :: Subst -> [Var] -> Subst Source #

Add the Vars to the in-scope set: see also extendInScope

extendSubstInScopeSet :: Subst -> VarSet -> Subst Source #

Add the Vars to the in-scope set: see also extendInScope

getSubstInScope :: Subst -> InScopeSet Source #

Find the in-scope set: see Note [The substitution invariant]

extendTvSubst :: Subst -> TyVar -> Type -> Subst Source #

Add a substitution for a TyVar to the Subst The TyVar *must* be a real TyVar, and not a CoVar You must ensure that the in-scope set is such that Note [The substitution invariant] holds after extending the substitution like this.

extendCvSubst :: Subst -> CoVar -> Coercion -> Subst Source #

Add a substitution from a CoVar to a Coercion to the Subst: you must ensure that the in-scope set satisfies Note [The substitution invariant] after extending the substitution like this

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

substBndr :: Subst -> Var -> (Subst, Var) Source #

Substitutes a Expr for another one according to the Subst given, returning the result and an updated Subst that should be used by subsequent substitutions. IdInfo is preserved by this process, although it is substituted into appropriately.

substBndrs :: Traversable f => Subst -> f Var -> (Subst, f Var) Source #

Applies substBndr to a number of Exprs, accumulating a new Subst left-to-right

substRecBndrs :: Traversable f => Subst -> f Id -> (Subst, f Id) Source #

Substitute in a mutually recursive group of Ids

cloneIdBndr :: Subst -> UniqSupply -> Id -> (Subst, Id) Source #

Very similar to substBndr, but it always allocates a new Unique for each variable in its output. It substitutes the IdInfo though. Discards non-Stable unfoldings

cloneIdBndrs :: Subst -> UniqSupply -> [Id] -> (Subst, [Id]) Source #

Applies cloneIdBndr to a number of Ids, 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 Ids