Safe Haskell | None |
---|---|
Language | GHC2021 |
Synopsis
- data CmmExpr
- cmmExprType :: Platform -> CmmExpr -> CmmType
- cmmExprWidth :: Platform -> CmmExpr -> Width
- cmmExprAlignment :: CmmExpr -> Alignment
- maybeInvertCmmExpr :: CmmExpr -> Maybe CmmExpr
- data CmmReg
- cmmRegType :: CmmReg -> CmmType
- cmmRegWidth :: CmmReg -> Width
- data CmmLit
- cmmLitType :: Platform -> CmmLit -> CmmType
- data AlignmentSpec
- 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
- data GlobalRegUse = GlobalRegUse {}
- 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
- class Ord r => DefinerOfRegs r a
- class Ord r => UserOfRegs r a
- foldRegsDefd :: DefinerOfRegs r a => Platform -> (b -> r -> b) -> b -> a -> b
- foldRegsUsed :: UserOfRegs r a => Platform -> (b -> r -> b) -> b -> a -> b
- foldLocalRegsDefd :: DefinerOfRegs LocalReg a => Platform -> (b -> LocalReg -> b) -> b -> a -> b
- foldLocalRegsUsed :: UserOfRegs LocalReg a => Platform -> (b -> LocalReg -> b) -> b -> a -> b
- type RegSet r = Set r
- type LocalRegSet = RegSet LocalReg
- type GlobalRegSet = RegSet GlobalReg
- emptyRegSet :: RegSet r
- elemRegSet :: Ord r => r -> RegSet r -> Bool
- extendRegSet :: Ord r => RegSet r -> r -> RegSet r
- deleteFromRegSet :: Ord r => RegSet r -> r -> RegSet r
- mkRegSet :: Ord r => [r] -> RegSet r
- plusRegSet :: Ord r => RegSet r -> RegSet r -> RegSet r
- minusRegSet :: Ord r => RegSet r -> RegSet r -> RegSet r
- timesRegSet :: Ord r => RegSet r -> RegSet r -> RegSet r
- sizeRegSet :: RegSet r -> Int
- nullRegSet :: RegSet r -> Bool
- regSetToList :: RegSet r -> [r]
- isTrivialCmmExpr :: CmmExpr -> Bool
- hasNoGlobalRegs :: CmmExpr -> Bool
- isLit :: CmmExpr -> Bool
- isComparisonExpr :: CmmExpr -> Bool
- data Area
- module GHC.Cmm.MachOp
- module GHC.Cmm.Type
Documentation
CmmLit !CmmLit | |
CmmLoad !CmmExpr !CmmType !AlignmentSpec | |
CmmReg !CmmReg | |
CmmMachOp MachOp [CmmExpr] | |
CmmStackSlot Area !Int | |
CmmRegOff !CmmReg !Int |
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.
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 #
CmmInt !Integer !Width | |
CmmFloat Rational !Width | |
CmmVec [CmmLit] | |
CmmLabel CLabel | |
CmmLabelOff CLabel !Int | |
CmmLabelDiffOff CLabel CLabel !Int !Width | |
CmmBlock !BlockId | |
CmmHighStackMark |
data AlignmentSpec Source #
Instances
Show AlignmentSpec Source # | |
Defined in GHC.Cmm.Expr showsPrec :: Int -> AlignmentSpec -> ShowS # show :: AlignmentSpec -> String # showList :: [AlignmentSpec] -> ShowS # | |
Eq AlignmentSpec Source # | |
Defined in GHC.Cmm.Expr (==) :: AlignmentSpec -> AlignmentSpec -> Bool # (/=) :: AlignmentSpec -> AlignmentSpec -> Bool # | |
Ord AlignmentSpec Source # | |
Defined in GHC.Cmm.Expr compare :: AlignmentSpec -> AlignmentSpec -> Ordering # (<) :: AlignmentSpec -> AlignmentSpec -> Bool # (<=) :: AlignmentSpec -> AlignmentSpec -> Bool # (>) :: AlignmentSpec -> AlignmentSpec -> Bool # (>=) :: AlignmentSpec -> AlignmentSpec -> Bool # max :: AlignmentSpec -> AlignmentSpec -> AlignmentSpec # min :: AlignmentSpec -> AlignmentSpec -> AlignmentSpec # |
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 #
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 # | |
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
currentTSOReg :: Platform -> CmmReg Source #
currentNurseryReg :: Platform -> CmmReg Source #
hpAllocReg :: Platform -> CmmReg Source #
class Ord r => DefinerOfRegs r a Source #
Instances
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 | |
Ord r => DefinerOfRegs r r Source # | |
Defined in GHC.Cmm.Expr foldRegsDefd :: Platform -> (b -> r -> b) -> b -> r -> b Source # | |
DefinerOfRegs r a => DefinerOfRegs r [a] Source # | |
Defined in GHC.Cmm.Expr foldRegsDefd :: Platform -> (b -> r -> b) -> b -> [a] -> b Source # | |
DefinerOfRegs GlobalRegUse (CmmNode e x) Source # | |
Defined in GHC.Cmm.Node foldRegsDefd :: Platform -> (b -> GlobalRegUse -> b) -> b -> CmmNode e x -> b Source # | |
DefinerOfRegs LocalReg (CmmNode e x) Source # | |
Defined in GHC.Cmm.Node |
class Ord r => UserOfRegs r a Source #
Instances
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 LocalRegSet = RegSet LocalReg Source #
type GlobalRegSet = RegSet GlobalReg Source #
emptyRegSet :: RegSet r Source #
sizeRegSet :: RegSet r -> Int Source #
nullRegSet :: RegSet r -> Bool Source #
regSetToList :: RegSet r -> [r] Source #
isTrivialCmmExpr :: CmmExpr -> Bool Source #
hasNoGlobalRegs :: CmmExpr -> Bool Source #
isComparisonExpr :: CmmExpr -> Bool 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.
module GHC.Cmm.MachOp
module GHC.Cmm.Type