GHC uses several kinds of name internally:
-
OccName.OccName
: see OccName -
RdrName.RdrName
: see RdrName -
Name
: see Name -
Id.Id
represents names that not only have aName
but also aTypeRep.Type
and some additional details (aIdInfo
and one ofVar.LocalIdDetails
orIdInfo.GlobalIdDetails
) that are added, modified and inspected by various compiler passes. TheseVar
names may either be global or local, see Var -
Var
: see Var
- type Id = Var
- type DictId = EvId
- mkGlobalId :: IdDetails -> Name -> Type -> IdInfo -> Id
- mkVanillaGlobal :: Name -> Type -> Id
- mkVanillaGlobalWithInfo :: Name -> Type -> IdInfo -> Id
- mkLocalId :: Name -> Type -> Id
- mkLocalIdWithInfo :: Name -> Type -> IdInfo -> Id
- mkExportedLocalId :: Name -> Type -> Id
- mkSysLocal :: FastString -> Unique -> Type -> Id
- mkSysLocalM :: MonadUnique m => FastString -> Type -> m Id
- mkUserLocal :: OccName -> Unique -> Type -> SrcSpan -> Id
- mkUserLocalM :: MonadUnique m => OccName -> Type -> SrcSpan -> m Id
- mkTemplateLocals :: [Type] -> [Id]
- mkTemplateLocalsNum :: Int -> [Type] -> [Id]
- mkTemplateLocal :: Int -> Type -> Id
- mkWorkerId :: Unique -> Id -> Type -> Id
- mkWiredInIdName :: Module -> FastString -> Unique -> Id -> Name
- idName :: Id -> Name
- idType :: Id -> Kind
- idUnique :: Id -> Unique
- idInfo :: Id -> IdInfo
- idDetails :: Id -> IdDetails
- isId :: Var -> Bool
- idPrimRep :: Id -> PrimRep
- recordSelectorFieldLabel :: Id -> (TyCon, FieldLabel)
- setIdName :: Id -> Name -> Id
- setIdUnique :: Id -> Unique -> Id
- setIdType :: Id -> Type -> Id
- setIdExported :: Id -> Id
- setIdNotExported :: Id -> Id
- globaliseId :: Id -> Id
- localiseId :: Id -> Id
- setIdInfo :: Id -> IdInfo -> Id
- lazySetIdInfo :: Id -> IdInfo -> Id
- modifyIdInfo :: (IdInfo -> IdInfo) -> Id -> Id
- maybeModifyIdInfo :: Maybe IdInfo -> Id -> Id
- zapLamIdInfo :: Id -> Id
- zapDemandIdInfo :: Id -> Id
- zapFragileIdInfo :: Id -> Id
- transferPolyIdInfo :: Id -> [Var] -> Id -> Id
- isImplicitId :: Id -> Bool
- isDeadBinder :: Id -> Bool
- isDictId :: Id -> Bool
- isStrictId :: Id -> Bool
- isExportedId :: Var -> Bool
- isLocalId :: Var -> Bool
- isGlobalId :: Var -> Bool
- isRecordSelector :: Id -> Bool
- isNaughtyRecordSelector :: Id -> Bool
- isClassOpId_maybe :: Id -> Maybe Class
- isDFunId :: Id -> Bool
- dfunNSilent :: Id -> Int
- isPrimOpId :: Id -> Bool
- isPrimOpId_maybe :: Id -> Maybe PrimOp
- isFCallId :: Id -> Bool
- isFCallId_maybe :: Id -> Maybe ForeignCall
- isDataConWorkId :: Id -> Bool
- isDataConWorkId_maybe :: Id -> Maybe DataCon
- isDataConId_maybe :: Id -> Maybe DataCon
- idDataCon :: Id -> DataCon
- isConLikeId :: Id -> Bool
- isBottomingId :: Id -> Bool
- idIsFrom :: Module -> Id -> Bool
- isTickBoxOp :: Id -> Bool
- isTickBoxOp_maybe :: Id -> Maybe TickBoxOp
- hasNoBinding :: Id -> Bool
- idInlinePragma :: Id -> InlinePragma
- setInlinePragma :: Id -> InlinePragma -> Id
- modifyInlinePragma :: Id -> (InlinePragma -> InlinePragma) -> Id
- idInlineActivation :: Id -> Activation
- setInlineActivation :: Id -> Activation -> Id
- idRuleMatchInfo :: Id -> RuleMatchInfo
- isOneShotBndr :: Id -> Bool
- isOneShotLambda :: Id -> Bool
- isStateHackType :: Type -> Bool
- setOneShotLambda :: Id -> Id
- clearOneShotLambda :: Id -> Id
- idArity :: Id -> Arity
- idDemandInfo :: Id -> Demand
- idDemandInfo_maybe :: Id -> Maybe Demand
- idStrictness :: Id -> StrictSig
- idStrictness_maybe :: Id -> Maybe StrictSig
- idUnfolding :: Id -> Unfolding
- realIdUnfolding :: Id -> Unfolding
- idSpecialisation :: Id -> SpecInfo
- idCoreRules :: Id -> [CoreRule]
- idHasRules :: Id -> Bool
- idCafInfo :: Id -> CafInfo
- idLBVarInfo :: Id -> LBVarInfo
- idOccInfo :: Id -> OccInfo
- setIdUnfoldingLazily :: Id -> Unfolding -> Id
- setIdUnfolding :: Id -> Unfolding -> Id
- setIdArity :: Id -> Arity -> Id
- setIdDemandInfo :: Id -> Demand -> Id
- setIdStrictness :: Id -> StrictSig -> Id
- zapIdStrictness :: Id -> Id
- setIdSpecialisation :: Id -> SpecInfo -> Id
- setIdCafInfo :: Id -> CafInfo -> Id
- setIdOccInfo :: Id -> OccInfo -> Id
- zapIdOccInfo :: Id -> Id
The main types
Simple construction
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
mkSysLocalM :: MonadUnique m => FastString -> Type -> m IdSource
mkUserLocalM :: MonadUnique m => OccName -> Type -> SrcSpan -> m IdSource
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 Id
s in bijection with Int
s, typically used in unfoldings
mkWorkerId :: Unique -> Id -> Type -> IdSource
Workers get local names. CoreTidy will externalise these if necessary
mkWiredInIdName :: Module -> FastString -> Unique -> Id -> NameSource
Taking an Id apart
recordSelectorFieldLabel :: Id -> (TyCon, FieldLabel)Source
Modifying an Id
setIdUnique :: Id -> Unique -> IdSource
setIdExported :: Id -> IdSource
setIdNotExported :: Id -> IdSource
globaliseId :: Id -> IdSource
If it's a local, make it global
localiseId :: Id -> IdSource
lazySetIdInfo :: Id -> IdInfo -> IdSource
zapLamIdInfo :: Id -> IdSource
zapDemandIdInfo :: Id -> IdSource
zapFragileIdInfo :: Id -> IdSource
Predicates on Ids
isImplicitId :: Id -> BoolSource
isImplicitId
tells whether an Id
s 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.
isDeadBinder :: Id -> BoolSource
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 (e.g., an
unlifted type, but see the comment for isStrictType
). 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"
isGlobalId :: Var -> BoolSource
isRecordSelector :: Id -> BoolSource
isClassOpId_maybe :: Id -> Maybe ClassSource
dfunNSilent :: Id -> IntSource
isPrimOpId :: Id -> BoolSource
isPrimOpId_maybe :: Id -> Maybe PrimOpSource
isDataConWorkId :: Id -> BoolSource
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
isConLikeId :: Id -> BoolSource
isBottomingId :: Id -> BoolSource
Returns true if an application to n args would diverge
isTickBoxOp :: Id -> BoolSource
hasNoBinding :: Id -> BoolSource
Returns True
of an Id
which may not have a
binding, even though it is defined in this module.
Inline pragma stuff
setInlinePragma :: Id -> InlinePragma -> IdSource
modifyInlinePragma :: Id -> (InlinePragma -> InlinePragma) -> IdSource
setInlineActivation :: Id -> Activation -> IdSource
One-shot lambdas
isOneShotBndr :: Id -> BoolSource
Returns whether the lambda associated with the Id
is certainly applied at most once
OR we are applying the "state hack" which makes it appear as if theis is the case for
lambdas used in IO
. You should prefer using this over isOneShotLambda
isOneShotLambda :: Id -> BoolSource
Returns whether the lambda associated with the Id
is certainly applied at most once.
You probably want to use isOneShotBndr
instead
isStateHackType :: Type -> BoolSource
Should we apply the state hack to values of this Type
?
setOneShotLambda :: Id -> IdSource
clearOneShotLambda :: Id -> IdSource
Reading IdInfo
fields
idDemandInfo :: Id -> DemandSource
idStrictness :: Id -> StrictSigSource
idUnfolding :: Id -> UnfoldingSource
realIdUnfolding :: Id -> UnfoldingSource
idSpecialisation :: Id -> SpecInfoSource
idCoreRules :: Id -> [CoreRule]Source
idHasRules :: Id -> BoolSource
idLBVarInfo :: Id -> LBVarInfoSource
Writing IdInfo
fields
setIdUnfoldingLazily :: Id -> Unfolding -> IdSource
setIdUnfolding :: Id -> Unfolding -> IdSource
setIdArity :: Id -> Arity -> IdSource
setIdDemandInfo :: Id -> Demand -> IdSource
setIdStrictness :: Id -> StrictSig -> IdSource
zapIdStrictness :: Id -> IdSource
setIdSpecialisation :: Id -> SpecInfo -> IdSource
setIdCafInfo :: Id -> CafInfo -> IdSource
setIdOccInfo :: Id -> OccInfo -> IdSource
zapIdOccInfo :: Id -> IdSource