ghc-6.10.3: The GHC APIContentsIndex
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
isCheapUnfolding :: Unfolding -> Bool
isCompulsoryUnfolding :: Unfolding -> Bool
hasUnfolding :: Unfolding -> Bool
hasSomeUnfolding :: Unfolding -> Bool
neverUnfold :: Unfolding -> Bool
couldBeSmallEnoughToInline :: Int -> CoreExpr -> Bool
certainlyWillInline :: Unfolding -> Bool
smallEnoughToInline :: Unfolding -> Bool
callSiteInline :: DynFlags -> Bool -> Id -> Bool -> [Bool] -> CallCtxt -> Maybe CoreExpr
data CallCtxt
= BoringCtxt
| ArgCtxt Bool Int
| CaseCtxt
Documentation
data Unfolding
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
When unfolding should take place
show/hide Instances
noUnfolding :: Unfolding
There is no known Unfolding
mkTopUnfolding :: CoreExpr -> Unfolding
mkImplicitUnfolding :: CoreExpr -> Unfolding
mkUnfolding :: Bool -> CoreExpr -> Unfolding
mkCompulsoryUnfolding :: CoreExpr -> Unfolding
seqUnfolding :: Unfolding -> ()
evaldUnfolding :: Unfolding
This unfolding marks the associated thing as being evaluated
mkOtherCon :: [AltCon] -> Unfolding
otherCons :: Unfolding -> [AltCon]
The constructors that the unfolding could never be: returns [] if no information is available
unfoldingTemplate :: Unfolding -> CoreExpr
Retrieves the template of an unfolding: panics if none is known
maybeUnfoldingTemplate :: Unfolding -> Maybe CoreExpr
Retrieves the template of an unfolding if possible
isEvaldUnfolding :: Unfolding -> Bool
Determines if it possibly the case that the unfolding will yield a value. Unlike isValueUnfolding it returns True for OtherCon
isValueUnfolding :: Unfolding -> Bool
Determines if it is certainly the case that the unfolding will yield a value (something in HNF): returns False if unsure
isCheapUnfolding :: Unfolding -> Bool
Is the thing we will unfold into certainly cheap?
isCompulsoryUnfolding :: Unfolding -> Bool
Must this unfolding happen for the code to be executable?
hasUnfolding :: Unfolding -> Bool
Do we have an available or compulsory unfolding?
hasSomeUnfolding :: Unfolding -> Bool
Only returns False if there is no unfolding information available at all
neverUnfold :: Unfolding -> Bool
Similar to not . hasUnfolding, but also returns True if it has an unfolding that says it should never occur
couldBeSmallEnoughToInline :: Int -> CoreExpr -> Bool
certainlyWillInline :: Unfolding -> Bool
smallEnoughToInline :: Unfolding -> Bool
callSiteInline :: DynFlags -> Bool -> Id -> Bool -> [Bool] -> CallCtxt -> Maybe CoreExpr
data CallCtxt
Constructors
BoringCtxt
ArgCtxt Bool Int
CaseCtxt
show/hide Instances
Produced by Haddock version 2.4.2