ghc-6.10.4: The GHC APIContentsIndex
Cmm
Synopsis
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 CmmFormalsWithoutKinds 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
= CmmInfoTable ProfilingInfo ClosureTypeTag ClosureTypeInfo
| CmmNonInfoTable
data ClosureTypeInfo
= ConstrInfo ClosureLayout ConstrTag ConstrDescription
| FunInfo ClosureLayout C_SRT FunType FunArity ArgDescr SlowEntry
| ThunkInfo ClosureLayout C_SRT
| ThunkSelectorInfo SelectorOffset C_SRT
| ContInfo [Maybe LocalReg] C_SRT
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
= CmmMayReturn
| CmmNeverReturns
data CmmStmt
= CmmNop
| CmmComment FastString
| CmmAssign CmmReg CmmExpr
| CmmStore CmmExpr CmmExpr
| CmmCall CmmCallTarget CmmFormals CmmActuals CmmSafety CmmReturnInfo
| CmmBranch BlockId
| CmmCondBranch CmmExpr BlockId
| CmmSwitch CmmExpr [Maybe BlockId]
| CmmJump CmmExpr CmmActuals
| CmmReturn CmmActuals
type CmmActual = CmmKinded CmmExpr
type CmmActuals = [CmmActual]
type CmmFormal = CmmKinded LocalReg
type CmmFormals = [CmmFormal]
type CmmKind = MachHint
type CmmFormalsWithoutKinds = [CmmFormalWithoutKind]
type CmmFormalWithoutKind = LocalReg
data CmmKinded a = CmmKinded {
kindlessCmm :: a
cmmKind :: CmmKind
}
data CmmSafety
= CmmUnsafe
| CmmSafe C_SRT
data CmmCallTarget
= CmmCallee CmmExpr CCallConv
| CmmPrim CallishMachOp
data CmmStatic
= CmmStaticLit CmmLit
| CmmUninitialised Int
| CmmAlign Int
| CmmDataLabel CLabel
| CmmString [Word8]
data Section
= Text
| Data
| ReadOnlyData
| RelocatableReadOnlyData
| UninitialisedData
| ReadOnlyData16
| OtherSection String
module CmmExpr
Documentation
newtype GenCmm d h g
Constructors
Cmm [GenCmmTop d h g]
show/hide Instances
(Outputable d, Outputable info, Outputable g) => Outputable (GenCmm d info g)
type Cmm = GenCmm CmmStatic CmmInfo (ListGraph CmmStmt)
Cmm with the info table as a data type
type RawCmm = GenCmm CmmStatic [CmmStatic] (ListGraph CmmStmt)
Cmm with the info tables converted to a list of CmmStatic
data GenCmmTop d h g
A top-level chunk, abstracted over the type of the contents of the basic blocks (Cmm or instructions are the likely instantiations).
Constructors
CmmProc h CLabel CmmFormalsWithoutKinds g
CmmData Section [d]
show/hide Instances
type CmmTop = GenCmmTop CmmStatic CmmInfo (ListGraph CmmStmt)
type RawCmmTop = GenCmmTop CmmStatic [CmmStatic] (ListGraph CmmStmt)
newtype ListGraph i
A control-flow graph represented as a list of extended basic blocks.
Constructors
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.
show/hide Instances
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
Constructors
CmmInfo (Maybe BlockId) (Maybe UpdateFrame) CmmInfoTable
show/hide Instances
data UpdateFrame
A frame that is to be pushed before entry to the function. Used to handle update frames.
Constructors
UpdateFrame CmmExpr [CmmExpr]
data CmmInfoTable
Constructors
CmmInfoTable ProfilingInfo ClosureTypeTag ClosureTypeInfo
CmmNonInfoTable
data ClosureTypeInfo
Constructors
ConstrInfo ClosureLayout ConstrTag ConstrDescription
FunInfo ClosureLayout C_SRT FunType FunArity ArgDescr SlowEntry
ThunkInfo ClosureLayout C_SRT
ThunkSelectorInfo SelectorOffset C_SRT
ContInfo [Maybe LocalReg] C_SRT
data ProfilingInfo
Constructors
ProfilingInfo CmmLit CmmLit
type ClosureTypeTag = StgHalfWord
data GenBasicBlock i
Constructors
BasicBlock BlockId [i]
show/hide Instances
type CmmBasicBlock = GenBasicBlock CmmStmt
blockId :: GenBasicBlock i -> BlockId
blockStmts :: GenBasicBlock i -> [i]
mapBlockStmts :: (i -> i') -> GenBasicBlock i -> GenBasicBlock i'
data CmmReturnInfo
Constructors
CmmMayReturn
CmmNeverReturns
data CmmStmt
Constructors
CmmNop
CmmComment FastString
CmmAssign CmmReg CmmExpr
CmmStore CmmExpr CmmExpr
CmmCall CmmCallTarget CmmFormals CmmActuals CmmSafety CmmReturnInfo
CmmBranch BlockId
CmmCondBranch CmmExpr BlockId
CmmSwitch CmmExpr [Maybe BlockId]
CmmJump CmmExpr CmmActuals
CmmReturn CmmActuals
show/hide Instances
type CmmActual = CmmKinded CmmExpr
type CmmActuals = [CmmActual]
type CmmFormal = CmmKinded LocalReg
type CmmFormals = [CmmFormal]
type CmmKind = MachHint
type CmmFormalsWithoutKinds = [CmmFormalWithoutKind]
type CmmFormalWithoutKind = LocalReg
data CmmKinded a
Constructors
CmmKinded
kindlessCmm :: a
cmmKind :: CmmKind
show/hide Instances
data CmmSafety
Constructors
CmmUnsafe
CmmSafe C_SRT
show/hide Instances
data CmmCallTarget
Constructors
CmmCallee CmmExpr CCallConv
CmmPrim CallishMachOp
show/hide Instances
data CmmStatic
Constructors
CmmStaticLit CmmLit
CmmUninitialised Int
CmmAlign Int
CmmDataLabel CLabel
CmmString [Word8]
show/hide Instances
data Section
Constructors
Text
Data
ReadOnlyData
RelocatableReadOnlyData
UninitialisedData
ReadOnlyData16
OtherSection String
module CmmExpr
Produced by Haddock version 2.4.2