Safe Haskell | None |
---|---|
Language | GHC2021 |
Synopsis
- data CmmReg
- cmmRegType :: CmmReg -> CmmType
- cmmRegWidth :: CmmReg -> Width
- data LocalReg = LocalReg !Unique !CmmType
- localRegType :: LocalReg -> CmmType
- data GlobalReg
- = VanillaReg !Int
- | FloatReg !Int
- | DoubleReg !Int
- | LongReg !Int
- | XmmReg !Int
- | YmmReg !Int
- | ZmmReg !Int
- | Sp
- | SpLim
- | Hp
- | HpLim
- | CCCS
- | CurrentTSO
- | CurrentNursery
- | HpAlloc
- | EagerBlackholeInfo
- | GCEnter1
- | GCFun
- | BaseReg
- | MachSp
- | UnwindReturnReg
- | PicBaseReg
- isArgReg :: GlobalReg -> Bool
- globalRegSpillType :: Platform -> GlobalReg -> CmmType
- pprGlobalReg :: IsLine doc => GlobalReg -> doc
- spReg :: Platform -> CmmReg
- hpReg :: Platform -> CmmReg
- spLimReg :: Platform -> CmmReg
- hpLimReg :: Platform -> CmmReg
- nodeReg :: Platform -> CmmReg
- currentTSOReg :: Platform -> CmmReg
- currentNurseryReg :: Platform -> CmmReg
- hpAllocReg :: Platform -> CmmReg
- cccsReg :: Platform -> CmmReg
- node :: GlobalReg
- baseReg :: Platform -> CmmReg
- data GlobalRegUse = GlobalRegUse {}
- pprGlobalRegUse :: IsLine doc => GlobalRegUse -> doc
- data GlobalArgRegs
Cmm Registers
Instances
Outputable CmmReg Source # | |
Show CmmReg Source # | |
Eq CmmReg Source # | |
Ord CmmReg Source # | |
DefinerOfRegs GlobalReg CmmReg Source # | |
Defined in GHC.Cmm.Expr | |
DefinerOfRegs GlobalRegUse CmmReg Source # | |
Defined in GHC.Cmm.Expr foldRegsDefd :: Platform -> (b -> GlobalRegUse -> b) -> b -> CmmReg -> b Source # | |
DefinerOfRegs LocalReg CmmReg Source # | |
Defined in GHC.Cmm.Expr | |
UserOfRegs GlobalReg CmmReg Source # | |
Defined in GHC.Cmm.Expr | |
UserOfRegs GlobalRegUse CmmReg Source # | |
Defined in GHC.Cmm.Expr foldRegsUsed :: Platform -> (b -> GlobalRegUse -> b) -> b -> CmmReg -> b Source # | |
UserOfRegs LocalReg CmmReg Source # | |
Defined in GHC.Cmm.Expr |
cmmRegType :: CmmReg -> CmmType Source #
cmmRegWidth :: CmmReg -> Width Source #
Local registers
Instances
Uniquable LocalReg Source # | |
Outputable LocalReg Source # | |
Show LocalReg Source # | |
Eq LocalReg Source # | |
Ord LocalReg Source # | |
Defined in GHC.Cmm.Reg | |
DefinerOfRegs LocalReg CmmReg Source # | |
Defined in GHC.Cmm.Expr | |
UserOfRegs LocalReg CmmReg Source # | |
Defined in GHC.Cmm.Expr | |
DefinerOfRegs LocalReg (CmmNode e x) Source # | |
Defined in GHC.Cmm.Node | |
UserOfRegs LocalReg (CmmNode e x) Source # | |
Defined in GHC.Cmm.Node |
localRegType :: LocalReg -> CmmType Source #
Global registers
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].
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
Outputable GlobalReg Source # | |
Show GlobalReg Source # | |
Eq GlobalReg Source # | |
Ord GlobalReg Source # | |
Defined in GHC.Cmm.Reg | |
DefinerOfRegs GlobalReg CmmReg Source # | |
Defined in GHC.Cmm.Expr | |
UserOfRegs GlobalReg CmmReg Source # | |
Defined in GHC.Cmm.Expr | |
OutputableP env GlobalReg Source # | |
pprGlobalReg :: IsLine doc => GlobalReg -> doc Source #
currentTSOReg :: Platform -> CmmReg Source #
currentNurseryReg :: Platform -> CmmReg Source #
hpAllocReg :: Platform -> CmmReg 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.
GlobalRegUse | |
|
Instances
pprGlobalRegUse :: IsLine doc => GlobalRegUse -> doc Source #
data GlobalArgRegs Source #
Global registers used for argument passing.
See Note [realArgRegsCover] in GHC.Cmm.CallConv.
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. |
Instances
Show GlobalArgRegs Source # | |
Defined in GHC.Cmm.Reg showsPrec :: Int -> GlobalArgRegs -> ShowS # show :: GlobalArgRegs -> String # showList :: [GlobalArgRegs] -> ShowS # | |
Eq GlobalArgRegs Source # | |
Defined in GHC.Cmm.Reg (==) :: GlobalArgRegs -> GlobalArgRegs -> Bool # (/=) :: GlobalArgRegs -> GlobalArgRegs -> Bool # | |
Ord GlobalArgRegs Source # | |
Defined in GHC.Cmm.Reg compare :: GlobalArgRegs -> GlobalArgRegs -> Ordering # (<) :: GlobalArgRegs -> GlobalArgRegs -> Bool # (<=) :: GlobalArgRegs -> GlobalArgRegs -> Bool # (>) :: GlobalArgRegs -> GlobalArgRegs -> Bool # (>=) :: GlobalArgRegs -> GlobalArgRegs -> Bool # max :: GlobalArgRegs -> GlobalArgRegs -> GlobalArgRegs # min :: GlobalArgRegs -> GlobalArgRegs -> GlobalArgRegs # |