ghc-6.12.3: The GHC APISource codeContentsIndex
StgSyn
Documentation
data GenStgArg occ Source
Constructors
StgVarArg occ
StgLitArg Literal
StgTypeArg Type
show/hide Instances
type GenStgLiveVars occ = UniqSet occSource
data GenStgBinding bndr occ Source
Constructors
StgNonRec bndr (GenStgRhs bndr occ)
StgRec [(bndr, GenStgRhs bndr occ)]
show/hide Instances
(Outputable bndr, Outputable bdee, Ord bdee) => Outputable (GenStgBinding bndr bdee)
data GenStgExpr bndr occ Source
Constructors
StgApp occ [GenStgArg occ]
StgLit Literal
StgConApp DataCon [GenStgArg occ]
StgOpApp StgOp [GenStgArg occ] Type
StgLam Type [bndr] StgExpr
StgCase (GenStgExpr bndr occ) (GenStgLiveVars occ) (GenStgLiveVars occ) bndr SRT AltType [GenStgAlt bndr occ]
StgLet (GenStgBinding bndr occ) (GenStgExpr bndr occ)
StgLetNoEscape (GenStgLiveVars occ) (GenStgLiveVars occ) (GenStgBinding bndr occ) (GenStgExpr bndr occ)
StgSCC CostCentre (GenStgExpr bndr occ)
StgTick Module Int (GenStgExpr bndr occ)
show/hide Instances
(Outputable bndr, Outputable bdee, Ord bdee) => Outputable (GenStgExpr bndr bdee)
data GenStgRhs bndr occ Source
Constructors
StgRhsClosure CostCentreStack StgBinderInfo [occ] !UpdateFlag SRT [bndr] (GenStgExpr bndr occ)
StgRhsCon CostCentreStack DataCon [GenStgArg occ]
show/hide Instances
(Outputable bndr, Outputable bdee, Ord bdee) => Outputable (GenStgRhs bndr bdee)
type GenStgAlt bndr occ = (AltCon, [bndr], [Bool], GenStgExpr bndr occ)Source
data AltType Source
Constructors
PolyAlt
UbxTupAlt TyCon
AlgAlt TyCon
PrimAlt TyCon
show/hide Instances
data UpdateFlag Source
Constructors
ReEntrant
Updatable
SingleEntry
show/hide Instances
isUpdatable :: UpdateFlag -> BoolSource
data StgBinderInfo Source
noBinderInfo :: StgBinderInfoSource
stgSatOcc :: StgBinderInfoSource
stgUnsatOcc :: StgBinderInfoSource
satCallsOnly :: StgBinderInfo -> BoolSource
combineStgBinderInfo :: StgBinderInfo -> StgBinderInfo -> StgBinderInfoSource
type StgArg = GenStgArg IdSource
type StgLiveVars = GenStgLiveVars IdSource
type StgBinding = GenStgBinding Id IdSource
type StgExpr = GenStgExpr Id IdSource
type StgRhs = GenStgRhs Id IdSource
type StgAlt = GenStgAlt Id IdSource
data StgOp Source
Constructors
StgPrimOp PrimOp
StgPrimCallOp PrimCall
StgFCallOp ForeignCall Unique
data SRT Source
Constructors
NoSRT
SRTEntries IdSet
SRT !Int !Int !Bitmap
stgBindHasCafRefs :: GenStgBinding bndr Id -> BoolSource
stgArgHasCafRefs :: GenStgArg Id -> BoolSource
stgRhsArity :: StgRhs -> IntSource
isDllConApp :: PackageId -> DataCon -> [StgArg] -> BoolSource
isStgTypeArg :: StgArg -> BoolSource
stgArgType :: StgArg -> TypeSource
pprStgBinding :: StgBinding -> SDocSource
pprStgBindings :: [StgBinding] -> SDocSource
pprStgBindingsWithSRTs :: [(StgBinding, [(Id, [Id])])] -> SDocSource
Produced by Haddock version 2.6.1