ghc-6.10.4: The GHC APIContentsIndex
Var
Contents
The main data type
Constructing Vars
Taking Vars apart
Modifying Vars
Predicates
Type variable data type
Constructing TyVars
Taking TyVars apart
Modifying TyVars
Coercion variable data type
Constructing CoVars
Taking CoVars apart
Modifying CoVars
Var type synonyms
Description

GHC uses several kinds of name internally:

  • OccName.OccName: see OccName
  • RdrName.RdrName: see RdrName
  • Name: see Name
  • Id.Id: see Id
  • Var is a synonym for the Id.Id type but it may additionally potentially contain type variables, which have a Kind rather than a Type and only contain some extra details during typechecking. These Var names may either be global or local, see Var

Global Ids and Vars are those that are imported or correspond to a data constructor, primitive operation, or record selectors. Local Ids and Vars are those bound within an expression (e.g. by a lambda) or at the top level of the module being compiled.

Synopsis
data Var
mkLocalIdVar :: Name -> Type -> IdInfo -> Var
mkExportedLocalIdVar :: Name -> Type -> IdInfo -> Var
mkGlobalIdVar :: GlobalIdDetails -> Name -> Type -> IdInfo -> Var
varName :: Var -> Name
varUnique :: Var -> Unique
varType :: Var -> Kind
varIdInfo :: Var -> IdInfo
globalIdVarDetails :: Var -> GlobalIdDetails
setVarName :: Var -> Name -> Var
setVarUnique :: Var -> Unique -> Var
setVarType :: Id -> Type -> Id
setIdVarExported :: Var -> Var
setIdVarNotExported :: Id -> Id
globaliseIdVar :: GlobalIdDetails -> Var -> Var
lazySetVarIdInfo :: Var -> IdInfo -> Var
isCoVar :: Var -> Bool
isIdVar :: Var -> Bool
isTyVar :: Var -> Bool
isTcTyVar :: Var -> Bool
isLocalVar :: Var -> Bool
isLocalIdVar :: Var -> Bool
isGlobalIdVar :: Var -> Bool
isExportedIdVar :: Var -> Bool
mustHaveLocalBinding :: Var -> Bool
type TyVar = Var
mkTyVar :: Name -> Kind -> TyVar
mkTcTyVar :: Name -> Kind -> TcTyVarDetails -> TyVar
mkWildCoVar :: Kind -> TyVar
tyVarName :: TyVar -> Name
tyVarKind :: TyVar -> Kind
tcTyVarDetails :: Var -> TcTyVarDetails
setTyVarName :: TyVar -> Name -> TyVar
setTyVarUnique :: TyVar -> Unique -> TyVar
setTyVarKind :: TyVar -> Kind -> TyVar
type CoVar = TyVar
mkCoVar :: Name -> Kind -> CoVar
coVarName :: CoVar -> Name
setCoVarUnique :: CoVar -> Unique -> CoVar
setCoVarName :: CoVar -> Name -> CoVar
type Id = Var
type DictId = Var
The main data type
data Var
Essentially a typed Name, that may also contain some additional information about the Var and it's use sites.
show/hide Instances
Constructing Vars
mkLocalIdVar :: Name -> Type -> IdInfo -> Var
For an explanation of global vs. local Vars, see Var
mkExportedLocalIdVar :: Name -> Type -> IdInfo -> Var
Exported Vars will not be removed as dead code
mkGlobalIdVar :: GlobalIdDetails -> Name -> Type -> IdInfo -> Var
For an explanation of global vs. local Vars, see Var
Taking Vars apart
varName :: Var -> Name
varUnique :: Var -> Unique
varType :: Var -> Kind
varIdInfo :: Var -> IdInfo
Extract Id information from the Var if it represents a global or local Id, otherwise panic
globalIdVarDetails :: Var -> GlobalIdDetails
Find the global Id information if the Var is a global Id, otherwise returns notGlobalId
Modifying Vars
setVarName :: Var -> Name -> Var
setVarUnique :: Var -> Unique -> Var
setVarType :: Id -> Type -> Id
setIdVarExported :: Var -> Var
Exports the given local Id. Can also be called on global Ids, such as data constructors and class operations, which are born as global Ids and automatically exported
setIdVarNotExported :: Id -> Id
We can only do this to LocalIds
globaliseIdVar :: GlobalIdDetails -> Var -> Var
If it's a local, make it global
lazySetVarIdInfo :: Var -> IdInfo -> Var
Predicates
isCoVar :: Var -> Bool
isIdVar :: Var -> Bool
isTyVar :: Var -> Bool
isTcTyVar :: Var -> Bool
isLocalVar :: Var -> Bool
isLocalVar returns True for type variables as well as local Ids These are the variables that we need to pay attention to when finding free variables, or doing dependency analysis.
isLocalIdVar :: Var -> Bool
isGlobalIdVar :: Var -> Bool
isExportedIdVar :: Var -> Bool
isExportedIdVar means "don't throw this away"
mustHaveLocalBinding :: Var -> Bool
mustHaveLocalBinding returns True of Ids and TyVars that must have a binding in this module. The converse is not quite right: there are some global Ids that must have bindings, such as record selectors. But that doesn't matter, because it's only used for assertions
Type variable data type
type TyVar = Var
Constructing TyVars
mkTyVar :: Name -> Kind -> TyVar
mkTcTyVar :: Name -> Kind -> TcTyVarDetails -> TyVar
mkWildCoVar :: Kind -> TyVar
Create a type variable that is never referred to, so its unique doesn't matter
Taking TyVars apart
tyVarName :: TyVar -> Name
tyVarKind :: TyVar -> Kind
tcTyVarDetails :: Var -> TcTyVarDetails
Modifying TyVars
setTyVarName :: TyVar -> Name -> TyVar
setTyVarUnique :: TyVar -> Unique -> TyVar
setTyVarKind :: TyVar -> Kind -> TyVar
Coercion variable data type
type CoVar = TyVar
Constructing CoVars
mkCoVar :: Name -> Kind -> CoVar
Taking CoVars apart
coVarName :: CoVar -> Name
Modifying CoVars
setCoVarUnique :: CoVar -> Unique -> CoVar
setCoVarName :: CoVar -> Name -> CoVar
Var type synonyms
type Id = Var
type DictId = Var
Produced by Haddock version 2.4.2