ghc-6.12.1: The GHC APISource codeContentsIndex
CmmExpr
Synopsis
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
= W8
| W16
| W32
| W64
| W80
| W128
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
= CmmLit CmmLit
| CmmLoad CmmExpr CmmType
| CmmReg CmmReg
| CmmMachOp MachOp [CmmExpr]
| CmmStackSlot Area Int
| CmmRegOff CmmReg Int
cmmExprType :: CmmExpr -> CmmType
cmmExprWidth :: CmmExpr -> Width
maybeInvertCmmExpr :: CmmExpr -> Maybe CmmExpr
data CmmReg
= CmmLocal LocalReg
| CmmGlobal GlobalReg
cmmRegType :: CmmReg -> CmmType
data CmmLit
= CmmInt Integer Width
| CmmFloat Rational Width
| CmmLabel CLabel
| CmmLabelOff CLabel Int
| CmmLabelDiffOff CLabel CLabel Int
| CmmBlock BlockId
| CmmHighStackMark
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
= VGcPtr
| VNonGcPtr
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
data Area
= RegSlot LocalReg
| CallArea AreaId
data AreaId
= Old
| Young BlockId
type SubArea = (Area, Int, Int)
type SubAreaSet = FiniteMap Area [SubArea]
type AreaMap = FiniteMap 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
data CmmType Source
show/hide Instances
b8 :: CmmTypeSource
b16 :: CmmTypeSource
b32 :: CmmTypeSource
b64 :: CmmTypeSource
f32 :: CmmTypeSource
f64 :: CmmTypeSource
bWord :: CmmTypeSource
bHalfWord :: CmmTypeSource
gcWord :: CmmTypeSource
cInt :: CmmTypeSource
cLong :: CmmTypeSource
cmmBits :: Width -> CmmTypeSource
cmmFloat :: Width -> CmmTypeSource
typeWidth :: CmmType -> WidthSource
cmmEqType :: CmmType -> CmmType -> BoolSource
cmmEqType_ignoring_ptrhood :: CmmType -> CmmType -> BoolSource
isFloatType :: CmmType -> BoolSource
isGcPtrType :: CmmType -> BoolSource
isWord32 :: CmmType -> BoolSource
isWord64 :: CmmType -> BoolSource
isFloat64 :: CmmType -> BoolSource
isFloat32 :: CmmType -> BoolSource
data Width Source
Constructors
W8
W16
W32
W64
W80
W128
show/hide Instances
widthInBits :: Width -> IntSource
widthInBytes :: Width -> IntSource
widthInLog :: Width -> IntSource
widthFromBytes :: Int -> WidthSource
wordWidth :: WidthSource
halfWordWidth :: WidthSource
cIntWidth :: WidthSource
cLongWidth :: WidthSource
narrowU :: Width -> Integer -> IntegerSource
narrowS :: Width -> Integer -> IntegerSource
data CmmExpr Source
Constructors
CmmLit CmmLit
CmmLoad CmmExpr CmmType
CmmReg CmmReg
CmmMachOp MachOp [CmmExpr]
CmmStackSlot Area Int
CmmRegOff CmmReg Int
show/hide Instances
cmmExprType :: CmmExpr -> CmmTypeSource
cmmExprWidth :: CmmExpr -> WidthSource
maybeInvertCmmExpr :: CmmExpr -> Maybe CmmExprSource
data CmmReg Source
Constructors
CmmLocal LocalReg
CmmGlobal GlobalReg
show/hide Instances
cmmRegType :: CmmReg -> CmmTypeSource
data CmmLit Source
Constructors
CmmInt Integer Width
CmmFloat Rational Width
CmmLabel CLabel
CmmLabelOff CLabel Int
CmmLabelDiffOff CLabel CLabel Int
CmmBlock BlockId
CmmHighStackMark
show/hide Instances
cmmLitType :: CmmLit -> CmmTypeSource
data LocalReg Source
Constructors
LocalReg !Unique CmmTypeParameters: 1. Identifier 2. Type
show/hide Instances
localRegType :: LocalReg -> CmmTypeSource
data GlobalReg Source
Constructors
VanillaReg !Int VGcPtr
FloatReg !Int
DoubleReg !Int
LongReg !Int
Sp
SpLim
Hp
HpLim
CurrentTSO
CurrentNursery
HpAlloc
EagerBlackholeInfo
GCEnter1
GCFun
BaseReg
PicBaseReg
show/hide Instances
globalRegType :: GlobalReg -> CmmTypeSource
spReg :: CmmRegSource
hpReg :: CmmRegSource
spLimReg :: CmmRegSource
nodeReg :: CmmRegSource
node :: GlobalRegSource
data VGcPtr Source
Constructors
VGcPtr
VNonGcPtr
show/hide Instances
vgcFlag :: CmmType -> VGcPtrSource
class DefinerOfLocalRegs a whereSource
Methods
foldRegsDefd :: (b -> LocalReg -> b) -> b -> a -> bSource
show/hide Instances
class UserOfLocalRegs a whereSource
Methods
foldRegsUsed :: (b -> LocalReg -> b) -> b -> a -> bSource
show/hide Instances
filterRegsUsed :: UserOfLocalRegs e => (LocalReg -> Bool) -> e -> RegSetSource
class DefinerOfSlots a whereSource
Methods
foldSlotsDefd :: (b -> SubArea -> b) -> b -> a -> bSource
show/hide Instances
class UserOfSlots a whereSource
Methods
foldSlotsUsed :: (b -> SubArea -> b) -> b -> a -> bSource
show/hide Instances
type RegSet = UniqSet LocalRegSource
Sets of local registers
emptyRegSet :: RegSetSource
elemRegSet :: LocalReg -> RegSet -> BoolSource
extendRegSet :: RegSet -> LocalReg -> RegSetSource
deleteFromRegSet :: RegSet -> LocalReg -> RegSetSource
mkRegSet :: [LocalReg] -> RegSetSource
plusRegSet :: RegSet -> RegSet -> RegSetSource
minusRegSet :: RegSet -> RegSet -> RegSetSource
timesRegSet :: RegSet -> RegSet -> RegSetSource
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
RegSlot LocalReg
CallArea AreaId
show/hide Instances
data AreaId Source
Constructors
Old
Young BlockId
show/hide Instances
type SubArea = (Area, Int, Int)Source
type SubAreaSet = FiniteMap Area [SubArea]Source
type AreaMap = FiniteMap Area IntSource
isStackSlotOf :: CmmExpr -> LocalReg -> BoolSource
data MachOp Source

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.

