| Safe Haskell | None |
|---|---|
| Language | Haskell98 |
StgSyn
- data GenStgArg occ
- type GenStgLiveVars occ = UniqSet occ
- data GenStgBinding bndr occ
- data GenStgExpr bndr occ
- = StgApp occ [GenStgArg occ]
- | StgLit Literal
- | StgConApp DataCon [GenStgArg occ]
- | StgOpApp StgOp [GenStgArg occ] Type
- | StgLam [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 !Bool !Bool (GenStgExpr bndr occ)
- | StgTick Module Int (GenStgExpr bndr occ)
- data GenStgRhs bndr occ
- = StgRhsClosure CostCentreStack StgBinderInfo [occ] !UpdateFlag SRT [bndr] (GenStgExpr bndr occ)
- | StgRhsCon CostCentreStack DataCon [GenStgArg occ]
- type GenStgAlt bndr occ = (AltCon, [bndr], [Bool], GenStgExpr bndr occ)
- data AltType
- data UpdateFlag
- 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
- data SRT
- stgBindHasCafRefs :: GenStgBinding bndr Id -> Bool
- stgArgHasCafRefs :: GenStgArg Id -> Bool
- stgRhsArity :: StgRhs -> Int
- isDllConApp :: DynFlags -> Module -> DataCon -> [StgArg] -> Bool
- stgArgType :: StgArg -> Type
- pprStgBinding :: StgBinding -> SDoc
- pprStgBindings :: [StgBinding] -> SDoc
- pprStgLVs :: Outputable occ => GenStgLiveVars occ -> SDoc
Documentation
Instances
| Outputable bdee => Outputable (GenStgArg bdee) |
type GenStgLiveVars occ = UniqSet occ Source
data GenStgBinding bndr occ Source
Instances
| (OutputableBndr 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 [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 !Bool !Bool (GenStgExpr bndr occ) | |
| StgTick Module Int (GenStgExpr bndr occ) |
Instances
| (OutputableBndr 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] |
Instances
| (OutputableBndr bndr, Outputable bdee, Ord bdee) => Outputable (GenStgRhs bndr bdee) |
type GenStgAlt bndr occ = (AltCon, [bndr], [Bool], GenStgExpr bndr occ) Source
Instances
isUpdatable :: UpdateFlag -> Bool Source
data StgBinderInfo Source
satCallsOnly :: StgBinderInfo -> Bool Source
type StgLiveVars = GenStgLiveVars Id Source
type StgBinding = GenStgBinding Id Id Source
type StgExpr = GenStgExpr Id Id Source
Constructors
| StgPrimOp PrimOp | |
| StgPrimCallOp PrimCall | |
| StgFCallOp ForeignCall Unique |
stgBindHasCafRefs :: GenStgBinding bndr Id -> Bool Source
stgArgHasCafRefs :: GenStgArg Id -> Bool Source
stgRhsArity :: StgRhs -> Int Source
isDllConApp :: DynFlags -> Module -> DataCon -> [StgArg] -> Bool Source
Does this constructor application refer to anything in a different *Windows* DLL? If so, we can't allocate it statically
stgArgType :: StgArg -> Type Source
Type of an StgArg
Very half baked becase we have lost the type arguments.
pprStgBinding :: StgBinding -> SDoc Source
pprStgBindings :: [StgBinding] -> SDoc Source
pprStgLVs :: Outputable occ => GenStgLiveVars occ -> SDoc Source