| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
GHC.Types.Id.Info
Synopsis
- data IdDetails
- pprIdDetails :: IdDetails -> SDoc
- coVarDetails :: IdDetails
- isCoVarDetails :: IdDetails -> Bool
- type JoinArity = Int
- isJoinIdDetails_maybe :: IdDetails -> Maybe (JoinArity, Maybe [CbvMark])
- data RecSelParent
- data IdInfo
- vanillaIdInfo :: IdInfo
- noCafIdInfo :: IdInfo
- data OneShotInfo
- oneShotInfo :: IdInfo -> OneShotInfo
- noOneShotInfo :: OneShotInfo
- hasNoOneShotInfo :: OneShotInfo -> Bool
- setOneShotInfo :: IdInfo -> OneShotInfo -> IdInfo
- zapLamInfo :: IdInfo -> Maybe IdInfo
- zapFragileInfo :: IdInfo -> Maybe IdInfo
- zapDemandInfo :: IdInfo -> Maybe IdInfo
- zapUsageInfo :: IdInfo -> Maybe IdInfo
- zapUsageEnvInfo :: IdInfo -> Maybe IdInfo
- zapUsedOnceInfo :: IdInfo -> Maybe IdInfo
- zapTailCallInfo :: IdInfo -> Maybe IdInfo
- zapCallArityInfo :: IdInfo -> IdInfo
- trimUnfolding :: Unfolding -> Unfolding
- type ArityInfo = Arity
- unknownArity :: Arity
- arityInfo :: IdInfo -> ArityInfo
- setArityInfo :: IdInfo -> ArityInfo -> IdInfo
- ppArityInfo :: Int -> SDoc
- callArityInfo :: IdInfo -> ArityInfo
- setCallArityInfo :: IdInfo -> ArityInfo -> IdInfo
- dmdSigInfo :: IdInfo -> DmdSig
- setDmdSigInfo :: IdInfo -> DmdSig -> IdInfo
- cprSigInfo :: IdInfo -> CprSig
- setCprSigInfo :: IdInfo -> CprSig -> IdInfo
- demandInfo :: IdInfo -> Demand
- setDemandInfo :: IdInfo -> Demand -> IdInfo
- pprStrictness :: DmdSig -> SDoc
- realUnfoldingInfo :: IdInfo -> Unfolding
- unfoldingInfo :: IdInfo -> Unfolding
- setUnfoldingInfo :: IdInfo -> Unfolding -> IdInfo
- hasInlineUnfolding :: IdInfo -> Bool
- type InlinePragInfo = InlinePragma
- inlinePragInfo :: IdInfo -> InlinePragma
- setInlinePragInfo :: IdInfo -> InlinePragma -> IdInfo
- data OccInfo- = ManyOccs { - occ_tail :: !TailCallInfo
 
- | IAmDead
- | OneOcc { }
- | IAmALoopBreaker { - occ_rules_only :: !RulesOnly
- occ_tail :: !TailCallInfo
 
 
- = ManyOccs { 
- isDeadOcc :: OccInfo -> Bool
- isStrongLoopBreaker :: OccInfo -> Bool
- isWeakLoopBreaker :: OccInfo -> Bool
- occInfo :: IdInfo -> OccInfo
- setOccInfo :: IdInfo -> OccInfo -> IdInfo
- data InsideLam
- type BranchCount = Int
- data TailCallInfo
- tailCallInfo :: OccInfo -> TailCallInfo
- isAlwaysTailCalled :: OccInfo -> Bool
- data RuleInfo = RuleInfo [CoreRule] DVarSet
- emptyRuleInfo :: RuleInfo
- isEmptyRuleInfo :: RuleInfo -> Bool
- ruleInfoFreeVars :: RuleInfo -> DVarSet
- ruleInfoRules :: RuleInfo -> [CoreRule]
- setRuleInfoHead :: Name -> RuleInfo -> RuleInfo
- ruleInfo :: IdInfo -> RuleInfo
- setRuleInfo :: IdInfo -> RuleInfo -> IdInfo
- tagSigInfo :: IdInfo -> Maybe TagSig
- data CafInfo
- ppCafInfo :: CafInfo -> SDoc
- mayHaveCafRefs :: CafInfo -> Bool
- cafInfo :: IdInfo -> CafInfo
- setCafInfo :: IdInfo -> CafInfo -> IdInfo
- data LambdaFormInfo
- lfInfo :: IdInfo -> Maybe LambdaFormInfo
- setLFInfo :: IdInfo -> LambdaFormInfo -> IdInfo
- setTagSig :: IdInfo -> TagSig -> IdInfo
- tagSig :: IdInfo -> Maybe TagSig
- data TickBoxOp = TickBox Module !TickBoxId
- type TickBoxId = Int
- data LevityInfo
- levityInfo :: IdInfo -> LevityInfo
- setNeverRepPoly :: HasDebugCallStack => IdInfo -> Type -> IdInfo
- setLevityInfoWithType :: IdInfo -> Type -> IdInfo
- isNeverRepPolyIdInfo :: IdInfo -> Bool
The IdDetails type
Identifier Details
The IdDetails of an Id give stable, and necessary,
 information about the Id.
Constructors
| VanillaId | |
| RecSelId | The  | 
| Fields 
 | |
| DataConWorkId DataCon | The  | 
| DataConWrapId DataCon | The  | 
| ClassOpId Class | The  | 
| PrimOpId PrimOp | The  | 
| FCallId ForeignCall | The  | 
| TickBoxOpId TickBoxOp | The  | 
| DFunId Bool | A dictionary function. 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 | 
| CoVarId | A coercion variable This only covers un-lifted coercions, of type (t1 ~# t2) or (t1 ~R# t2), not their lifted variants | 
| JoinId JoinArity (Maybe [CbvMark]) | An  | 
| WorkerLikeId [CbvMark] | An  | 
Instances
pprIdDetails :: IdDetails -> SDoc Source #
coVarDetails :: IdDetails Source #
Just a synonym for CoVarId. Written separately so it can be
 exported in the hs-boot file.
The number of arguments that a join point takes. Unlike the arity of a function, this is a purely syntactic property and is fixed when the join point is created (or converted from a value). Both type and value arguments are counted.
data RecSelParent Source #
Recursive Selector Parent
Constructors
| RecSelData TyCon | |
| RecSelPatSyn PatSyn | 
Instances
| Outputable RecSelParent Source # | |
| Defined in GHC.Types.Id.Info Methods ppr :: RecSelParent -> SDoc Source # | |
| Eq RecSelParent Source # | |
| Defined in GHC.Types.Id.Info | |
The IdInfo type
Identifier Information
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.
Most of the IdInfo gives information about the value, or definition, of
 the Id, independent of its usage. Exceptions to this
 are demandInfo, occInfo, oneShotInfo and callArityInfo.
Performance note: when we update IdInfo, we have to reallocate this
 entire record, so it is a good idea not to let this data structure get
 too big.
Instances
vanillaIdInfo :: IdInfo Source #
Basic IdInfo that carries no useful information whatsoever
noCafIdInfo :: IdInfo Source #
More informative IdInfo we can use when we know the Id has no CAF references
The OneShotInfo type
data OneShotInfo Source #
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.
See also Note [OneShotInfo overview] above.
Constructors
| NoOneShotInfo | No information | 
| OneShotLam | The lambda is applied at most once. | 
Instances
| Outputable OneShotInfo Source # | |
| Defined in GHC.Types.Basic Methods ppr :: OneShotInfo -> SDoc Source # | |
| Eq OneShotInfo Source # | |
| Defined in GHC.Types.Basic | |
oneShotInfo :: IdInfo -> OneShotInfo Source #
Info about a lambda-bound variable, if the Id is one
noOneShotInfo :: OneShotInfo Source #
It is always safe to assume that an Id has no lambda-bound variable information
hasNoOneShotInfo :: OneShotInfo -> Bool Source #
setOneShotInfo :: IdInfo -> OneShotInfo -> IdInfo infixl 1 Source #
Zapping various forms of Info
zapLamInfo :: IdInfo -> Maybe IdInfo Source #
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
zapUsageEnvInfo :: IdInfo -> Maybe IdInfo Source #
Remove usage environment info from the strictness signature on the IdInfo
zapCallArityInfo :: IdInfo -> IdInfo Source #
trimUnfolding :: Unfolding -> Unfolding Source #
The ArityInfo type
type ArityInfo = Arity Source #
Arity Information
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.
Invariant: the Arity of an Id must never exceed the number of
 value arguments that appear in the type of the Id.
 See Note [Arity and function types].
unknownArity :: Arity Source #
It is always safe to assume that an Id has an arity of 0
arityInfo :: IdInfo -> ArityInfo Source #
Id arity, as computed by GHC.Core.Opt.Arity. Specifies how many arguments
 this Id has to be applied to before it doesn any meaningful work.
ppArityInfo :: Int -> SDoc Source #
callArityInfo :: IdInfo -> ArityInfo Source #
How this is called. This is the number of arguments to which a binding can be eta-expanded without losing any sharing. n = all calls have at least n arguments
Demand and strictness Info
dmdSigInfo :: IdInfo -> DmdSig Source #
A strictness signature. Digests how a function uses its arguments
 if applied to at least arityInfo arguments.
cprSigInfo :: IdInfo -> CprSig Source #
Information on whether the function will ultimately return a freshly allocated constructor.
demandInfo :: IdInfo -> Demand Source #
ID demand information
pprStrictness :: DmdSig -> SDoc Source #
Unfolding Info
realUnfoldingInfo :: IdInfo -> Unfolding Source #
The Ids unfolding
unfoldingInfo :: IdInfo -> Unfolding Source #
Essentially returns the realUnfoldingInfo field, but does not expose the
 unfolding of a strong loop breaker.
This is the right thing to call if you plan to decide whether an unfolding will inline.
hasInlineUnfolding :: IdInfo -> Bool Source #
True of a non-loop-breaker Id that has a stable unfolding that is
   (a) always inlined; that is, with an UnfWhen guidance, or
   (b) a DFunUnfolding which never needs to be inlined
The InlinePragInfo type
type InlinePragInfo = InlinePragma Source #
Inline Pragma Information
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 -> InlinePragma Source #
Any inline pragma attached to the Id
setInlinePragInfo :: IdInfo -> InlinePragma -> IdInfo infixl 1 Source #
The OccInfo type
identifier Occurrence Information
Constructors
| ManyOccs | There are many occurrences, or unknown occurrences | 
| Fields 
 | |
| IAmDead | Marks unused variables. Sometimes useful for lambda and case-bound variables. | 
| OneOcc | Occurs exactly once (per branch), not inside a rule | 
| Fields 
 | |
| IAmALoopBreaker | 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 | 
| Fields 
 | |
isStrongLoopBreaker :: OccInfo -> Bool Source #
isWeakLoopBreaker :: OccInfo -> Bool Source #
Inside Lambda
Constructors
| IsInsideLam | Occurs inside a non-linear lambda Substituting a redex for this occurrence is dangerous because it might duplicate work. | 
| NotInsideLam | 
type BranchCount = Int Source #
data TailCallInfo Source #
Constructors
| AlwaysTailCalled JoinArity | |
| NoTailCallInfo | 
Instances
| Outputable TailCallInfo Source # | |
| Defined in GHC.Types.Basic Methods ppr :: TailCallInfo -> SDoc Source # | |
| Eq TailCallInfo Source # | |
| Defined in GHC.Types.Basic | |
tailCallInfo :: OccInfo -> TailCallInfo Source #
isAlwaysTailCalled :: OccInfo -> Bool Source #
The RuleInfo type
Rule Information
Records the specializations of this Id that we know about
 in the form of rewrite CoreRules that target them
emptyRuleInfo :: RuleInfo Source #
Assume that no specializations exist: always safe
isEmptyRuleInfo :: RuleInfo -> Bool Source #
ruleInfoFreeVars :: RuleInfo -> DVarSet Source #
Retrieve the locally-defined free variables of both the left and right hand sides of the specialization rules
ruleInfoRules :: RuleInfo -> [CoreRule] Source #
setRuleInfoHead :: Name -> RuleInfo -> RuleInfo Source #
Change the name of the function the rule is keyed on all of the CoreRules
ruleInfo :: IdInfo -> RuleInfo Source #
Specialisations of the Ids function which exist.
 See Note [Specialisations and RULES in IdInfo]
The CAFInfo type
Constant applicative form Information
Records whether an Id makes Constant Applicative Form references
Constructors
| MayHaveCafRefs | Indicates that the  
 | 
| NoCafRefs | A function or static constructor that refers to no CAFs. | 
mayHaveCafRefs :: CafInfo -> Bool Source #
The LambdaFormInfo type
data LambdaFormInfo Source #
Information about an identifier, from the code generator's point of view. Every identifier is bound to a LambdaFormInfo in the environment, which gives the code generator enough info to be able to tail call or return that identifier.
Instances
| Outputable LambdaFormInfo Source # | |
| Defined in GHC.StgToCmm.Types Methods ppr :: LambdaFormInfo -> SDoc Source # | |
Tick-box Info
Tick box for Hpc-style coverage
Instances
Levity info
data LevityInfo Source #
Instances
| Outputable LevityInfo Source # | |
| Defined in GHC.Types.Id.Info Methods ppr :: LevityInfo -> SDoc Source # | |
| Eq LevityInfo Source # | |
| Defined in GHC.Types.Id.Info | |
levityInfo :: IdInfo -> LevityInfo Source #
When applied, will this Id ever have a representation-polymorphic type?
setNeverRepPoly :: HasDebugCallStack => IdInfo -> Type -> IdInfo infixl 1 Source #
Marks an IdInfo describing an Id that is never representation-polymorphic (even when applied). The Type is only there for checking that it's really never representation-polymorphic.
isNeverRepPolyIdInfo :: IdInfo -> Bool Source #