ghc-9.12: The GHC API
Safe HaskellNone
LanguageGHC2021

GHC.Cmm.Expr

Synopsis

Documentation

data CmmExpr Source #

Instances

Instances details
Show CmmExpr Source # 
Instance details

Defined in GHC.Cmm.Expr

Eq CmmExpr Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

(==) :: CmmExpr -> CmmExpr -> Bool #

(/=) :: CmmExpr -> CmmExpr -> Bool #

(Ord r, UserOfRegs r CmmReg) => UserOfRegs r CmmExpr Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

foldRegsUsed :: Platform -> (b -> r -> b) -> b -> CmmExpr -> b Source #

OutputableP Platform CmmExpr Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

pdoc :: Platform -> CmmExpr -> SDoc Source #

cmmExprAlignment :: CmmExpr -> Alignment Source #

Returns an alignment in bytes of a CmmExpr when it's a statically known integer constant, otherwise returns an alignment of 1 byte. The caller is responsible for using with a sensible CmmExpr argument.

data CmmReg Source #

Instances

Instances details
Outputable CmmReg Source # 
Instance details

Defined in GHC.Cmm.Reg

Methods

ppr :: CmmReg -> SDoc Source #

Show CmmReg Source # 
Instance details

Defined in GHC.Cmm.Reg

Eq CmmReg Source # 
Instance details

Defined in GHC.Cmm.Reg

Methods

(==) :: CmmReg -> CmmReg -> Bool #

(/=) :: CmmReg -> CmmReg -> Bool #

Ord CmmReg Source # 
Instance details

Defined in GHC.Cmm.Reg

DefinerOfRegs GlobalReg CmmReg Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

foldRegsDefd :: Platform -> (b -> GlobalReg -> b) -> b -> CmmReg -> b Source #

DefinerOfRegs GlobalRegUse CmmReg Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

foldRegsDefd :: Platform -> (b -> GlobalRegUse -> b) -> b -> CmmReg -> b Source #

DefinerOfRegs LocalReg CmmReg Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

foldRegsDefd :: Platform -> (b -> LocalReg -> b) -> b -> CmmReg -> b Source #

UserOfRegs GlobalReg CmmReg Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

foldRegsUsed :: Platform -> (b -> GlobalReg -> b) -> b -> CmmReg -> b Source #

UserOfRegs GlobalRegUse CmmReg Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

foldRegsUsed :: Platform -> (b -> GlobalRegUse -> b) -> b -> CmmReg -> b Source #

UserOfRegs LocalReg CmmReg Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

foldRegsUsed :: Platform -> (b -> LocalReg -> b) -> b -> CmmReg -> b Source #

data CmmLit Source #

Instances

Instances details
Outputable CmmLit Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

ppr :: CmmLit -> SDoc Source #

Show CmmLit Source # 
Instance details

Defined in GHC.Cmm.Expr

Eq CmmLit Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

(==) :: CmmLit -> CmmLit -> Bool #

(/=) :: CmmLit -> CmmLit -> Bool #

OutputableP Platform CmmLit Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

pdoc :: Platform -> CmmLit -> SDoc Source #

data LocalReg Source #

Constructors

LocalReg !Unique !CmmType

Parameters: 1. Identifier 2. Type

Instances

Instances details
Uniquable LocalReg Source # 
Instance details

Defined in GHC.Cmm.Reg

Outputable LocalReg Source # 
Instance details

Defined in GHC.Cmm.Reg

Methods

ppr :: LocalReg -> SDoc Source #

Show LocalReg Source # 
Instance details

Defined in GHC.Cmm.Reg

Eq LocalReg Source # 
Instance details

Defined in GHC.Cmm.Reg

Ord LocalReg Source # 
Instance details

Defined in GHC.Cmm.Reg

DefinerOfRegs LocalReg CmmReg Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

foldRegsDefd :: Platform -> (b -> LocalReg -> b) -> b -> CmmReg -> b Source #

UserOfRegs LocalReg CmmReg Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

foldRegsUsed :: Platform -> (b -> LocalReg -> b) -> b -> CmmReg -> b Source #

DefinerOfRegs LocalReg (CmmNode e x) Source # 
Instance details

Defined in GHC.Cmm.Node

Methods

foldRegsDefd :: Platform -> (b -> LocalReg -> b) -> b -> CmmNode e x -> b Source #

UserOfRegs LocalReg (CmmNode e x) Source # 
Instance details

Defined in GHC.Cmm.Node

Methods

foldRegsUsed :: Platform -> (b -> LocalReg -> b) -> b -> CmmNode e x -> b Source #

data GlobalReg Source #

An abstract global register for the STG machine.