Constructors
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
show/hide Instances
pprMachOp :: MachOp -> SDocSource
isCommutableMachOp :: MachOp -> BoolSource

Returns True if the MachOp has commutable arguments. This is used in the platform-independent Cmm optimisations.

If in doubt, return False. This generates worse code on the native routes, but is otherwise harmless.

isAssociativeMachOp :: MachOp -> BoolSource

Returns True if the MachOp is associative (i.e. (x+y)+z == x+(y+z)) This is used in the platform-independent Cmm optimisations.

If in doubt, return False. This generates worse code on the native routes, but is otherwise harmless.

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.
maybeInvertComparison :: MachOp -> Maybe MachOpSource
mo_wordAdd :: MachOpSource
mo_wordSub :: MachOpSource
mo_wordEq :: MachOpSource
mo_wordNe :: MachOpSource
mo_wordMul :: MachOpSource
mo_wordSQuot :: MachOpSource
mo_wordSRem :: MachOpSource
mo_wordSNeg :: MachOpSource
mo_wordUQuot :: MachOpSource
mo_wordURem :: MachOpSource
mo_wordSGe :: MachOpSource
mo_wordSLe :: MachOpSource
mo_wordSGt :: MachOpSource
mo_wordSLt :: MachOpSource
mo_wordUGe :: MachOpSource
mo_wordULe :: MachOpSource
mo_wordUGt :: MachOpSource
mo_wordULt :: MachOpSource
mo_wordAnd :: MachOpSource
mo_wordOr :: MachOpSource
mo_wordXor :: MachOpSource
mo_wordNot :: MachOpSource
mo_wordShl :: MachOpSource
mo_wordSShr :: MachOpSource
mo_wordUShr :: MachOpSource
mo_u_8To32 :: MachOpSource
mo_s_8To32 :: MachOpSource
mo_u_16To32 :: MachOpSource
mo_s_16To32 :: MachOpSource
mo_u_8ToWord :: MachOpSource
mo_s_8ToWord :: MachOpSource
mo_u_16ToWord :: MachOpSource
mo_s_16ToWord :: MachOpSource
mo_u_32ToWord :: MachOpSource
mo_s_32ToWord :: MachOpSource
mo_32To8 :: MachOpSource
mo_32To16 :: MachOpSource
mo_WordTo8 :: MachOpSource
mo_WordTo16 :: MachOpSource
mo_WordTo32 :: MachOpSource
Produced by Haddock version 2.6.0