Safe Haskell | Safe-Infered |
---|
- type CmmGroup = GenCmmGroup CmmStatics CmmInfo (ListGraph CmmStmt)
- type GenCmmGroup d h g = [GenCmmDecl d h g]
- type RawCmmGroup = GenCmmGroup CmmStatics (Maybe CmmStatics) (ListGraph CmmStmt)
- type CmmDecl = GenCmmDecl CmmStatics CmmInfo (ListGraph CmmStmt)
- type RawCmmDecl = GenCmmDecl CmmStatics (Maybe CmmStatics) (ListGraph CmmStmt)
- newtype ListGraph i = ListGraph [GenBasicBlock i]
- data CmmInfo = CmmInfo (Maybe BlockId) (Maybe UpdateFrame) CmmInfoTable
- data UpdateFrame = UpdateFrame CmmExpr [CmmExpr]
- 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
- = CmmNop
- | CmmComment FastString
- | CmmAssign CmmReg CmmExpr
- | CmmStore CmmExpr CmmExpr
- | CmmCall CmmCallTarget [HintedCmmFormal] [HintedCmmActual] 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
- 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 CmmInfo (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 CmmDecl = GenCmmDecl CmmStatics CmmInfo (ListGraph CmmStmt)Source
type RawCmmDecl = GenCmmDecl 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.
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] |
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 | |
UserOfLocalRegs CmmStmt | enable us to fold used registers over '[CmmActual]' and '[CmmFormal]' |
CmmHinted | |
|
Eq a => Eq (CmmHinted a) | |
PlatformOutputable a => PlatformOutputable (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
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).
(PlatformOutputable d, PlatformOutputable info, PlatformOutputable i) => PlatformOutputable (GenCmmDecl d info i) |
data ForeignHint Source
module CmmExpr