Make Control.Exception buildable by nhc98.
[haskell-directory.git] / GHC / Int.hs
index 4416bfe..2bb7d5c 100644 (file)
@@ -15,6 +15,7 @@
 
 #include "MachDeps.h"
 
+-- #hide
 module GHC.Int (
     Int8(..), Int16(..), Int32(..), Int64(..))
     where
@@ -77,26 +78,32 @@ instance Enum Int8 where
 
 instance Integral Int8 where
     quot    x@(I8# x#) y@(I8# y#)
-        | y /= 0                  = I8# (narrow8Int# (x# `quotInt#` y#))
-        | otherwise               = divZeroError
+        | y == 0                     = divZeroError
+        | x == minBound && y == (-1) = overflowError
+        | otherwise                  = I8# (narrow8Int# (x# `quotInt#` y#))
     rem     x@(I8# x#) y@(I8# y#)
-        | y /= 0                  = I8# (narrow8Int# (x# `remInt#` y#))
-        | otherwise               = divZeroError
+        | y == 0                     = divZeroError
+        | x == minBound && y == (-1) = overflowError
+        | otherwise                  = I8# (narrow8Int# (x# `remInt#` y#))
     div     x@(I8# x#) y@(I8# y#)
-        | y /= 0                  = I8# (narrow8Int# (x# `divInt#` y#))
-        | otherwise               = divZeroError
+        | y == 0                     = divZeroError
+        | x == minBound && y == (-1) = overflowError
+        | otherwise                  = I8# (narrow8Int# (x# `divInt#` y#))
     mod     x@(I8# x#) y@(I8# y#)
-        | y /= 0                  = I8# (narrow8Int# (x# `modInt#` y#))
-        | otherwise               = divZeroError
+        | y == 0                     = divZeroError
+        | x == minBound && y == (-1) = overflowError
+        | otherwise                  = I8# (narrow8Int# (x# `modInt#` y#))
     quotRem x@(I8# x#) y@(I8# y#)
-        | y /= 0                  = (I8# (narrow8Int# (x# `quotInt#` y#)),
-                                    I8# (narrow8Int# (x# `remInt#` y#)))
-        | otherwise               = divZeroError
+        | y == 0                     = divZeroError
+        | x == minBound && y == (-1) = overflowError
+        | otherwise                  = (I8# (narrow8Int# (x# `quotInt#` y#)),
+                                       I8# (narrow8Int# (x# `remInt#` y#)))
     divMod  x@(I8# x#) y@(I8# y#)
-        | y /= 0                  = (I8# (narrow8Int# (x# `divInt#` y#)),
-                                    I8# (narrow8Int# (x# `modInt#` y#)))
-        | otherwise               = divZeroError
-    toInteger (I8# x#)            = S# x#
+        | y == 0                     = divZeroError
+        | x == minBound && y == (-1) = overflowError
+        | otherwise                  = (I8# (narrow8Int# (x# `divInt#` y#)),
+                                       I8# (narrow8Int# (x# `modInt#` y#)))
+    toInteger (I8# x#)               = S# x#
 
 instance Bounded Int8 where
     minBound = -0x80
@@ -104,14 +111,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#))
@@ -123,8 +131,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#)
@@ -183,26 +191,32 @@ instance Enum Int16 where
 
 instance Integral Int16 where
     quot    x@(I16# x#) y@(I16# y#)
-        | y /= 0                  = I16# (narrow16Int# (x# `quotInt#` y#))
-        | otherwise               = divZeroError
+        | y == 0                     = divZeroError
+        | x == minBound && y == (-1) = overflowError
+        | otherwise                  = I16# (narrow16Int# (x# `quotInt#` y#))
     rem     x@(I16# x#) y@(I16# y#)
-        | y /= 0                  = I16# (narrow16Int# (x# `remInt#` y#))
-        | otherwise               = divZeroError
+        | y == 0                     = divZeroError
+        | x == minBound && y == (-1) = overflowError
+        | otherwise                  = I16# (narrow16Int# (x# `remInt#` y#))
     div     x@(I16# x#) y@(I16# y#)
-        | y /= 0                  = I16# (narrow16Int# (x# `divInt#` y#))
-        | otherwise               = divZeroError
+        | y == 0                     = divZeroError
+        | x == minBound && y == (-1) = overflowError
+        | otherwise                  = I16# (narrow16Int# (x# `divInt#` y#))
     mod     x@(I16# x#) y@(I16# y#)
-        | y /= 0                  = I16# (narrow16Int# (x# `modInt#` y#))
-        | otherwise               = divZeroError
+        | y == 0                     = divZeroError
+        | x == minBound && y == (-1) = overflowError
+        | otherwise                  = I16# (narrow16Int# (x# `modInt#` y#))
     quotRem x@(I16# x#) y@(I16# y#)
-        | y /= 0                  = (I16# (narrow16Int# (x# `quotInt#` y#)),
-                                    I16# (narrow16Int# (x# `remInt#` y#)))
-        | otherwise               = divZeroError
+        | y == 0                     = divZeroError
+        | x == minBound && y == (-1) = overflowError
+        | otherwise                  = (I16# (narrow16Int# (x# `quotInt#` y#)),
+                                        I16# (narrow16Int# (x# `remInt#` y#)))
     divMod  x@(I16# x#) y@(I16# y#)
-        | y /= 0                  = (I16# (narrow16Int# (x# `divInt#` y#)),
-                                    I16# (narrow16Int# (x# `modInt#` y#)))
-        | otherwise               = divZeroError
-    toInteger (I16# x#)           = S# x#
+        | y == 0                     = divZeroError
+        | x == minBound && y == (-1) = overflowError
+        | otherwise                  = (I16# (narrow16Int# (x# `divInt#` y#)),
+                                        I16# (narrow16Int# (x# `modInt#` y#)))
+    toInteger (I16# x#)              = S# x#
 
 instance Bounded Int16 where
     minBound = -0x8000
@@ -210,14 +224,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#))
@@ -229,8 +244,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#)
@@ -299,23 +314,31 @@ instance Enum Int32 where
 
 instance Integral Int32 where
     quot    x@(I32# x#) y@(I32# y#)
-        | y /= 0                  = I32# (x# `quotInt32#` y#)
-        | otherwise               = divZeroError
+        | y == 0                     = divZeroError
+        | x == minBound && y == (-1) = overflowError
+        | otherwise                  = I32# (x# `quotInt32#` y#)
     rem     x@(I32# x#) y@(I32# y#)
-        | y /= 0                  = I32# (x# `remInt32#` y#)
-        | otherwise               = divZeroError
+        | y == 0                  = divZeroError
+        | x == minBound && y == (-1) = overflowError
+        | otherwise               = I32# (x# `remInt32#` y#)
     div     x@(I32# x#) y@(I32# y#)
-        | y /= 0                  = I32# (x# `divInt32#` y#)
-        | otherwise               = divZeroError
+        | y == 0                  = divZeroError
+        | x == minBound && y == (-1) = overflowError
+        | otherwise               = I32# (x# `divInt32#` y#)
     mod     x@(I32# x#) y@(I32# y#)
-        | y /= 0                  = I32# (x# `modInt32#` y#)
-        | otherwise               = divZeroError
+        | y == 0                  = divZeroError
+        | x == minBound && y == (-1) = overflowError
+        | otherwise               = I32# (x# `modInt32#` y#)
     quotRem x@(I32# x#) y@(I32# y#)
-        | y /= 0                  = (I32# (x# `quotInt32#` y#), I32# (x# `remInt32#` y#))
-        | otherwise               = divZeroError
+        | y == 0                  = divZeroError
+        | x == minBound && y == (-1) = overflowError
+        | otherwise               = (I32# (x# `quotInt32#` y#),
+                                     I32# (x# `remInt32#` y#))
     divMod  x@(I32# x#) y@(I32# y#)
-        | y /= 0                  = (I32# (x# `divInt32#` y#), I32# (x# `modInt32#` y#))
-        | otherwise               = divZeroError
+        | y == 0                  = divZeroError
+        | x == minBound && y == (-1) = overflowError
+        | otherwise               = (I32# (x# `divInt32#` y#),
+                                     I32# (x# `modInt32#` y#))
     toInteger x@(I32# x#)
        | x >= fromIntegral (minBound::Int) && x <= fromIntegral (maxBound::Int)
                                   = S# (int32ToInt# x#)
@@ -340,6 +363,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#))
@@ -443,31 +468,39 @@ instance Enum Int32 where
 
 instance Integral Int32 where
     quot    x@(I32# x#) y@(I32# y#)
-        | y /= 0                  = I32# (narrow32Int# (x# `quotInt#` y#))
-        | otherwise               = divZeroError
+        | y == 0                     = divZeroError
+        | x == minBound && y == (-1) = overflowError
+        | otherwise                  = I32# (narrow32Int# (x# `quotInt#` y#))
     rem     x@(I32# x#) y@(I32# y#)
-        | y /= 0                  = I32# (narrow32Int# (x# `remInt#` y#))
-        | otherwise               = divZeroError
+        | y == 0                     = divZeroError
+        | x == minBound && y == (-1) = overflowError
+        | otherwise                  = I32# (narrow32Int# (x# `remInt#` y#))
     div     x@(I32# x#) y@(I32# y#)
-        | y /= 0                  = I32# (narrow32Int# (x# `divInt#` y#))
-        | otherwise               = divZeroError
+        | y == 0                     = divZeroError
+        | x == minBound && y == (-1) = overflowError
+        | otherwise                  = I32# (narrow32Int# (x# `divInt#` y#))
     mod     x@(I32# x#) y@(I32# y#)
-        | y /= 0                  = I32# (narrow32Int# (x# `modInt#` y#))
-        | otherwise               = divZeroError
+        | y == 0                     = divZeroError
+        | x == minBound && y == (-1) = overflowError
+        | otherwise                  = I32# (narrow32Int# (x# `modInt#` y#))
     quotRem x@(I32# x#) y@(I32# y#)
-        | y /= 0                  = (I32# (narrow32Int# (x# `quotInt#` y#)),
-                                    I32# (narrow32Int# (x# `remInt#` y#)))
-        | otherwise               = divZeroError
+        | y == 0                     = divZeroError
+        | x == minBound && y == (-1) = overflowError
+        | otherwise                  = (I32# (narrow32Int# (x# `quotInt#` y#)),
+                                     I32# (narrow32Int# (x# `remInt#` y#)))
     divMod  x@(I32# x#) y@(I32# y#)
-        | y /= 0                  = (I32# (narrow32Int# (x# `divInt#` y#)),
-                                    I32# (narrow32Int# (x# `modInt#` y#)))
-        | otherwise               = divZeroError
-    toInteger (I32# x#)           = S# x#
+        | y == 0                     = divZeroError
+        | x == minBound && y == (-1) = overflowError
+        | otherwise                  = (I32# (narrow32Int# (x# `divInt#` y#)),
+                                     I32# (narrow32Int# (x# `modInt#` y#)))
+    toInteger (I32# x#)              = S# x#
 
 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#))
@@ -479,8 +512,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#)
@@ -508,9 +541,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
@@ -566,27 +598,37 @@ instance Enum Int64 where
 
 instance Integral Int64 where
     quot    x@(I64# x#) y@(I64# y#)
-        | y /= 0                  = I64# (x# `quotInt64#` y#)
-        | otherwise               = divZeroError
+        | y == 0                     = divZeroError
+        | x == minBound && y == (-1) = overflowError
+        | otherwise                  = I64# (x# `quotInt64#` y#)
     rem     x@(I64# x#) y@(I64# y#)
-        | y /= 0                  = I64# (x# `remInt64#` y#)
-        | otherwise               = divZeroError
+        | y == 0                     = divZeroError
+        | x == minBound && y == (-1) = overflowError
+        | otherwise                  = I64# (x# `remInt64#` y#)
     div     x@(I64# x#) y@(I64# y#)
-        | y /= 0                  = I64# (x# `divInt64#` y#)
-        | otherwise               = divZeroError
+        | y == 0                     = divZeroError
+        | x == minBound && y == (-1) = overflowError
+        | otherwise                  = I64# (x# `divInt64#` y#)
     mod     x@(I64# x#) y@(I64# y#)
-        | y /= 0                  = I64# (x# `modInt64#` y#)
-        | otherwise               = divZeroError
+        | y == 0                     = divZeroError
+        | x == minBound && y == (-1) = overflowError
+        | otherwise                  = I64# (x# `modInt64#` y#)
     quotRem x@(I64# x#) y@(I64# y#)
-        | y /= 0                  = (I64# (x# `quotInt64#` y#), I64# (x# `remInt64#` y#))
-        | otherwise               = divZeroError
+        | y == 0                     = divZeroError
+        | x == minBound && y == (-1) = overflowError
+        | otherwise                  = (I64# (x# `quotInt64#` y#),
+                                        I64# (x# `remInt64#` y#))
     divMod  x@(I64# x#) y@(I64# y#)
-        | y /= 0                  = (I64# (x# `divInt64#` y#), I64# (x# `modInt64#` y#))
-        | otherwise               = divZeroError
+        | y == 0                     = divZeroError
+        | x == minBound && y == (-1) = overflowError
+        | otherwise                  = (I64# (x# `divInt64#` y#),
+                                        I64# (x# `modInt64#` y#))
     toInteger x@(I64# x#)
-       | x >= fromIntegral (minBound::Int) && x <= fromIntegral (maxBound::Int)
-                                  = S# (int64ToInt# x#)
-        | otherwise               = case int64ToInteger# x# of (# s, d #) -> J# s d
+       | x >= fromIntegral (minBound::Int) &&
+          x <= fromIntegral (maxBound::Int)
+                                     = S# (int64ToInt# x#)
+        | otherwise                  = case int64ToInteger# x# of
+                                           (# s, d #) -> J# s d
 
 
 divInt64#, modInt64# :: Int64# -> Int64# -> Int64#
@@ -608,6 +650,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#))
@@ -644,33 +688,33 @@ a `iShiftRA64#` b | b >=# 64# = if a `ltInt64#` (intToInt64# 0#)
                  | otherwise = a `uncheckedIShiftRA64#` b
 
 
-foreign import ccall unsafe "stg_eqInt64"       eqInt64#       :: Int64# -> Int64# -> Bool
-foreign import ccall unsafe "stg_neInt64"       neInt64#       :: Int64# -> Int64# -> Bool
-foreign import ccall unsafe "stg_ltInt64"       ltInt64#       :: Int64# -> Int64# -> Bool
-foreign import ccall unsafe "stg_leInt64"       leInt64#       :: Int64# -> Int64# -> Bool
-foreign import ccall unsafe "stg_gtInt64"       gtInt64#       :: Int64# -> Int64# -> Bool
-foreign import ccall unsafe "stg_geInt64"       geInt64#       :: Int64# -> Int64# -> Bool
-foreign import ccall unsafe "stg_plusInt64"     plusInt64#     :: Int64# -> Int64# -> Int64#
-foreign import ccall unsafe "stg_minusInt64"    minusInt64#    :: Int64# -> Int64# -> Int64#
-foreign import ccall unsafe "stg_timesInt64"    timesInt64#    :: Int64# -> Int64# -> Int64#
-foreign import ccall unsafe "stg_negateInt64"   negateInt64#   :: Int64# -> Int64#
-foreign import ccall unsafe "stg_quotInt64"     quotInt64#     :: Int64# -> Int64# -> Int64#
-foreign import ccall unsafe "stg_remInt64"      remInt64#      :: Int64# -> Int64# -> Int64#
-foreign import ccall unsafe "stg_intToInt64"    intToInt64#    :: Int# -> Int64#
-foreign import ccall unsafe "stg_int64ToInt"    int64ToInt#    :: Int64# -> Int#
-foreign import ccall unsafe "stg_wordToWord64"  wordToWord64#  :: Word# -> Word64#
-foreign import ccall unsafe "stg_int64ToWord64" int64ToWord64# :: Int64# -> Word64#
-foreign import ccall unsafe "stg_word64ToInt64" word64ToInt64# :: Word64# -> Int64#
-foreign import ccall unsafe "stg_and64"         and64#         :: Word64# -> Word64# -> Word64#
-foreign import ccall unsafe "stg_or64"          or64#          :: Word64# -> Word64# -> Word64#
-foreign import ccall unsafe "stg_xor64"         xor64#         :: Word64# -> Word64# -> Word64#
-foreign import ccall unsafe "stg_not64"         not64#         :: Word64# -> Word64#
-foreign import ccall unsafe "stg_uncheckedShiftL64"      uncheckedShiftL64#      :: Word64# -> Int# -> Word64#
-foreign import ccall unsafe "stg_uncheckedShiftRL64"     uncheckedShiftRL64#     :: Word64# -> Int# -> Word64#
-foreign import ccall unsafe "stg_uncheckedIShiftL64"     uncheckedIShiftL64#     :: Int64# -> Int# -> Int64#
-foreign import ccall unsafe "stg_uncheckedIShiftRA64"    uncheckedIShiftRA64#    :: Int64# -> Int# -> Int64#
-
-foreign import ccall unsafe "stg_integerToInt64"  integerToInt64#  :: Int# -> ByteArray# -> Int64#
+foreign import ccall unsafe "hs_eqInt64"       eqInt64#       :: Int64# -> Int64# -> Bool
+foreign import ccall unsafe "hs_neInt64"       neInt64#       :: Int64# -> Int64# -> Bool
+foreign import ccall unsafe "hs_ltInt64"       ltInt64#       :: Int64# -> Int64# -> Bool
+foreign import ccall unsafe "hs_leInt64"       leInt64#       :: Int64# -> Int64# -> Bool
+foreign import ccall unsafe "hs_gtInt64"       gtInt64#       :: Int64# -> Int64# -> Bool
+foreign import ccall unsafe "hs_geInt64"       geInt64#       :: Int64# -> Int64# -> Bool
+foreign import ccall unsafe "hs_plusInt64"     plusInt64#     :: Int64# -> Int64# -> Int64#
+foreign import ccall unsafe "hs_minusInt64"    minusInt64#    :: Int64# -> Int64# -> Int64#
+foreign import ccall unsafe "hs_timesInt64"    timesInt64#    :: Int64# -> Int64# -> Int64#
+foreign import ccall unsafe "hs_negateInt64"   negateInt64#   :: Int64# -> Int64#
+foreign import ccall unsafe "hs_quotInt64"     quotInt64#     :: Int64# -> Int64# -> Int64#
+foreign import ccall unsafe "hs_remInt64"      remInt64#      :: Int64# -> Int64# -> Int64#
+foreign import ccall unsafe "hs_intToInt64"    intToInt64#    :: Int# -> Int64#
+foreign import ccall unsafe "hs_int64ToInt"    int64ToInt#    :: Int64# -> Int#
+foreign import ccall unsafe "hs_wordToWord64"  wordToWord64#  :: Word# -> Word64#
+foreign import ccall unsafe "hs_int64ToWord64" int64ToWord64# :: Int64# -> Word64#
+foreign import ccall unsafe "hs_word64ToInt64" word64ToInt64# :: Word64# -> Int64#
+foreign import ccall unsafe "hs_and64"         and64#         :: Word64# -> Word64# -> Word64#
+foreign import ccall unsafe "hs_or64"          or64#          :: Word64# -> Word64# -> Word64#
+foreign import ccall unsafe "hs_xor64"         xor64#         :: Word64# -> Word64# -> Word64#
+foreign import ccall unsafe "hs_not64"         not64#         :: Word64# -> Word64#
+foreign import ccall unsafe "hs_uncheckedShiftL64"      uncheckedShiftL64#      :: Word64# -> Int# -> Word64#
+foreign import ccall unsafe "hs_uncheckedShiftRL64"     uncheckedShiftRL64#     :: Word64# -> Int# -> Word64#
+foreign import ccall unsafe "hs_uncheckedIShiftL64"     uncheckedIShiftL64#     :: Int64# -> Int# -> Int64#
+foreign import ccall unsafe "hs_uncheckedIShiftRA64"    uncheckedIShiftRA64#    :: Int64# -> Int# -> Int64#
+
+foreign import ccall unsafe "hs_integerToInt64"  integerToInt64#  :: Int# -> ByteArray# -> Int64#
 
 {-# RULES
 "fromIntegral/Int->Int64"    fromIntegral = \(I#   x#) -> I64# (intToInt64# x#)
@@ -721,29 +765,37 @@ instance Enum Int64 where
 
 instance Integral Int64 where
     quot    x@(I64# x#) y@(I64# y#)
-        | y /= 0                  = I64# (x# `quotInt#` y#)
-        | otherwise               = divZeroError
+        | y == 0                     = divZeroError
+        | x == minBound && y == (-1) = overflowError
+        | otherwise                  = I64# (x# `quotInt#` y#)
     rem     x@(I64# x#) y@(I64# y#)
-        | y /= 0                  = I64# (x# `remInt#` y#)
-        | otherwise               = divZeroError
+        | y == 0                     = divZeroError
+        | x == minBound && y == (-1) = overflowError
+        | otherwise                  = I64# (x# `remInt#` y#)
     div     x@(I64# x#) y@(I64# y#)
-        | y /= 0                  = I64# (x# `divInt#` y#)
-        | otherwise               = divZeroError
+        | y == 0                     = divZeroError
+        | x == minBound && y == (-1) = overflowError
+        | otherwise                  = I64# (x# `divInt#` y#)
     mod     x@(I64# x#) y@(I64# y#)
-        | y /= 0                  = I64# (x# `modInt#` y#)
-        | otherwise               = divZeroError
+        | y == 0                     = divZeroError
+        | x == minBound && y == (-1) = overflowError
+        | otherwise                  = I64# (x# `modInt#` y#)
     quotRem x@(I64# x#) y@(I64# y#)
-        | y /= 0                  = (I64# (x# `quotInt#` y#), I64# (x# `remInt#` y#))
-        | otherwise               = divZeroError
+        | y == 0                     = divZeroError
+        | x == minBound && y == (-1) = overflowError
+        | otherwise                  = (I64# (x# `quotInt#` y#), I64# (x# `remInt#` y#))
     divMod  x@(I64# x#) y@(I64# y#)
-        | y /= 0                  = (I64# (x# `divInt#` y#), I64# (x# `modInt#` y#))
-        | otherwise               = divZeroError
-    toInteger (I64# x#)           = S# x#
+        | y == 0                     = divZeroError
+        | x == minBound && y == (-1) = overflowError
+        | otherwise                  = (I64# (x# `divInt#` y#), I64# (x# `modInt#` y#))
+    toInteger (I64# x#)              = S# x#
 
 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#))
@@ -755,8 +807,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#)
@@ -779,6 +831,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