| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Id
Contents
Description
GHC uses several kinds of name internally:
- OccName: see OccName
- RdrName: see RdrName
- Name: see Name
- Idrepresents names that not only have a- Namebut also a- Typeand some additional details (a- IdInfoand one of- LocalIdDetailsor- GlobalIdDetails) that are added, modified and inspected by various compiler passes. These- Varnames may either be global or local, see Var
- Var: see Var
Synopsis
- data Var
- type Id = Var
- isId :: Var -> Bool
- type InVar = Var
- type InId = Id
- type OutVar = Var
- type OutId = Id
- mkGlobalId :: IdDetails -> Name -> Type -> IdInfo -> Id
- mkVanillaGlobal :: Name -> Type -> Id
- mkVanillaGlobalWithInfo :: Name -> Type -> IdInfo -> Id
- mkLocalId :: Name -> Type -> Id
- mkLocalCoVar :: Name -> Type -> CoVar
- mkLocalIdOrCoVar :: Name -> Type -> Id
- mkLocalIdOrCoVarWithInfo :: Name -> Type -> IdInfo -> Id
- mkLocalIdWithInfo :: Name -> Type -> IdInfo -> Id
- mkExportedLocalId :: IdDetails -> Name -> Type -> Id
- mkExportedVanillaId :: Name -> Type -> Id
- mkSysLocal :: FastString -> Unique -> Type -> Id
- mkSysLocalM :: MonadUnique m => FastString -> Type -> m Id
- mkSysLocalOrCoVar :: FastString -> Unique -> Type -> Id
- mkSysLocalOrCoVarM :: MonadUnique m => FastString -> Type -> m Id
- mkUserLocal :: OccName -> Unique -> Type -> SrcSpan -> Id
- mkUserLocalOrCoVar :: OccName -> Unique -> Type -> SrcSpan -> 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 :: HasDebugCallStack => Id -> IdInfo
- idDetails :: Id -> IdDetails
- recordSelectorTyCon :: Id -> RecSelParent
- 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 :: HasDebugCallStack => (IdInfo -> IdInfo) -> Id -> Id
- maybeModifyIdInfo :: Maybe IdInfo -> Id -> Id
- zapLamIdInfo :: Id -> Id
- zapIdDemandInfo :: Id -> Id
- zapIdUsageInfo :: Id -> Id
- zapIdUsageEnvInfo :: Id -> Id
- zapIdUsedOnceInfo :: Id -> Id
- zapIdTailCallInfo :: Id -> Id
- zapFragileIdInfo :: Id -> Id
- zapIdStrictness :: Id -> Id
- zapStableUnfolding :: Id -> Id
- transferPolyIdInfo :: Id -> [Var] -> Id -> Id
- isImplicitId :: Id -> Bool
- isDeadBinder :: Id -> Bool
- isStrictId :: Id -> Bool
- isExportedId :: Var -> Bool
- isLocalId :: Var -> Bool
- isGlobalId :: Var -> Bool
- isRecordSelector :: Id -> Bool
- isNaughtyRecordSelector :: Id -> Bool
- isPatSynRecordSelector :: Id -> Bool
- isDataConRecordSelector :: 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
- isDataConWrapId :: Id -> Bool
- isDataConWrapId_maybe :: Id -> Maybe DataCon
- isDataConId_maybe :: Id -> Maybe DataCon
- idDataCon :: Id -> DataCon
- isConLikeId :: Id -> Bool
- isBottomingId :: Var -> Bool
- idIsFrom :: Module -> Id -> Bool
- hasNoBinding :: Id -> Bool
- type DictId = EvId
- isDictId :: Id -> Bool
- isEvVar :: Var -> Bool
- type JoinId = Id
- isJoinId :: Var -> Bool
- isJoinId_maybe :: Var -> Maybe JoinArity
- idJoinArity :: JoinId -> JoinArity
- asJoinId :: Id -> JoinArity -> JoinId
- asJoinId_maybe :: Id -> Maybe JoinArity -> Id
- zapJoinId :: Id -> Id
- idInlinePragma :: Id -> InlinePragma
- setInlinePragma :: Id -> InlinePragma -> Id
- modifyInlinePragma :: Id -> (InlinePragma -> InlinePragma) -> Id
- idInlineActivation :: Id -> Activation
- setInlineActivation :: Id -> Activation -> Id
- idRuleMatchInfo :: Id -> RuleMatchInfo
- isOneShotBndr :: Var -> Bool
- isProbablyOneShotLambda :: Id -> Bool
- setOneShotLambda :: Id -> Id
- clearOneShotLambda :: Id -> Id
- updOneShotInfo :: Id -> OneShotInfo -> Id
- setIdOneShotInfo :: Id -> OneShotInfo -> Id
- isStateHackType :: Type -> Bool
- stateHackOneShot :: OneShotInfo
- typeOneShot :: Type -> OneShotInfo
- idArity :: Id -> Arity
- idCallArity :: Id -> Arity
- idFunRepArity :: Id -> RepArity
- idUnfolding :: Id -> Unfolding
- realIdUnfolding :: Id -> Unfolding
- idSpecialisation :: Id -> RuleInfo
- idCoreRules :: Id -> [CoreRule]
- idHasRules :: Id -> Bool
- idCafInfo :: Id -> CafInfo
- idOneShotInfo :: Id -> OneShotInfo
- idStateHackOneShotInfo :: Id -> OneShotInfo
- idOccInfo :: Id -> OccInfo
- isNeverLevPolyId :: Id -> Bool
- setIdUnfolding :: Id -> Unfolding -> Id
- setCaseBndrEvald :: StrictnessMark -> Id -> Id
- setIdArity :: Id -> Arity -> Id
- setIdCallArity :: Id -> Arity -> Id
- setIdSpecialisation :: Id -> RuleInfo -> Id
- setIdCafInfo :: Id -> CafInfo -> Id
- setIdOccInfo :: Id -> OccInfo -> Id
- zapIdOccInfo :: Id -> Id
- setIdDemandInfo :: Id -> Demand -> Id
- setIdStrictness :: Id -> StrictSig -> Id
- idDemandInfo :: Id -> Demand
- idStrictness :: Id -> StrictSig
The main types
Variable
Essentially a typed Name, that may also contain some additional information
 about the Var and its use sites.
