ghc-6.12.2: The GHC APISource codeContentsIndex
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 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
= CmmInfoTable HasStaticClosure ProfilingInfo ClosureTypeTag ClosureTypeInfo
| CmmNonInfoTable
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
= CmmMayReturn
| CmmNeverReturns
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
= CmmUnsafe
| CmmSafe C_SRT
data CmmCallTarget
= CmmCallee CmmExpr CCallConv
| CmmPrim CallishMachOp
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
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
= Text
| Data
| ReadOnlyData
| RelocatableReadOnlyData
| UninitialisedData
| ReadOnlyData16
| OtherSection String
module CmmExpr
Documentation
newtype GenCmm d h g Source
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)Source
Cmm with the info table as a data type
type RawCmm = GenCmm CmmStatic [CmmStatic] (ListGraph CmmStmt)Source
Cmm with the info tables converted to a list of CmmStatic
data GenCmmTop 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).
Constructors
CmmProc h CLabel CmmFormals g
CmmData Section [d]
show/hide Instances
type CmmTop = GenCmmTop CmmStatic CmmInfo (ListGraph CmmStmt)Source
type RawCmmTop = GenCmmTop CmmStatic [CmmStatic] (ListGraph CmmStmt)Source
newtype ListGraph i Source
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'Source
cmmTopMapGraph :: (g -> g') -> GenCmmTop d h g -> GenCmmTop d h g'Source
cmmMapGraphM :: Monad m => (String -> g -> m g') -> GenCmm d h g -> m (GenCmm d h g')Source
cmmTopMapGraphM :: Monad m => (String -> g -> m g') -> GenCmmTop d h g -> m (GenCmmTop d h g')Source
data CmmInfo Source
Constructors
CmmInfo (Maybe BlockId) (Maybe UpdateFrame) CmmInfoTable
show/hide Instances
data UpdateFrame Source
A frame that is to be pushed before entry to the function. Used to handle update frames.
Constructors
UpdateFrame CmmExpr [CmmExpr]
data CmmInfoTable Source
Constructors
CmmInfoTable HasStaticClosure ProfilingInfo ClosureTypeTag ClosureTypeInfo
CmmNonInfoTable
type HasStaticClosure = BoolSource
data ClosureTypeInfo Source
Constructors
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
data ProfilingInfo Source
Constructors
ProfilingInfo CmmLit CmmLit
type ClosureTypeTag = StgHalfWordSource
data GenBasicBlock i Source
Constructors
BasicBlock BlockId [i]
show/hide Instances
type CmmBasicBlock = GenBasicBlock CmmStmtSource
blockId :: GenBasicBlock i -> BlockIdSource
blockStmts :: GenBasicBlock i -> [i]Source
mapBlockStmts :: (i -> i') -> GenBasicBlock i -> GenBasicBlock i'Source
data CmmReturnInfo Source
Constructors
CmmMayReturn
CmmNeverReturns
data CmmStmt Source
Constructors
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
show/hide Instances
type CmmActual = CmmExprSource
type CmmActuals = [CmmActual]Source
type CmmFormal = LocalRegSource
type CmmFormals = [CmmFormal]Source
type HintedCmmFormal = CmmHinted CmmFormalSource
type HintedCmmFormals = [HintedCmmFormal]Source
type HintedCmmActual = CmmHinted CmmActualSource
type HintedCmmActuals = [HintedCmmActual]Source
data CmmSafety Source
Constructors
CmmUnsafe
CmmSafe C_SRT
show/hide Instances
data CmmCallTarget Source
Constructors
CmmCallee CmmExpr CCallConv
CmmPrim CallishMachOp
show/hide Instances
data CallishMachOp Source
Constructors
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
show/hide Instances
pprCallishMachOp :: CallishMachOp -> SDocSource
data ForeignHint Source
Constructors
NoHint
AddrHint
SignedHint
show/hide Instances
data CmmHinted a Source
Constructors
CmmHinted
hintlessCmm :: a
cmmHint :: ForeignHint
show/hide Instances
data CmmStatic Source
Constructors
CmmStaticLit CmmLit
CmmUninitialised Int
CmmAlign Int
CmmDataLabel CLabel
CmmString [Word8]
show/hide Instances
data Section Source
Constructors
Text
Data
ReadOnlyData
RelocatableReadOnlyData
UninitialisedData
ReadOnlyData16
OtherSection String
module CmmExpr
Produced by Haddock version 2.6.1