ghc-8.6.2: The GHC API

Safe HaskellNone
LanguageHaskell2010

StgSyn

Synopsis

Documentation

data GenStgArg occ Source #

Constructors

StgVarArg occ 
StgLitArg Literal 
Instances
Outputable bdee => Outputable (GenStgArg bdee) # 
Instance details

Defined in StgSyn

Methods

ppr :: GenStgArg bdee -> SDoc Source #

pprPrec :: Rational -> GenStgArg bdee -> SDoc Source #

data GenStgTopBinding bndr occ Source #

A top-level binding.

Constructors

StgTopLifted (GenStgBinding bndr occ) 
StgTopStringLit bndr ByteString 
Instances
(OutputableBndr bndr, Outputable bdee, Ord bdee) => Outputable (GenStgTopBinding bndr bdee) # 
Instance details

Defined in StgSyn

Methods

ppr :: GenStgTopBinding bndr bdee -> SDoc Source #

pprPrec :: Rational -> GenStgTopBinding bndr bdee -> SDoc Source #

data GenStgBinding bndr occ Source #

Constructors

StgNonRec bndr (GenStgRhs bndr occ) 
StgRec [(bndr, GenStgRhs bndr occ)] 
Instances
(OutputableBndr bndr, Outputable bdee, Ord bdee) => Outputable (GenStgBinding bndr bdee) # 
Instance details

Defined in StgSyn

Methods

ppr :: GenStgBinding bndr bdee -> SDoc Source #

pprPrec :: Rational -> GenStgBinding bndr bdee -> SDoc Source #

data GenStgExpr bndr occ Source #

Constructors

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) # 
Instance details

Defined in StgSyn

Methods

ppr :: GenStgExpr bndr bdee -> SDoc Source #

pprPrec :: Rational -> GenStgExpr bndr bdee -> SDoc Source #

data GenStgRhs bndr occ Source #

Instances
(OutputableBndr bndr, Outputable bdee, Ord bdee) => Outputable (GenStgRhs bndr bdee) # 
Instance details

Defined in StgSyn

Methods

ppr :: GenStgRhs bndr bdee -> SDoc Source #

pprPrec :: Rational -> GenStgRhs bndr bdee -> SDoc Source #

type GenStgAlt bndr occ = (AltCon, [bndr], GenStgExpr bndr occ) Source #

data AltType Source #

Instances
Outputable AltType # 
Instance details

Defined in StgSyn

data UpdateFlag Source #

Instances
Outputable UpdateFlag # 
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) -> StgExpr -> ([Tickish Id], StgExpr) 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].