diff options
author | Ben Gamari <ben@smart-cactus.org> | 2018-11-07 08:06:18 -0500 |
---|---|---|
committer | Ben Gamari <ben@smart-cactus.org> | 2018-11-07 08:09:40 -0500 |
commit | 39cd12b8d73b9d931ce1acaa7d9e74271c51086f (patch) | |
tree | ad699c69d96bda2e5ffb3426e8b83a7ed34c711b | |
parent | 802ce6eb090838d4e7573d96cf056afd2d898b78 (diff) | |
download | haskell-39cd12b8d73b9d931ce1acaa7d9e74271c51086f.tar.gz |
Revert "Multiple fixes / improvements for LLVM backend"
This reverts commit adcb5fb47c0942671d409b940d8884daa9359ca4.
-rw-r--r-- | compiler/llvmGen/Llvm/Types.hs | 2 | ||||
-rw-r--r-- | compiler/llvmGen/LlvmCodeGen/Base.hs | 62 | ||||
-rw-r--r-- | compiler/llvmGen/LlvmCodeGen/CodeGen.hs | 60 | ||||
-rw-r--r-- | llvm-passes | 2 | ||||
-rw-r--r-- | testsuite/tests/codeGen/should_run/all.T | 3 |
5 files changed, 62 insertions, 67 deletions
diff --git a/compiler/llvmGen/Llvm/Types.hs b/compiler/llvmGen/Llvm/Types.hs index a45004d3a8..bc7bbaab1b 100644 --- a/compiler/llvmGen/Llvm/Types.hs +++ b/compiler/llvmGen/Llvm/Types.hs @@ -564,7 +564,7 @@ instance Outputable LlvmFuncAttr where ppr OptSize = text "optsize" ppr NoReturn = text "noreturn" ppr NoUnwind = text "nounwind" - ppr ReadNone = text "readnone" + ppr ReadNone = text "readnon" ppr ReadOnly = text "readonly" ppr Ssp = text "ssp" ppr SspReq = text "ssqreq" diff --git a/compiler/llvmGen/LlvmCodeGen/Base.hs b/compiler/llvmGen/LlvmCodeGen/Base.hs index ec91bacc4c..6e20da48c1 100644 --- a/compiler/llvmGen/LlvmCodeGen/Base.hs +++ b/compiler/llvmGen/LlvmCodeGen/Base.hs @@ -26,7 +26,7 @@ module LlvmCodeGen.Base ( 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, @@ -58,8 +58,6 @@ import ErrUtils import qualified Stream import Control.Monad (ap) -import Data.List (sort) -import Data.Maybe (mapMaybe) -- ---------------------------------------------------------------------------- -- * Some Data Types @@ -149,58 +147,16 @@ llvmFunSection dflags lbl -- | 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] diff --git a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs index de839fbdeb..bb82049dda 100644 --- a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs +++ b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs @@ -14,7 +14,7 @@ import LlvmCodeGen.Base import LlvmCodeGen.Regs import BlockId -import CodeGen.Platform ( activeStgRegs ) +import CodeGen.Platform ( activeStgRegs, callerSaves ) import CLabel import Cmm import PprCmm @@ -211,6 +211,7 @@ genCall t@(PrimTarget (MO_Prefetch_Data localityInt)) [] args 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) @@ -293,6 +294,7 @@ genCall t@(PrimTarget op) [] args 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 [] @@ -447,6 +449,7 @@ genCall target res args = runStmtsDecls $ do | never_returns = statement $ Unreachable | otherwise = return () + doTrashStmts -- make the actual call case retTy of @@ -1787,9 +1790,12 @@ genLit _ CmmHighStackMark 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 @@ -1819,9 +1825,14 @@ funPrologue live cmmBlocks = do 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 @@ -1833,17 +1844,39 @@ funEpilogue live = do 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 @@ -1965,6 +1998,11 @@ getCmmRegW = lift . getCmmReg 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 + -- | Return element of single-element list; 'panic' if list is not a single-element list singletonPanic :: String -> [a] -> a singletonPanic _ [x] = x diff --git a/llvm-passes b/llvm-passes index 14eb62d87c..5183c9f2ab 100644 --- a/llvm-passes +++ b/llvm-passes @@ -1,5 +1,5 @@ [ -(0, "-mem2reg -globalopt -lower-expect"), +(0, "-mem2reg -globalopt"), (1, "-O1 -globalopt"), (2, "-O2") ] diff --git a/testsuite/tests/codeGen/should_run/all.T b/testsuite/tests/codeGen/should_run/all.T index f7ec405b16..3935574549 100644 --- a/testsuite/tests/codeGen/should_run/all.T +++ b/testsuite/tests/codeGen/should_run/all.T @@ -172,7 +172,8 @@ test('T13825-unit', test('T14619', normal, compile_and_run, ['']) test('T14754', normal, compile_and_run, ['']) test('T14346', only_ways(['threaded1','threaded2']), compile_and_run, ['-O -threaded']) -test('T14251', normal, compile_and_run, ['']) +test('T14251', [expect_broken_for(14251, ['optllvm'])], + compile_and_run, ['']) # These actually used to fail with all optimisation settings, but adding -O just # to make sure |