ghc-6.10.3: The GHC APIContentsIndex
StgSyn
Documentation
data GenStgArg occ
Constructors
StgVarArg occ
StgLitArg Literal
StgTypeArg Type
show/hide Instances
type GenStgLiveVars occ = UniqSet occ
data GenStgBinding bndr occ
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
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
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)
data AltType
Constructors
PolyAlt
UbxTupAlt TyCon
AlgAlt TyCon
PrimAlt TyCon
show/hide Instances
data UpdateFlag
Constructors
ReEntrant
Updatable
SingleEntry
show/hide Instances
isUpdatable :: UpdateFlag -> Bool
data StgBinderInfo
noBinderInfo :: StgBinderInfo
stgSatOcc :: StgBinderInfo
stgUnsatOcc :: StgBinderInfo
satCallsOnly :: StgBinderInfo -> Bool
combineStgBinderInfo :: StgBinderInfo -> StgBinderInfo -> StgBinderInfo
type StgArg = GenStgArg Id
type StgLiveVars = GenStgLiveVars Id
type StgBinding = GenStgBinding Id Id
type StgExpr = GenStgExpr Id Id
type StgRhs = GenStgRhs Id Id
type StgAlt = GenStgAlt Id Id
data StgOp
Constructors
StgPrimOp PrimOp
StgFCallOp ForeignCall Unique
data SRT
Constructors
NoSRT
SRTEntries IdSet
SRT !Int !Int !Bitmap
stgBindHasCafRefs :: GenStgBinding bndr Id -> Bool
stgArgHasCafRefs :: GenStgArg Id -> Bool
stgRhsArity :: StgRhs -> Int
isDllConApp :: PackageId -> DataCon -> [StgArg] -> Bool
isStgTypeArg :: StgArg -> Bool
stgArgType :: StgArg -> Type
pprStgBinding :: StgBinding -> SDoc
pprStgBindings :: [StgBinding] -> SDoc
pprStgBindingsWithSRTs :: [(StgBinding, [(Id, [Id])])] -> SDoc
Produced by Haddock version 2.4.2