cmmToLlvmType, widthToLlvmFloat, widthToLlvmInt, llvmFunTy,
llvmFunSig, llvmFunArgs, llvmStdFunAttrs, llvmFunAlign, llvmInfAlign,
- llvmPtrBits, tysToParams, llvmFunSection, padLiveArgs, isSSE,
+ llvmPtrBits, tysToParams, llvmFunSection,
strCLabel_llvm, strDisplayName_llvm, strProcedureName_llvm,
getGlobalPtr, generateExternDecls,
import qualified Stream
import Control.Monad (ap)
-import Data.List (sort)
-import Data.Maybe (mapMaybe)
-- ----------------------------------------------------------------------------
-- * Some Data Types
-- | A Function's arguments
llvmFunArgs :: DynFlags -> LiveGlobalRegs -> [LlvmVar]
llvmFunArgs dflags live =
- map (lmGlobalRegArg dflags) (filter isPassed allRegs)
+ map (lmGlobalRegArg dflags) (filter isPassed (activeStgRegs platform))
where platform = targetPlatform dflags
- allRegs = activeStgRegs platform
- paddedLive = map (\(_,r) -> r) $ padLiveArgs live
- isLive r = r `elem` alwaysLive || r `elem` paddedLive
+ isLive r = not (isSSE r) || r `elem` alwaysLive || r `elem` live
isPassed r = not (isSSE r) || isLive r
-
-
-isSSE :: GlobalReg -> Bool
-isSSE (FloatReg _) = True
-isSSE (DoubleReg _) = True
-isSSE (XmmReg _) = True
-isSSE (YmmReg _) = True
-isSSE (ZmmReg _) = True
-isSSE _ = False
-
-sseRegNum :: GlobalReg -> Maybe Int
-sseRegNum (FloatReg i) = Just i
-sseRegNum (DoubleReg i) = Just i
-sseRegNum (XmmReg i) = Just i
-sseRegNum (YmmReg i) = Just i
-sseRegNum (ZmmReg i) = Just i
-sseRegNum _ = Nothing
-
--- the bool indicates whether the global reg was added as padding.
--- the returned list is not sorted in any particular order,
--- but does indicate the set of live registers needed, with SSE padding.
-padLiveArgs :: LiveGlobalRegs -> [(Bool, GlobalReg)]
-padLiveArgs live = allRegs
- where
- sseRegNums = sort $ mapMaybe sseRegNum live
- (_, padding) = foldl assignSlots (1, []) $ sseRegNums
- allRegs = padding ++ map (\r -> (False, r)) live
-
- assignSlots (i, acc) regNum
- | i == regNum = -- don't need padding here
- (i+1, acc)
- | i < regNum = let -- add padding for slots i .. regNum-1
- numNeeded = regNum-i
- acc' = genPad i numNeeded ++ acc
- in
- (regNum+1, acc')
- | otherwise = error "padLiveArgs -- i > regNum ??"
-
- genPad start n =
- take n $ flip map (iterate (+1) start) (\i ->
- (True, FloatReg i))
- -- NOTE: Picking float should be fine for the following reasons:
- -- (1) Float aliases with all the other SSE register types on
- -- the given platform.
- -- (2) The argument is not live anyways.
-
+ isSSE (FloatReg _) = True
+ isSSE (DoubleReg _) = True
+ isSSE (XmmReg _) = True
+ isSSE (YmmReg _) = True
+ isSSE (ZmmReg _) = True
+ isSSE _ = False
-- | Llvm standard fun attributes
llvmStdFunAttrs :: [LlvmFuncAttr]
import LlvmCodeGen.Regs
import BlockId
-import CodeGen.Platform ( activeStgRegs )
+import CodeGen.Platform ( activeStgRegs, callerSaves )
import CLabel
import Cmm
import PprCmm
fptr <- liftExprData $ getFunPtr funTy t
argVars' <- castVarsW Signed $ zip argVars argTy
+ doTrashStmts
let argSuffix = [mkIntLit i32 0, mkIntLit i32 localityInt, mkIntLit i32 1]
statement $ Expr $ Call StdCall fptr (argVars' ++ argSuffix) []
| otherwise = panic $ "prefetch locality level integer must be between 0 and 3, given: " ++ (show localityInt)
fptr <- getFunPtrW funTy t
argVars' <- castVarsW Signed $ zip argVars argTy
+ doTrashStmts
let alignVal = mkIntLit i32 align
arguments = argVars' ++ (alignVal:isVolVal)
statement $ Expr $ Call StdCall fptr arguments []
| never_returns = statement $ Unreachable
| otherwise = return ()
+ doTrashStmts
-- make the actual call
case retTy of
funPrologue :: LiveGlobalRegs -> [CmmBlock] -> LlvmM StmtData
funPrologue live cmmBlocks = do
+ trash <- getTrashRegs
let getAssignedRegs :: CmmNode O O -> [CmmReg]
getAssignedRegs (CmmAssign reg _) = [reg]
- getAssignedRegs (CmmUnsafeForeignCall _ rs _) = map CmmLocal rs
+ -- Calls will trash all registers. Unfortunately, this needs them to
+ -- be stack-allocated in the first place.
+ getAssignedRegs (CmmUnsafeForeignCall _ rs _) = map CmmGlobal trash ++ map CmmLocal rs
getAssignedRegs _ = []
getRegsBlock (_, body, _) = concatMap getAssignedRegs $ blockToList body
assignedRegs = nub $ concatMap (getRegsBlock . blockSplit) cmmBlocks
funEpilogue :: LiveGlobalRegs -> LlvmM ([LlvmVar], LlvmStatements)
funEpilogue live = do
- -- the bool indicates whether the register is padding.
- let alwaysNeeded = map (\r -> (False, r)) alwaysLive
- livePadded = alwaysNeeded ++ padLiveArgs live
+ -- Have information and liveness optimisation is enabled?
+ let liveRegs = alwaysLive ++ live
+ isSSE (FloatReg _) = True
+ isSSE (DoubleReg _) = True
+ isSSE (XmmReg _) = True
+ isSSE (YmmReg _) = True
+ isSSE (ZmmReg _) = True
+ isSSE _ = False
-- Set to value or "undef" depending on whether the register is
-- actually live
let ty = (pLower . getVarType $ lmGlobalRegVar dflags r)
return (Just $ LMLitVar $ LMUndefLit ty, nilOL)
platform <- getDynFlag targetPlatform
- let allRegs = activeStgRegs platform
- loads <- flip mapM allRegs $ \r -> case () of
- _ | (False, r) `elem` livePadded
- -> loadExpr r -- if r is not padding, load it
- | not (isSSE r) || (True, r) `elem` livePadded
- -> loadUndef r
+ loads <- flip mapM (activeStgRegs platform) $ \r -> case () of
+ _ | r `elem` liveRegs -> loadExpr r
+ | not (isSSE r) -> loadUndef r
| otherwise -> return (Nothing, nilOL)
let (vars, stmts) = unzip loads
return (catMaybes vars, concatOL stmts)
+
+-- | A series of statements to trash all the STG registers.
+--
+-- In LLVM we pass the STG registers around everywhere in function calls.
+-- So this means LLVM considers them live across the entire function, when
+-- in reality they usually aren't. For Caller save registers across C calls
+-- the saving and restoring of them is done by the Cmm code generator,
+-- using Cmm local vars. So to stop LLVM saving them as well (and saving
+-- all of them since it thinks they're always live, we trash them just
+-- before the call by assigning the 'undef' value to them. The ones we
+-- need are restored from the Cmm local var and the ones we don't need
+-- are fine to be trashed.
+getTrashStmts :: LlvmM LlvmStatements
+getTrashStmts = do
+ regs <- getTrashRegs
+ stmts <- flip mapM regs $ \ r -> do
+ reg <- getCmmReg (CmmGlobal r)
+ let ty = (pLower . getVarType) reg
+ return $ Store (LMLitVar $ LMUndefLit ty) reg
+ return $ toOL stmts
+
+getTrashRegs :: LlvmM [GlobalReg]
+getTrashRegs = do plat <- getLlvmPlatform
+ return $ filter (callerSaves plat) (activeStgRegs plat)
+
-- | Get a function pointer to the CLabel specified.
--
-- This is for Haskell functions, function type is assumed, so doesn't work
genLoadW :: Atomic -> CmmExpr -> CmmType -> WriterT LlvmAccum LlvmM LlvmVar
genLoadW atomic e ty = liftExprData $ genLoad atomic e ty
+doTrashStmts :: WriterT LlvmAccum LlvmM ()
+doTrashStmts = do
+ stmts <- lift getTrashStmts
+ tell $ LlvmAccum stmts mempty