Safe Haskell | None |
---|
- type CmmGroup = GenCmmGroup CmmStatics CmmInfoTable (ListGraph CmmStmt)
- type GenCmmGroup d h g = [GenCmmDecl d h g]
- type RawCmmGroup = GenCmmGroup CmmStatics (Maybe CmmStatics) (ListGraph CmmStmt)
- type CmmDecl = GenCmmDecl CmmStatics CmmInfoTable (ListGraph CmmStmt)
- type RawCmmDecl = GenCmmDecl CmmStatics (Maybe CmmStatics) (ListGraph CmmStmt)
- newtype ListGraph i = ListGraph [GenBasicBlock i]
- data CmmInfoTable
- = CmmInfoTable { }
- | CmmNonInfoTable
- data ClosureTypeInfo
- = Constr ConstrTag ConstrDescription
- | Fun FunArity ArgDescr
- | Thunk
- | ThunkSelector SelectorOffset
- | BlackHole
- data CmmStatic
- = CmmStaticLit CmmLit
- | CmmUninitialised Int
- | CmmString [Word8]
- data CmmStatics = Statics CLabel [CmmStatic]
- type CmmFormal = LocalReg
- type CmmActual = CmmExpr
- cmmMapGraph :: (g -> g') -> GenCmmGroup d h g -> GenCmmGroup d h g'
- cmmTopMapGraph :: (g -> g') -> GenCmmDecl d h g -> GenCmmDecl 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
- data CmmReturnInfo
- data CmmHinted a = CmmHinted {
- hintlessCmm :: a
- cmmHint :: ForeignHint
- type HintedCmmFormal = CmmHinted CmmFormal
- type HintedCmmActual = CmmHinted CmmActual
- data CmmSafety
- data CmmCallTarget
- data GenCmmDecl d h g
- data ForeignHint
- = NoHint
- | AddrHint
- | SignedHint
- module CmmExpr
- data Section
- data ProfilingInfo
- = NoProfilingInfo
- | ProfilingInfo [Word8] [Word8]
- data C_SRT
- = NoC_SRT
- | C_SRT !CLabel !WordOff !StgHalfWord
Documentation
type CmmGroup = GenCmmGroup CmmStatics CmmInfoTable (ListGraph CmmStmt)Source
Cmm with the info table as a data type
type GenCmmGroup d h g = [GenCmmDecl d h g]Source
type RawCmmGroup = GenCmmGroup 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 RawCmmDecl = GenCmmDecl CmmStatics (Maybe CmmStatics) (ListGraph CmmStmt)Source
A control-flow graph represented as a list of extended basic blocks.
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.
BlockIds must be unique across an entire compilation unit, since they are translated to assembly-language labels, which scope across a whole compilation unit.
Outputable instr => Outputable (ListGraph instr) |
data ClosureTypeInfo Source
Constr ConstrTag ConstrDescription | |
Fun FunArity ArgDescr | |
Thunk | |
ThunkSelector SelectorOffset | |
BlackHole |
cmmMapGraph :: (g -> g') -> GenCmmGroup d h g -> GenCmmGroup d h g'Source
cmmTopMapGraph :: (g -> g') -> GenCmmDecl d h g -> GenCmmDecl d h g'Source
data GenBasicBlock i Source
BasicBlock BlockId [i] |
Outputable instr => Outputable (GenBasicBlock instr) | |
UserOfLocalRegs i => UserOfLocalRegs (GenBasicBlock i) |
blockId :: GenBasicBlock i -> BlockIdSource
The branch block id is that of the first block in the branch, which is that branch's entry point
blockStmts :: GenBasicBlock i -> [i]Source
mapBlockStmts :: (i -> i') -> GenBasicBlock i -> GenBasicBlock i'Source
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) | |
DefinerOfLocalRegs a => DefinerOfLocalRegs (CmmHinted a) | |
UserOfLocalRegs a => UserOfLocalRegs (CmmHinted a) |
data CmmCallTarget Source
data GenCmmDecl d h g Source
A top-level chunk, abstracted over the type of the contents of the basic blocks (Cmm or instructions are the likely instantiations).
(Outputable d, Outputable info, Outputable i) => Outputable (GenCmmDecl d info i) |
module CmmExpr