- data CmmType
- b8 :: CmmType
- b16 :: CmmType
- b32 :: CmmType
- b64 :: CmmType
- f32 :: CmmType
- f64 :: CmmType
- bWord :: CmmType
- bHalfWord :: CmmType
- gcWord :: CmmType
- cInt :: CmmType
- cLong :: CmmType
- cmmBits :: Width -> CmmType
- cmmFloat :: Width -> CmmType
- typeWidth :: CmmType -> Width
- cmmEqType :: CmmType -> CmmType -> Bool
- cmmEqType_ignoring_ptrhood :: CmmType -> CmmType -> Bool
- isFloatType :: CmmType -> Bool
- isGcPtrType :: CmmType -> Bool
- isWord32 :: CmmType -> Bool
- isWord64 :: CmmType -> Bool
- isFloat64 :: CmmType -> Bool
- isFloat32 :: CmmType -> Bool
- data Width
- widthInBits :: Width -> Int
- widthInBytes :: Width -> Int
- widthInLog :: Width -> Int
- widthFromBytes :: Int -> Width
- wordWidth :: Width
- halfWordWidth :: Width
- cIntWidth :: Width
- cLongWidth :: Width
- narrowU :: Width -> Integer -> Integer
- narrowS :: Width -> Integer -> Integer
- data CmmExpr
- cmmExprType :: CmmExpr -> CmmType
- cmmExprWidth :: CmmExpr -> Width
- maybeInvertCmmExpr :: CmmExpr -> Maybe CmmExpr
- data CmmReg
- cmmRegType :: CmmReg -> CmmType
- data CmmLit
- cmmLitType :: CmmLit -> CmmType
- data LocalReg = LocalReg !Unique CmmType
- localRegType :: LocalReg -> CmmType
- data GlobalReg
- = VanillaReg !Int VGcPtr
- | FloatReg !Int
- | DoubleReg !Int
- | LongReg !Int
- | Sp
- | SpLim
- | Hp
- | HpLim
- | CurrentTSO
- | CurrentNursery
- | HpAlloc
- | EagerBlackholeInfo
- | GCEnter1
- | GCFun
- | BaseReg
- | PicBaseReg
- globalRegType :: GlobalReg -> CmmType
- spReg :: CmmReg
- hpReg :: CmmReg
- spLimReg :: CmmReg
- nodeReg :: CmmReg
- node :: GlobalReg
- data VGcPtr
- vgcFlag :: CmmType -> VGcPtr
- class DefinerOfLocalRegs a where
- foldRegsDefd :: (b -> LocalReg -> b) -> b -> a -> b
- class UserOfLocalRegs a where
- foldRegsUsed :: (b -> LocalReg -> b) -> b -> a -> b
- filterRegsUsed :: UserOfLocalRegs e => (LocalReg -> Bool) -> e -> RegSet
- class DefinerOfSlots a where
- foldSlotsDefd :: (b -> SubArea -> b) -> b -> a -> b
- class UserOfSlots a where
- foldSlotsUsed :: (b -> SubArea -> b) -> b -> a -> b
- type RegSet = UniqSet LocalReg
- emptyRegSet :: RegSet
- elemRegSet :: LocalReg -> RegSet -> Bool
- extendRegSet :: RegSet -> LocalReg -> RegSet
- deleteFromRegSet :: RegSet -> LocalReg -> RegSet
- mkRegSet :: [LocalReg] -> RegSet
- plusRegSet :: RegSet -> RegSet -> RegSet
- minusRegSet :: RegSet -> RegSet -> RegSet
- timesRegSet :: RegSet -> RegSet -> RegSet
- regUsedIn :: CmmReg -> CmmExpr -> Bool
- data Area
- data AreaId
- type SubArea = (Area, Int, Int)
- type SubAreaSet = Map Area [SubArea]
- type AreaMap = Map Area Int
- isStackSlotOf :: CmmExpr -> LocalReg -> Bool
- data MachOp
- = MO_Add Width
- | MO_Sub Width
- | MO_Eq Width
- | MO_Ne Width
- | MO_Mul Width
- | MO_S_MulMayOflo Width
- | MO_S_Quot Width
- | MO_S_Rem Width
- | MO_S_Neg Width
- | MO_U_MulMayOflo Width
- | MO_U_Quot Width
- | MO_U_Rem Width
- | MO_S_Ge Width
- | MO_S_Le Width
- | MO_S_Gt Width
- | MO_S_Lt Width
- | MO_U_Ge Width
- | MO_U_Le Width
- | MO_U_Gt Width
- | MO_U_Lt Width
- | MO_F_Add Width
- | MO_F_Sub Width
- | MO_F_Neg Width
- | MO_F_Mul Width
- | MO_F_Quot Width
- | MO_F_Eq Width
- | MO_F_Ne Width
- | MO_F_Ge Width
- | MO_F_Le Width
- | MO_F_Gt Width
- | MO_F_Lt Width
- | MO_And Width
- | MO_Or Width
- | MO_Xor Width
- | MO_Not Width
- | MO_Shl Width
- | MO_U_Shr Width
- | MO_S_Shr Width
- | MO_SF_Conv Width Width
- | MO_FS_Conv Width Width
- | MO_SS_Conv Width Width
- | MO_UU_Conv Width Width
- | MO_FF_Conv Width Width
- pprMachOp :: MachOp -> SDoc
- isCommutableMachOp :: MachOp -> Bool
- isAssociativeMachOp :: MachOp -> Bool
- isComparisonMachOp :: MachOp -> Bool
- machOpResultType :: MachOp -> [CmmType] -> CmmType
- machOpArgReps :: MachOp -> [Width]
- maybeInvertComparison :: MachOp -> Maybe MachOp
- mo_wordAdd :: MachOp
- mo_wordSub :: MachOp
- mo_wordEq :: MachOp
- mo_wordNe :: MachOp
- mo_wordMul :: MachOp
- mo_wordSQuot :: MachOp
- mo_wordSRem :: MachOp
- mo_wordSNeg :: MachOp
- mo_wordUQuot :: MachOp
- mo_wordURem :: MachOp
- mo_wordSGe :: MachOp
- mo_wordSLe :: MachOp
- mo_wordSGt :: MachOp
- mo_wordSLt :: MachOp
- mo_wordUGe :: MachOp
- mo_wordULe :: MachOp
- mo_wordUGt :: MachOp
- mo_wordULt :: MachOp
- mo_wordAnd :: MachOp
- mo_wordOr :: MachOp
- mo_wordXor :: MachOp
- mo_wordNot :: MachOp
- mo_wordShl :: MachOp
- mo_wordSShr :: MachOp
- mo_wordUShr :: MachOp
- mo_u_8To32 :: MachOp
- mo_s_8To32 :: MachOp
- mo_u_16To32 :: MachOp
- mo_s_16To32 :: MachOp
- mo_u_8ToWord :: MachOp
- mo_s_8ToWord :: MachOp
- mo_u_16ToWord :: MachOp
- mo_s_16ToWord :: MachOp
- mo_u_32ToWord :: MachOp
- mo_s_32ToWord :: MachOp
- mo_32To8 :: MachOp
- mo_32To16 :: MachOp
- mo_WordTo8 :: MachOp
- mo_WordTo16 :: MachOp
- mo_WordTo32 :: MachOp
Documentation
isFloatType :: CmmType -> BoolSource
isGcPtrType :: CmmType -> BoolSource
widthInBits :: Width -> IntSource
widthInBytes :: Width -> IntSource
widthInLog :: Width -> IntSource
widthFromBytes :: Int -> WidthSource
cmmExprType :: CmmExpr -> CmmTypeSource
cmmExprWidth :: CmmExpr -> WidthSource
cmmRegType :: CmmReg -> CmmTypeSource
cmmLitType :: CmmLit -> CmmTypeSource
class DefinerOfLocalRegs a whereSource
foldRegsDefd :: (b -> LocalReg -> b) -> b -> a -> bSource
class UserOfLocalRegs a whereSource
foldRegsUsed :: (b -> LocalReg -> b) -> b -> a -> bSource
UserOfLocalRegs RegSet | |
UserOfLocalRegs LocalReg | |
UserOfLocalRegs CmmReg | |
UserOfLocalRegs CmmExpr | |
UserOfLocalRegs CmmCallTarget | |
UserOfLocalRegs CmmStmt | enable us to fold used registers over |
UserOfLocalRegs MidCallTarget | |
UserOfLocalRegs Last | |
UserOfLocalRegs Middle | |
UserOfLocalRegs a => UserOfLocalRegs [a] | |
UserOfLocalRegs a => UserOfLocalRegs (Maybe a) | |
UserOfLocalRegs a => UserOfLocalRegs (CmmHinted a) | |
UserOfLocalRegs i => UserOfLocalRegs (GenBasicBlock i) | |
UserOfLocalRegs a => UserOfLocalRegs (ZLast a) |
filterRegsUsed :: UserOfLocalRegs e => (LocalReg -> Bool) -> e -> RegSetSource
class DefinerOfSlots a whereSource
foldSlotsDefd :: (b -> SubArea -> b) -> b -> a -> bSource
class UserOfSlots a whereSource
foldSlotsUsed :: (b -> SubArea -> b) -> b -> a -> bSource
UserOfSlots CmmExpr | |
UserOfSlots CmmCallTarget | |
UserOfSlots MidCallTarget | |
UserOfSlots Last | |
UserOfSlots Middle | |
UserOfSlots a => UserOfSlots [a] | |
UserOfSlots a => UserOfSlots (Maybe a) | |
UserOfSlots a => UserOfSlots (CmmHinted a) | |
UserOfSlots l => UserOfSlots (ZLast l) |
elemRegSet :: LocalReg -> RegSet -> BoolSource
extendRegSet :: RegSet -> LocalReg -> RegSetSource
deleteFromRegSet :: RegSet -> LocalReg -> RegSetSource
plusRegSet :: RegSet -> RegSet -> RegSetSource
minusRegSet :: RegSet -> RegSet -> RegSetSource
timesRegSet :: RegSet -> RegSet -> RegSetSource
A stack area is either the stack slot where a variable is spilled or the stack space where function arguments and results are passed.
type SubAreaSet = Map Area [SubArea]Source
isStackSlotOf :: CmmExpr -> LocalReg -> BoolSource
Machine-level primops; ones which we can reasonably delegate to the native code generators to handle. Basically contains C's primops and no others.
Nomenclature: all ops indicate width and signedness, where appropriate. Widths: 8/16/32/64 means the given size, obviously. Nat means the operation works on STG word sized objects. Signedness: S means signed, U means unsigned. For operations where signedness is irrelevant or makes no difference (for example integer add), the signedness component is omitted.
An exception: NatP is a ptr-typed native word. From the point of view of the native code generators this distinction is irrelevant, but the C code generator sometimes needs this info to emit the right casts.
isComparisonMachOp :: MachOp -> BoolSource
Returns True
if the MachOp is a comparison.
If in doubt, return False. This generates worse code on the native routes, but is otherwise harmless.
machOpResultType :: MachOp -> [CmmType] -> CmmTypeSource
Returns the MachRep of the result of a MachOp.
machOpArgReps :: MachOp -> [Width]Source
This function is used for debugging only: we can check whether an application of a MachOp is type-correct by checking that the MachReps of its arguments are the same as the MachOp expects. This is used when linting a CmmExpr.