[commit: packages/base] master: Use new bitwise Int# primops in Data.Bits (re #8791) (0fc4fb5)

git at git.haskell.org git at git.haskell.org
Wed Feb 19 22:00:28 UTC 2014


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/0fc4fb5477d3ca22a8b6894db5b1112b9badfdc4/base

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

commit 0fc4fb5477d3ca22a8b6894db5b1112b9badfdc4
Author: Chris Dueck <crdueck at uwaterloo.ca>
Date:   Wed Feb 19 22:18:14 2014 +0100

    Use new bitwise Int# primops in Data.Bits (re #8791)
    
    The new primops (see also #7689) allow to optimize
    `instance Bits Int` by allowing to operate directly on Int#
    instead of having to convert to Word# and back to Int# again.
    
    Authored-by: Chris Dueck <crdueck at uwaterloo.ca>
    Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org>


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

0fc4fb5477d3ca22a8b6894db5b1112b9badfdc4
 Data/Bits.hs |   20 +++++++-------------
 1 file changed, 7 insertions(+), 13 deletions(-)

diff --git a/Data/Bits.hs b/Data/Bits.hs
index 16a5b58..c6bd8da 100644
--- a/Data/Bits.hs
+++ b/Data/Bits.hs
@@ -347,14 +347,10 @@ instance Bits Int where
 
     testBit = testBitDefault
 
-    (I# x#) .&.   (I# y#)  = I# (word2Int# (int2Word# x# `and#` int2Word# y#))
-
-    (I# x#) .|.   (I# y#)  = I# (word2Int# (int2Word# x# `or#`  int2Word# y#))
-
-    (I# x#) `xor` (I# y#)  = I# (word2Int# (int2Word# x# `xor#` int2Word# y#))
-
-    complement (I# x#)     = I# (word2Int# (int2Word# x# `xor#` int2Word# (-1#)))
-
+    (I# x#) .&.   (I# y#)          = I# (x# `andI#` y#)
+    (I# x#) .|.   (I# y#)          = I# (x# `orI#`  y#)
+    (I# x#) `xor` (I# y#)          = I# (x# `xorI#` y#)
+    complement (I# x#)             = I# (notI# x#)
     (I# x#) `shift` (I# i#)
         | isTrue# (i# >=# 0#)      = I# (x# `iShiftL#` i#)
         | otherwise                = I# (x# `iShiftRA#` negateInt# i#)
@@ -365,11 +361,9 @@ instance Bits Int where
 
     {-# INLINE rotate #-} 	-- See Note [Constant folding for rotate]
     (I# x#) `rotate` (I# i#) =
-        I# (word2Int# ((x'# `uncheckedShiftL#` i'#) `or#`
-                       (x'# `uncheckedShiftRL#` (wsib -# i'#))))
+        I# ((x# `uncheckedIShiftL#` i'#) `orI#` (x# `uncheckedIShiftRL#` (wsib -# i'#)))
       where
-        !x'# = int2Word# x#
-        !i'# = word2Int# (int2Word# i# `and#` int2Word# (wsib -# 1#))
+        !i'# = i# `andI#` (wsib -# 1#)
         !wsib = WORD_SIZE_IN_BITS#   {- work around preprocessor problem (??) -}
     bitSizeMaybe i         = Just (finiteBitSize i)
     bitSize i              = finiteBitSize i
@@ -402,7 +396,7 @@ instance Bits Word where
         | isTrue# (i'# ==# 0#) = W# x#
         | otherwise  = W# ((x# `uncheckedShiftL#` i'#) `or#` (x# `uncheckedShiftRL#` (wsib -# i'#)))
         where
-        !i'# = word2Int# (int2Word# i# `and#` int2Word# (wsib -# 1#))
+        !i'# = i# `andI#` (wsib -# 1#)
         !wsib = WORD_SIZE_IN_BITS#  {- work around preprocessor problem (??) -}
     bitSizeMaybe i           = Just (finiteBitSize i)
     bitSize i                = finiteBitSize i



More information about the ghc-commits mailing list