ghc-6.12.3: The GHC APISource codeContentsIndex
Id
Contents
The main types
Simple construction
Taking an Id apart
Modifying an Id
Predicates on Ids
Inline pragma stuff
One-shot lambdas
Reading IdInfo fields
Writing IdInfo fields
Description

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 a Name but also a TypeRep.Type and some additional details (a IdInfo and one of Var.LocalIdDetails or IdInfo.GlobalIdDetails) that are added, modified and inspected by various compiler passes. These Var names may either be global or local, see Var
  • Var: see Var
Synopsis
type Id = Var
type DictId = Var
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
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
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
idNewDemandInfo :: Id -> Demand
idNewDemandInfo_maybe :: Id -> Maybe Demand
idNewStrictness :: Id -> StrictSig
idNewStrictness_maybe :: Id -> Maybe StrictSig
idWorkerInfo :: Id -> WorkerInfo
idUnfolding :: Id -> Unfolding
idSpecialisation :: Id -> SpecInfo
idCoreRules :: Id -> [CoreRule]
idHasRules :: Id -> Bool
idCafInfo :: Id -> CafInfo
idLBVarInfo :: Id -> LBVarInfo
idOccInfo :: Id -> OccInfo
setIdUnfolding :: Id -> Unfolding -> Id
setIdArity :: Id -> Arity -> Id
setIdNewDemandInfo :: Id -> Demand -> Id
setIdNewStrictness :: Id -> StrictSig -> Id
zapIdNewStrictness :: Id -> Id
setIdWorkerInfo :: Id -> WorkerInfo -> Id
setIdSpecialisation :: Id -> SpecInfo -> Id
setIdCafInfo :: Id -> CafInfo -> Id
setIdOccInfo :: Id -> OccInfo -> Id
zapIdOccInfo :: Id -> Id
The main types
type Id = VarSource
type DictId = VarSource
Simple construction
mkGlobalId :: IdDetails -> Name -> Type -> IdInfo -> IdSource
For an explanation of global vs. local Ids, see Var
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
mkLocalIdWithInfo :: Name -> Type -> IdInfo -> IdSource
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) that are created by the compiler out of thin air
mkSysLocalM :: MonadUnique m => FastString -> Type -> m IdSource
mkUserLocal :: OccName -> Unique -> Type -> SrcSpan -> IdSource
Create a user local Id. These are local Ids (see Var) with a name and location that the user might recognize
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 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
idName :: Id -> NameSource
idType :: Id -> KindSource
idUnique :: Id -> UniqueSource
idInfo :: Id -> IdInfoSource
idDetails :: Id -> IdDetailsSource
isId :: Var -> BoolSource
idPrimRep :: Id -> PrimRepSource
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
setIdName :: Id -> Name -> IdSource
setIdUnique :: Id -> Unique -> IdSource
setIdType :: Id -> Type -> IdSource
Not only does this set the Id Type, it also evaluates the type to try and reduce space usage
setIdExported :: Id -> IdSource
setIdNotExported :: Id -> IdSource
globaliseId :: Id -> IdSource
If it's a local, make it global
localiseId :: Id -> IdSource
setIdInfo :: Id -> IdInfo -> IdSource
lazySetIdInfo :: Id -> IdInfo -> IdSource
modifyIdInfo :: (IdInfo -> IdInfo) -> Id -> IdSource
maybeModifyIdInfo :: Maybe IdInfo -> Id -> IdSource
zapLamIdInfo :: Id -> IdSource
zapDemandIdInfo :: Id -> IdSource
zapFragileIdInfo :: Id -> IdSource
transferPolyIdInfo :: Id -> [Var] -> Id -> IdSource
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.
isDeadBinder :: Id -> BoolSource
isDictId :: 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"
isLocalId :: Var -> BoolSource
isGlobalId :: Var -> BoolSource
isRecordSelector :: Id -> BoolSource
isNaughtyRecordSelector :: Id -> BoolSource
isClassOpId_maybe :: Id -> Maybe ClassSource
isDFunId :: Id -> BoolSource
isPrimOpId :: Id -> BoolSource
isPrimOpId_maybe :: Id -> Maybe PrimOpSource
isFCallId :: Id -> BoolSource
isFCallId_maybe :: Id -> Maybe ForeignCallSource
isDataConWorkId :: Id -> BoolSource
isDataConWorkId_maybe :: Id -> Maybe DataConSource
isDataConId_maybe :: Id -> Maybe DataConSource
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
idIsFrom :: Module -> Id -> BoolSource
isTickBoxOp :: Id -> BoolSource
isTickBoxOp_maybe :: Id -> Maybe TickBoxOpSource
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
idInlinePragma :: Id -> InlinePragmaSource
setInlinePragma :: Id -> InlinePragma -> IdSource
modifyInlinePragma :: Id -> (InlinePragma -> InlinePragma) -> IdSource
idInlineActivation :: Id -> ActivationSource
setInlineActivation :: Id -> Activation -> IdSource
idRuleMatchInfo :: Id -> RuleMatchInfoSource
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
idArity :: Id -> AritySource
idNewDemandInfo :: Id -> DemandSource
idNewDemandInfo_maybe :: Id -> Maybe DemandSource
idNewStrictness :: Id -> StrictSigSource
idNewStrictness_maybe :: Id -> Maybe StrictSigSource
idWorkerInfo :: Id -> WorkerInfoSource
idUnfolding :: Id -> UnfoldingSource
idSpecialisation :: Id -> SpecInfoSource
idCoreRules :: Id -> [CoreRule]Source
idHasRules :: Id -> BoolSource
idCafInfo :: Id -> CafInfoSource
idLBVarInfo :: Id -> LBVarInfoSource
idOccInfo :: Id -> OccInfoSource
Writing IdInfo fields
setIdUnfolding :: Id -> Unfolding -> IdSource
setIdArity :: Id -> Arity -> IdSource
setIdNewDemandInfo :: Id -> Demand -> IdSource
setIdNewStrictness :: Id -> StrictSig -> IdSource
zapIdNewStrictness :: Id -> IdSource
setIdWorkerInfo :: Id -> WorkerInfo -> IdSource
setIdSpecialisation :: Id -> SpecInfo -> IdSource
setIdCafInfo :: Id -> CafInfo -> IdSource
setIdOccInfo :: Id -> OccInfo -> IdSource
zapIdOccInfo :: Id -> IdSource
Produced by Haddock version 2.6.1