- addIdReps :: [Id] -> [(CgRep, Id)]
- cgLit :: Literal -> FCode CmmLit
- emitDataLits :: CLabel -> [CmmLit] -> Code
- mkDataLits :: CLabel -> [CmmLit] -> GenCmmTop CmmStatics info graph
- emitRODataLits :: String -> CLabel -> [CmmLit] -> Code
- mkRODataLits :: CLabel -> [CmmLit] -> GenCmmTop CmmStatics info graph
- emitIf :: CmmExpr -> Code -> Code
- emitIfThenElse :: CmmExpr -> Code -> Code -> Code
- emitRtsCall :: PackageId -> FastString -> [CmmHinted CmmExpr] -> Bool -> Code
- emitRtsCallWithVols :: PackageId -> FastString -> [CmmHinted CmmExpr] -> [GlobalReg] -> Bool -> Code
- emitRtsCallWithResult :: LocalReg -> ForeignHint -> PackageId -> FastString -> [CmmHinted CmmExpr] -> Bool -> Code
- assignTemp :: CmmExpr -> FCode CmmExpr
- assignTemp_ :: CmmExpr -> FCode CmmExpr
- newTemp :: CmmType -> FCode LocalReg
- emitSimultaneously :: CmmStmts -> Code
- emitSwitch :: CmmExpr -> [(ConTagZ, CgStmts)] -> Maybe CgStmts -> ConTagZ -> ConTagZ -> Code
- emitLitSwitch :: CmmExpr -> [(Literal, CgStmts)] -> CgStmts -> Code
- tagToClosure :: TyCon -> CmmExpr -> CmmExpr
- callerSaves :: GlobalReg -> Bool
- callerSaveVolatileRegs :: Maybe [GlobalReg] -> ([CmmStmt], [CmmStmt])
- get_GlobalReg_addr :: GlobalReg -> CmmExpr
- activeStgRegs :: [GlobalReg]
- fixStgRegisters :: RawCmmTop -> RawCmmTop
- cmmNeWord, cmmAndWord, cmmOrWord, cmmEqWord :: CmmExpr -> CmmExpr -> CmmExpr
- cmmNegate :: CmmExpr -> CmmExpr
- cmmUGtWord :: CmmExpr -> CmmExpr -> CmmExpr
- cmmSubWord :: CmmExpr -> CmmExpr -> CmmExpr
- cmmMulWord :: CmmExpr -> CmmExpr -> CmmExpr
- cmmAddWord :: CmmExpr -> CmmExpr -> CmmExpr
- cmmUShrWord :: CmmExpr -> CmmExpr -> CmmExpr
- cmmOffsetExprW :: CmmExpr -> CmmExpr -> CmmExpr
- cmmOffsetExprB :: CmmExpr -> CmmExpr -> CmmExpr
- cmmRegOffW :: CmmReg -> WordOff -> CmmExpr
- cmmRegOffB :: CmmReg -> ByteOff -> CmmExpr
- cmmLabelOffW :: CLabel -> WordOff -> CmmLit
- cmmLabelOffB :: CLabel -> ByteOff -> CmmLit
- cmmOffsetW :: CmmExpr -> WordOff -> CmmExpr
- cmmOffsetB :: CmmExpr -> ByteOff -> CmmExpr
- cmmOffsetLitW :: CmmLit -> WordOff -> CmmLit
- cmmOffsetLitB :: CmmLit -> ByteOff -> CmmLit
- cmmLoadIndexW :: CmmExpr -> Int -> CmmType -> CmmExpr
- cmmConstrTag :: CmmExpr -> CmmExpr
- cmmConstrTag1 :: CmmExpr -> CmmExpr
- tagForCon :: DataCon -> ConTagZ
- tagCons :: DataCon -> CmmExpr -> CmmExpr
- isSmallFamily :: Int -> Bool
- cmmUntag :: CmmExpr -> CmmExpr
- cmmIsTagged :: CmmExpr -> CmmExpr
- cmmGetTag :: CmmExpr -> CmmExpr
- addToMem :: Width -> CmmExpr -> Int -> CmmStmt
- addToMemE :: Width -> CmmExpr -> CmmExpr -> CmmStmt
- mkWordCLit :: StgWord -> CmmLit
- mkStringCLit :: String -> FCode CmmLit
- mkByteStringCLit :: [Word8] -> FCode CmmLit
- packHalfWordsCLit :: (Integral a, Integral b) => a -> b -> CmmLit
- blankWord :: CmmStatic
- getSRTInfo :: FCode C_SRT
Documentation
emitDataLits :: CLabel -> [CmmLit] -> CodeSource
mkDataLits :: CLabel -> [CmmLit] -> GenCmmTop CmmStatics info graphSource
mkRODataLits :: CLabel -> [CmmLit] -> GenCmmTop CmmStatics info graphSource
:: PackageId | package the function is in |
-> FastString | name of function |
-> [CmmHinted CmmExpr] | function args |
-> Bool | whether this is a safe call |
-> Code | cmm code |
Emit code to call a Cmm function.
emitRtsCallWithVols :: PackageId -> FastString -> [CmmHinted CmmExpr] -> [GlobalReg] -> Bool -> CodeSource
emitRtsCallWithResult :: LocalReg -> ForeignHint -> PackageId -> FastString -> [CmmHinted CmmExpr] -> Bool -> CodeSource
assignTemp :: CmmExpr -> FCode CmmExprSource
If the expression is trivial, return it. Otherwise, assign the expression to a temporary register and return an expression referring to this register.
assignTemp_ :: CmmExpr -> FCode CmmExprSource
If the expression is trivial and doesn't refer to a global register, return it. Otherwise, assign the expression to a temporary register and return an expression referring to this register.
tagToClosure :: TyCon -> CmmExpr -> CmmExprSource
callerSaves :: GlobalReg -> BoolSource
Returns True
if this global register is stored in a caller-saves
machine register.
get_GlobalReg_addr :: GlobalReg -> CmmExprSource
We map STG registers onto appropriate CmmExprs. Either they map to real machine registers or stored as offsets from BaseReg. Given a GlobalReg, get_GlobalReg_addr always produces the register table address for it.
activeStgRegs :: [GlobalReg]Source
Here is where the STG register map is defined for each target arch. The order matters (for the llvm backend anyway)! We must make sure to maintain the order here with the order used in the LLVM calling conventions. Note that also, this isn't all registers, just the ones that are currently possbily mapped to real registers.
fixStgRegisters :: RawCmmTop -> RawCmmTopSource
Fixup global registers so that they assign to locations within the RegTable if they aren't pinned for the current target.
cmmUGtWord :: CmmExpr -> CmmExpr -> CmmExprSource
cmmSubWord :: CmmExpr -> CmmExpr -> CmmExprSource
cmmMulWord :: CmmExpr -> CmmExpr -> CmmExprSource
cmmAddWord :: CmmExpr -> CmmExpr -> CmmExprSource
cmmUShrWord :: CmmExpr -> CmmExpr -> CmmExprSource
cmmOffsetExprW :: CmmExpr -> CmmExpr -> CmmExprSource
cmmOffsetExprB :: CmmExpr -> CmmExpr -> CmmExprSource
cmmRegOffW :: CmmReg -> WordOff -> CmmExprSource
cmmRegOffB :: CmmReg -> ByteOff -> CmmExprSource
cmmLabelOffW :: CLabel -> WordOff -> CmmLitSource
cmmLabelOffB :: CLabel -> ByteOff -> CmmLitSource
cmmOffsetW :: CmmExpr -> WordOff -> CmmExprSource
cmmOffsetB :: CmmExpr -> ByteOff -> CmmExprSource
cmmOffsetLitW :: CmmLit -> WordOff -> CmmLitSource
cmmOffsetLitB :: CmmLit -> ByteOff -> CmmLitSource
cmmConstrTag :: CmmExpr -> CmmExprSource
isSmallFamily :: Int -> BoolSource
cmmIsTagged :: CmmExpr -> CmmExprSource
mkWordCLit :: StgWord -> CmmLitSource
mkStringCLit :: String -> FCode CmmLitSource
mkByteStringCLit :: [Word8] -> FCode CmmLitSource
packHalfWordsCLit :: (Integral a, Integral b) => a -> b -> CmmLitSource