See also GlobalRegUse, which denotes a usage of a register at a particular type (e.g. using a 32-bit wide register to store an 8-bit wide value), as per Note [GlobalReg vs GlobalRegUse].

Constructors

VanillaReg !Int 
FloatReg !Int 
DoubleReg !Int 
LongReg !Int 
XmmReg !Int 
YmmReg !Int 
ZmmReg !Int 
Sp

Stack ptr; points to last occupied stack location.

SpLim

Stack limit

Hp

Heap ptr; points to last occupied heap location.

HpLim

Heap limit register

CCCS

Current cost-centre stack

CurrentTSO

pointer to current thread's TSO

CurrentNursery

pointer to allocation area

HpAlloc

allocation count for heap check failure

EagerBlackholeInfo

address of stg_EAGER_BLACKHOLE_info

GCEnter1

address of stg_gc_enter_1

GCFun

address of stg_gc_fun

BaseReg

Base offset for the register table, used for accessing registers which do not have real registers assigned to them. This register will only appear after we have expanded GlobalReg into memory accesses (where necessary) in the native code generator.

MachSp

The register used by the platform for the C stack pointer. This is a break in the STG abstraction used exclusively to setup stack unwinding information.

UnwindReturnReg

A dummy register used to indicate to the stack unwinder where a routine would return to.

PicBaseReg

Base Register for PIC (position-independent code) calculations.

Only used inside the native code generator. Its exact meaning differs from platform to platform (see module PositionIndependentCode).

Instances

Instances details
Outputable GlobalReg Source # 
Instance details

Defined in GHC.Cmm.Reg

Methods

ppr :: GlobalReg -> SDoc Source #

Show GlobalReg Source # 
Instance details

Defined in GHC.Cmm.Reg

Eq GlobalReg Source # 
Instance details

Defined in GHC.Cmm.Reg

Ord GlobalReg Source # 
Instance details

Defined in GHC.Cmm.Reg

DefinerOfRegs GlobalReg CmmReg Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

foldRegsDefd :: Platform -> (b -> GlobalReg -> b) -> b -> CmmReg -> b Source #

UserOfRegs GlobalReg CmmReg Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

foldRegsUsed :: Platform -> (b -> GlobalReg -> b) -> b -> CmmReg -> b Source #

OutputableP env GlobalReg Source # 
Instance details

Defined in GHC.Cmm.Reg

Methods

pdoc :: env -> GlobalReg -> SDoc Source #

data GlobalRegUse Source #

A use of a global register at a particular type.

While a GlobalReg identifies a global register in the STG machine, a GlobalRegUse also contains information about the type we are storing in the register.

See Note [GlobalReg vs GlobalRegUse] for more information.

Constructors

GlobalRegUse 

Fields

Instances

Instances details
Outputable GlobalRegUse Source # 
Instance details

Defined in GHC.Cmm.Reg

Show GlobalRegUse Source # 
Instance details

Defined in GHC.Cmm.Reg

Eq GlobalRegUse Source # 
Instance details

Defined in GHC.Cmm.Reg

Ord GlobalRegUse Source # 
Instance details

Defined in GHC.Cmm.Reg

DefinerOfRegs GlobalRegUse CmmReg Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

foldRegsDefd :: Platform -> (b -> GlobalRegUse -> b) -> b -> CmmReg -> b Source #

UserOfRegs GlobalRegUse CmmReg Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

foldRegsUsed :: Platform -> (b -> GlobalRegUse -> b) -> b -> CmmReg -> b Source #

DefinerOfRegs GlobalRegUse (CmmNode e x) Source # 
Instance details

Defined in GHC.Cmm.Node

Methods

foldRegsDefd :: Platform -> (b -> GlobalRegUse -> b) -> b -> CmmNode e x -> b Source #

UserOfRegs GlobalRegUse (CmmNode e x) Source # 
Instance details

Defined in GHC.Cmm.Node

Methods

foldRegsUsed :: Platform -> (b -> GlobalRegUse -> b) -> b -> CmmNode e x -> b Source #

class Ord r => DefinerOfRegs r a Source #

Minimal complete definition

foldRegsDefd

Instances

Instances details
DefinerOfRegs GlobalReg CmmReg Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

foldRegsDefd :: Platform -> (b -> GlobalReg -> b) -> b -> CmmReg -> b Source #

DefinerOfRegs GlobalRegUse CmmReg Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

foldRegsDefd :: Platform -> (b -> GlobalRegUse -> b) -> b -> CmmReg -> b Source #

DefinerOfRegs LocalReg CmmReg Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

foldRegsDefd :: Platform -> (b -> LocalReg -> b) -> b -> CmmReg -> b Source #

