Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data GenStgArg occ
- data GenStgTopBinding bndr occ
- = StgTopLifted (GenStgBinding bndr occ)
- | StgTopStringLit bndr ByteString
- data GenStgBinding bndr occ
- data GenStgExpr bndr occ
- = StgApp occ [GenStgArg occ]
- | StgLit Literal
- | StgConApp DataCon [GenStgArg occ] [Type]
- | StgOpApp StgOp [GenStgArg occ] Type
- | StgLam (NonEmpty bndr) StgExpr
- | StgCase (GenStgExpr bndr occ) bndr AltType [GenStgAlt bndr occ]
- | StgLet (GenStgBinding bndr occ) (GenStgExpr bndr occ)
- | StgLetNoEscape (GenStgBinding bndr occ) (GenStgExpr bndr occ)
- | StgTick (Tickish bndr) (GenStgExpr bndr occ)
- data GenStgRhs bndr occ
- = StgRhsClosure CostCentreStack StgBinderInfo [occ] !UpdateFlag [bndr] (GenStgExpr bndr occ)
- | StgRhsCon CostCentreStack DataCon [GenStgArg occ]
- type GenStgAlt bndr occ = (AltCon, [bndr], 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 StgTopBinding = GenStgTopBinding Id Id
- type StgBinding = GenStgBinding Id Id
- type StgExpr = GenStgExpr Id Id
- type StgRhs = GenStgRhs Id Id
- type StgAlt = GenStgAlt Id Id
- type InStgArg = StgArg
- type InStgTopBinding = StgTopBinding
- type InStgBinding = StgBinding
- type InStgExpr = StgExpr
- type InStgRhs = StgRhs
- type InStgAlt = StgAlt
- type OutStgArg = StgArg
- type OutStgTopBinding = StgTopBinding
- type OutStgBinding = StgBinding
- type OutStgExpr = StgExpr
- type OutStgRhs = StgRhs
- type OutStgAlt = StgAlt
- data StgOp
- topStgBindHasCafRefs :: GenStgTopBinding bndr Id -> Bool
- stgArgHasCafRefs :: GenStgArg Id -> Bool
- stgRhsArity :: StgRhs -> Int
- isDllConApp :: DynFlags -> Module -> DataCon -> [StgArg] -> Bool
- stgArgType :: StgArg -> Type
- stripStgTicksTop :: (Tickish Id -> Bool) -> StgExpr -> ([Tickish Id], StgExpr)
- stgCaseBndrInScope :: AltType -> Bool -> Bool
- pprStgBinding :: StgBinding -> SDoc
- pprStgTopBindings :: [StgTopBinding] -> SDoc
Documentation
data GenStgTopBinding bndr occ Source #
A top-level binding.
StgTopLifted (GenStgBinding bndr occ) | |
StgTopStringLit bndr ByteString |
Instances
(OutputableBndr bndr, Outputable bdee, Ord bdee) => Outputable (GenStgTopBinding bndr bdee) # | |
data GenStgBinding bndr occ Source #
Instances
(OutputableBndr bndr, Outputable bdee, Ord bdee) => Outputable (GenStgBinding bndr bdee) # | |
data GenStgExpr bndr occ Source #
StgApp occ [GenStgArg occ] | |
StgLit Literal | |
StgConApp DataCon [GenStgArg occ] [Type] | |
StgOpApp StgOp [GenStgArg occ] Type | |
StgLam (NonEmpty bndr) StgExpr | |
StgCase (GenStgExpr bndr occ) bndr AltType [GenStgAlt bndr occ] | |
StgLet (GenStgBinding bndr occ) (GenStgExpr bndr occ) | |
StgLetNoEscape (GenStgBinding bndr occ) (GenStgExpr bndr occ) | |
StgTick (Tickish bndr) (GenStgExpr bndr occ) |
Instances
(OutputableBndr bndr, Outputable bdee, Ord bdee) => Outputable (GenStgExpr bndr bdee) # | |
data GenStgRhs bndr occ Source #
StgRhsClosure CostCentreStack StgBinderInfo [occ] !UpdateFlag [bndr] (GenStgExpr bndr occ) | |
StgRhsCon CostCentreStack DataCon [GenStgArg occ] |
type GenStgAlt bndr occ = (AltCon, [bndr], GenStgExpr bndr occ) Source #
data UpdateFlag Source #
Instances
Outputable UpdateFlag # | |
isUpdatable :: UpdateFlag -> Bool Source #
data StgBinderInfo Source #
satCallsOnly :: StgBinderInfo -> Bool Source #
type StgTopBinding = GenStgTopBinding Id Id Source #
type StgBinding = GenStgBinding Id Id Source #
type InStgTopBinding = StgTopBinding Source #
type InStgBinding = StgBinding Source #
type OutStgTopBinding = StgTopBinding Source #
type OutStgBinding = StgBinding Source #
type OutStgExpr = StgExpr Source #
topStgBindHasCafRefs :: GenStgTopBinding bndr 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 because we have lost the type arguments.
stripStgTicksTop :: (Tickish Id -> Bool) -> StgExpr -> ([Tickish Id], StgExpr) Source #
Strip ticks of a given type from an STG expression
Given an alt type and whether the program is unarised, return whether the case binder is in scope.
Case binders of unboxed tuple or unboxed sum type always dead after the unariser has run. See Note [Post-unarisation invariants].
pprStgBinding :: StgBinding -> SDoc Source #
pprStgTopBindings :: [StgTopBinding] -> SDoc Source #