- type Cmm = GenCmm CmmStatics CmmInfo (ListGraph CmmStmt)
- type RawCmm = GenCmm CmmStatics (Maybe CmmStatics) (ListGraph CmmStmt)
- type CmmTop = GenCmmTop CmmStatics CmmInfo (ListGraph CmmStmt)
- type RawCmmTop = GenCmmTop CmmStatics (Maybe CmmStatics) (ListGraph CmmStmt)
- newtype ListGraph i = ListGraph [GenBasicBlock i]
- data CmmInfo = CmmInfo (Maybe BlockId) (Maybe UpdateFrame) CmmInfoTable
- data UpdateFrame = UpdateFrame CmmExpr [CmmExpr]
- cmmMapGraph :: (g -> g') -> GenCmm d h g -> GenCmm d h g'
- cmmTopMapGraph :: (g -> g') -> GenCmmTop d h g -> GenCmmTop d h g'
- cmmMapGraphM :: Monad m => (String -> g -> m g') -> GenCmm d h g -> m (GenCmm d h g')
- cmmTopMapGraphM :: Monad m => (String -> g -> m g') -> GenCmmTop d h g -> m (GenCmmTop d h g')
- data GenBasicBlock i = BasicBlock BlockId [i]
- type CmmBasicBlock = GenBasicBlock CmmStmt
- blockId :: GenBasicBlock i -> BlockId
- blockStmts :: GenBasicBlock i -> [i]
- mapBlockStmts :: (i -> i') -> GenBasicBlock i -> GenBasicBlock i'
- data CmmStmt
- = CmmNop
- | CmmComment FastString
- | CmmAssign CmmReg CmmExpr
- | CmmStore CmmExpr CmmExpr
- | CmmCall CmmCallTarget [HintedCmmFormal] [HintedCmmActual] CmmSafety CmmReturnInfo
- | CmmBranch BlockId
- | CmmCondBranch CmmExpr BlockId
- | CmmSwitch CmmExpr [Maybe BlockId]
- | CmmJump CmmExpr [HintedCmmActual]
- | CmmReturn [HintedCmmActual]
- data CmmReturnInfo
- data CmmHinted a = CmmHinted {
- hintlessCmm :: a
- cmmHint :: ForeignHint
- type HintedCmmFormal = CmmHinted CmmFormal
- type HintedCmmActual = CmmHinted CmmActual
- data CmmSafety
- data CmmCallTarget
- module CmmDecl
- module CmmExpr
Documentation
type Cmm = GenCmm CmmStatics CmmInfo (ListGraph CmmStmt)Source
Cmm with the info table as a data type
type RawCmm = GenCmm CmmStatics (Maybe CmmStatics) (ListGraph CmmStmt)Source
Cmm with the info tables converted to a list of CmmStatic
along with the info
table label. If we are building without tables-next-to-code there will be no statics
INVARIANT: if there is an info table, it has at least one CmmStatic
type RawCmmTop = GenCmmTop CmmStatics (Maybe CmmStatics) (ListGraph CmmStmt)Source
A control-flow graph represented as a list of extended basic blocks.
ListGraph [GenBasicBlock i] | Code, may be empty. The first block is the entry point. The order is otherwise initially unimportant, but at some point the code gen will fix the order. |
PlatformOutputable instr => PlatformOutputable (ListGraph instr) |
data UpdateFrame Source
A frame that is to be pushed before entry to the function.
Used to handle update
frames.
cmmMapGraph :: (g -> g') -> GenCmm d h g -> GenCmm d h g'Source
cmmTopMapGraph :: (g -> g') -> GenCmmTop d h g -> GenCmmTop d h g'Source
cmmTopMapGraphM :: Monad m => (String -> g -> m g') -> GenCmmTop d h g -> m (GenCmmTop d h g')Source
data GenBasicBlock i Source
BasicBlock BlockId [i] |
PlatformOutputable instr => PlatformOutputable (GenBasicBlock instr) | |
UserOfLocalRegs i => UserOfLocalRegs (GenBasicBlock i) |
blockId :: GenBasicBlock i -> BlockIdSource
blockStmts :: GenBasicBlock i -> [i]Source
mapBlockStmts :: (i -> i') -> GenBasicBlock i -> GenBasicBlock i'Source
PlatformOutputable CmmStmt | |
Outputable CmmStmt | |
UserOfLocalRegs CmmStmt | enable us to fold used registers over '[CmmActual]' and '[CmmFormal]' |
CmmHinted | |
|
Eq a => Eq (CmmHinted a) | |
Outputable a => Outputable (CmmHinted a) | |
UserOfSlots a => UserOfSlots (CmmHinted a) | |
DefinerOfLocalRegs a => DefinerOfLocalRegs (CmmHinted a) | |
UserOfLocalRegs a => UserOfLocalRegs (CmmHinted a) |
data CmmCallTarget Source
module CmmDecl
module CmmExpr