Safe Haskell | None |
---|
- type CmmProgram = [CmmGroup]
- type CmmGroup = GenCmmGroup CmmStatics CmmTopInfo CmmGraph
- type GenCmmGroup d h g = [GenCmmDecl d h g]
- type CmmDecl = GenCmmDecl CmmStatics CmmTopInfo CmmGraph
- data GenCmmDecl d h g
- type CmmGraph = GenCmmGraph CmmNode
- data GenCmmGraph n = CmmGraph {}
- type CmmBlock = Block CmmNode C C
- data Section
- data CmmStatics = Statics CLabel [CmmStatic]
- data CmmStatic
- = CmmStaticLit CmmLit
- | CmmUninitialised Int
- | CmmString [Word8]
- type CmmReplGraph e x = GenCmmReplGraph CmmNode e x
- type GenCmmReplGraph n e x = UniqSM (Maybe (Graph n e x))
- type CmmFwdRewrite f = FwdRewrite UniqSM CmmNode f
- type CmmBwdRewrite f = BwdRewrite UniqSM CmmNode f
- data CmmTopInfo = TopInfo {}
- data CmmStackInfo = StackInfo {}
- data CmmInfoTable
- = CmmInfoTable { }
- | CmmNonInfoTable
- data ClosureTypeInfo
- = Constr ConstrTag ConstrDescription
- | Fun FunArity ArgDescr
- | Thunk
- | ThunkSelector SelectorOffset
- | BlackHole
- data C_SRT
- = NoC_SRT
- | C_SRT !CLabel !WordOff !StgHalfWord
- needsSRT :: C_SRT -> Bool
- data ProfilingInfo
- = NoProfilingInfo
- | ProfilingInfo [Word8] [Word8]
- type ConstrDescription = [Word8]
- module CmmNode
- module CmmExpr
Cmm top-level datatypes
type CmmProgram = [CmmGroup]Source
type GenCmmGroup d h g = [GenCmmDecl d h g]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) |
type CmmGraph = GenCmmGraph CmmNodeSource
Cmm graphs
type CmmReplGraph e x = GenCmmReplGraph CmmNode e xSource
type GenCmmReplGraph n e x = UniqSM (Maybe (Graph n e x))Source
type CmmFwdRewrite f = FwdRewrite UniqSM CmmNode fSource
type CmmBwdRewrite f = BwdRewrite UniqSM CmmNode fSource
Info Tables
data CmmTopInfo Source
data CmmStackInfo Source
data ClosureTypeInfo Source
Constr ConstrTag ConstrDescription | |
Fun FunArity ArgDescr | |
Thunk | |
ThunkSelector SelectorOffset | |
BlackHole |
type ConstrDescription = [Word8]Source
Statements, expressions and types
module CmmNode
module CmmExpr