ghc-6.10.3: The GHC APIContentsIndex
IdInfo
Contents
The GlobalIdDetails type
The IdInfo type
Zapping various forms of Info
The ArityInfo type
Demand and strictness Info
The WorkerInfo type
Unfolding Info
The InlinePragInfo type
The OccInfo type
The SpecInfo type
The CAFInfo type
The LBVarInfo type
Tick-box Info
Synopsis
data GlobalIdDetails
= VanillaGlobal
| RecordSelId {
sel_tycon :: TyCon
sel_label :: FieldLabel
sel_naughty :: Bool
}
| DataConWorkId DataCon
| DataConWrapId DataCon
| ClassOpId Class
| PrimOpId PrimOp
| FCallId ForeignCall
| TickBoxOpId TickBoxOp
| NotGlobalId
notGlobalId :: GlobalIdDetails
data IdInfo
vanillaIdInfo :: IdInfo
noCafIdInfo :: IdInfo
seqIdInfo :: IdInfo -> ()
megaSeqIdInfo :: IdInfo -> ()
zapLamInfo :: IdInfo -> Maybe IdInfo
zapDemandInfo :: IdInfo -> Maybe IdInfo
zapFragileInfo :: IdInfo -> Maybe IdInfo
type ArityInfo = Arity
unknownArity :: Arity
arityInfo :: IdInfo -> ArityInfo
setArityInfo :: IdInfo -> ArityInfo -> IdInfo
ppArityInfo :: Int -> SDoc
newStrictnessInfo :: IdInfo -> Maybe StrictSig
setNewStrictnessInfo :: IdInfo -> Maybe StrictSig -> IdInfo
newDemandInfo :: IdInfo -> Maybe Demand
setNewDemandInfo :: IdInfo -> Maybe Demand -> IdInfo
pprNewStrictness :: Maybe StrictSig -> SDoc
setAllStrictnessInfo :: IdInfo -> Maybe StrictSig -> IdInfo
data WorkerInfo
= NoWorker
| HasWorker Id Arity
workerExists :: WorkerInfo -> Bool
wrapperArity :: WorkerInfo -> Arity
workerId :: WorkerInfo -> Id
workerInfo :: IdInfo -> WorkerInfo
setWorkerInfo :: IdInfo -> WorkerInfo -> IdInfo
ppWorkerInfo :: WorkerInfo -> SDoc
unfoldingInfo :: IdInfo -> Unfolding
setUnfoldingInfo :: IdInfo -> Unfolding -> IdInfo
setUnfoldingInfoLazily :: IdInfo -> Unfolding -> IdInfo
type InlinePragInfo = Activation
inlinePragInfo :: IdInfo -> InlinePragInfo
setInlinePragInfo :: IdInfo -> InlinePragInfo -> IdInfo
data OccInfo
= NoOccInfo
| IAmDead
| OneOcc !InsideLam !OneBranch !InterestingCxt
| IAmALoopBreaker !RulesOnly
isFragileOcc :: OccInfo -> Bool
isDeadOcc :: OccInfo -> Bool
isLoopBreaker :: OccInfo -> Bool
occInfo :: IdInfo -> OccInfo
setOccInfo :: IdInfo -> OccInfo -> IdInfo
type InsideLam = Bool
type OneBranch = Bool
insideLam :: InsideLam
notInsideLam :: InsideLam
oneBranch :: OneBranch
notOneBranch :: OneBranch
data SpecInfo = SpecInfo [CoreRule] VarSet
isEmptySpecInfo :: SpecInfo -> Bool
specInfoFreeVars :: SpecInfo -> VarSet
specInfoRules :: SpecInfo -> [CoreRule]
seqSpecInfo :: SpecInfo -> ()
setSpecInfoHead :: Name -> SpecInfo -> SpecInfo
specInfo :: IdInfo -> SpecInfo
setSpecInfo :: IdInfo -> SpecInfo -> IdInfo
data CafInfo
= MayHaveCafRefs
| NoCafRefs
ppCafInfo :: CafInfo -> SDoc
mayHaveCafRefs :: CafInfo -> Bool
cafInfo :: IdInfo -> CafInfo
setCafInfo :: IdInfo -> CafInfo -> IdInfo
data LBVarInfo
= NoLBVarInfo
| IsOneShotLambda
noLBVarInfo :: LBVarInfo
hasNoLBVarInfo :: LBVarInfo -> Bool
lbvarInfo :: IdInfo -> LBVarInfo
setLBVarInfo :: IdInfo -> LBVarInfo -> IdInfo
data TickBoxOp = TickBox Module !TickBoxId
type TickBoxId = Int
The GlobalIdDetails type
data GlobalIdDetails
Information pertaining to global Ids. See Var for the distinction between global and local in this context
Constructors
VanillaGlobalThe Id is imported from elsewhere or is a default method Id
RecordSelIdThe Id for a record selector
sel_tycon :: TyConFor a data type family, this is the instance TyCon not the family TyCon
sel_label :: FieldLabel
sel_naughty :: Bool
DataConWorkId DataConThe Id is for a data constructor worker
DataConWrapId DataConThe Id is for a data constructor wrapper
ClassOpId ClassThe Id is an operation of a class
PrimOpId PrimOpThe Id is for a primitive operator
FCallId ForeignCallThe Id is for a foreign call
TickBoxOpId TickBoxOpThe Id is for a HPC tick box (both traditional and binary)
NotGlobalIdUsed as a convenient extra return value from globalIdDetails
show/hide Instances
notGlobalId :: GlobalIdDetails
An entirely unhelpful GlobalIdDetails
The IdInfo type
data IdInfo

