Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
GHC uses several kinds of name internally:
OccName
: see GHC.Types.Name.OccurrenceRdrName
: see GHC.Types.Name.ReaderName
: see GHC.Types.NameId
represents names that not only have aName
but also aType
and some additional details (aIdInfo
and one of LocalIdDetails or GlobalIdDetails) that are added, modified and inspected by various compiler passes. TheseVar
names may either be global or local, see GHC.Types.VarVar
: see GHC.Types.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 :: HasDebugCallStack => Name -> Mult -> Type -> Id
- mkLocalCoVar :: Name -> Type -> CoVar
- mkLocalIdOrCoVar :: Name -> Mult -> Type -> Id
- mkLocalIdWithInfo :: HasDebugCallStack => Name -> Mult -> Type -> IdInfo -> Id
- mkExportedLocalId :: IdDetails -> Name -> Type -> Id
- mkExportedVanillaId :: Name -> Type -> Id
- mkSysLocal :: FastString -> Unique -> Mult -> Type -> Id
- mkSysLocalM :: MonadUnique m => FastString -> Mult -> Type -> m Id
- mkSysLocalOrCoVar :: FastString -> Unique -> Mult -> Type -> Id
- mkSysLocalOrCoVarM :: MonadUnique m => FastString -> Mult -> Type -> m Id
- mkUserLocal :: OccName -> Unique -> Mult -> Type -> SrcSpan -> Id
- mkUserLocalOrCoVar :: OccName -> Unique -> Mult -> Type -> SrcSpan -> Id
- mkTemplateLocals :: [Type] -> [Id]
- mkTemplateLocalsNum :: Int -> [Type] -> [Id]
- mkTemplateLocal :: Int -> Type -> Id
- mkScaledTemplateLocal :: Int -> Scaled Type -> Id
- mkWorkerId :: Unique -> Id -> Type -> Id
- idName :: Id -> Name
- idType :: Id -> Kind
- idMult :: Id -> Mult
- idScaledType :: Id -> Scaled Type
- idUnique :: Id -> Unique
- idInfo :: HasDebugCallStack => Id -> IdInfo
- idDetails :: Id -> IdDetails
- recordSelectorTyCon :: Id -> RecSelParent
- recordSelectorTyCon_maybe :: Id -> Maybe RecSelParent
- setIdName :: Id -> Name -> Id
- setIdUnique :: Id -> Unique -> Id
- setIdType :: Id -> Type -> Id
- setIdMult :: Id -> Mult -> Id
- updateIdTypeButNotMult :: (Type -> Type) -> Id -> Id
- updateIdTypeAndMult :: (Type -> Type) -> Id -> Id
- updateIdTypeAndMultM :: Monad m => (Type -> m Type) -> Id -> m 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
- zapIdDmdSig :: Id -> Id
- zapStableUnfolding :: Id -> Id
- transferPolyIdInfo :: Id -> [Var] -> Id -> Id
- scaleIdBy :: Mult -> Id -> Id
- scaleVarBy :: Mult -> Var -> Var
- 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 :: 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
- isWorkerLikeId :: Id -> Bool
- isDeadEndId :: Var -> Bool
- idIsFrom :: Module -> Id -> Bool
- hasNoBinding :: Id -> 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
- setOneShotLambda :: Id -> Id
- clearOneShotLambda :: Id -> Id
- updOneShotInfo :: Id -> OneShotInfo -> Id
- setIdOneShotInfo :: Id -> OneShotInfo -> Id
- idArity :: Id -> Arity
- idCallArity :: Id -> Arity
- idFunRepArity :: Id -> RepArity
- idSpecialisation :: Id -> RuleInfo
- idCoreRules :: Id -> [CoreRule]
- idHasRules :: Id -> Bool
- idCafInfo :: Id -> CafInfo
- idLFInfo_maybe :: Id -> Maybe LambdaFormInfo
- idOneShotInfo :: Id -> OneShotInfo
- idOccInfo :: Id -> OccInfo
- type IdUnfoldingFun = Id -> Unfolding
- idUnfolding :: IdUnfoldingFun
- realIdUnfolding :: Id -> Unfolding
- alwaysActiveUnfoldingFun :: IdUnfoldingFun
- whenActiveUnfoldingFun :: (Activation -> Bool) -> IdUnfoldingFun
- noUnfoldingFun :: IdUnfoldingFun
- setIdUnfolding :: Id -> Unfolding -> Id
- zapIdUnfolding :: Id -> 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
- setIdLFInfo :: Id -> LambdaFormInfo -> Id
- setIdDemandInfo :: Id -> Demand -> Id
- setIdDmdSig :: Id -> DmdSig -> Id
- setIdCprSig :: Id -> CprSig -> Id
- setIdCbvMarks :: Id -> [CbvMark] -> Id
- idCbvMarks_maybe :: Id -> Maybe [CbvMark]
- idCbvMarkArity :: Id -> Arity
- asWorkerLikeId :: Id -> Id
- asNonWorkerLikeId :: Id -> Id
- idDemandInfo :: Id -> Demand
- idDmdSig :: Id -> DmdSig
- idCprSig :: Id -> CprSig
- idTagSig_maybe :: Id -> Maybe TagSig
- setIdTagSig :: Id -> TagSig -> Id
The main types
Variable
Essentially a typed Name
, that may also contain some additional information
about the Var
and its use sites.
Instances
Data Var Source # | |
Defined in GHC.Types.Var gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Var -> c Var Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Var Source # toConstr :: Var -> Constr Source # dataTypeOf :: Var -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Var) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Var) Source # gmapT :: (forall b. Data b => b -> b) -> Var -> Var Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Var -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Var -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Var -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Var -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Var -> m Var Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Var -> m Var Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Var -> m Var Source # | |
NamedThing Var Source # | |
HasOccName Var Source # | |
Uniquable Var Source # | |
Outputable Var Source # | |
OutputableBndr Var Source # | |
Defined in GHC.Core.Ppr | |
Eq Var Source # | |
Ord Var Source # | |
Eq (DeBruijn CoreAlt) Source # | |
Eq (DeBruijn CoreExpr) Source # | |
Eq (DeBruijn Var) Source # | |
OutputableBndr (Id, TagSig) Source # | |
type Anno Id Source # | |
Defined in GHC.Hs.Extension | |
type Anno (LocatedN Id) Source # | |
Defined in GHC.Hs.Binds | |
type Anno [LocatedN Id] Source # | |
Defined in GHC.Hs.Binds |
Is this a value-level (i.e., computationally relevant) Var
entifier?
Satisfies isId = not . isTyVar
.
In and Out variants
Simple construction
mkGlobalId :: IdDetails -> Name -> Type -> IdInfo -> Id Source #
For an explanation of global vs. local Id
s, see GHC.Types.Var.Var
mkLocalId :: HasDebugCallStack => Name -> Mult -> Type -> Id Source #
For an explanation of global vs. local Id
s, see GHC.Types.Var
mkLocalIdOrCoVar :: Name -> Mult -> Type -> Id Source #
Like mkLocalId
, but checks the type to see if it should make a covar
mkLocalIdWithInfo :: HasDebugCallStack => Name -> Mult -> Type -> IdInfo -> Id Source #
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 -> Mult -> Type -> Id Source #
mkSysLocalM :: MonadUnique m => FastString -> Mult -> Type -> m Id Source #
mkSysLocalOrCoVar :: FastString -> Unique -> Mult -> Type -> Id Source #
Like mkSysLocal
, but checks to see if we have a covar type
mkSysLocalOrCoVarM :: MonadUnique m => FastString -> Mult -> Type -> m Id Source #
mkUserLocal :: OccName -> Unique -> Mult -> Type -> SrcSpan -> Id Source #
Create a user local Id
. These are local Id
s (see GHC.Types.Var) with a name and location that the user might recognize
mkUserLocalOrCoVar :: OccName -> Unique -> Mult -> 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 Id
s in bijection with Int
s, 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 #
zapIdDmdSig :: Id -> Id Source #
zapStableUnfolding :: Id -> Id Source #
scaleVarBy :: Mult -> Var -> Var Source #
Like scaleIdBy
, but skips non-Ids. Useful for scaling
a mixed list of ids and tyvars.
Predicates on Ids
isImplicitId :: Id -> Bool Source #
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 -> Bool Source #
isStrictId :: Id -> Bool Source #
isStrictId
says whether either
(a) the Id
has a strict demand placed on it or
(b) definitely has a "strict type", such that it can always be
evaluated strictly (i.e an unlifted type)
We need to check (b) as well as (a), because when 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
.
Returns False if the type is levity polymorphic; False is always safe.
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 #
isClassOpId :: 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 #
isWorkerLikeId :: Id -> Bool Source #
An Id for which we might require all callers to pass strict arguments properly tagged + evaluated.
See Note [CBV Function Ids]
isDeadEndId :: Var -> Bool Source #
Returns true if an application to n args diverges or throws an exception See Note [Dead ends] in GHC.Types.Demand.
hasNoBinding :: Id -> Bool Source #
Returns True
of an Id
which may not have a
binding, even though it is defined in this module.
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
setOneShotLambda :: Id -> Id Source #
clearOneShotLambda :: Id -> Id Source #
updOneShotInfo :: Id -> OneShotInfo -> Id Source #
setIdOneShotInfo :: Id -> OneShotInfo -> Id infixl 1 Source #
Reading IdInfo
fields
idCallArity :: Id -> Arity Source #
idFunRepArity :: Id -> RepArity Source #
This function counts all arguments post-unarisation, which includes arguments with no runtime representation -- see Note [Unarisation and arity]
idSpecialisation :: Id -> RuleInfo Source #
idCoreRules :: Id -> [CoreRule] Source #
idHasRules :: Id -> Bool Source #
idLFInfo_maybe :: Id -> Maybe LambdaFormInfo Source #
idOneShotInfo :: Id -> OneShotInfo Source #
type IdUnfoldingFun = Id -> Unfolding Source #
idUnfolding :: IdUnfoldingFun Source #
Returns the Id
s unfolding, but does not expose the unfolding of a strong
loop breaker. See unfoldingInfo
.
If you really want the unfolding of a strong loopbreaker, call realIdUnfolding
.
realIdUnfolding :: Id -> Unfolding Source #
Expose the unfolding if there is one, including for loop breakers
alwaysActiveUnfoldingFun :: IdUnfoldingFun Source #
Returns an unfolding only if (a) not a strong loop breaker and (b) always active
whenActiveUnfoldingFun :: (Activation -> Bool) -> IdUnfoldingFun Source #
Returns an unfolding only if (a) not a strong loop breaker and (b) active in according to is_active
Writing IdInfo
fields
zapIdUnfolding :: Id -> Id Source #
Similar to trimUnfolding, but also removes evaldness info.
setCaseBndrEvald :: StrictnessMark -> Id -> Id Source #
zapIdOccInfo :: Id -> Id Source #
setIdLFInfo :: Id -> LambdaFormInfo -> Id Source #
setIdCbvMarks :: Id -> [CbvMark] -> Id infixl 1 Source #
If all marks are NotMarkedStrict we just set nothing.
idCbvMarkArity :: Id -> Arity Source #
asWorkerLikeId :: Id -> Id Source #
Turn this id into a WorkerLikeId if possible.
asNonWorkerLikeId :: Id -> Id Source #
Remove any cbv marks on arguments from a given Id.
idDemandInfo :: Id -> Demand Source #