Safe Haskell | None |
---|
- data IdDetails
- = VanillaId
- | RecSelId {
- sel_tycon :: TyCon
- sel_naughty :: Bool
- | DataConWorkId DataCon
- | DataConWrapId DataCon
- | ClassOpId Class
- | PrimOpId PrimOp
- | FCallId ForeignCall
- | TickBoxOpId TickBoxOp
- | DFunId Int Bool
- pprIdDetails :: IdDetails -> SDoc
- coVarDetails :: IdDetails
- 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
- strictnessInfo :: IdInfo -> Maybe StrictSig
- setStrictnessInfo :: IdInfo -> Maybe StrictSig -> IdInfo
- demandInfo :: IdInfo -> Maybe Demand
- setDemandInfo :: IdInfo -> Maybe Demand -> IdInfo
- pprStrictness :: Maybe StrictSig -> SDoc
- unfoldingInfo :: IdInfo -> Unfolding
- setUnfoldingInfo :: IdInfo -> Unfolding -> IdInfo
- setUnfoldingInfoLazily :: IdInfo -> Unfolding -> IdInfo
- type InlinePragInfo = InlinePragma
- inlinePragInfo :: IdInfo -> InlinePragma
- setInlinePragInfo :: IdInfo -> InlinePragma -> IdInfo
- data OccInfo
- = NoOccInfo
- | IAmDead
- | OneOcc !InsideLam !OneBranch !InterestingCxt
- | IAmALoopBreaker !RulesOnly
- isDeadOcc :: OccInfo -> Bool
- isStrongLoopBreaker :: OccInfo -> Bool
- isWeakLoopBreaker :: 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
- emptySpecInfo :: SpecInfo
- isEmptySpecInfo :: SpecInfo -> Bool
- specInfoFreeVars :: SpecInfo -> VarSet
- specInfoRules :: SpecInfo -> [CoreRule]
- seqSpecInfo :: SpecInfo -> ()
- setSpecInfoHead :: Name -> SpecInfo -> SpecInfo
- specInfo :: IdInfo -> SpecInfo
- setSpecInfo :: IdInfo -> SpecInfo -> IdInfo
- data CafInfo
- ppCafInfo :: CafInfo -> SDoc
- mayHaveCafRefs :: CafInfo -> Bool
- cafInfo :: IdInfo -> CafInfo
- setCafInfo :: IdInfo -> CafInfo -> IdInfo
- data LBVarInfo
- noLBVarInfo :: LBVarInfo
- hasNoLBVarInfo :: LBVarInfo -> Bool
- lbvarInfo :: IdInfo -> LBVarInfo
- setLBVarInfo :: IdInfo -> LBVarInfo -> IdInfo
- data TickBoxOp = TickBox Module !TickBoxId
- type TickBoxId = Int
The IdDetails type
The IdDetails
of an Id
give stable, and necessary,
information about the Id.
VanillaId | |
RecSelId | The |
DataConWorkId DataCon | The |
DataConWrapId DataCon | The |
ClassOpId Class | The |
PrimOpId PrimOp | The |
FCallId ForeignCall | The |
TickBoxOpId TickBoxOp | The |
DFunId Int Bool | A dictionary function. Int = the number of silent arguments to the dfun e.g. class D a => C a where ... instance C a => C [a] has is_silent = 1, because the dfun has type dfun :: (D a, C a) => C [a] See the DFun Superclass Invariant in TcInstDcls Bool = True = the class has only one method, so may be implemented with a newtype, so it might be bad to be strict on this dictionary |
pprIdDetails :: IdDetails -> SDocSource
The IdInfo type
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 Id
s 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
.
Basic IdInfo
that carries no useful information whatsoever
More informative IdInfo
we can use when we know the Id
has no CAF references
megaSeqIdInfo :: IdInfo -> ()Source
Evaluate all the fields of the IdInfo
that are generally demanded by the
compiler
Zapping various forms of Info
zapLamInfo :: IdInfo -> Maybe IdInfoSource
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 IdInfoSource
Remove demand info on the IdInfo
if it is present, otherwise return Nothing
zapFragileInfo :: IdInfo -> Maybe IdInfoSource
Zap info that depends on free variables
The ArityInfo type
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.
It is always safe to assume that an Id
has an arity of 0
setArityInfo :: IdInfo -> ArityInfo -> IdInfoSource
ppArityInfo :: Int -> SDocSource
Demand and strictness Info
strictnessInfo :: IdInfo -> Maybe StrictSigSource
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.
demandInfo :: IdInfo -> Maybe DemandSource
Id demand information. Similarly we want to know if there's no known demand yet, for when we are looking for CPR info
Unfolding Info
unfoldingInfo :: IdInfo -> UnfoldingSource
The Id
s unfolding
setUnfoldingInfo :: IdInfo -> Unfolding -> IdInfoSource
The InlinePragInfo type
type InlinePragInfo = InlinePragmaSource
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 -> InlinePragmaSource
Any inline pragma atached to the Id
setInlinePragInfo :: IdInfo -> InlinePragma -> IdInfoSource
The OccInfo type
Identifier occurrence information
NoOccInfo | There are many occurrences, or unknown occurences |
IAmDead | Marks unused variables. Sometimes useful for lambda and case-bound variables. |
OneOcc !InsideLam !OneBranch !InterestingCxt | Occurs exactly once, not inside a rule |
IAmALoopBreaker !RulesOnly | This 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 |
setOccInfo :: IdInfo -> OccInfo -> IdInfoSource
The SpecInfo type
Records the specializations of this Id
that we know about
in the form of rewrite CoreRule
s that target them
emptySpecInfo :: SpecInfoSource
Assume that no specilizations exist: always safe
specInfoFreeVars :: SpecInfo -> VarSetSource
Retrieve the locally-defined free variables of both the left and right hand sides of the specialization rules
specInfoRules :: SpecInfo -> [CoreRule]Source
seqSpecInfo :: SpecInfo -> ()Source
setSpecInfoHead :: Name -> SpecInfo -> SpecInfoSource
Change the name of the function the rule is keyed on on all of the CoreRule
s
specInfo :: IdInfo -> SpecInfoSource
Specialisations of the Id
s function which exist
See Note [Specialisations and RULES in IdInfo]
setSpecInfo :: IdInfo -> SpecInfo -> IdInfoSource
The CAFInfo type
Records whether an Id
makes Constant Applicative Form references
MayHaveCafRefs | Indicates that the
|
NoCafRefs | A function or static constructor that refers to no CAFs. |
mayHaveCafRefs :: CafInfo -> BoolSource
setCafInfo :: IdInfo -> CafInfo -> IdInfoSource
The LBVarInfo type
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.
NoLBVarInfo | No information |
IsOneShotLambda | The lambda is applied at most once). |
noLBVarInfo :: LBVarInfoSource
It is always safe to assume that an Id
has no lambda-bound variable information
setLBVarInfo :: IdInfo -> LBVarInfo -> IdInfoSource