[commit: ghc] master: cmm: Optimise remainders by powers of two (23116df)

git at git.haskell.org git at git.haskell.org
Wed Nov 22 02:48:04 UTC 2017


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/23116dfee485902cb3c26640e38f62032bebe72d/ghc

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

commit 23116dfee485902cb3c26640e38f62032bebe72d
Author: Ben Gamari <ben at smart-cactus.org>
Date:   Tue Nov 21 21:14:31 2017 -0500

    cmm: Optimise remainders by powers of two
    
    Test Plan: validate
    
    Reviewers: bgamari, simonmar
    
    Reviewed By: bgamari
    
    Subscribers: rwbarton, thomie
    
    GHC Trac Issues: #14437
    
    Differential Revision: https://phabricator.haskell.org/D4180


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

23116dfee485902cb3c26640e38f62032bebe72d
 compiler/cmm/CmmOpt.hs | 66 +++++++++++++++++++++++++++++++-------------------
 1 file changed, 41 insertions(+), 25 deletions(-)

diff --git a/compiler/cmm/CmmOpt.hs b/compiler/cmm/CmmOpt.hs
index 4b1c8d0..f9b1260 100644
--- a/compiler/cmm/CmmOpt.hs
+++ b/compiler/cmm/CmmOpt.hs
@@ -357,35 +357,51 @@ cmmMachOpFoldM dflags mop [x, (CmmLit (CmmInt n _))]
         MO_U_Quot rep
            | Just p <- exactLog2 n ->
                  Just (cmmMachOpFold dflags (MO_U_Shr rep) [x, CmmLit (CmmInt p rep)])
+        MO_U_Rem rep
+           | Just _ <- exactLog2 n ->
+                 Just (cmmMachOpFold dflags (MO_And rep) [x, CmmLit (CmmInt (n - 1) rep)])
         MO_S_Quot rep
            | Just p <- exactLog2 n,
-             CmmReg _ <- x ->   -- We duplicate x below, hence require
+             CmmReg _ <- x ->   -- We duplicate x in signedQuotRemHelper, hence require
                                 -- it is a reg.  FIXME: remove this restriction.
-                -- shift right is not the same as quot, because it rounds
-                -- to minus infinity, whereasq quot rounds toward zero.
-                -- To fix this up, we add one less than the divisor to the
-                -- dividend if it is a negative number.
-                --
-                -- to avoid a test/jump, we use the following sequence:
-                --      x1 = x >> word_size-1  (all 1s if -ve, all 0s if +ve)
-                --      x2 = y & (divisor-1)
-                --      result = (x+x2) >>= log2(divisor)
-                -- this could be done a bit more simply using conditional moves,
-                -- but we're processor independent here.
-                --
-                -- we optimise the divide by 2 case slightly, generating
-                --      x1 = x >> word_size-1  (unsigned)
-                --      return = (x + x1) >>= log2(divisor)
-                let
-                    bits = fromIntegral (widthInBits rep) - 1
-                    shr = if p == 1 then MO_U_Shr rep else MO_S_Shr rep
-                    x1 = CmmMachOp shr [x, CmmLit (CmmInt bits rep)]
-                    x2 = if p == 1 then x1 else
-                         CmmMachOp (MO_And rep) [x1, CmmLit (CmmInt (n-1) rep)]
-                    x3 = CmmMachOp (MO_Add rep) [x, x2]
-                in
-                Just (cmmMachOpFold dflags (MO_S_Shr rep) [x3, CmmLit (CmmInt p rep)])
+                Just (cmmMachOpFold dflags (MO_S_Shr rep)
+                  [signedQuotRemHelper rep p, CmmLit (CmmInt p rep)])
+        MO_S_Rem rep
+           | Just p <- exactLog2 n,
+             CmmReg _ <- x ->   -- We duplicate x in signedQuotRemHelper, hence require
+                                -- it is a reg.  FIXME: remove this restriction.
+                -- We replace (x `rem` 2^p) by (x - (x `quot` 2^p) * 2^p).
+                -- Moreover, we fuse MO_S_Shr (last operation of MO_S_Quot)
+                -- and MO_S_Shl (multiplication by 2^p) into a single MO_And operation.
+                Just (cmmMachOpFold dflags (MO_Sub rep)
+                    [x, cmmMachOpFold dflags (MO_And rep)
+                      [signedQuotRemHelper rep p, CmmLit (CmmInt (- n) rep)]])
         _ -> Nothing
+  where
+    -- In contrast with unsigned integers, for signed ones
+    -- shift right is not the same as quot, because it rounds
+    -- to minus infinity, whereas quot rounds toward zero.
+    -- To fix this up, we add one less than the divisor to the
+    -- dividend if it is a negative number.
+    --
+    -- to avoid a test/jump, we use the following sequence:
+    --      x1 = x >> word_size-1  (all 1s if -ve, all 0s if +ve)
+    --      x2 = y & (divisor-1)
+    --      result = x + x2
+    -- this could be done a bit more simply using conditional moves,
+    -- but we're processor independent here.
+    --
+    -- we optimise the divide by 2 case slightly, generating
+    --      x1 = x >> word_size-1  (unsigned)
+    --      return = x + x1
+    signedQuotRemHelper :: Width -> Integer -> CmmExpr
+    signedQuotRemHelper rep p = CmmMachOp (MO_Add rep) [x, x2]
+      where
+        bits = fromIntegral (widthInBits rep) - 1
+        shr = if p == 1 then MO_U_Shr rep else MO_S_Shr rep
+        x1 = CmmMachOp shr [x, CmmLit (CmmInt bits rep)]
+        x2 = if p == 1 then x1 else
+             CmmMachOp (MO_And rep) [x1, CmmLit (CmmInt (n-1) rep)]
 
 -- ToDo (#7116): optimise floating-point multiplication, e.g. x*2.0 -> x+x
 -- Unfortunately this needs a unique supply because x might not be a



More information about the ghc-commits mailing list