ghc-9.0.2: The GHC API
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.Stg.Syntax

Synopsis

Documentation

data StgArg Source #

Constructors

StgVarArg Id 
StgLitArg Literal 

Instances

Instances details
Outputable StgArg Source # 
Instance details

Defined in GHC.Stg.Syntax

data GenStgTopBinding pass Source #

A top-level binding.

data GenStgBinding pass Source #

Constructors

StgNonRec (BinderP pass) (GenStgRhs pass) 
StgRec [(BinderP pass, GenStgRhs pass)] 

data GenStgRhs pass Source #

Constructors

StgRhsClosure 

Fields

StgRhsCon CostCentreStack DataCon [StgArg] 

type GenStgAlt pass = (AltCon, [BinderP pass], GenStgExpr pass) Source #

data AltType Source #

Instances

Instances details
Outputable AltType Source # 
Instance details

Defined in GHC.Stg.Syntax

data StgPass Source #

Used as a data type index for the stgSyn AST

Constructors

Vanilla 
LiftLams 
CodeGen 

type family BinderP (pass :: StgPass) Source #

Instances

Instances details
type BinderP 'CodeGen Source # 
Instance details

Defined in GHC.Stg.Syntax

type BinderP 'LiftLams Source # 
Instance details

Defined in GHC.Stg.Lift.Analysis

type BinderP 'Vanilla Source # 
Instance details

Defined in GHC.Stg.Syntax

type family XRhsClosure (pass :: StgPass) Source #

Instances

Instances details
type XRhsClosure 'CodeGen Source #

Code gen needs to track non-global free vars

Instance details

Defined in GHC.Stg.Syntax

type XRhsClosure 'LiftLams Source # 
Instance details

Defined in GHC.Stg.Lift.Analysis

type XRhsClosure 'Vanilla Source # 
Instance details

Defined in GHC.Stg.Syntax

type family XLet (pass :: StgPass) Source #

Instances

Instances details
type XLet 'CodeGen Source # 
Instance details

Defined in GHC.Stg.Syntax

type XLet 'LiftLams Source # 
Instance details

Defined in GHC.Stg.Lift.Analysis

type XLet 'Vanilla Source # 
Instance details

Defined in GHC.Stg.Syntax

type family XLetNoEscape (pass :: StgPass) Source #

Instances

Instances details
type XLetNoEscape 'CodeGen Source # 
Instance details

Defined in GHC.Stg.Syntax

type XLetNoEscape 'LiftLams Source # 
Instance details

Defined in GHC.Stg.Lift.Analysis

type XLetNoEscape 'Vanilla Source # 
Instance details

Defined in GHC.Stg.Syntax

data NoExtFieldSilent Source #

Like NoExtField, but with an Outputable instance that returns empty.

Instances

Instances details
Data NoExtFieldSilent Source # 
Instance details

Defined in GHC.Stg.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NoExtFieldSilent -> c NoExtFieldSilent Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NoExtFieldSilent Source #

toConstr :: NoExtFieldSilent -> Constr Source #

dataTypeOf :: NoExtFieldSilent -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NoExtFieldSilent) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NoExtFieldSilent) Source #

gmapT :: (forall b. Data b => b -> b) -> NoExtFieldSilent -> NoExtFieldSilent Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NoExtFieldSilent -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NoExtFieldSilent -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> NoExtFieldSilent -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NoExtFieldSilent -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NoExtFieldSilent -> m NoExtFieldSilent Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NoExtFieldSilent -> m NoExtFieldSilent Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NoExtFieldSilent -> m NoExtFieldSilent Source #

Outputable NoExtFieldSilent Source # 
Instance details

Defined in GHC.Stg.Syntax

Eq NoExtFieldSilent Source # 
Instance details

Defined in GHC.Stg.Syntax

Ord NoExtFieldSilent Source # 
Instance details

Defined in GHC.Stg.Syntax

noExtFieldSilent :: NoExtFieldSilent Source #

Used when constructing a term with an unused extension point that should not appear in pretty-printed output at all.

data UpdateFlag Source #

Instances

Instances details
Outputable UpdateFlag Source # 
Instance details

Defined in GHC.Stg.Syntax

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.

stgCaseBndrInScope Source #

Arguments

:: AltType 
-> Bool

unarised?

-> Bool 

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].

data StgPprOpts Source #

STG pretty-printing options

Constructors

StgPprOpts 

Fields

initStgPprOpts :: DynFlags -> StgPprOpts Source #

Initialize STG pretty-printing options from DynFlags

panicStgPprOpts :: StgPprOpts Source #

STG pretty-printing options used for panic messages