An IdInfo gives optional information about an Id. If present it never lies, but it may not be present, in which case there is always a conservative assumption which can be made.

Two Ids may have different info even though they have the same Unique (and are hence the same Id); for example, one might lack the properties attached to the other.

The IdInfo gives information about the value, or definition, of the Id. It does not contain information about the Id's usage, except for demandInfo and lbvarInfo.

vanillaIdInfo :: IdInfo
Basic IdInfo that carries no useful information whatsoever
noCafIdInfo :: IdInfo
More informative IdInfo we can use when we know the Id has no CAF references
seqIdInfo :: IdInfo -> ()
Just evaluate the IdInfo to WHNF
megaSeqIdInfo :: IdInfo -> ()
Evaluate all the fields of the IdInfo that are generally demanded by the compiler
Zapping various forms of Info
zapLamInfo :: IdInfo -> Maybe IdInfo

This is used to remove information on lambda binders that we have setup as part of a lambda group, assuming they will be applied all at once, but turn out to be part of an unsaturated lambda as in e.g:

 (\x1. \x2. e) arg1
zapDemandInfo :: IdInfo -> Maybe IdInfo
Remove demand info on the IdInfo if it is present, otherwise return Nothing
zapFragileInfo :: IdInfo -> Maybe IdInfo
Zap info that depends on free variables
The ArityInfo type
type ArityInfo = Arity

An ArityInfo of n tells us that partial application of this Id to up to n-1 value arguments does essentially no work.

That is not necessarily the same as saying that it has n leading lambdas, because coerces may get in the way.

The arity might increase later in the compilation process, if an extra lambda floats up to the binding site.

unknownArity :: Arity
It is always safe to assume that an Id has an arity of 0
arityInfo :: IdInfo -> ArityInfo
Id arity
setArityInfo :: IdInfo -> ArityInfo -> IdInfo
ppArityInfo :: Int -> SDoc
Demand and strictness Info
newStrictnessInfo :: IdInfo -> Maybe StrictSig
Id strictness information. Reason for Maybe: the DmdAnal phase needs to know whether this is the first visit, so it can assign botSig. Other customers want topSig. So Nothing is good.
setNewStrictnessInfo :: IdInfo -> Maybe StrictSig -> IdInfo
newDemandInfo :: IdInfo -> Maybe Demand
Id demand information. Similarly we want to know if there's no known demand yet, for when we are looking for CPR info
setNewDemandInfo :: IdInfo -> Maybe Demand -> IdInfo
pprNewStrictness :: Maybe StrictSig -> SDoc
setAllStrictnessInfo :: IdInfo -> Maybe StrictSig -> IdInfo
Set old and new strictness information together
The WorkerInfo type
data WorkerInfo
If this Id has a worker then we store a reference to it. Worker functions are generated by the worker/wrapper pass, using information information from strictness analysis.
Constructors
NoWorkerNo known worker function
HasWorker Id ArityThe Arity is the arity of the wrapper at the moment of the worker/wrapper split, which may be different from the current Id Aritiy
workerExists :: WorkerInfo -> Bool
wrapperArity :: WorkerInfo -> Arity
The Arity of the worker function at the time of the split if it exists, or a panic otherwise
workerId :: WorkerInfo -> Id
The Id of the worker function if it exists, or a panic otherwise
workerInfo :: IdInfo -> WorkerInfo
Pointer to worker function. Within one module this is irrelevant; the inlining of a worker is handled via the Unfolding. However, when the module is imported by others, the WorkerInfo is used only to indicate the form of the RHS, so that interface files don't actually need to contain the RHS; it can be derived from the strictness info
setWorkerInfo :: IdInfo -> WorkerInfo -> IdInfo
ppWorkerInfo :: WorkerInfo -> SDoc
Unfolding Info
unfoldingInfo :: IdInfo -> Unfolding
The Ids unfolding
setUnfoldingInfo :: IdInfo -> Unfolding -> IdInfo
setUnfoldingInfoLazily :: IdInfo -> Unfolding -> IdInfo
The InlinePragInfo type
type InlinePragInfo = Activation

