Inline shift in GHC's Bits instances for {Int,Word}{,8,16,32,64}
authorSamuel Bronson <naesten@gmail.com>
Mon, 9 Oct 2006 02:09:06 +0000 (02:09 +0000)
committerSamuel Bronson <naesten@gmail.com>
Mon, 9 Oct 2006 02:09:06 +0000 (02:09 +0000)
Data/Bits.hs
GHC/Int.hs
GHC/Word.hs

index 1c9cc4c..eb8ace1 100644 (file)
@@ -192,6 +192,8 @@ class Num a => Bits a where
     x `rotateR` i = x `rotate` (-i)
 
 instance Bits Int where
+    {-# INLINE shift #-}
+
 #ifdef __GLASGOW_HASKELL__
     (I# x#) .&.   (I# y#)  = I# (word2Int# (int2Word# x# `and#` int2Word# y#))
     (I# x#) .|.   (I# y#)  = I# (word2Int# (int2Word# x# `or#`  int2Word# y#))
index 6fb44ca..3fff7dd 100644 (file)
@@ -112,6 +112,8 @@ instance Read Int8 where
     readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
 
 instance Bits Int8 where
+    {-# INLINE shift #-}
+
     (I8# x#) .&.   (I8# y#)   = I8# (word2Int# (int2Word# x# `and#` int2Word# y#))
     (I8# x#) .|.   (I8# y#)   = I8# (word2Int# (int2Word# x# `or#`  int2Word# y#))
     (I8# x#) `xor` (I8# y#)   = I8# (word2Int# (int2Word# x# `xor#` int2Word# y#))
@@ -217,6 +219,8 @@ instance Read Int16 where
     readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
 
 instance Bits Int16 where
+    {-# INLINE shift #-}
+
     (I16# x#) .&.   (I16# y#)  = I16# (word2Int# (int2Word# x# `and#` int2Word# y#))
     (I16# x#) .|.   (I16# y#)  = I16# (word2Int# (int2Word# x# `or#`  int2Word# y#))
     (I16# x#) `xor` (I16# y#)  = I16# (word2Int# (int2Word# x# `xor#` int2Word# y#))
@@ -339,6 +343,8 @@ instance Read Int32 where
     readsPrec p s = [(fromInteger x, r) | (x, r) <- readsPrec p s]
 
 instance Bits Int32 where
+    {-# INLINE shift #-}
+
     (I32# x#) .&.   (I32# y#)  = I32# (word32ToInt32# (int32ToWord32# x# `and32#` int32ToWord32# y#))
     (I32# x#) .|.   (I32# y#)  = I32# (word32ToInt32# (int32ToWord32# x# `or32#`  int32ToWord32# y#))
     (I32# x#) `xor` (I32# y#)  = I32# (word32ToInt32# (int32ToWord32# x# `xor32#` int32ToWord32# y#))
@@ -467,6 +473,8 @@ instance Read Int32 where
     readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
 
 instance Bits Int32 where
+    {-# INLINE shift #-}
+
     (I32# x#) .&.   (I32# y#)  = I32# (word2Int# (int2Word# x# `and#` int2Word# y#))
     (I32# x#) .|.   (I32# y#)  = I32# (word2Int# (int2Word# x# `or#`  int2Word# y#))
     (I32# x#) `xor` (I32# y#)  = I32# (word2Int# (int2Word# x# `xor#` int2Word# y#))
@@ -606,6 +614,8 @@ instance Read Int64 where
     readsPrec p s = [(fromInteger x, r) | (x, r) <- readsPrec p s]
 
 instance Bits Int64 where
+    {-# INLINE shift #-}
+
     (I64# x#) .&.   (I64# y#)  = I64# (word64ToInt64# (int64ToWord64# x# `and64#` int64ToWord64# y#))
     (I64# x#) .|.   (I64# y#)  = I64# (word64ToInt64# (int64ToWord64# x# `or64#`  int64ToWord64# y#))
     (I64# x#) `xor` (I64# y#)  = I64# (word64ToInt64# (int64ToWord64# x# `xor64#` int64ToWord64# y#))
@@ -742,6 +752,8 @@ instance Read Int64 where
     readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
 
 instance Bits Int64 where
+    {-# INLINE shift #-}
+
     (I64# x#) .&.   (I64# y#)  = I64# (word2Int# (int2Word# x# `and#` int2Word# y#))
     (I64# x#) .|.   (I64# y#)  = I64# (word2Int# (int2Word# x# `or#`  int2Word# y#))
     (I64# x#) `xor` (I64# y#)  = I64# (word2Int# (int2Word# x# `xor#` int2Word# y#))
index 7bdbe67..87b6e63 100644 (file)
@@ -153,6 +153,8 @@ instance Read Word where
     readsPrec p s = [(fromInteger x, r) | (x, r) <- readsPrec p s]
 
 instance Bits Word where
+    {-# INLINE shift #-}
+
     (W# x#) .&.   (W# y#)    = W# (x# `and#` y#)
     (W# x#) .|.   (W# y#)    = W# (x# `or#`  y#)
     (W# x#) `xor` (W# y#)    = W# (x# `xor#` y#)
@@ -251,6 +253,8 @@ instance Read Word8 where
     readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
 
 instance Bits Word8 where
+    {-# INLINE shift #-}
+
     (W8# x#) .&.   (W8# y#)   = W8# (x# `and#` y#)
     (W8# x#) .|.   (W8# y#)   = W8# (x# `or#`  y#)
     (W8# x#) `xor` (W8# y#)   = W8# (x# `xor#` y#)
@@ -350,6 +354,8 @@ instance Read Word16 where
     readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
 
 instance Bits Word16 where
+    {-# INLINE shift #-}
+
     (W16# x#) .&.   (W16# y#)  = W16# (x# `and#` y#)
     (W16# x#) .|.   (W16# y#)  = W16# (x# `or#`  y#)
     (W16# x#) `xor` (W16# y#)  = W16# (x# `xor#` y#)
@@ -447,6 +453,8 @@ instance Integral Word32 where
         | otherwise                 = case word32ToInteger# x# of (# s, d #) -> J# s d
 
 instance Bits Word32 where
+    {-# INLINE shift #-}
+
     (W32# x#) .&.   (W32# y#)  = W32# (x# `and32#` y#)
     (W32# x#) .|.   (W32# y#)  = W32# (x# `or32#`  y#)
     (W32# x#) `xor` (W32# y#)  = W32# (x# `xor32#` y#)
@@ -576,6 +584,8 @@ instance Integral Word32 where
 #endif
 
 instance Bits Word32 where
+    {-# INLINE shift #-}
+
     (W32# x#) .&.   (W32# y#)  = W32# (x# `and#` y#)
     (W32# x#) .|.   (W32# y#)  = W32# (x# `or#`  y#)
     (W32# x#) `xor` (W32# y#)  = W32# (x# `xor#` y#)
@@ -703,6 +713,8 @@ instance Integral Word64 where
         | otherwise                 = case word64ToInteger# x# of (# s, d #) -> J# s d
 
 instance Bits Word64 where
+    {-# INLINE shift #-}
+
     (W64# x#) .&.   (W64# y#)  = W64# (x# `and64#` y#)
     (W64# x#) .|.   (W64# y#)  = W64# (x# `or64#`  y#)
     (W64# x#) `xor` (W64# y#)  = W64# (x# `xor64#` y#)
@@ -833,6 +845,8 @@ instance Integral Word64 where
         i# = word2Int# x#
 
 instance Bits Word64 where
+    {-# INLINE shift #-}
+
     (W64# x#) .&.   (W64# y#)  = W64# (x# `and#` y#)
     (W64# x#) .|.   (W64# y#)  = W64# (x# `or#`  y#)
     (W64# x#) `xor` (W64# y#)  = W64# (x# `xor#` y#)