Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data StgArg
- data GenStgTopBinding pass
- = StgTopLifted (GenStgBinding pass)
- | StgTopStringLit Id ByteString
- data GenStgBinding pass
- data GenStgExpr pass
- = StgApp Id [StgArg]
- | StgLit Literal
- | StgConApp DataCon [StgArg] [Type]
- | StgOpApp StgOp [StgArg] Type
- | StgLam (NonEmpty (BinderP pass)) StgExpr
- | StgCase (GenStgExpr pass) (BinderP pass) AltType [GenStgAlt pass]
- | StgLet (XLet pass) (GenStgBinding pass) (GenStgExpr pass)
- | StgLetNoEscape (XLetNoEscape pass) (GenStgBinding pass) (GenStgExpr pass)
- | StgTick (Tickish Id) (GenStgExpr pass)
- data GenStgRhs pass
- = StgRhsClosure (XRhsClosure pass) CostCentreStack !UpdateFlag [BinderP pass] (GenStgExpr pass)
- | StgRhsCon CostCentreStack DataCon [StgArg]
- type GenStgAlt pass = (AltCon, [BinderP pass], GenStgExpr pass)
- data AltType
- data StgPass
- type family BinderP (pass :: StgPass)
- type family XRhsClosure (pass :: StgPass)
- type family XLet (pass :: StgPass)
- type family XLetNoEscape (pass :: StgPass)
- data NoExtFieldSilent
- noExtFieldSilent :: NoExtFieldSilent
- type OutputablePass pass = (Outputable (XLet pass), Outputable (XLetNoEscape pass), Outputable (XRhsClosure pass), OutputableBndr (BinderP pass))
- data UpdateFlag
- isUpdatable :: UpdateFlag -> Bool
- type StgTopBinding = GenStgTopBinding 'Vanilla
- type StgBinding = GenStgBinding 'Vanilla
- type StgExpr = GenStgExpr 'Vanilla
- type StgRhs = GenStgRhs 'Vanilla
- type StgAlt = GenStgAlt 'Vanilla
- type CgStgTopBinding = GenStgTopBinding 'CodeGen
- type CgStgBinding = GenStgBinding 'CodeGen
- type CgStgExpr = GenStgExpr 'CodeGen
- type CgStgRhs = GenStgRhs 'CodeGen
- type CgStgAlt = GenStgAlt 'CodeGen
- type LlStgTopBinding = GenStgTopBinding 'LiftLams
- type LlStgBinding = GenStgBinding 'LiftLams
- type LlStgExpr = GenStgExpr 'LiftLams
- type LlStgRhs = GenStgRhs 'LiftLams
- type LlStgAlt = GenStgAlt 'LiftLams
- 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
- stgRhsArity :: StgRhs -> Int
- isDllConApp :: DynFlags -> Module -> DataCon -> [StgArg] -> Bool
- stgArgType :: StgArg -> Type
- stripStgTicksTop :: (Tickish Id -> Bool) -> GenStgExpr p -> ([Tickish Id], GenStgExpr p)
- stripStgTicksTopE :: (Tickish Id -> Bool) -> GenStgExpr p -> GenStgExpr p
- stgCaseBndrInScope :: AltType -> Bool -> Bool
- bindersOf :: BinderP a ~ Id => GenStgBinding a -> [Id]
- bindersOfTop :: BinderP a ~ Id => GenStgTopBinding a -> [Id]
- bindersOfTopBinds :: BinderP a ~ Id => [GenStgTopBinding a] -> [Id]
- data StgPprOpts = StgPprOpts {
- stgSccEnabled :: !Bool
- initStgPprOpts :: DynFlags -> StgPprOpts
- panicStgPprOpts :: StgPprOpts
- pprStgArg :: StgArg -> SDoc
- pprStgExpr :: OutputablePass pass => StgPprOpts -> GenStgExpr pass -> SDoc
- pprStgRhs :: OutputablePass pass => StgPprOpts -> GenStgRhs pass -> SDoc
- pprStgBinding :: StgPprOpts -> StgBinding -> SDoc
- pprGenStgTopBinding :: OutputablePass pass => StgPprOpts -> GenStgTopBinding pass -> SDoc
- pprStgTopBinding :: StgPprOpts -> StgTopBinding -> SDoc
- pprGenStgTopBindings :: OutputablePass pass => StgPprOpts -> [GenStgTopBinding pass] -> SDoc
- pprStgTopBindings :: StgPprOpts -> [StgTopBinding] -> SDoc
Documentation
data GenStgTopBinding pass Source #
A top-level binding.
data GenStgBinding pass Source #
data GenStgExpr pass Source #
StgApp Id [StgArg] | |
StgLit Literal | |
StgConApp DataCon [StgArg] [Type] | |
StgOpApp StgOp [StgArg] Type | |
StgLam (NonEmpty (BinderP pass)) StgExpr | |
StgCase (GenStgExpr pass) (BinderP pass) AltType [GenStgAlt pass] | |
StgLet (XLet pass) (GenStgBinding pass) (GenStgExpr pass) | |
StgLetNoEscape (XLetNoEscape pass) (GenStgBinding pass) (GenStgExpr pass) | |
StgTick (Tickish Id) (GenStgExpr pass) |
StgRhsClosure | |
| |
StgRhsCon CostCentreStack DataCon [StgArg] |
type family XRhsClosure (pass :: StgPass) Source #
Instances
type XRhsClosure 'Vanilla # | |
Defined in GHC.Stg.Syntax | |
type XRhsClosure 'LiftLams # | |
Defined in GHC.Stg.Lift.Analysis | |
type XRhsClosure 'CodeGen # | Code gen needs to track non-global free vars |
Defined in GHC.Stg.Syntax |
type family XLet (pass :: StgPass) Source #
Instances
type XLet 'Vanilla # | |
Defined in GHC.Stg.Syntax | |
type XLet 'LiftLams # | |
Defined in GHC.Stg.Lift.Analysis | |
type XLet 'CodeGen # | |
Defined in GHC.Stg.Syntax |
type family XLetNoEscape (pass :: StgPass) Source #
Instances
type XLetNoEscape 'Vanilla # | |
Defined in GHC.Stg.Syntax | |
type XLetNoEscape 'LiftLams # | |
Defined in GHC.Stg.Lift.Analysis | |
type XLetNoEscape 'CodeGen # | |
Defined in GHC.Stg.Syntax |
data NoExtFieldSilent Source #
Like NoExtField
, but with an Outputable
instance that
returns empty
.
Instances
noExtFieldSilent :: NoExtFieldSilent Source #
Used when constructing a term with an unused extension point that should not appear in pretty-printed output at all.
type OutputablePass pass = (Outputable (XLet pass), Outputable (XLetNoEscape pass), Outputable (XRhsClosure pass), OutputableBndr (BinderP pass)) Source #
data UpdateFlag Source #
Instances
Outputable UpdateFlag # | |
Defined in GHC.Stg.Syntax |
isUpdatable :: UpdateFlag -> Bool Source #
type StgTopBinding = GenStgTopBinding 'Vanilla Source #
type StgBinding = GenStgBinding 'Vanilla Source #
type StgExpr = GenStgExpr 'Vanilla Source #
type CgStgTopBinding = GenStgTopBinding 'CodeGen Source #
type CgStgBinding = GenStgBinding 'CodeGen Source #
type CgStgExpr = GenStgExpr 'CodeGen Source #
type LlStgTopBinding = GenStgTopBinding 'LiftLams Source #
type LlStgBinding = GenStgBinding 'LiftLams Source #
type LlStgExpr = GenStgExpr 'LiftLams Source #
type InStgTopBinding = StgTopBinding Source #
type InStgBinding = StgBinding Source #
type OutStgTopBinding = StgTopBinding Source #
type OutStgBinding = StgBinding Source #
type OutStgExpr = StgExpr 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) -> GenStgExpr p -> ([Tickish Id], GenStgExpr p) Source #
Strip ticks of a given type from an STG expression.
stripStgTicksTopE :: (Tickish Id -> Bool) -> GenStgExpr p -> GenStgExpr p Source #
Strip ticks of a given type from an STG expression returning only the 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].
bindersOfTop :: BinderP a ~ Id => GenStgTopBinding a -> [Id] Source #
bindersOfTopBinds :: BinderP a ~ Id => [GenStgTopBinding a] -> [Id] Source #
data StgPprOpts Source #
STG pretty-printing options
StgPprOpts | |
|
initStgPprOpts :: DynFlags -> StgPprOpts Source #
Initialize STG pretty-printing options from DynFlags
panicStgPprOpts :: StgPprOpts Source #
STG pretty-printing options used for panic messages
pprStgExpr :: OutputablePass pass => StgPprOpts -> GenStgExpr pass -> SDoc Source #
pprStgRhs :: OutputablePass pass => StgPprOpts -> GenStgRhs pass -> SDoc Source #
pprStgBinding :: StgPprOpts -> StgBinding -> SDoc Source #
pprGenStgTopBinding :: OutputablePass pass => StgPprOpts -> GenStgTopBinding pass -> SDoc Source #
pprStgTopBinding :: StgPprOpts -> StgTopBinding -> SDoc Source #
pprGenStgTopBindings :: OutputablePass pass => StgPprOpts -> [GenStgTopBinding pass] -> SDoc Source #
pprStgTopBindings :: StgPprOpts -> [StgTopBinding] -> SDoc Source #