Instances
| Eq Var Source # | |
| Data Var Source # | |
| Defined in Var Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Var -> c Var # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Var # dataTypeOf :: Var -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Var) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Var) # gmapT :: (forall b. Data b => b -> b) -> Var -> Var # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Var -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Var -> r # gmapQ :: (forall d. Data d => d -> u) -> Var -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Var -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Var -> m Var # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Var -> m Var # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Var -> m Var # | |
| Ord Var Source # | |
| OutputableBndr Var Source # | |
| Outputable Var Source # | |
| Uniquable Var Source # | |
| HasOccName Var Source # | |
| NamedThing Var Source # | |
Is this a value-level (i.e., computationally relevant) Identifier?
 Satisfies isId = not . isTyVar.
In and Out variants
Simple construction
mkLocalIdOrCoVar :: Name -> Type -> Id Source #
Like mkLocalId, but checks the type to see if it should make a covar
mkLocalIdOrCoVarWithInfo :: Name -> Type -> IdInfo -> Id Source #
Make a local id, with the IdDetails set to CoVarId if the type indicates so.
mkExportedLocalId :: IdDetails -> Name -> Type -> Id Source #
Create a local Id that is marked as exported.
 This prevents things attached to it from being removed as dead code.
 See Note [Exported LocalIds]