Tells when the inlining is active. When it is active the thing may be inlined, depending on how big it is.

If there was an INLINE pragma, then as a separate matter, the RHS will have been made to look small with a Core inline Note

The default InlinePragInfo is AlwaysActive, so the info serves entirely as a way to inhibit inlining until we want it

inlinePragInfo :: IdInfo -> InlinePragInfo
Any inline pragma atached to the Id
setInlinePragInfo :: IdInfo -> InlinePragInfo -> IdInfo
The OccInfo type
data OccInfo
Identifier occurrence information
Constructors
NoOccInfoThere are many occurrences, or unknown occurences
IAmDeadMarks unused variables. Sometimes useful for lambda and case-bound variables.
OneOcc !InsideLam !OneBranch !InterestingCxtOccurs exactly once, not inside a rule
IAmALoopBreaker !RulesOnlyThis identifier breaks a loop of mutually recursive functions. The field marks whether it is only a loop breaker due to a reference in a rule
show/hide Instances
isFragileOcc :: OccInfo -> Bool
isDeadOcc :: OccInfo -> Bool
isLoopBreaker :: OccInfo -> Bool
occInfo :: IdInfo -> OccInfo
How the Id occurs in the program
setOccInfo :: IdInfo -> OccInfo -> IdInfo
type InsideLam = Bool
type OneBranch = Bool
insideLam :: InsideLam
notInsideLam :: InsideLam
oneBranch :: OneBranch
notOneBranch :: OneBranch
The SpecInfo type
data SpecInfo
Records the specializations of this Id that we know about in the form of rewrite CoreRules that target them
Constructors
SpecInfo [CoreRule] VarSet
isEmptySpecInfo :: SpecInfo -> Bool
specInfoFreeVars :: SpecInfo -> VarSet
Retrieve the locally-defined free variables of both the left and right hand sides of the specialization rules
specInfoRules :: SpecInfo -> [CoreRule]
seqSpecInfo :: SpecInfo -> ()
setSpecInfoHead :: Name -> SpecInfo -> SpecInfo
Change the name of the function the rule is keyed on on all of the CoreRules
specInfo :: IdInfo -> SpecInfo
Specialisations of the Ids function which exist
setSpecInfo :: IdInfo -> SpecInfo -> IdInfo
The CAFInfo type
data CafInfo
Records whether an Id makes Constant Applicative Form references
Constructors
MayHaveCafRefs

Indicates that the Id is for either:

1. A function or static constructor that refers to one or more CAFs, or

2. A real live CAF

NoCafRefsA function or static constructor that refers to no CAFs.
ppCafInfo :: CafInfo -> SDoc
mayHaveCafRefs :: CafInfo -> Bool
cafInfo :: IdInfo -> CafInfo
Id CAF info
setCafInfo :: IdInfo -> CafInfo -> IdInfo
The LBVarInfo type
data LBVarInfo

If the Id is a lambda-bound variable then it may have lambda-bound variable info. Sometimes we know whether the lambda binding this variable is a "one-shot" lambda; that is, whether it is applied at most once.

This information may be useful in optimisation, as computations may safely be floated inside such a lambda without risk of duplicating work.

Constructors
NoLBVarInfoNo information
IsOneShotLambdaThe lambda is applied at most once).
show/hide Instances
noLBVarInfo :: LBVarInfo
It is always safe to assume that an Id has no lambda-bound variable information
hasNoLBVarInfo :: LBVarInfo -> Bool
lbvarInfo :: IdInfo -> LBVarInfo
Info about a lambda-bound variable, if the Id is one
setLBVarInfo :: IdInfo -> LBVarInfo -> IdInfo
Tick-box Info
data TickBoxOp
Tick box for Hpc-style coverage
Constructors
TickBox Module !TickBoxId
show/hide Instances
type TickBoxId = Int
Produced by Haddock version 2.4.2