ghc-7.8.20140130: The GHC API

Safe HaskellNone
LanguageHaskell98

Id

Contents

Description

GHC uses several kinds of name internally:

  • OccName: see "OccName#name_types"
  • RdrName: see "RdrName#name_types"
  • Name: see "Name#name_types"
  • Id represents names that not only have a Name but also a Type and some additional details (a IdInfo and one of LocalIdDetails or GlobalIdDetails) that are added, modified and inspected by various compiler passes. These Var names may either be global or local, see "Var#globalvslocal"
  • Var: see "Var#name_types"

Synopsis

The main types

data VarSource

Essentially a typed Name, that may also contain some additional information about the Var and it's use sites.

type Id = VarSource

Simple construction

mkGlobalId :: IdDetails -> Name -> Type -> IdInfo -> IdSource

For an explanation of global vs. local Ids, see "Var#globalvslocal"

mkVanillaGlobal :: Name -> Type -> IdSource

Make a global Id without any extra information at all

mkVanillaGlobalWithInfo :: Name -> Type -> IdInfo -> IdSource

Make a global Id with no global information but some generic IdInfo

mkLocalId :: Name -> Type -> IdSource

For an explanation of global vs. local Ids, see "Var#globalvslocal"

mkExportedLocalId :: Name -> Type -> IdSource

Create a local Id that is marked as exported. This prevents things attached to it from being removed as dead code.

mkSysLocal :: FastString -> Unique -> Type -> IdSource

Create a system local Id. These are local Ids (see "Var#globalvslocal") that are created by the compiler out of thin air

mkUserLocal :: OccName -> Unique -> Type -> SrcSpan -> IdSource

Create a user local Id. These are local Ids (see "Var#globalvslocal") with a name and location that the user might recognize

mkTemplateLocals :: [Type] -> [Id]Source

Create a template local for a series of types

mkTemplateLocalsNum :: Int -> [Type] -> [Id]Source

Create a template local for a series of type, but start from a specified template local

mkTemplateLocal :: Int -> Type -> IdSource

Create a template local: a family of system local Ids in bijection with Ints, typically used in unfoldings

mkWorkerId :: Unique -> Id -> Type -> IdSource

Workers get local names. CoreTidy will externalise these if necessary

Taking an Id apart

recordSelectorFieldLabel :: Id -> (TyCon, FieldLabel)Source

If the Id is that for a record selector, extract the sel_tycon and label. Panic otherwise

Modifying an Id

setIdType :: Id -> Type -> IdSource

Not only does this set the Id Type, it also evaluates the type to try and reduce space usage

globaliseId :: Id -> IdSource

If it's a local, make it global

Predicates on Ids

isImplicitId :: Id -> BoolSource

isImplicitId tells whether an Ids info is implied by other declarations, so we don't need to put its signature in an interface file, even if it's mentioned in some other interface unfolding.

isStrictId :: Id -> BoolSource

This predicate says whether the Id has a strict demand placed on it or has a type such that it can always be evaluated strictly (i.e an unlifted type, as of GHC 7.6). We need to check separately whether the Id has a so-called "strict type" because if the demand for the given id hasn't been computed yet but id has a strict type, we still want isStrictId id to be True.

isExportedId :: Var -> BoolSource

isExportedIdVar means "don't throw this away"

idDataCon :: Id -> DataConSource

Get from either the worker or the wrapper Id to the DataCon. Currently used only in the desugarer.

INVARIANT: idDataCon (dataConWrapId d) = d: remember, dataConWrapId can return either the wrapper or the worker

isBottomingId :: Id -> BoolSource

Returns true if an application to n args would diverge

hasNoBinding :: Id -> BoolSource

Returns True of an Id which may not have a binding, even though it is defined in this module.

Evidence variables

Inline pragma stuff

One-shot lambdas

isOneShotBndr :: Var -> BoolSource

Returns whether the lambda associated with the Id is certainly applied at most once This one is the "business end", called externally. It works on type variables as well as Ids, returning True Its main purpose is to encapsulate the Horrible State Hack

isOneShotLambda :: Id -> BoolSource

Returns whether the lambda associated with the Id is certainly applied at most once. You probably want to use isOneShotBndr instead

stateHackOneShot :: OneShotInfoSource

Should we apply the state hack to values of this Type?

Reading IdInfo fields

Writing IdInfo fields