ghc-6.12.2: The GHC APISource codeContentsIndex
CoreUnfold
Synopsis
data Unfolding
data UnfoldingGuidance
noUnfolding :: Unfolding
mkTopUnfolding :: CoreExpr -> Unfolding
mkImplicitUnfolding :: CoreExpr -> Unfolding
mkUnfolding :: Bool -> CoreExpr -> Unfolding
mkCompulsoryUnfolding :: CoreExpr -> Unfolding
seqUnfolding :: Unfolding -> ()
evaldUnfolding :: Unfolding
mkOtherCon :: [AltCon] -> Unfolding
otherCons :: Unfolding -> [AltCon]
unfoldingTemplate :: Unfolding -> CoreExpr
maybeUnfoldingTemplate :: Unfolding -> Maybe CoreExpr
isEvaldUnfolding :: Unfolding -> Bool
isValueUnfolding :: Unfolding -> Bool
isExpandableUnfolding :: Unfolding -> Bool
isCompulsoryUnfolding :: Unfolding -> Bool
hasUnfolding :: Unfolding -> Bool
hasSomeUnfolding :: Unfolding -> Bool
neverUnfold :: Unfolding -> Bool
interestingArg :: CoreExpr -> ArgSummary
data ArgSummary
= TrivArg
| NonTrivArg
| ValueArg
couldBeSmallEnoughToInline :: Int -> CoreExpr -> Bool
certainlyWillInline :: Unfolding -> Bool
smallEnoughToInline :: Unfolding -> Bool
callSiteInline :: DynFlags -> Bool -> Id -> Bool -> [ArgSummary] -> CallCtxt -> Maybe CoreExpr
data CallCtxt
= BoringCtxt
| ArgCtxt Bool Int
| ValAppCtxt
| CaseCtxt
Documentation
data Unfolding Source
Records the unfolding of an identifier, which is approximately the form the identifier would have if we substituted its definition in for the identifier. This type should be treated as abstract everywhere except in CoreUnfold
show/hide Instances
data UnfoldingGuidance Source
When unfolding should take place
show/hide Instances
noUnfolding :: UnfoldingSource
There is no known Unfolding
mkTopUnfolding :: CoreExpr -> UnfoldingSource
mkImplicitUnfolding :: CoreExpr -> UnfoldingSource
mkUnfolding :: Bool -> CoreExpr -> UnfoldingSource
mkCompulsoryUnfolding :: CoreExpr -> UnfoldingSource
seqUnfolding :: Unfolding -> ()Source
evaldUnfolding :: UnfoldingSource
This unfolding marks the associated thing as being evaluated
mkOtherCon :: [AltCon] -> UnfoldingSource
otherCons :: Unfolding -> [AltCon]Source
The constructors that the unfolding could never be: returns [] if no information is available
unfoldingTemplate :: Unfolding -> CoreExprSource
Retrieves the template of an unfolding: panics if none is known
maybeUnfoldingTemplate :: Unfolding -> Maybe CoreExprSource
Retrieves the template of an unfolding if possible
isEvaldUnfolding :: Unfolding -> BoolSource
Determines if it possibly the case that the unfolding will yield a value. Unlike isValueUnfolding it returns True for OtherCon
isValueUnfolding :: Unfolding -> BoolSource
Determines if it is certainly the case that the unfolding will yield a value (something in HNF): returns False if unsure
isExpandableUnfolding :: Unfolding -> BoolSource
isCompulsoryUnfolding :: Unfolding -> BoolSource
Must this unfolding happen for the code to be executable?
hasUnfolding :: Unfolding -> BoolSource
Do we have an available or compulsory unfolding?
hasSomeUnfolding :: Unfolding -> BoolSource
Only returns False if there is no unfolding information available at all
neverUnfold :: Unfolding -> BoolSource
Similar to not . hasUnfolding, but also returns True if it has an unfolding that says it should never occur
interestingArg :: CoreExpr -> ArgSummarySource
data ArgSummary Source
Constructors
TrivArg
NonTrivArg
ValueArg
show/hide Instances
couldBeSmallEnoughToInline :: Int -> CoreExpr -> BoolSource
certainlyWillInline :: Unfolding -> BoolSource
smallEnoughToInline :: Unfolding -> BoolSource
callSiteInline :: DynFlags -> Bool -> Id -> Bool -> [ArgSummary] -> CallCtxt -> Maybe CoreExprSource
data CallCtxt Source
Constructors
BoringCtxt
ArgCtxt Bool Int
ValAppCtxt
CaseCtxt
show/hide Instances
Produced by Haddock version 2.6.1