mkSysLocal :: FastString -> Unique -> Type -> Id Source #
mkSysLocalM :: MonadUnique m => FastString -> Type -> m Id Source #
mkSysLocalOrCoVar :: FastString -> Unique -> Type -> Id Source #
Like mkSysLocal, but checks to see if we have a covar type
mkSysLocalOrCoVarM :: MonadUnique m => FastString -> Type -> m Id Source #
mkUserLocalOrCoVar :: OccName -> Unique -> Type -> SrcSpan -> Id Source #
Like mkUserLocal, but checks if we have a coercion type
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 -> Id Source #
Create a template local: a family of system local Ids in bijection with Ints, typically used in unfoldings
mkWorkerId :: Unique -> Id -> Type -> Id Source #
Workers get local names. CoreTidy will externalise these if necessary
Taking an Id apart
recordSelectorTyCon :: Id -> RecSelParent Source #
Modifying an Id
setIdExported :: Id -> Id Source #
setIdNotExported :: Id -> Id Source #
globaliseId :: Id -> Id Source #
If it's a local, make it global
localiseId :: Id -> Id Source #
modifyIdInfo :: HasDebugCallStack => (IdInfo -> IdInfo) -> Id -> Id Source #
zapLamIdInfo :: Id -> Id Source #
zapIdDemandInfo :: Id -> Id Source #
zapIdUsageInfo :: Id -> Id Source #
zapIdUsageEnvInfo :: Id -> Id Source #
zapIdUsedOnceInfo :: Id -> Id Source #
zapIdTailCallInfo :: Id -> Id Source #
zapFragileIdInfo :: Id -> Id Source #
zapIdStrictness :: Id -> Id Source #
zapStableUnfolding :: Id -> Id Source #
Predicates on Ids
isImplicitId :: Id -> Bool Source #
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 -> Bool Source #
isStrictId :: Id -> Bool Source #
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 -> Bool Source #
isExportedIdVar means "don't throw this away"
isGlobalId :: Var -> Bool Source #
isRecordSelector :: Id -> Bool Source #
isNaughtyRecordSelector :: Id -> Bool Source #
isPatSynRecordSelector :: Id -> Bool Source #
isDataConRecordSelector :: Id -> Bool Source #
isPrimOpId :: Id -> Bool Source #
isFCallId_maybe :: Id -> Maybe ForeignCall Source #
isDataConWorkId :: Id -> Bool Source #
isDataConWrapId :: Id -> Bool Source #
idDataCon :: Id -> DataCon Source #
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 -> Bool Source #
isBottomingId :: Var -> Bool Source #
Returns true if an application to n args would diverge
hasNoBinding :: Id -> Bool Source #
Returns True of an Id which may not have a
 binding, even though it is defined in this module.
Evidence variables
Join variables
idJoinArity :: JoinId -> JoinArity Source #
Inline pragma stuff
idInlinePragma :: Id -> InlinePragma Source #
setInlinePragma :: Id -> InlinePragma -> Id infixl 1 Source #
modifyInlinePragma :: Id -> (InlinePragma -> InlinePragma) -> Id Source #
idInlineActivation :: Id -> Activation Source #
setInlineActivation :: Id -> Activation -> Id infixl 1 Source #
idRuleMatchInfo :: Id -> RuleMatchInfo Source #
One-shot lambdas
isOneShotBndr :: Var -> Bool Source #
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
 See Note [The state-transformer hack] in CoreArity
isProbablyOneShotLambda :: Id -> Bool Source #
setOneShotLambda :: Id -> Id Source #
clearOneShotLambda :: Id -> Id Source #
updOneShotInfo :: Id -> OneShotInfo -> Id Source #
setIdOneShotInfo :: Id -> OneShotInfo -> Id infixl 1 Source #
isStateHackType :: Type -> Bool Source #
stateHackOneShot :: OneShotInfo Source #
Should we apply the state hack to values of this Type?
typeOneShot :: Type -> OneShotInfo Source #
Reading IdInfo fields
idCallArity :: Id -> Arity Source #
idFunRepArity :: Id -> RepArity Source #
idUnfolding :: Id -> Unfolding Source #
realIdUnfolding :: Id -> Unfolding Source #
idSpecialisation :: Id -> RuleInfo Source #
idCoreRules :: Id -> [CoreRule] Source #
idHasRules :: Id -> Bool Source #
idOneShotInfo :: Id -> OneShotInfo Source #
idStateHackOneShotInfo :: Id -> OneShotInfo Source #
Like idOneShotInfo, but taking the Horrible State Hack in to account
 See Note [The state-transformer hack] in CoreArity
isNeverLevPolyId :: Id -> Bool Source #
Writing IdInfo fields
setCaseBndrEvald :: StrictnessMark -> Id -> Id Source #
zapIdOccInfo :: Id -> Id Source #
idDemandInfo :: Id -> Demand Source #
idStrictness :: Id -> StrictSig Source #
Accesses the Id's strictnessInfo.