diff --git a/compiler/GHC/CmmToAsm/AArch64/Instr.hs b/compiler/GHC/CmmToAsm/AArch64/Instr.hs index d1bd8bd6efbe2e83241f8d520bf94f3dce0a55f2..30f3313f30ba45e056922c634c993e0765fef695 100644 --- a/compiler/GHC/CmmToAsm/AArch64/Instr.hs +++ b/compiler/GHC/CmmToAsm/AArch64/Instr.hs @@ -301,20 +301,15 @@ isJumpishInstr instr = case instr of -- | Checks whether this instruction is a jump/branch instruction. -- One that can change the flow of control in a way that the -- register allocator needs to worry about. -jumpDestsOfInstr :: Instr -> [Maybe BlockId] +jumpDestsOfInstr :: Instr -> [BlockId] jumpDestsOfInstr (ANN _ i) = jumpDestsOfInstr i -jumpDestsOfInstr i = case i of - (CBZ _ t) -> [ mkDest t ] - (CBNZ _ t) -> [ mkDest t ] - (J t) -> [ mkDest t ] - (B t) -> [ mkDest t ] - (BL t _ _) -> [ mkDest t ] - (BCOND _ t) -> [ mkDest t ] - _ -> [] - where - mkDest (TBlock id) = Just id - mkDest TLabel{} = Nothing - mkDest TReg{} = Nothing +jumpDestsOfInstr (CBZ _ t) = [ id | TBlock id <- [t]] +jumpDestsOfInstr (CBNZ _ t) = [ id | TBlock id <- [t]] +jumpDestsOfInstr (J t) = [id | TBlock id <- [t]] +jumpDestsOfInstr (B t) = [id | TBlock id <- [t]] +jumpDestsOfInstr (BL t _ _) = [ id | TBlock id <- [t]] +jumpDestsOfInstr (BCOND _ t) = [ id | TBlock id <- [t]] +jumpDestsOfInstr _ = [] -- | Change the destination of this jump instruction. -- Used in the linear allocator when adding fixup blocks for join diff --git a/compiler/GHC/CmmToAsm/BlockLayout.hs b/compiler/GHC/CmmToAsm/BlockLayout.hs index 2f594a831732aab4b6732d8e951dbba49b3052ba..052d4ae3c2883c4ef48e98a4b185496f36d1b97d 100644 --- a/compiler/GHC/CmmToAsm/BlockLayout.hs +++ b/compiler/GHC/CmmToAsm/BlockLayout.hs @@ -771,7 +771,7 @@ dropJumps :: forall a i. Instruction i => LabelMap a -> [GenBasicBlock i] dropJumps _ [] = [] dropJumps info (BasicBlock lbl ins:todo) | Just ins <- nonEmpty ins --This can happen because of shortcutting - , [Just dest] <- jumpDestsOfInstr (NE.last ins) + , [dest] <- jumpDestsOfInstr (NE.last ins) , BasicBlock nextLbl _ : _ <- todo , not (mapMember dest info) , nextLbl == dest @@ -870,7 +870,7 @@ mkNode edgeWeights block@(BasicBlock id instrs) = | length successors > 2 || edgeWeight info <= 0 -> [] | otherwise -> [target] | Just instr <- lastMaybe instrs - , [one] <- jumpBlockDestsOfInstr instr + , [one] <- jumpDestsOfInstr instr = [one] | otherwise = [] diff --git a/compiler/GHC/CmmToAsm/Instr.hs b/compiler/GHC/CmmToAsm/Instr.hs index 5ecf4f3284d6a92d8aa515ad7deb56e117a58a7f..aa8f538e07ee9ff30512ac7338359ab5c723650e 100644 --- a/compiler/GHC/CmmToAsm/Instr.hs +++ b/compiler/GHC/CmmToAsm/Instr.hs @@ -17,8 +17,6 @@ import GHC.Cmm.BlockId import GHC.CmmToAsm.Config import GHC.Data.FastString -import Data.Maybe (catMaybes) - -- | Holds a list of source and destination registers used by a -- particular instruction. -- @@ -75,17 +73,9 @@ class Instruction instr where -- | Give the possible destinations of this jump instruction. -- Must be defined for all jumpish instructions. - -- Returns Nothing for non BlockId destinations. jumpDestsOfInstr - :: instr -> [Maybe BlockId] - - -- | Give the possible block destinations of this jump instruction. - -- Must be defined for all jumpish instructions. - jumpBlockDestsOfInstr :: instr -> [BlockId] - jumpBlockDestsOfInstr = catMaybes . jumpDestsOfInstr - -- | Change the destination of this jump instruction. -- Used in the linear allocator when adding fixup blocks for join diff --git a/compiler/GHC/CmmToAsm/PPC/Instr.hs b/compiler/GHC/CmmToAsm/PPC/Instr.hs index fb3e29f175f3796a67ed25b46bff070642c3fb87..c0783ae29368fb5bc7fc322f94a80c42f423401f 100644 --- a/compiler/GHC/CmmToAsm/PPC/Instr.hs +++ b/compiler/GHC/CmmToAsm/PPC/Instr.hs @@ -513,15 +513,12 @@ isJumpishInstr instr -- | Checks whether this instruction is a jump/branch instruction. -- One that can change the flow of control in a way that the -- register allocator needs to worry about. -jumpDestsOfInstr :: Instr -> [Maybe BlockId] +jumpDestsOfInstr :: Instr -> [BlockId] jumpDestsOfInstr insn = case insn of - BCC _ id _ -> [Just id] - BCCFAR _ id _ -> [Just id] - BCTR targets _ _ -> targets - BCTRL{} -> [Nothing] - BL{} -> [Nothing] - JMP{} -> [Nothing] + BCC _ id _ -> [id] + BCCFAR _ id _ -> [id] + BCTR targets _ _ -> [id | Just id <- targets] _ -> [] diff --git a/compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs b/compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs index 36e61491628df906d0732fdfcf59b4ceb24908ad..59ce2a74c1521cd1faf6bada62c3126dce764e4e 100644 --- a/compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs +++ b/compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs @@ -207,7 +207,7 @@ cleanForward platform blockId assoc acc (li : instrs) -- Remember the association over a jump. | LiveInstr instr _ <- li - , targets <- jumpBlockDestsOfInstr instr + , targets <- jumpDestsOfInstr instr , not $ null targets = do mapM_ (accJumpValid assoc) targets cleanForward platform blockId assoc (li : acc) instrs @@ -386,7 +386,7 @@ cleanBackward' liveSlotsOnEntry reloadedBy noReloads acc (li : instrs) -- it always does, but if those reloads are cleaned the slot -- liveness map doesn't get updated. | LiveInstr instr _ <- li - , targets <- jumpBlockDestsOfInstr instr + , targets <- jumpDestsOfInstr instr = do let slotsReloadedByTargets = IntSet.unions diff --git a/compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs b/compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs index 80ab36c10d9f9b250e9278f291626a20d5fa93e6..61c4d9769478bf34c83b66f67b78dfb8206df766 100644 --- a/compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs +++ b/compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs @@ -57,7 +57,7 @@ joinToTargets block_live id instr = return ([], instr) | otherwise - = joinToTargets' block_live [] id instr (jumpBlockDestsOfInstr instr) + = joinToTargets' block_live [] id instr (jumpDestsOfInstr instr) ----- joinToTargets' diff --git a/compiler/GHC/CmmToAsm/Reg/Liveness.hs b/compiler/GHC/CmmToAsm/Reg/Liveness.hs index 3f766d3ce14e9f557128bd4bea90865f39d3912a..0a0aa247a41f2c9f2eb9edc89e90647fb9b10f55 100644 --- a/compiler/GHC/CmmToAsm/Reg/Liveness.hs +++ b/compiler/GHC/CmmToAsm/Reg/Liveness.hs @@ -468,7 +468,7 @@ slurpReloadCoalesce live -- if we hit a jump, remember the current slotMap | LiveInstr (Instr instr) _ <- li - , targets <- jumpBlockDestsOfInstr instr + , targets <- jumpDestsOfInstr instr , not $ null targets = do mapM_ (accSlotMap slotMap) targets return (slotMap, Nothing) @@ -760,7 +760,7 @@ sccBlocks blocks entries mcfg = map (fmap node_payload) sccs sccs = stronglyConnCompG g2 getOutEdges :: Instruction instr => [instr] -> [BlockId] - getOutEdges instrs = concatMap jumpBlockDestsOfInstr instrs + getOutEdges instrs = concatMap jumpDestsOfInstr instrs -- This is truly ugly, but I don't see a good alternative. -- Digraph just has the wrong API. We want to identify nodes @@ -837,7 +837,7 @@ checkIsReverseDependent sccs' slurpJumpDestsOfBlock (BasicBlock _ instrs) = unionManyUniqSets - $ map (mkUniqSet . jumpBlockDestsOfInstr) + $ map (mkUniqSet . jumpDestsOfInstr) [ i | LiveInstr i _ <- instrs] @@ -1047,7 +1047,7 @@ liveness1 platform liveregs blockmap (LiveInstr instr _) -- union in the live regs from all the jump destinations of this -- instruction. - targets = jumpBlockDestsOfInstr instr -- where we go from here + targets = jumpDestsOfInstr instr -- where we go from here not_a_branch = null targets targetLiveRegs target diff --git a/compiler/GHC/CmmToAsm/X86/Instr.hs b/compiler/GHC/CmmToAsm/X86/Instr.hs index 44578a10efe9eb44932e4b0b2a7c4cbdcb0a86ce..8cdf26f40e0fc60c311a62249001e13a74f6f482 100644 --- a/compiler/GHC/CmmToAsm/X86/Instr.hs +++ b/compiler/GHC/CmmToAsm/X86/Instr.hs @@ -672,16 +672,13 @@ isJumpishInstr instr jumpDestsOfInstr :: Instr - -> [Maybe BlockId] + -> [BlockId] jumpDestsOfInstr insn = case insn of - JXX _ id -> [Just id] - JMP_TBL _ ids _ _ -> [(mkDest dest) | Just dest <- ids] + JXX _ id -> [id] + JMP_TBL _ ids _ _ -> [id | Just (DestBlockId id) <- ids] _ -> [] - where - mkDest (DestBlockId id) = Just id - mkDest _ = Nothing patchJumpInstr diff --git a/testsuite/tests/codeGen/should_run/T24507.hs b/testsuite/tests/codeGen/should_run/T24507.hs deleted file mode 100644 index 31fd42a52c8b8a84ee3a323d59d27b00e69cb4e5..0000000000000000000000000000000000000000 --- a/testsuite/tests/codeGen/should_run/T24507.hs +++ /dev/null @@ -1,15 +0,0 @@ -{-# LANGUAGE MagicHash #-} -{-# LANGUAGE UnboxedTuples #-} -{-# LANGUAGE GHCForeignImportPrim #-} -{-# LANGUAGE UnliftedFFITypes #-} - -module Main where - -import GHC.Exts - -foreign import prim "foo" foo :: Int# -> Int# - -main = do - - let f x = case x of I# x' -> case foo x' of x -> print (I# x) - mapM_ f [1..7] \ No newline at end of file diff --git a/testsuite/tests/codeGen/should_run/T24507.stdout b/testsuite/tests/codeGen/should_run/T24507.stdout deleted file mode 100644 index f4b0843eecbe9e3ab107ab6bcd894b2d32ea9071..0000000000000000000000000000000000000000 --- a/testsuite/tests/codeGen/should_run/T24507.stdout +++ /dev/null @@ -1,7 +0,0 @@ -1 -2 -2 -2 -2 -2 -2 diff --git a/testsuite/tests/codeGen/should_run/T24507_cmm.cmm b/testsuite/tests/codeGen/should_run/T24507_cmm.cmm deleted file mode 100644 index 28db7bf7f674c615c047978d6f2accbf577d46bf..0000000000000000000000000000000000000000 --- a/testsuite/tests/codeGen/should_run/T24507_cmm.cmm +++ /dev/null @@ -1,35 +0,0 @@ -#include "Cmm.h" - -bar() { - return (2); -} - -foo(W_ x) { - - switch(x) { - case 1: goto a; - case 2: goto b; - case 3: goto c; - case 4: goto d; - case 5: goto e; - case 6: goto f; - case 7: goto g; - } - return (1); - - a: - return (1); - b: - jump bar(); - c: - jump bar(); - d: - jump bar(); - e: - jump bar(); - f: - jump bar(); - g: - jump bar(); - -} diff --git a/testsuite/tests/codeGen/should_run/all.T b/testsuite/tests/codeGen/should_run/all.T index 2b8220db8e5c34cffbb5a1bd3a60277f087a390a..4bfa5b3be465cea9544c2409648f7de12f152d7a 100644 --- a/testsuite/tests/codeGen/should_run/all.T +++ b/testsuite/tests/codeGen/should_run/all.T @@ -243,6 +243,3 @@ test('MulMayOflo_full', test('T24264run', normal, compile_and_run, ['']) test('T24295a', normal, compile_and_run, ['-O -floopification']) test('T24295b', normal, compile_and_run, ['-O -floopification -fpedantic-bottoms']) - -test('T24507', [req_cmm], multi_compile_and_run, - ['T24507', [('T24507_cmm.cmm', '')], '-O2'])