ghc-6.12.1: The GHC APISource codeContentsIndex
CmmUtils
Synopsis
type CmmStmts = OrdList CmmStmt
noStmts :: CmmStmts
oneStmt :: CmmStmt -> CmmStmts
mkStmts :: [CmmStmt] -> CmmStmts
plusStmts :: CmmStmts -> CmmStmts -> CmmStmts
stmtList :: CmmStmts -> [CmmStmt]
isNopStmt :: CmmStmt -> Bool
primRepCmmType :: PrimRep -> CmmType
primRepForeignHint :: PrimRep -> ForeignHint
typeCmmType :: Type -> CmmType
typeForeignHint :: Type -> ForeignHint
isTrivialCmmExpr :: CmmExpr -> Bool
hasNoGlobalRegs :: CmmExpr -> Bool
cmmRegOff :: CmmReg -> Int -> CmmExpr
cmmLabelOff :: CLabel -> Int -> CmmLit
cmmOffset :: CmmExpr -> Int -> CmmExpr
cmmOffsetLit :: CmmLit -> Int -> CmmLit
cmmIndex :: Width -> CmmExpr -> Int -> CmmExpr
cmmOffsetExpr :: CmmExpr -> CmmExpr -> CmmExpr
cmmIndexExpr :: Width -> CmmExpr -> CmmExpr -> CmmExpr
cmmLoadIndex :: CmmType -> CmmExpr -> Int -> CmmExpr
mkIntCLit :: Int -> CmmLit
zeroCLit :: CmmLit
mkLblExpr :: CLabel -> CmmExpr
maybeAssignTemp :: [Unique] -> CmmExpr -> ([Unique], [CmmStmt], CmmExpr)
loadArgsIntoTemps :: [Unique] -> HintedCmmActuals -> ([Unique], [CmmStmt], HintedCmmActuals)
Documentation
type CmmStmts = OrdList CmmStmtSource
noStmts :: CmmStmtsSource
oneStmt :: CmmStmt -> CmmStmtsSource
mkStmts :: [CmmStmt] -> CmmStmtsSource
plusStmts :: CmmStmts -> CmmStmts -> CmmStmtsSource
stmtList :: CmmStmts -> [CmmStmt]Source
isNopStmt :: CmmStmt -> BoolSource
primRepCmmType :: PrimRep -> CmmTypeSource
primRepForeignHint :: PrimRep -> ForeignHintSource
typeCmmType :: Type -> CmmTypeSource
typeForeignHint :: Type -> ForeignHintSource
isTrivialCmmExpr :: CmmExpr -> BoolSource
hasNoGlobalRegs :: CmmExpr -> BoolSource
cmmRegOff :: CmmReg -> Int -> CmmExprSource
cmmLabelOff :: CLabel -> Int -> CmmLitSource
cmmOffset :: CmmExpr -> Int -> CmmExprSource
cmmOffsetLit :: CmmLit -> Int -> CmmLitSource
cmmIndex :: Width -> CmmExpr -> Int -> CmmExprSource
Useful for creating an index into an array, with a staticaly known offset. The type is the element type; used for making the multiplier
cmmOffsetExpr :: CmmExpr -> CmmExpr -> CmmExprSource
cmmIndexExpr :: Width -> CmmExpr -> CmmExpr -> CmmExprSource
Useful for creating an index into an array, with an unknown offset.
cmmLoadIndex :: CmmType -> CmmExpr -> Int -> CmmExprSource
mkIntCLit :: Int -> CmmLitSource
zeroCLit :: CmmLitSource
mkLblExpr :: CLabel -> CmmExprSource
maybeAssignTemp :: [Unique] -> CmmExpr -> ([Unique], [CmmStmt], CmmExpr)Source
loadArgsIntoTemps :: [Unique] -> HintedCmmActuals -> ([Unique], [CmmStmt], HintedCmmActuals)Source
Produced by Haddock version 2.6.0