ghc-7.10.2: The GHC API

Safe HaskellNone
LanguageHaskell2010

CoreSubst

Contents

Synopsis

Main data types

data Subst Source

A substitution environment, containing both Id and TyVar substitutions.

Some invariants apply to how you use the substitution:

  1. The in-scope set contains at least those Ids and TyVars that will be in scope after applying the substitution to a term. Precisely, the in-scope set must be a superset of the free vars of the substitution range that might possibly clash with locally-bound variables in the thing being substituted in.
  2. You may apply the substitution only once

There are various ways of setting up the in-scope set such that the first of these invariants hold:

  • Arrange that the in-scope set really is all the things in scope
  • Arrange that it's the free vars of the range of the substitution
  • Make it empty, if you know that all the free vars of the substitution are fresh, and hence can't possibly clash

Instances

type TvSubstEnv = TyVarEnv Type Source

A substitution of Types for TyVars and Kinds for KindVars

data IdSubstEnv Source

An environment for substituting for Ids See Note [IdSubstEnv]

data InScopeSet Source

A set of variables that are in scope at some point

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

substSpec :: Subst -> Id -> SpecInfo -> SpecInfo Source

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

substExprSC :: SDoc -> Subst -> CoreExpr -> CoreExpr Source

Apply a substitution to an entire CoreExpr. Remember, you may only apply the substitution once: see CoreSubst

Do *not* attempt to short-cut in the case of an empty substitution! See Note [Extending the Subst]

substBind :: 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 :: 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

substUnfoldingSC :: Subst -> Unfolding -> Unfolding Source

Substitutes for the Ids within an unfolding

lookupIdSubst :: SDoc -> Subst -> Id -> CoreExpr Source

Find the substitution for an Id in the Subst

lookupTvSubst :: Subst -> TyVar -> Type Source

Find the substitution for a TyVar in the Subst

lookupCvSubst :: Subst -> CoVar -> Coercion Source

Find the coercion substitution for a CoVar in the Subst

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

substInScope :: Subst -> InScopeSet Source

Find the in-scope set: see CoreSubst

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 the CoreSubst is true after extending the substitution like this

extendIdSubstList :: Subst -> [(Id, CoreExpr)] -> Subst Source

Adds multiple Id substitutions to the Subst: see also extendIdSubst

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

Add a substitution for a TyVar to the Subst: you must ensure that the in-scope set is such that the CoreSubst is true after extending the substitution like this

extendTvSubstList :: Subst -> [(TyVar, Type)] -> Subst Source

Adds multiple TyVar substitutions to the Subst: see also extendTvSubst

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 is such that the CoreSubst is true after extending the substitution like this

extendCvSubstList :: Subst -> [(CoVar, Coercion)] -> Subst Source

Adds multiple CoVar -> Coercion substitutions to the Subst: see also extendCvSubst

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, and 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

Remove all substitutions for Ids and Vars that might have been built up while preserving the in-scope set

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 Vars 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 Ids and hence none are TyVars or CoVars

Substituting and cloning binders

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

Substitutes a Var 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 :: Subst -> [Var] -> (Subst, [Var]) Source

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

substRecBndrs :: Subst -> [Id] -> (Subst, [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.

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

Applies cloneIdBndr to a number of Ids, accumulating a final substitution from left to right

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

Clone a mutually recursive group of Ids

Simple expression optimiser

simpleOptExprWith :: Subst -> InExpr -> OutExpr Source

exprIsConApp_maybe :: InScopeEnv -> CoreExpr -> Maybe (DataCon, [Type], [CoreExpr]) Source

Returns Just (dc, [t1..tk], [x1..xn]) if the argument expression is a *saturated* constructor application of the form dc t1..tk x1 .. xn, where t1..tk are the *universally-qantified* type args of dc