[commit: ghc] wip/T10137: Revert "CmmSwitch: Build the if-then-else branch with >= instead of <" (27a5e9e)

git at git.haskell.org git at git.haskell.org
Tue Mar 17 15:58:40 UTC 2015


Repository : ssh://git@git.haskell.org/ghc

On branch  : wip/T10137
Link       : http://ghc.haskell.org/trac/ghc/changeset/27a5e9e53699a00471d0255faf514dda4b603ed6/ghc

>---------------------------------------------------------------

commit 27a5e9e53699a00471d0255faf514dda4b603ed6
Author: Joachim Breitner <mail at joachim-breitner.de>
Date:   Tue Mar 17 16:56:51 2015 +0100

    Revert "CmmSwitch: Build the if-then-else branch with >= instead of <"
    
    This reverts commit c0f7bc7599a58a9044a1b8f81eb2715cd90ea028.


>---------------------------------------------------------------

27a5e9e53699a00471d0255faf514dda4b603ed6
 compiler/cmm/CmmCreateSwitchPlans.hs | 6 +++---
 compiler/cmm/CmmSwitch.hs            | 4 ++--
 compiler/cmm/CmmUtils.hs             | 5 ++---
 3 files changed, 7 insertions(+), 8 deletions(-)

diff --git a/compiler/cmm/CmmCreateSwitchPlans.hs b/compiler/cmm/CmmCreateSwitchPlans.hs
index 450e399..0fac30c 100644
--- a/compiler/cmm/CmmCreateSwitchPlans.hs
+++ b/compiler/cmm/CmmCreateSwitchPlans.hs
@@ -57,13 +57,13 @@ implementSwitchPlan dflags scope expr = go
       = return (emptyBlock `blockJoinTail` CmmBranch l, [])
     go (JumpTable ids)
       = return (emptyBlock `blockJoinTail` CmmSwitch expr ids, [])
-    go (IfGe signed i ids1 ids2)
+    go (IfLT signed i ids1 ids2)
       = do
         (bid1, newBlocks1) <- go' ids1
         (bid2, newBlocks2) <- go' ids2
 
-        let lt | signed    = cmmSGeWord
-               | otherwise = cmmUGeWord
+        let lt | signed    = cmmSLtWord
+               | otherwise = cmmULtWord
             scrut = lt dflags expr $ CmmLit $ mkWordCLit dflags i
             lastNode = CmmCondBranch scrut bid1 bid2
             lastBlock = emptyBlock `blockJoinTail` lastNode
diff --git a/compiler/cmm/CmmSwitch.hs b/compiler/cmm/CmmSwitch.hs
index c16818d..800ee7d 100644
--- a/compiler/cmm/CmmSwitch.hs
+++ b/compiler/cmm/CmmSwitch.hs
@@ -216,7 +216,7 @@ eqSwitchTargetWith eq (SwitchTargets signed1 range1 mbdef1 ids1) (SwitchTargets
 data SwitchPlan
     = Unconditionally Label
     | IfEqual Integer Label SwitchPlan
-    | IfGe Bool Integer SwitchPlan SwitchPlan
+    | IfLT Bool Integer SwitchPlan SwitchPlan
     | JumpTable SwitchTargets
   deriving Show
 --
@@ -341,7 +341,7 @@ findSingleValues (p, [])
 -- Build a balanced tree from a separated list
 buildTree :: Bool -> FlatSwitchPlan -> SwitchPlan
 buildTree _ (p,[]) = p
-buildTree signed sl = IfGe signed m (buildTree signed sl2) (buildTree signed sl1)
+buildTree signed sl = IfLT signed m (buildTree signed sl1) (buildTree signed sl2)
   where 
     (sl1, m, sl2) = divideSL sl
 
diff --git a/compiler/cmm/CmmUtils.hs b/compiler/cmm/CmmUtils.hs
index ef67bfc..be1b1fe 100644
--- a/compiler/cmm/CmmUtils.hs
+++ b/compiler/cmm/CmmUtils.hs
@@ -29,7 +29,7 @@ module CmmUtils(
         cmmIndex, cmmIndexExpr, cmmLoadIndex, cmmLoadIndexW,
         cmmNegate,
         cmmULtWord, cmmUGeWord, cmmUGtWord, cmmUShrWord,
-        cmmSLtWord, cmmSGeWord,
+        cmmSLtWord,
         cmmNeWord, cmmEqWord,
         cmmOrWord, cmmAndWord,
         cmmSubWord, cmmAddWord, cmmMulWord, cmmQuotWord,
@@ -314,7 +314,7 @@ cmmLoadIndexW dflags base off ty = CmmLoad (cmmOffsetW dflags base off) ty
 
 -----------------------
 cmmULtWord, cmmUGeWord, cmmUGtWord, cmmUShrWord,
-  cmmSLtWord, cmmSGeWord,
+  cmmSLtWord,
   cmmNeWord, cmmEqWord,
   cmmOrWord, cmmAndWord,
   cmmSubWord, cmmAddWord, cmmMulWord, cmmQuotWord
@@ -328,7 +328,6 @@ cmmUGeWord dflags e1 e2 = CmmMachOp (mo_wordUGe dflags) [e1, e2]
 cmmUGtWord dflags e1 e2 = CmmMachOp (mo_wordUGt dflags) [e1, e2]
 --cmmShlWord dflags e1 e2 = CmmMachOp (mo_wordShl dflags) [e1, e2]
 cmmSLtWord dflags e1 e2 = CmmMachOp (mo_wordSLt dflags) [e1, e2]
-cmmSGeWord dflags e1 e2 = CmmMachOp (mo_wordSGe dflags) [e1, e2]
 cmmUShrWord dflags e1 e2 = CmmMachOp (mo_wordUShr dflags) [e1, e2]
 cmmAddWord dflags e1 e2 = CmmMachOp (mo_wordAdd dflags) [e1, e2]
 cmmSubWord dflags e1 e2 = CmmMachOp (mo_wordSub dflags) [e1, e2]



More information about the ghc-commits mailing list