ghc-9.12: The GHC API
Safe HaskellNone
LanguageGHC2021

GHC.Cmm.Reg

Synopsis

Cmm Registers

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 #

Local registers

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 #

Global registers

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 #

data GlobalArgRegs Source #

Global registers used for argument passing.

See Note [realArgRegsCover] in GHC.Cmm.CallConv.

Constructors

GP_ARG_REGS

General-purpose (integer) argument-passing registers.

SCALAR_ARG_REGS

Scalar (integer & floating-point) argument-passing registers.

V16_ARG_REGS

16 byte vector argument-passing registers, together with integer & floating-point argument-passing scalar registers.

V32_ARG_REGS

32 byte vector argument-passing registers, together with integer & floating-point argument-passing scalar registers.

V64_ARG_REGS

64 byte vector argument-passing registers, together with integer & floating-point argument-passing scalar registers.