ghc-6.10.4: The GHC APIContentsIndex
ClosureInfo
Documentation
data ClosureInfo
Constructors
ClosureInfo
closureName :: !Name
closureLFInfo :: !LambdaFormInfo
closureSMRep :: !SMRep
closureSRT :: !C_SRT
closureType :: !Type
closureDescr :: !String
ConInfo
closureCon :: !DataCon
closureSMRep :: !SMRep
data LambdaFormInfo
Constructors
LFReEntrant TopLevelFlag !Int !Bool ArgDescr
LFCon DataCon
LFThunk TopLevelFlag !Bool !Bool StandardFormInfo !Bool
LFUnknown !Bool
LFLetNoEscape !Int
LFBlackHole CLabel
data StandardFormInfo
Constructors
NonStandardThunk
SelectorThunk WordOff
ApThunk Int
data SMRep
data ArgDescr
Constructors
ArgSpec !StgHalfWord
ArgGen Liveness
data Liveness
Constructors
SmallLiveness StgWord
BigLiveness CLabel
data C_SRT
Constructors
NoC_SRT
C_SRT !CLabel !WordOff !StgHalfWord
show/hide Instances
needsSRT :: C_SRT -> Bool
mkLFThunk
mkLFReEntrant :: TopLevelFlag -> [Id] -> [Id] -> ArgDescr -> LambdaFormInfo
mkConLFInfo :: DataCon -> LambdaFormInfo
mkSelectorLFInfo
mkApLFInfo
mkLFImported :: Id -> LambdaFormInfo
mkLFArgument
mkLFLetNoEscape
mkClosureInfo :: Bool -> Id -> LambdaFormInfo -> Int -> Int -> C_SRT -> String -> ClosureInfo
mkConInfo :: Bool -> DataCon -> Int -> Int -> ClosureInfo
maybeIsLFCon :: LambdaFormInfo -> Maybe DataCon
closureSize :: ClosureInfo -> WordOff
closureNonHdrSize :: ClosureInfo -> WordOff
closureGoodStuffSize :: ClosureInfo -> WordOff
closurePtrsSize :: ClosureInfo -> WordOff
slopSize
infoTableLabelFromCI :: ClosureInfo -> CLabel
closureLabelFromCI
isLFThunk :: LambdaFormInfo -> Bool
closureUpdReqd :: ClosureInfo -> Bool
closureNeedsUpdSpace
closureIsThunk :: ClosureInfo -> Bool
closureSingleEntry :: ClosureInfo -> Bool
closureReEntrant :: ClosureInfo -> Bool
isConstrClosure_maybe :: ClosureInfo -> Maybe DataCon
closureFunInfo :: ClosureInfo -> Maybe (Int, ArgDescr)
isStandardFormThunk :: LambdaFormInfo -> Bool
isKnownFun :: LambdaFormInfo -> Bool
funTag :: ClosureInfo -> Int
funTagLFInfo :: LambdaFormInfo -> Int
tagForArity :: Int -> Maybe Int
enterIdLabel
enterLocalIdLabel
enterReturnPtLabel
nodeMustPointToIt :: LambdaFormInfo -> Bool
data CallMethod
Constructors
EnterIt
JumpToIt CLabel
ReturnIt
ReturnCon DataCon
SlowCall
DirectEntry CLabel Int
getCallMethod :: Name -> LambdaFormInfo -> Int -> CallMethod
blackHoleOnEntry :: ClosureInfo -> Bool
staticClosureRequired :: Name -> StgBinderInfo -> LambdaFormInfo -> Bool
getClosureType :: Bool -> WordOff -> LambdaFormInfo -> ClosureType
isToplevClosure :: ClosureInfo -> Bool
closureValDescr :: ClosureInfo -> String
closureTypeDescr :: ClosureInfo -> String
isStaticClosure :: ClosureInfo -> Bool
cafBlackHoleClosureInfo
seCafBlackHoleClosureInfo
staticClosureNeedsLink :: ClosureInfo -> Bool
Produced by Haddock version 2.4.2