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 theId.Id
type but it may additionally potentially contain type variables, which have aKind
rather than aType
and only contain some extra details during typechecking. TheseVar
names may either be global or local, see Var
Global Id
s and Var
s are those that are imported or correspond to a data constructor, primitive operation, or record selectors.
Local Id
s and Var
s are those bound within an expression (e.g. by a lambda) or at the top level of the module being compiled.
- data Var
- type TyVar = Var
- type CoVar = TyVar
- type Id = Var
- type DictId = EvId
- type DFunId = Id
- type EvVar = Var
- type EvId = Id
- type IpId = EvId
- varName :: Var -> Name
- varUnique :: Var -> Unique
- varType :: Var -> Kind
- setVarName :: Var -> Name -> Var
- setVarUnique :: Var -> Unique -> Var
- setVarType :: Id -> Type -> Id
- mkGlobalVar :: IdDetails -> Name -> Type -> IdInfo -> Id
- mkLocalVar :: IdDetails -> Name -> Type -> IdInfo -> Id
- mkExportedLocalVar :: IdDetails -> Name -> Type -> IdInfo -> Id
- idInfo :: Id -> IdInfo
- idDetails :: Id -> IdDetails
- lazySetIdInfo :: Id -> IdInfo -> Var
- setIdDetails :: Id -> IdDetails -> Id
- globaliseId :: Id -> Id
- setIdExported :: Id -> Id
- setIdNotExported :: Id -> Id
- isCoVar :: Var -> Bool
- isId :: Var -> Bool
- isTyCoVar :: Var -> Bool
- isTyVar :: Var -> Bool
- isTcTyVar :: Var -> Bool
- isLocalVar :: Var -> Bool
- isLocalId :: Var -> Bool
- isGlobalId :: Var -> Bool
- isExportedId :: Var -> Bool
- mustHaveLocalBinding :: Var -> Bool
- mkTyVar :: Name -> Kind -> TyVar
- mkTcTyVar :: Name -> Kind -> TcTyVarDetails -> TyVar
- mkWildCoVar :: Kind -> TyVar
- tyVarName :: TyVar -> Name
- tyVarKind :: TyVar -> Kind
- tcTyVarDetails :: TyVar -> TcTyVarDetails
- setTcTyVarDetails :: TyVar -> TcTyVarDetails -> TyVar
- setTyVarName :: TyVar -> Name -> TyVar
- setTyVarUnique :: TyVar -> Unique -> TyVar
- setTyVarKind :: TyVar -> Kind -> TyVar
- mkCoVar :: Name -> Kind -> CoVar
- coVarName :: CoVar -> Name
- setCoVarUnique :: CoVar -> Unique -> CoVar
- setCoVarName :: CoVar -> Name -> CoVar
The main data type and synonyms
Taking Var
s apart
Modifying Var
s
setVarName :: Var -> Name -> VarSource
setVarUnique :: Var -> Unique -> VarSource
setVarType :: Id -> Type -> IdSource
Constructing, taking apart, modifying Id
s
mkExportedLocalVar :: IdDetails -> Name -> Type -> IdInfo -> IdSource
Exported Var
s will not be removed as dead code
lazySetIdInfo :: Id -> IdInfo -> VarSource
setIdDetails :: Id -> IdDetails -> IdSource
globaliseId :: Id -> IdSource
If it's a local, make it global
setIdExported :: Id -> IdSource
setIdNotExported :: Id -> IdSource
We can only do this to LocalIds
Predicates
isLocalVar :: Var -> BoolSource
isLocalVar
returns True
for type variables as well as local Id
s
These are the variables that we need to pay attention to when finding free
variables, or doing dependency analysis.
isGlobalId :: Var -> BoolSource
isExportedId :: Var -> BoolSource
isExportedIdVar
means "don't throw this away"
mustHaveLocalBinding :: Var -> BoolSource
mustHaveLocalBinding
returns True
of Id
s and TyVar
s
that must have a binding in this module. The converse
is not quite right: there are some global Id
s that must have
bindings, such as record selectors. But that doesn't matter,
because it's only used for assertions
Constructing TyVar
s
mkWildCoVar :: Kind -> TyVarSource
Create a type variable that is never referred to, so its unique doesn't matter
Taking TyVar
s apart
setTcTyVarDetails :: TyVar -> TcTyVarDetails -> TyVarSource
Modifying TyVar
s
setTyVarName :: TyVar -> Name -> TyVarSource
setTyVarUnique :: TyVar -> Unique -> TyVarSource
setTyVarKind :: TyVar -> Kind -> TyVarSource
Constructing CoVar
s
Taking CoVar
s apart
Modifying CoVar
s
setCoVarUnique :: CoVar -> Unique -> CoVarSource
setCoVarName :: CoVar -> Name -> CoVarSource