remove conflicting import for nhc98
[haskell-directory.git] / GHC / Int.hs
index e48656d..7ee7b1b 100644 (file)
@@ -105,14 +105,15 @@ instance Bounded Int8 where
 
 instance Ix Int8 where
     range (m,n)              = [m..n]
-    unsafeIndex b@(m,_) i    = fromIntegral (i - m)
+    unsafeIndex b@(m,_) i    = fromIntegral i - fromIntegral m
     inRange (m,n) i          = m <= i && i <= n
-    unsafeRangeSize b@(_l,h) = unsafeIndex b h + 1
 
 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#))
@@ -124,8 +125,8 @@ instance Bits Int8 where
         | i'# ==# 0# 
         = I8# x#
         | otherwise
-        = I8# (narrow8Int# (word2Int# ((x'# `shiftL#` i'#) `or#`
-                                       (x'# `shiftRL#` (8# -# i'#)))))
+        = I8# (narrow8Int# (word2Int# ((x'# `uncheckedShiftL#` i'#) `or#`
+                                       (x'# `uncheckedShiftRL#` (8# -# i'#)))))
         where
         x'# = narrow8Word# (int2Word# x#)
         i'# = word2Int# (int2Word# i# `and#` int2Word# 7#)
@@ -211,14 +212,15 @@ instance Bounded Int16 where
 
 instance Ix Int16 where
     range (m,n)              = [m..n]
-    unsafeIndex b@(m,_) i    = fromIntegral (i - m)
+    unsafeIndex b@(m,_) i    = fromIntegral i - fromIntegral m
     inRange (m,n) i          = m <= i && i <= n
-    unsafeRangeSize b@(_l,h) = unsafeIndex b h + 1
 
 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#))
@@ -230,8 +232,8 @@ instance Bits Int16 where
         | i'# ==# 0# 
         = I16# x#
         | otherwise
-        = I16# (narrow16Int# (word2Int# ((x'# `shiftL#` i'#) `or#`
-                                         (x'# `shiftRL#` (16# -# i'#)))))
+        = I16# (narrow16Int# (word2Int# ((x'# `uncheckedShiftL#` i'#) `or#`
+                                         (x'# `uncheckedShiftRL#` (16# -# i'#)))))
         where
         x'# = narrow16Word# (int2Word# x#)
         i'# = word2Int# (int2Word# i# `and#` int2Word# 15#)
@@ -341,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#))
@@ -469,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#))
@@ -480,8 +486,8 @@ instance Bits Int32 where
         | i'# ==# 0# 
         = I32# x#
         | otherwise
-        = I32# (narrow32Int# (word2Int# ((x'# `shiftL#` i'#) `or#`
-                                        (x'# `shiftRL#` (32# -# i'#)))))
+        = I32# (narrow32Int# (word2Int# ((x'# `uncheckedShiftL#` i'#) `or#`
+                                         (x'# `uncheckedShiftRL#` (32# -# i'#)))))
         where
         x'# = narrow32Word# (int2Word# x#)
         i'# = word2Int# (int2Word# i# `and#` int2Word# 31#)
@@ -509,9 +515,8 @@ instance Bounded Int32 where
 
 instance Ix Int32 where
     range (m,n)              = [m..n]
-    unsafeIndex b@(m,_) i    = fromIntegral (i - m)
+    unsafeIndex b@(m,_) i    = fromIntegral i - fromIntegral m
     inRange (m,n) i          = m <= i && i <= n
-    unsafeRangeSize b@(_l,h) = unsafeIndex b h + 1
 
 ------------------------------------------------------------------------
 -- type Int64
@@ -609,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#))
@@ -745,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#))
@@ -756,8 +765,8 @@ instance Bits Int64 where
         | i'# ==# 0# 
         = I64# x#
         | otherwise
-        = I64# (word2Int# ((x'# `shiftL#` i'#) `or#`
-                           (x'# `shiftRL#` (64# -# i'#))))
+        = I64# (word2Int# ((x'# `uncheckedShiftL#` i'#) `or#`
+                           (x'# `uncheckedShiftRL#` (64# -# i'#))))
         where
         x'# = int2Word# x#
         i'# = word2Int# (int2Word# i# `and#` int2Word# 63#)
@@ -780,6 +789,5 @@ instance Bounded Int64 where
 
 instance Ix Int64 where
     range (m,n)              = [m..n]
-    unsafeIndex b@(m,_) i    = fromIntegral (i - m)
+    unsafeIndex b@(m,_) i    = fromIntegral i - fromIntegral m
     inRange (m,n) i          = m <= i && i <= n
-    unsafeRangeSize b@(_l,h) = unsafeIndex b h + 1