Repository : ssh://darcs.haskell.org//srv/darcs/packages/base

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/efb2439ed297d4190966ebea6f051ea42bf3a2ee

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

commit efb2439ed297d4190966ebea6f051ea42bf3a2ee
Author: Ian Lynagh <[email protected]>
Date:   Mon May 21 20:41:51 2012 +0100

    Use Word literals directly, rather than converting Int literals

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

 GHC/Base.lhs |    4 ++--
 GHC/Char.hs  |    2 +-
 GHC/Int.hs   |   10 +++++-----
 GHC/Word.hs  |   18 +++++++++---------
 4 files changed, 17 insertions(+), 17 deletions(-)

diff --git a/GHC/Base.lhs b/GHC/Base.lhs
index 2f457a8..f684563 100644
--- a/GHC/Base.lhs
+++ b/GHC/Base.lhs
@@ -776,13 +776,13 @@ Similarly for Float (#5178):
 -- | Shift the argument left by the specified number of bits
 -- (which must be non-negative).
 shiftL# :: Word# -> Int# -> Word#
-a `shiftL#` b   | b >=# WORD_SIZE_IN_BITS# = int2Word# 0#
+a `shiftL#` b   | b >=# WORD_SIZE_IN_BITS# = 0##
                 | otherwise                = a `uncheckedShiftL#` b
 
 -- | Shift the argument right by the specified number of bits
 -- (which must be non-negative).
 shiftRL# :: Word# -> Int# -> Word#
-a `shiftRL#` b  | b >=# WORD_SIZE_IN_BITS# = int2Word# 0#
+a `shiftRL#` b  | b >=# WORD_SIZE_IN_BITS# = 0##
                 | otherwise                = a `uncheckedShiftRL#` b
 
 -- | Shift the argument left by the specified number of bits
diff --git a/GHC/Char.hs b/GHC/Char.hs
index 398ff81..4666161 100644
--- a/GHC/Char.hs
+++ b/GHC/Char.hs
@@ -9,7 +9,7 @@ import GHC.Show
 -- | The 'Prelude.toEnum' method restricted to the type 'Data.Char.Char'.
 chr :: Int -> Char
 chr i@(I# i#)
- | int2Word# i# `leWord#` int2Word# 0x10FFFF# = C# (chr# i#)
+ | int2Word# i# `leWord#` 0x10FFFF## = C# (chr# i#)
  | otherwise
     = error ("Prelude.chr: bad argument: " ++ showSignedInt (I# 9#) i "")
 
diff --git a/GHC/Int.hs b/GHC/Int.hs
index a2bcae5..21c0f4f 100644
--- a/GHC/Int.hs
+++ b/GHC/Int.hs
@@ -155,7 +155,7 @@ instance Bits Int8 where
                                        (x'# `uncheckedShiftRL#` (8# -# i'#)))))
         where
         !x'# = narrow8Word# (int2Word# x#)
-        !i'# = word2Int# (int2Word# i# `and#` int2Word# 7#)
+        !i'# = word2Int# (int2Word# i# `and#` 7##)
     bitSize  _                = 8
     isSigned _                = True
     popCount (I8# x#)         = I# (word2Int# (popCnt8# (int2Word# x#)))
@@ -310,7 +310,7 @@ instance Bits Int16 where
                                          (x'# `uncheckedShiftRL#` (16# -# 
i'#)))))
         where
         !x'# = narrow16Word# (int2Word# x#)
-        !i'# = word2Int# (int2Word# i# `and#` int2Word# 15#)
+        !i'# = word2Int# (int2Word# i# `and#` 15##)
     bitSize  _                 = 16
     isSigned _                 = True
     popCount (I16# x#)         = I# (word2Int# (popCnt16# (int2Word# x#)))
@@ -471,7 +471,7 @@ instance Bits Int32 where
                                          (x'# `uncheckedShiftRL#` (32# -# 
i'#)))))
         where
         !x'# = narrow32Word# (int2Word# x#)
-        !i'# = word2Int# (int2Word# i# `and#` int2Word# 31#)
+        !i'# = word2Int# (int2Word# i# `and#` 31##)
     bitSize  _                 = 32
     isSigned _                 = True
     popCount (I32# x#)         = I# (word2Int# (popCnt32# (int2Word# x#)))
@@ -661,7 +661,7 @@ instance Bits Int64 where
                                 (x'# `uncheckedShiftRL64#` (64# -# i'#))))
         where
         !x'# = int64ToWord64# x#
-        !i'# = word2Int# (int2Word# i# `and#` int2Word# 63#)
+        !i'# = word2Int# (int2Word# i# `and#` 63##)
     bitSize  _                 = 64
     isSigned _                 = True
     popCount (I64# x#)         =
@@ -798,7 +798,7 @@ instance Bits Int64 where
                            (x'# `uncheckedShiftRL#` (64# -# i'#))))
         where
         !x'# = int2Word# x#
-        !i'# = word2Int# (int2Word# i# `and#` int2Word# 63#)
+        !i'# = word2Int# (int2Word# i# `and#` 63##)
     bitSize  _                 = 64
     isSigned _                 = True
     popCount (I64# x#)         = I# (word2Int# (popCnt64# (int2Word# x#)))
diff --git a/GHC/Word.hs b/GHC/Word.hs
index c0d8141..0dcb0e3 100644
--- a/GHC/Word.hs
+++ b/GHC/Word.hs
@@ -124,9 +124,9 @@ instance Bounded Word where
     -- use unboxed literals for maxBound, because GHC doesn't optimise
     -- (fromInteger 0xffffffff :: Word).
 #if WORD_SIZE_IN_BITS == 32
-    maxBound = W# (int2Word# 0xFFFFFFFF#)
+    maxBound = W# 0xFFFFFFFF##
 #else
-    maxBound = W# (int2Word# 0xFFFFFFFFFFFFFFFF#)
+    maxBound = W# 0xFFFFFFFFFFFFFFFF##
 #endif
 
 instance Ix Word where
@@ -275,7 +275,7 @@ instance Bits Word8 where
         | otherwise  = W8# (narrow8Word# ((x# `uncheckedShiftL#` i'#) `or#`
                                           (x# `uncheckedShiftRL#` (8# -# 
i'#))))
         where
-        !i'# = word2Int# (int2Word# i# `and#` int2Word# 7#)
+        !i'# = word2Int# (int2Word# i# `and#` 7##)
     bitSize  _                = 8
     isSigned _                = False
     popCount (W8# x#)         = I# (word2Int# (popCnt8# x#))
@@ -418,7 +418,7 @@ instance Bits Word16 where
         | otherwise  = W16# (narrow16Word# ((x# `uncheckedShiftL#` i'#) `or#`
                                             (x# `uncheckedShiftRL#` (16# -# 
i'#))))
         where
-        !i'# = word2Int# (int2Word# i# `and#` int2Word# 15#)
+        !i'# = word2Int# (int2Word# i# `and#` 15##)
     bitSize  _                = 16
     isSigned _                = False
     popCount (W16# x#)        = I# (word2Int# (popCnt16# x#))
@@ -602,7 +602,7 @@ instance Bits Word32 where
         | otherwise  = W32# (narrow32Word# ((x# `uncheckedShiftL#` i'#) `or#`
                                             (x# `uncheckedShiftRL#` (32# -# 
i'#))))
         where
-        !i'# = word2Int# (int2Word# i# `and#` int2Word# 31#)
+        !i'# = word2Int# (int2Word# i# `and#` 31##)
     bitSize  _                = 32
     isSigned _                = False
     popCount (W32# x#)        = I# (word2Int# (popCnt32# x#))
@@ -735,7 +735,7 @@ instance Bits Word64 where
         | otherwise  = W64# ((x# `uncheckedShiftL64#` i'#) `or64#`
                              (x# `uncheckedShiftRL64#` (64# -# i'#)))
         where
-        !i'# = word2Int# (int2Word# i# `and#` int2Word# 63#)
+        !i'# = word2Int# (int2Word# i# `and#` 63##)
     bitSize  _                = 64
     isSigned _                = False
     popCount (W64# x#)        = I# (word2Int# (popCnt64# x#))
@@ -749,10 +749,10 @@ instance Bits Word64 where
 
 shiftL64#, shiftRL64# :: Word64# -> Int# -> Word64#
 
-a `shiftL64#` b  | b >=# 64#  = wordToWord64# (int2Word# 0#)
+a `shiftL64#` b  | b >=# 64#  = wordToWord64# 0##
                  | otherwise  = a `uncheckedShiftL64#` b
 
-a `shiftRL64#` b | b >=# 64#  = wordToWord64# (int2Word# 0#)
+a `shiftRL64#` b | b >=# 64#  = wordToWord64# 0##
                  | otherwise  = a `uncheckedShiftRL64#` b
 
 {-# RULES
@@ -850,7 +850,7 @@ instance Bits Word64 where
         | otherwise  = W64# ((x# `uncheckedShiftL#` i'#) `or#`
                              (x# `uncheckedShiftRL#` (64# -# i'#)))
         where
-        !i'# = word2Int# (int2Word# i# `and#` int2Word# 63#)
+        !i'# = word2Int# (int2Word# i# `and#` 63##)
     bitSize  _                = 64
     isSigned _                = False
     popCount (W64# x#)        = I# (word2Int# (popCnt64# x#))



_______________________________________________
Cvs-libraries mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-libraries

Reply via email to