ghc-7.4.2: The GHC API

Safe HaskellNone

VarEnv

Contents

Synopsis

Var, Id and TyVar environments (maps)

type VarEnv elt = UniqFM eltSource

type IdEnv elt = VarEnv eltSource

type TyVarEnv elt = VarEnv eltSource

type CoVarEnv elt = VarEnv eltSource

Manipulating these environments

mkVarEnv :: [(Var, a)] -> VarEnv aSource

extendVarEnv_C :: (a -> a -> a) -> VarEnv a -> Var -> a -> VarEnv aSource

extendVarEnv_Acc :: (a -> b -> b) -> (a -> b) -> VarEnv b -> Var -> a -> VarEnv bSource

plusVarEnv_C :: (a -> a -> a) -> VarEnv a -> VarEnv a -> VarEnv aSource

alterVarEnv :: (Maybe a -> Maybe a) -> VarEnv a -> Var -> VarEnv aSource

mapVarEnv :: (a -> b) -> VarEnv a -> VarEnv bSource

zipVarEnv :: [Var] -> [a] -> VarEnv aSource

modifyVarEnv :: (a -> a) -> VarEnv a -> Var -> VarEnv aSource

foldVarEnv :: (a -> b -> b) -> b -> VarEnv a -> bSource

The InScopeSet type

data InScopeSet Source

A set of variables that are in scope at some point

Operations on InScopeSets

lookupInScope :: InScopeSet -> Var -> Maybe VarSource

Look up a variable the InScopeSet. This lets you map from the variable's identity (unique) to its full value.

uniqAway :: InScopeSet -> Var -> VarSource

uniqAway in_scope v finds a unique that is not used in the in-scope set, and gives that to v.

The RnEnv2 type

data RnEnv2 Source

When we are comparing (or matching) types or terms, we are faced with "going under" corresponding binders. E.g. when comparing:

 \x. e1	~   \y. e2

Basically we want to rename [x -> y] or [y -> x], but there are lots of things we must be careful of. In particular, x might be free in e2, or y in e1. So the idea is that we come up with a fresh binder that is free in neither, and rename x and y respectively. That means we must maintain:

  1. A renaming for the left-hand expression
  2. A renaming for the right-hand expressions
  3. An in-scope set

Furthermore, when matching, we want to be able to have an 'occurs check', to prevent:

 \x. f   ~   \y. y

matching with [f -> y]. So for each expression we want to know that set of locally-bound variables. That is precisely the domain of the mappings 1. and 2., but we must ensure that we always extend the mappings as we go in.

All of this information is bundled up in the RnEnv2

Operations on RnEnv2s

rnBndr2 :: RnEnv2 -> Var -> Var -> RnEnv2Source

rnBndr2 env bL bR goes under a binder bL in the Left term, and binder bR in the Right term. It finds a new binder, new_b, and returns an environment mapping bL -> new_b and bR -> new_b

rnBndrs2 :: RnEnv2 -> [Var] -> [Var] -> RnEnv2Source

Applies rnBndr2 to several variables: the two variable lists must be of equal length

rnOccL :: RnEnv2 -> Var -> VarSource

Look up the renaming of an occurrence in the left or right term

rnOccR :: RnEnv2 -> Var -> VarSource

Look up the renaming of an occurrence in the left or right term

inRnEnvL :: RnEnv2 -> Var -> BoolSource

Tells whether a variable is locally bound

inRnEnvR :: RnEnv2 -> Var -> BoolSource

Tells whether a variable is locally bound

rnOccL_maybe :: RnEnv2 -> Var -> Maybe VarSource

Look up the renaming of an occurrence in the left or right term

rnOccR_maybe :: RnEnv2 -> Var -> Maybe VarSource

Look up the renaming of an occurrence in the left or right term

rnBndrL :: RnEnv2 -> Var -> (RnEnv2, Var)Source

Similar to rnBndr2 but used when there's a binder on the left side only.

rnBndrR :: RnEnv2 -> Var -> (RnEnv2, Var)Source

Similar to rnBndr2 but used when there's a binder on the right side only.

nukeRnEnvL :: RnEnv2 -> RnEnv2Source

Wipe the left or right side renaming

nukeRnEnvR :: RnEnv2 -> RnEnv2Source

Wipe the left or right side renaming

rnEtaL :: RnEnv2 -> Var -> (RnEnv2, Var)Source

Similar to rnBndrL but used for eta expansion See Note [Eta expansion]

rnEtaR :: RnEnv2 -> Var -> (RnEnv2, Var)Source

Similar to rnBndr2 but used for eta expansion See Note [Eta expansion]

TidyEnv and its operation

type TidyEnv = (TidyOccEnv, VarEnv Var)Source

When tidying up print names, we keep a mapping of in-scope occ-names (the TidyOccEnv) and a Var-to-Var of the current renamings