ghc-lib-0.20190423: The GHC API, decoupled from GHC versions

Safe HaskellNone
LanguageHaskell2010

StgSyn

Synopsis

Documentation

data StgArg Source #

Constructors

StgVarArg Id 
StgLitArg Literal 
Instances
Outputable StgArg Source # 
Instance details

Defined in StgSyn

Methods

ppr :: StgArg -> SDoc #

pprPrec :: Rational -> StgArg -> SDoc #

data GenStgTopBinding pass Source #

A top-level binding.

Instances
OutputablePass pass => Outputable (GenStgTopBinding pass) Source # 
Instance details

Defined in StgSyn

data GenStgBinding pass Source #

Constructors

StgNonRec (BinderP pass) (GenStgRhs pass) 
StgRec [(BinderP pass, GenStgRhs pass)] 
Instances
OutputablePass pass => Outputable (GenStgBinding pass) Source # 
Instance details

Defined in StgSyn

Methods

ppr :: GenStgBinding pass -> SDoc #

pprPrec :: Rational -> GenStgBinding pass -> SDoc #

data GenStgExpr pass Source #

Instances
OutputablePass pass => Outputable (GenStgExpr pass) Source # 
Instance details

Defined in StgSyn

Methods

ppr :: GenStgExpr pass -> SDoc #

pprPrec :: Rational -> GenStgExpr pass -> SDoc #

data GenStgRhs pass Source #

Constructors

StgRhsClosure 

Fields

StgRhsCon CostCentreStack DataCon [StgArg] 
Instances
OutputablePass pass => Outputable (GenStgRhs pass) Source # 
Instance details

Defined in StgSyn

Methods

ppr :: GenStgRhs pass -> SDoc #

pprPrec :: Rational -> GenStgRhs pass -> SDoc #

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

data AltType Source #

Instances
Outputable AltType Source # 
Instance details

Defined in StgSyn

Methods

ppr :: AltType -> SDoc #

pprPrec :: Rational -> AltType -> SDoc #

data StgPass Source #

Used as a data type index for the stgSyn AST

Constructors

Vanilla 
LiftLams 
CodeGen 

type family BinderP (pass :: StgPass) Source #

Instances
type BinderP Vanilla Source # 
Instance details

Defined in StgSyn

type BinderP LiftLams Source # 
Instance details

Defined in StgLiftLams.Analysis

type BinderP CodeGen Source # 
Instance details

Defined in StgSyn

type family XRhsClosure (pass :: StgPass) Source #

Instances
type XRhsClosure Vanilla Source # 
Instance details

Defined in StgSyn

type XRhsClosure LiftLams Source # 
Instance details

Defined in StgLiftLams.Analysis

type XRhsClosure CodeGen Source #

Code gen needs to track non-global free vars

Instance details

Defined in StgSyn

type family XLet (pass :: StgPass) Source #

Instances
type XLet Vanilla Source # 
Instance details

Defined in StgSyn

type XLet LiftLams Source # 
Instance details

Defined in StgLiftLams.Analysis

type XLet CodeGen Source # 
Instance details

Defined in StgSyn

type family XLetNoEscape (pass :: StgPass) Source #

Instances
type XLetNoEscape Vanilla Source # 
Instance details

Defined in StgSyn

type XLetNoEscape LiftLams Source # 
Instance details

Defined in StgLiftLams.Analysis

type XLetNoEscape CodeGen Source # 
Instance details

Defined in StgSyn

data NoExtSilent Source #

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

Instances
Eq NoExtSilent Source # 
Instance details

Defined in StgSyn

Data NoExtSilent Source # 
Instance details

Defined in StgSyn

Methods

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

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

toConstr :: NoExtSilent -> Constr #

dataTypeOf :: NoExtSilent -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord NoExtSilent Source # 
Instance details

Defined in StgSyn

Outputable NoExtSilent Source # 
Instance details

Defined in StgSyn

noExtSilent :: NoExtSilent 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
Outputable UpdateFlag Source # 
Instance details

Defined in StgSyn

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

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