- newtype GenCmm d h g = Cmm [GenCmmTop d h g]
- type Cmm = GenCmm CmmStatic CmmInfo (ListGraph CmmStmt)
- type RawCmm = GenCmm CmmStatic [CmmStatic] (ListGraph CmmStmt)
- data GenCmmTop d h g
- = CmmProc h CLabel CmmFormals g
- | CmmData Section [d]
- type CmmTop = GenCmmTop CmmStatic CmmInfo (ListGraph CmmStmt)
- type RawCmmTop = GenCmmTop CmmStatic [CmmStatic] (ListGraph CmmStmt)
- newtype ListGraph i = ListGraph [GenBasicBlock i]
- 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 CmmInfo = CmmInfo (Maybe BlockId) (Maybe UpdateFrame) CmmInfoTable
- data UpdateFrame = UpdateFrame CmmExpr [CmmExpr]
- data CmmInfoTable
- type HasStaticClosure = Bool
- data ClosureTypeInfo
- = ConstrInfo ClosureLayout ConstrTag ConstrDescription
- | FunInfo ClosureLayout C_SRT FunArity ArgDescr SlowEntry
- | ThunkInfo ClosureLayout C_SRT
- | ThunkSelectorInfo SelectorOffset C_SRT
- | ContInfo [Maybe LocalReg] C_SRT
- type ConstrDescription = CmmLit
- data ProfilingInfo = ProfilingInfo CmmLit CmmLit
- type ClosureTypeTag = StgHalfWord
- 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 CmmReturnInfo
- data CmmStmt
- = CmmNop
- | CmmComment FastString
- | CmmAssign CmmReg CmmExpr
- | CmmStore CmmExpr CmmExpr
- | CmmCall CmmCallTarget HintedCmmFormals HintedCmmActuals CmmSafety CmmReturnInfo
- | CmmBranch BlockId
- | CmmCondBranch CmmExpr BlockId
- | CmmSwitch CmmExpr [Maybe BlockId]
- | CmmJump CmmExpr HintedCmmActuals
- | CmmReturn HintedCmmActuals
- type CmmActual = CmmExpr
- type CmmActuals = [CmmActual]
- type CmmFormal = LocalReg
- type CmmFormals = [CmmFormal]
- type HintedCmmFormal = CmmHinted CmmFormal
- type HintedCmmFormals = [HintedCmmFormal]
- type HintedCmmActual = CmmHinted CmmActual
- type HintedCmmActuals = [HintedCmmActual]
- data CmmSafety
- data CmmCallTarget
- data CallishMachOp
- = MO_F64_Pwr
- | MO_F64_Sin
- | MO_F64_Cos
- | MO_F64_Tan
- | MO_F64_Sinh
- | MO_F64_Cosh
- | MO_F64_Tanh
- | MO_F64_Asin
- | MO_F64_Acos
- | MO_F64_Atan
- | MO_F64_Log
- | MO_F64_Exp
- | MO_F64_Sqrt
- | MO_F32_Pwr
- | MO_F32_Sin
- | MO_F32_Cos
- | MO_F32_Tan
- | MO_F32_Sinh
- | MO_F32_Cosh
- | MO_F32_Tanh
- | MO_F32_Asin
- | MO_F32_Acos
- | MO_F32_Atan
- | MO_F32_Log
- | MO_F32_Exp
- | MO_F32_Sqrt
- | MO_WriteBarrier
- | MO_Touch
- pprCallishMachOp :: CallishMachOp -> SDoc
- data ForeignHint
- = NoHint
- | AddrHint
- | SignedHint
- data CmmHinted a = CmmHinted {
- hintlessCmm :: a
- cmmHint :: ForeignHint
- data CmmStatic
- = CmmStaticLit CmmLit
- | CmmUninitialised Int
- | CmmAlign Int
- | CmmDataLabel CLabel
- | CmmString [Word8]
- data Section
- module CmmExpr
Documentation
(Outputable d, Outputable info, Outputable g) => Outputable (GenCmm d info g) |
type RawCmm = GenCmm CmmStatic [CmmStatic] (ListGraph CmmStmt)Source
Cmm with the info tables converted to a list of CmmStatic
A top-level chunk, abstracted over the type of the contents of the basic blocks (Cmm or instructions are the likely instantiations).
CmmProc h CLabel CmmFormals g | |
CmmData Section [d] |
(Outputable d, Outputable info, Outputable i) => Outputable (GenCmmTop d info i) |
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. |
Outputable instr => Outputable (ListGraph instr) |
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 UpdateFrame Source
A frame that is to be pushed before entry to the function.
Used to handle update
frames.
data CmmInfoTable Source
type HasStaticClosure = BoolSource
data ClosureTypeInfo Source
ConstrInfo ClosureLayout ConstrTag ConstrDescription | |
FunInfo ClosureLayout C_SRT FunArity ArgDescr SlowEntry | |
ThunkInfo ClosureLayout C_SRT | |
ThunkSelectorInfo SelectorOffset C_SRT | |
ContInfo [Maybe LocalReg] C_SRT |
type ConstrDescription = CmmLitSource
type ClosureTypeTag = StgHalfWordSource
data GenBasicBlock i Source
BasicBlock BlockId [i] |
Outputable instr => Outputable (GenBasicBlock instr) | |
UserOfLocalRegs i => UserOfLocalRegs (GenBasicBlock i) |
blockId :: GenBasicBlock i -> BlockIdSource
blockStmts :: GenBasicBlock i -> [i]Source
mapBlockStmts :: (i -> i') -> GenBasicBlock i -> GenBasicBlock i'Source
Outputable CmmStmt | |
UserOfLocalRegs CmmStmt | enable us to fold used registers over |
type CmmActuals = [CmmActual]Source
type CmmFormals = [CmmFormal]Source
type HintedCmmFormals = [HintedCmmFormal]Source
type HintedCmmActuals = [HintedCmmActual]Source
data CmmCallTarget Source
data CallishMachOp Source
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) |
module CmmExpr