Ord r => DefinerOfRegs r r Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

foldRegsDefd :: Platform -> (b -> r -> b) -> b -> r -> b Source #

DefinerOfRegs r a => DefinerOfRegs r [a] Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

foldRegsDefd :: Platform -> (b -> r -> b) -> b -> [a] -> b Source #

DefinerOfRegs GlobalRegUse (CmmNode e x) Source # 
Instance details

Defined in GHC.Cmm.Node

Methods

foldRegsDefd :: Platform -> (b -> GlobalRegUse -> b) -> b -> CmmNode e x -> b Source #

DefinerOfRegs LocalReg (CmmNode e x) Source # 
Instance details

Defined in GHC.Cmm.Node

Methods

foldRegsDefd :: Platform -> (b -> LocalReg -> b) -> b -> CmmNode e x -> b Source #

class Ord r => UserOfRegs r a Source #

Minimal complete definition

foldRegsUsed

Instances

Instances details
UserOfRegs GlobalReg CmmReg Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

foldRegsUsed :: Platform -> (b -> GlobalReg -> b) -> b -> CmmReg -> b Source #

UserOfRegs GlobalRegUse CmmReg Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

foldRegsUsed :: Platform -> (b -> GlobalRegUse -> b) -> b -> CmmReg -> b Source #

UserOfRegs LocalReg CmmReg Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

foldRegsUsed :: Platform -> (b -> LocalReg -> b) -> b -> CmmReg -> b Source #

(Ord r, UserOfRegs r CmmReg) => UserOfRegs r CmmExpr Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

foldRegsUsed :: Platform -> (b -> r -> b) -> b -> CmmExpr -> b Source #

(Ord r, UserOfRegs r CmmReg) => UserOfRegs r ForeignTarget Source # 
Instance details

Defined in GHC.Cmm.Node

Methods

foldRegsUsed :: Platform -> (b -> r -> b) -> b -> ForeignTarget -> b Source #

Ord r => UserOfRegs r r Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

foldRegsUsed :: Platform -> (b -> r -> b) -> b -> r -> b Source #

UserOfRegs r a => UserOfRegs r [a] Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

foldRegsUsed :: Platform -> (b -> r -> b) -> b -> [a] -> b Source #

UserOfRegs GlobalRegUse (CmmNode e x) Source # 
Instance details

Defined in GHC.Cmm.Node

Methods

foldRegsUsed :: Platform -> (b -> GlobalRegUse -> b) -> b -> CmmNode e x -> b Source #

UserOfRegs LocalReg (CmmNode e x) Source # 
Instance details

Defined in GHC.Cmm.Node

Methods

foldRegsUsed :: Platform -> (b -> LocalReg -> b) -> b -> CmmNode e x -> b Source #

foldRegsDefd :: DefinerOfRegs r a => Platform -> (b -> r -> b) -> b -> a -> b Source #

foldRegsUsed :: UserOfRegs r a => Platform -> (b -> r -> b) -> b -> a -> b Source #

foldLocalRegsDefd :: DefinerOfRegs LocalReg a => Platform -> (b -> LocalReg -> b) -> b -> a -> b Source #

foldLocalRegsUsed :: UserOfRegs LocalReg a => Platform -> (b -> LocalReg -> b) -> b -> a -> b Source #

type RegSet r = Set r Source #

Sets of registers

elemRegSet :: Ord r => r -> RegSet r -> Bool Source #

extendRegSet :: Ord r => RegSet r -> r -> RegSet r Source #

mkRegSet :: Ord r => [r] -> RegSet r Source #

plusRegSet :: Ord r => RegSet r -> RegSet r -> RegSet r Source #

minusRegSet :: Ord r => RegSet r -> RegSet r -> RegSet r Source #

timesRegSet :: Ord r => RegSet r -> RegSet r -> RegSet r Source #

data Area Source #

A stack area is either the stack slot where a variable is spilled or the stack space where function arguments and results are passed.

Constructors

Old 
Young !BlockId 

Instances

Instances details
Outputable Area Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

ppr :: Area -> SDoc Source #

Show Area Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

showsPrec :: Int -> Area -> ShowS #

show :: Area -> String #

showList :: [Area] -> ShowS #

Eq Area Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

(==) :: Area -> Area -> Bool #

(/=) :: Area -> Area -> Bool #

Ord Area Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

compare :: Area -> Area -> Ordering #

(<) :: Area -> Area -> Bool #

(<=) :: Area -> Area -> Bool #

(>) :: Area -> Area -> Bool #

(>=) :: Area -> Area -> Bool #

max :: Area -> Area -> Area #

min :: Area -> Area -> Area #