ghc-6.12.2: The GHC APISource codeContentsIndex
CoreSubst
Contents
Main data types
Substituting into expressions and related types
Operations on substitutions
Substituting and cloning binders
Synopsis
data Subst
type TvSubstEnv = TyVarEnv Type
type IdSubstEnv = IdEnv CoreExpr
data InScopeSet
deShadowBinds :: [CoreBind] -> [CoreBind]
substTy :: Subst -> Type -> Type
substExpr :: Subst -> CoreExpr -> CoreExpr
substBind :: Subst -> CoreBind -> (Subst, CoreBind)
substSpec :: Subst -> Id -> SpecInfo -> SpecInfo
substWorker :: Subst -> WorkerInfo -> WorkerInfo
lookupIdSubst :: Subst -> Id -> CoreExpr
lookupTvSubst :: Subst -> TyVar -> Type
emptySubst :: Subst
mkEmptySubst :: InScopeSet -> Subst
mkSubst :: InScopeSet -> TvSubstEnv -> IdSubstEnv -> Subst
substInScope :: Subst -> InScopeSet
isEmptySubst :: Subst -> Bool
extendIdSubst :: Subst -> Id -> CoreExpr -> Subst
extendIdSubstList :: Subst -> [(Id, CoreExpr)] -> Subst
extendTvSubst :: Subst -> TyVar -> Type -> Subst
extendTvSubstList :: Subst -> [(TyVar, Type)] -> Subst
extendSubst :: Subst -> Var -> CoreArg -> Subst
extendSubstList :: Subst -> [(Var, CoreArg)] -> Subst
zapSubstEnv :: Subst -> Subst
extendInScope :: Subst -> Var -> Subst
extendInScopeList :: Subst -> [Var] -> Subst
extendInScopeIds :: Subst -> [Id] -> Subst
isInScope :: Var -> Subst -> Bool
substBndr :: Subst -> Var -> (Subst, Var)
substBndrs :: Subst -> [Var] -> (Subst, [Var])
substRecBndrs :: Subst -> [Id] -> (Subst, [Id])
cloneIdBndr :: Subst -> UniqSupply -> Id -> (Subst, Id)
cloneIdBndrs :: Subst -> UniqSupply -> [Id] -> (Subst, [Id])
cloneRecIdBndrs :: Subst -> UniqSupply -> [Id] -> (Subst, [Id])
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
show/hide Instances
type TvSubstEnv = TyVarEnv TypeSource
A substitition of Types for TyVars
type IdSubstEnv = IdEnv CoreExprSource
An environment for substituting for Ids
data InScopeSet Source
A set of variables that are in scope at some point
show/hide Instances
Substituting into expressions and related types
deShadowBinds :: [CoreBind] -> [CoreBind]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, becuase 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.)

substTy :: Subst -> Type -> TypeSource
See substTy
substExpr :: Subst -> CoreExpr -> CoreExprSource

Apply a substititon to an entire CoreExpr. Rememeber, 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 substititon to an entire CoreBind, additionally returning an updated Subst that should be used by subsequent substitutons.
substSpec :: Subst -> Id -> SpecInfo -> SpecInfoSource
Substitutes for the Ids within the WorkerInfo given the new function Id
substWorker :: Subst -> WorkerInfo -> WorkerInfoSource
Substitutes for the Ids within the WorkerInfo
lookupIdSubst :: Subst -> Id -> CoreExprSource
Find the substitution for an Id in the Subst
lookupTvSubst :: Subst -> TyVar -> TypeSource
Find the substitution for a TyVar in the Subst
Operations on substitutions
emptySubst :: SubstSource
mkEmptySubst :: InScopeSet -> SubstSource
mkSubst :: InScopeSet -> TvSubstEnv -> IdSubstEnv -> SubstSource
substInScope :: Subst -> InScopeSetSource
Find the in-scope set: see CoreSubst
isEmptySubst :: Subst -> BoolSource
extendIdSubst :: Subst -> Id -> CoreExpr -> SubstSource
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)] -> SubstSource
Adds multiple Id substitutions to the Subst: see also extendIdSubst
extendTvSubst :: Subst -> TyVar -> Type -> SubstSource
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)] -> SubstSource
Adds multiple TyVar substitutions to the Subst: see also extendTvSubst
extendSubst :: Subst -> Var -> CoreArg -> SubstSource
Add a substitution for a TyVar or Id as appropriate to the Var being added. See also extendIdSubst and extendTvSubst
extendSubstList :: Subst -> [(Var, CoreArg)] -> SubstSource
Add a substitution for a TyVar or Id as appropriate to all the Vars being added. See also extendSubst
zapSubstEnv :: Subst -> SubstSource
Remove all substitutions for Ids and Vars that might have been built up while preserving the in-scope set
extendInScope :: Subst -> Var -> SubstSource
Add the Var to the in-scope set: as a side effect, removes any existing substitutions for it
extendInScopeList :: Subst -> [Var] -> SubstSource
Add the Vars to the in-scope set: see also extendInScope
extendInScopeIds :: Subst -> [Id] -> SubstSource
Optimized version of extendInScopeList that can be used if you are certain all the things being added are Ids and hence none are TyVars
isInScope :: Var -> Subst -> BoolSource
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 substitutons. 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 and removes all IdInfo
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
Produced by Haddock version 2.6.1