[project @ 1999-08-30 18:19:39 by simonpj]
[ghc-hetmet.git] / ghc / lib / exts / Int.lhs
index f5be8ca..894386d 100644 (file)
@@ -1,5 +1,5 @@
 %
-% (c) The AQUA Project, Glasgow University, 1997-1998
+% (c) The AQUA Project, Glasgow University, 1997-1999
 %
 
 \section[Int]{Module @Int@}
@@ -15,17 +15,41 @@ module Int
        , Int16
        , Int32
        , Int64
+
+        , int8ToInt16   -- :: Int8  -> Int16
+        , int8ToInt32   -- :: Int8  -> Int32
+        , int8ToInt64   -- :: Int8  -> Int64
+
+        , int16ToInt8   -- :: Int16 -> Int8
+        , int16ToInt32  -- :: Int16 -> Int32
+        , int16ToInt64  -- :: Int16 -> Int64
+
+        , int32ToInt8   -- :: Int32 -> Int8
+        , int32ToInt16  -- :: Int32 -> Int16
+        , int32ToInt64  -- :: Int32 -> Int64
+
+        , int64ToInt8   -- :: Int64 -> Int8
+        , int64ToInt16  -- :: Int64 -> Int16
+        , int64ToInt32  -- :: Int64 -> Int32
+
        , int8ToInt  -- :: Int8  -> Int
-       , intToInt8  -- :: Int   -> Int8
        , int16ToInt -- :: Int16 -> Int
-       , intToInt16 -- :: Int   -> Int16
        , int32ToInt -- :: Int32 -> Int
-       , intToInt32 -- :: Int   -> Int32
+       , int64ToInt -- :: Int32 -> Int
 
-       , intToInt64 -- :: Int   -> Int64
-       , int64ToInt -- :: Int64 -> Int
+       , intToInt8  -- :: Int   -> Int8
+       , intToInt16 -- :: Int   -> Int16
+       , intToInt32 -- :: Int   -> Int32
+       , intToInt64 -- :: Int   -> Int32
 
+        , integerToInt8  -- :: Integer -> Int8
+        , integerToInt16 -- :: Integer -> Int16
+        , integerToInt32 -- :: Integer -> Int32
         , integerToInt64 -- :: Integer -> Int64
+
+        , int8ToInteger  -- :: Int8    -> Integer
+        , int16ToInteger -- :: Int16   -> Integer
+        , int32ToInteger -- :: Int32   -> Integer
         , int64ToInteger -- :: Int64   -> Integer
 
        -- plus Eq, Ord, Num, Bounded, Real, Integral, Ix, Enum, Read,
@@ -53,16 +77,18 @@ module Int
        , sizeofInt32
        , sizeofInt64
        
-#ifndef __PARALLEL_HASKELL__
        -- The "official" place to get these from is Foreign
+#ifndef __PARALLEL_HASKELL__
        , indexInt8OffForeignObj
        , indexInt16OffForeignObj
        , indexInt32OffForeignObj
        , indexInt64OffForeignObj
+
        , readInt8OffForeignObj
        , readInt16OffForeignObj
        , readInt32OffForeignObj
        , readInt64OffForeignObj
+
        , writeInt8OffForeignObj
        , writeInt16OffForeignObj
        , writeInt32OffForeignObj
@@ -72,41 +98,62 @@ module Int
        -- non-standard, GHC specific
        , intToWord
 
+       -- Internal, do not use.
+       , int8ToInt#
+       , int16ToInt#
+       , int32ToInt#
+
        ) where
 
-import GlaExts
+#ifdef __HUGS__
+import PreludeBuiltin
+#else
+import PrelBase
+import CCall
+import PrelForeign
+import PrelIOBase
+import PrelAddr ( Int64(..), Word64(..), Addr(..), Word(..) )
+#endif
 import Ix
 import Bits
-import PrelGHC
-import CCall
+import PrelNum ( Num(..), Integral(..) )       -- To get fromInt/toInt
+import Ratio   ( (%) )
 import Numeric ( readDec )
 import Word    ( Word32 )
-import PrelForeign
 
 -----------------------------------------------------------------------------
 -- The "official" coercion functions
 -----------------------------------------------------------------------------
 
 int8ToInt  :: Int8  -> Int
-intToInt8  :: Int   -> Int8
 int16ToInt :: Int16 -> Int
-intToInt16 :: Int   -> Int16
 int32ToInt :: Int32 -> Int
-intToInt32 :: Int   -> Int32
 
--- And some non-exported ones
+int8ToInt#  :: Int8  -> Int#
+int16ToInt# :: Int16 -> Int#
+int32ToInt# :: Int32 -> Int#
+
+intToInt8  :: Int   -> Int8
+intToInt16 :: Int   -> Int16
+intToInt32 :: Int   -> Int32
 
 int8ToInt16  :: Int8  -> Int16
 int8ToInt32  :: Int8  -> Int32
+
 int16ToInt8  :: Int16 -> Int8
 int16ToInt32 :: Int16 -> Int32
+
 int32ToInt8  :: Int32 -> Int8
 int32ToInt16 :: Int32 -> Int16
 
 int8ToInt16  (I8#  x) = I16# x
 int8ToInt32  (I8#  x) = I32# x
+int8ToInt64          = int32ToInt64 . int8ToInt32
+
 int16ToInt8  (I16# x) = I8#  x
 int16ToInt32 (I16# x) = I32# x
+int16ToInt64         = int32ToInt64 . int16ToInt32
+
 int32ToInt8  (I32# x) = I8#  x
 int32ToInt16 (I32# x) = I16# x
 
@@ -122,8 +169,11 @@ data Int8 = I8# Int#
 instance CCallable Int8
 instance CReturnable Int8
 
-int8ToInt (I8# x) = I# (int8ToInt# x)
-int8ToInt# x = if x' <=# 0x7f# then x' else x' -# 0x100#
+int8ToInt (I8# x)  = I# (i8ToInt# x)
+int8ToInt# (I8# x) = i8ToInt# x
+
+i8ToInt# :: Int# -> Int#
+i8ToInt# x = if x' <=# 0x7f# then x' else x' -# 0x100#
    where x' = word2Int# (int2Word# x `and#` int2Word# 0xff#)
 
 --
@@ -132,6 +182,8 @@ int8ToInt# x = if x' <=# 0x7f# then x' else x' -# 0x100#
 -- i.e., show (intToInt8 511) => "-1"
 --
 intToInt8 (I# x) = I8# (intToInt8# x)
+
+intToInt8# :: Int# -> Int#
 intToInt8# i# = word2Int# ((int2Word# i#) `and#` int2Word# 0xff#)
 
 instance Eq  Int8     where 
@@ -139,7 +191,7 @@ instance Eq  Int8     where
   (I8# x#) /= (I8# y#) = x# /=# y#
 
 instance Ord Int8 where 
-  compare (I8# x#) (I8# y#) = compareInt# (int8ToInt# x#) (int8ToInt# y#)
+  compare (I8# x#) (I8# y#) = compareInt# (i8ToInt# x#) (i8ToInt# y#)
 
 compareInt# :: Int# -> Int# -> Ordering
 compareInt# x# y#
@@ -158,8 +210,8 @@ instance Num Int8 where
 
   abs           = absReal
   signum        = signumReal
-  fromInteger (J# a# s# d#)
-                = case (integer2Int# a# s# d#) of { i# -> I8# (intToInt8# i#) }
+  fromInteger (S# i#)    = I8# (intToInt8# i#)
+  fromInteger (J# s# d#) = I8# (intToInt8# (integer2Int# s# d#))
   fromInt       = intToInt8
 
 instance Bounded Int8 where
@@ -170,45 +222,59 @@ instance Real Int8 where
     toRational x = toInteger x % 1
 
 instance Integral Int8 where
-    div x@(I8# x#) y@(I8# y#) = 
-       if x > 0 && y < 0       then quotInt8 (x-y-1) y
-       else if x < 0 && y > 0  then quotInt8 (x-y+1) y
-       else quotInt8 x y
+    div x y
+       | x > 0 && y < 0 = quotInt8 (x-y-1) y
+       | x < 0 && y > 0        = quotInt8 (x-y+1) y
+       | otherwise      = quotInt8 x y
+
     quot x@(I8# _) y@(I8# y#)
        | y# /=# 0# = x `quotInt8` y
-       | otherwise = error "Integral.Int8.quot: divide by 0\n"
+       | otherwise = divZeroError "quot{Int8}" x
     rem x@(I8# _) y@(I8# y#)
        | y# /=# 0#  = x `remInt8` y
-       | otherwise  = error "Integral.Int8.rem: divide by 0\n"
-    mod x@(I8# x#) y@(I8# y#) =
-       if x > 0 && y < 0 || x < 0 && y > 0 then
-         if r/=0 then r+y else 0
-       else
-         r
+       | otherwise  = divZeroError "rem{Int8}" x
+    mod x y
+       | x > 0 && y < 0 || x < 0 && y > 0 = if r/=0 then r+y else 0
+       | otherwise = r
        where r = remInt8 x y
+
     a@(I8# _) `quotRem` b@(I8# _) = (a `quotInt8` b, a `remInt8` b)
     toInteger i8  = toInteger (int8ToInt i8)
     toInt     i8  = int8ToInt i8
 
-remInt8  (I8# x) (I8# y) = I8# (intToInt8# ((int8ToInt# x) `remInt#` (int8ToInt# y)))
-quotInt8 (I8# x) (I8# y) = I8# (intToInt8# ((int8ToInt# x) `quotInt#` (int8ToInt# y)))
+remInt8, quotInt8 :: Int8 -> Int8 -> Int8
+remInt8  (I8# x) (I8# y) = I8# (intToInt8# ((i8ToInt# x) `remInt#`  (i8ToInt# y)))
+quotInt8 (I8# x) (I8# y) = I8# (intToInt8# ((i8ToInt# x) `quotInt#` (i8ToInt# y)))
 
 instance Ix Int8 where
     range (m,n)          = [m..n]
-    index b@(m,n) i
+    index b@(m,_) i
              | inRange b i = int8ToInt (i - m)
-             | otherwise   = error (showString "Ix{Int8}.index: Index " .
-                                    showParen True (showsPrec 0 i) .
-                                     showString " out of range " $
-                                    showParen True (showsPrec 0 b) "")
+             | otherwise   = indexError i b "Int8"
     inRange (m,n) i      = m <= i && i <= n
 
 instance Enum Int8 where
-    toEnum         = intToInt8
-    fromEnum       = int8ToInt
-    enumFrom c       = map toEnum [fromEnum c .. fromEnum (maxBound::Int8)]
-    enumFromThen c d = map toEnum [fromEnum c, fromEnum d .. fromEnum (last::Int8)]
-                         where last = if d < c then minBound else maxBound
+    succ i
+      | i == maxBound = succError "Int8"
+      | otherwise     = i+1
+    pred i
+      | i == minBound = predError "Int8"
+      | otherwise     = i-1
+
+    toEnum x
+      | x >= toInt (minBound::Int8) && x <= toInt (maxBound::Int8) 
+      = intToInt8 x
+      | otherwise
+      = toEnumError "Int8" x (minBound::Int8,maxBound::Int8)
+
+    fromEnum           = int8ToInt
+    enumFrom e1        = map toEnum [fromEnum e1 .. fromEnum (maxBound::Int8)]
+    enumFromThen e1 e2 = 
+             map toEnum [fromEnum e1, fromEnum e2 .. fromEnum (last::Int8)]
+               where 
+                  last 
+                    | e2 < e1   = minBound
+                    | otherwise = maxBound
 
 instance Read Int8 where
     readsPrec p s = [ (intToInt8 x,r) | (x,r) <- readsPrec p s ]
@@ -225,13 +291,13 @@ instance Bits Int8 where
   (I8# x) `xor` (I8# y) = I8# (word2Int# ((int2Word# x) `xor#` (int2Word# y)))
   complement (I8# x)    = I8# (word2Int# ((int2Word# x) `xor#` (int2Word# 0xff#)))
   shift (I8# x) i@(I# i#)
-       | i > 0     = I8# (intToInt8# (iShiftL# (int8ToInt# x)  i#))
-       | otherwise = I8# (intToInt8# (iShiftRA# (int8ToInt# x) (negateInt# i#)))
+       | i > 0     = I8# (intToInt8# (iShiftL# (i8ToInt# x)  i#))
+       | otherwise = I8# (intToInt8# (iShiftRA# (i8ToInt# x) (negateInt# i#)))
   i8@(I8# x)  `rotate` (I# i)
         | i ==# 0#    = i8
        | i ># 0#     = 
             I8# (intToInt8# ( word2Int#  (
-                    (int2Word# (iShiftL# (int8ToInt# x) i'))
+                    (int2Word# (iShiftL# (i8ToInt# x) i'))
                             `or#`
                      (int2Word# (iShiftRA# (word2Int# (
                                                (int2Word# x) `and#` 
@@ -266,12 +332,16 @@ data Int16  = I16# Int#
 instance CCallable Int16
 instance CReturnable Int16
 
-int16ToInt (I16# x) = I# (int16ToInt# x)
+int16ToInt  (I16# x) = I# (i16ToInt# x)
+int16ToInt# (I16# x) = i16ToInt# x
 
-int16ToInt# x = if x' <=# 0x7fff# then x' else x' -# 0x10000#
+i16ToInt# :: Int# -> Int#
+i16ToInt# x = if x' <=# 0x7fff# then x' else x' -# 0x10000#
    where x' = word2Int# (int2Word# x `and#` int2Word# 0xffff#)
 
 intToInt16 (I# x) = I16# (intToInt16# x)
+
+intToInt16# :: Int# -> Int#
 intToInt16# i# = word2Int# ((int2Word# i#) `and#` int2Word# 0xffff#)
 
 instance Eq  Int16     where
@@ -279,7 +349,7 @@ instance Eq  Int16     where
   (I16# x#) /= (I16# y#) = x# /=# y#
 
 instance Ord Int16 where
-  compare (I16# x#) (I16# y#) = compareInt# (int16ToInt# x#) (int16ToInt# y#)
+  compare (I16# x#) (I16# y#) = compareInt# (i16ToInt# x#) (i16ToInt# y#)
 
 instance Num Int16 where
   (I16# x#) + (I16# y#) = I16# (intToInt16# (x# +# y#))
@@ -291,8 +361,8 @@ instance Num Int16 where
       else I16# (0x10000# -# x#)
   abs           = absReal
   signum        = signumReal
-  fromInteger (J# a# s# d#)
-                = case (integer2Int# a# s# d#) of { i# -> I16# (intToInt16# i#) }
+  fromInteger (S# i#)    = I16# (intToInt16# i#)
+  fromInteger (J# s# d#) = I16# (intToInt16# (integer2Int# s# d#))
   fromInt       = intToInt16
 
 instance Bounded Int16 where
@@ -303,45 +373,59 @@ instance Real Int16 where
     toRational x = toInteger x % 1
 
 instance Integral Int16 where
-    div x@(I16# x#) y@(I16# y#) = 
-       if x > 0 && y < 0       then quotInt16 (x-y-1) y
-       else if x < 0 && y > 0  then quotInt16 (x-y+1) y
-       else quotInt16 x y
+    div x y
+       | x > 0 && y < 0        = quotInt16 (x-y-1) y
+       | x < 0 && y > 0        = quotInt16 (x-y+1) y
+       | otherwise     = quotInt16 x y
+
     quot x@(I16# _) y@(I16# y#)
        | y# /=# 0#      = x `quotInt16` y
-       | otherwise      = error "Integral.Int16.quot: divide by 0\n"
+       | otherwise      = divZeroError "quot{Int16}" x
     rem x@(I16# _) y@(I16# y#)
        | y# /=# 0#      = x `remInt16` y
-       | otherwise      = error "Integral.Int16.rem: divide by 0\n"
-    mod x@(I16# x#) y@(I16# y#) =
-       if x > 0 && y < 0 || x < 0 && y > 0 then
-         if r/=0 then r+y else 0
-       else
-         r
+       | otherwise      = divZeroError "rem{Int16}" x
+    mod x y
+       | x > 0 && y < 0 || x < 0 && y > 0 = if r/=0 then r+y else 0
+       | otherwise                       = r
        where r = remInt16 x y
+
     a@(I16# _) `quotRem` b@(I16# _) = (a `quotInt16` b, a `remInt16` b)
     toInteger i16  = toInteger (int16ToInt i16)
     toInt     i16  = int16ToInt i16
 
-remInt16  (I16# x) (I16# y) = I16# (intToInt16# ((int16ToInt# x) `remInt#` (int16ToInt# y)))
-quotInt16 (I16# x) (I16# y) = I16# (intToInt16# ((int16ToInt# x) `quotInt#` (int16ToInt# y)))
+remInt16, quotInt16 :: Int16 -> Int16 -> Int16
+remInt16  (I16# x) (I16# y) = I16# (intToInt16# ((i16ToInt# x) `remInt#` (i16ToInt# y)))
+quotInt16 (I16# x) (I16# y) = I16# (intToInt16# ((i16ToInt# x) `quotInt#` (i16ToInt# y)))
 
 instance Ix Int16 where
     range (m,n)          = [m..n]
-    index b@(m,n) i
+    index b@(m,_) i
              | inRange b i = int16ToInt (i - m)
-             | otherwise   = error (showString "Ix{Int16}.index: Index " .
-                                    showParen True (showsPrec 0 i) .
-                                     showString " out of range " $
-                                    showParen True (showsPrec 0 b) "")
+             | otherwise   = indexError i b "Int16"
     inRange (m,n) i      = m <= i && i <= n
 
 instance Enum Int16 where
-    toEnum           = intToInt16
+    succ i
+      | i == maxBound = succError "Int16"
+      | otherwise     = i+1
+
+    pred i
+      | i == minBound = predError "Int16"
+      | otherwise     = i-1
+
+    toEnum x
+      | x >= toInt (minBound::Int16) && x <= toInt (maxBound::Int16) 
+      = intToInt16 x
+      | otherwise
+      = toEnumError "Int16" x (minBound::Int16, maxBound::Int16)
+
     fromEnum         = int16ToInt
-    enumFrom c       = map toEnum [fromEnum c .. fromEnum (maxBound::Int16)]
-    enumFromThen c d = map toEnum [fromEnum c, fromEnum d .. fromEnum (last::Int16)]
-                         where last = if d < c then minBound else maxBound
+
+    enumFrom e1        = map toEnum [fromEnum e1 .. fromEnum (maxBound::Int16)]
+    enumFromThen e1 e2 = map toEnum [fromEnum e1, fromEnum e2 .. fromEnum (last::Int16)]
+                         where last 
+                                 | e2 < e1   = minBound
+                                 | otherwise = maxBound
 
 instance Read Int16 where
     readsPrec p s = [ (intToInt16 x,r) | (x,r) <- readsPrec p s ]
@@ -358,13 +442,13 @@ instance Bits Int16 where
   (I16# x) `xor` (I16# y) = I16# (word2Int# ((int2Word# x) `xor#`  (int2Word# y)))
   complement (I16# x)    = I16# (word2Int# ((int2Word# x) `xor#` (int2Word# 0xffff#)))
   shift (I16# x) i@(I# i#)
-       | i > 0     = I16# (intToInt16# (iShiftL# (int16ToInt# x)  i#))
-       | otherwise = I16# (intToInt16# (iShiftRA# (int16ToInt# x) (negateInt# i#)))
+       | i > 0     = I16# (intToInt16# (iShiftL# (i16ToInt# x)  i#))
+       | otherwise = I16# (intToInt16# (iShiftRA# (i16ToInt# x) (negateInt# i#)))
   i16@(I16# x)  `rotate` (I# i)
         | i ==# 0#    = i16
        | i ># 0#     = 
             I16# (intToInt16# (word2Int# (
-                   (int2Word# (iShiftL# (int16ToInt# x) i')) 
+                   (int2Word# (iShiftL# (i16ToInt# x) i')) 
                             `or#`
                     (int2Word# (iShiftRA# ( word2Int# (
                                    (int2Word# x) `and#` (int2Word# (0x100# -# pow2# i2))))
@@ -396,14 +480,15 @@ data Int32  = I32# Int#
 instance CCallable Int32
 instance CReturnable Int32
 
-int32ToInt (I32# x) = I# (int32ToInt# x)
+int32ToInt  (I32# x) = I# (i32ToInt# x)
+int32ToInt# (I32# x) = i32ToInt# x
 
-int32ToInt# :: Int# -> Int#
+i32ToInt# :: Int# -> Int#
 #if WORD_SIZE_IN_BYTES > 4
-int32ToInt# x = if x' <=# 0x7fffffff# then x' else x' -# 0x100000000#
+i32ToInt# x = if x' <=# 0x7fffffff# then x' else x' -# 0x100000000#
    where x' = word2Int# (int2Word# x `and#` int2Word# 0xffffffff#)
 #else
-int32ToInt# x = x
+i32ToInt# x = x
 #endif
 
 intToInt32 (I# x) = I32# (intToInt32# x)
@@ -419,7 +504,7 @@ instance Eq  Int32     where
   (I32# x#) /= (I32# y#) = x# /=# y#
 
 instance Ord Int32    where
-  compare (I32# x#) (I32# y#) = compareInt# (int32ToInt# x#) (int32ToInt# y#)
+  compare (I32# x#) (I32# y#) = compareInt# (i32ToInt# x#) (i32ToInt# y#)
 
 instance Num Int32 where
   (I32# x#) + (I32# y#) = I32# (intToInt32# (x# +# y#))
@@ -435,59 +520,73 @@ instance Num Int32 where
 #endif
   abs           = absReal
   signum        = signumReal
-  fromInteger (J# a# s# d#)
-                = case (integer2Int# a# s# d#) of { i# -> I32# (intToInt32# i#) }
+  fromInteger (S# i#)    = I32# (intToInt32# i#)
+  fromInteger (J# s# d#) = I32# (intToInt32# (integer2Int# s# d#))
   fromInt       = intToInt32
 
--- ToDo: remove LitLit when minBound::Int is fixed (currently it's one
--- too high, and doesn't allow the correct minBound to be defined here).
 instance Bounded Int32 where 
-    minBound = case ``0x80000000'' of { I# x -> I32# x }
-    maxBound = I32# 0x7fffffff#
+    minBound = fromInt minBound
+    maxBound = fromInt maxBound
 
 instance Real Int32 where
     toRational x = toInteger x % 1
 
 instance Integral Int32 where
-    div x@(I32# x#) y@(I32# y#) = 
-       if x > 0 && y < 0       then quotInt32 (x-y-1) y
-       else if x < 0 && y > 0  then quotInt32 (x-y+1) y
-       else quotInt32 x y
+    div x y
+       | x > 0 && y < 0        = quotInt32 (x-y-1) y
+       | x < 0 && y > 0        = quotInt32 (x-y+1) y
+       | otherwise      = quotInt32 x y
     quot x@(I32# _) y@(I32# y#)
        | y# /=# 0#  = x `quotInt32` y
-       | otherwise  = error "Integral.Int32.quot: divide by 0\n"
+       | otherwise  = divZeroError "quot{Int32}" x
     rem x@(I32# _) y@(I32# y#)
        | y# /=# 0#  = x `remInt32` y
-       | otherwise  = error "Integral.Int32.rem: divide by 0\n"
-    mod x@(I32# x#) y@(I32# y#) =
-       if x > 0 && y < 0 || x < 0 && y > 0 then
-         if r/=0 then r+y else 0
-       else
-         r
+       | otherwise  = divZeroError "rem{Int32}" x
+    mod x y
+       | x > 0 && y < 0 || x < 0 && y > 0 = if r/=0 then r+y else 0
+       | otherwise                       = r
        where r = remInt32 x y
+
     a@(I32# _) `quotRem` b@(I32# _) = (a `quotInt32` b, a `remInt32` b)
     toInteger i32  = toInteger (int32ToInt i32)
     toInt     i32  = int32ToInt i32
 
-remInt32  (I32# x) (I32# y) = I32# (intToInt32# ((int32ToInt# x) `remInt#` (int32ToInt# y)))
-quotInt32 (I32# x) (I32# y) = I32# (intToInt32# ((int32ToInt# x) `quotInt#` (int32ToInt# y)))
+remInt32, quotInt32 :: Int32 -> Int32 -> Int32
+remInt32  (I32# x) (I32# y) = I32# (intToInt32# ((i32ToInt# x) `remInt#` (i32ToInt# y)))
+quotInt32 (I32# x) (I32# y) = I32# (intToInt32# ((i32ToInt# x) `quotInt#` (i32ToInt# y)))
 
 instance Ix Int32 where
     range (m,n)          = [m..n]
-    index b@(m,n) i
+    index b@(m,_) i
              | inRange b i = int32ToInt (i - m)
-             | otherwise   = error (showString "Ix{Int32}.index: Index " .
-                                    showParen True (showsPrec 0 i) .
-                                     showString " out of range " $
-                                    showParen True (showsPrec 0 b) "")
+             | otherwise   = indexError i b "Int32"
     inRange (m,n) i      = m <= i && i <= n
 
 instance Enum Int32 where
-    toEnum         = intToInt32
-    fromEnum       = int32ToInt
-    enumFrom c       = map toEnum [fromEnum c .. fromEnum (maxBound::Int32)]
-    enumFromThen c d = map toEnum [fromEnum c, fromEnum d .. fromEnum (last::Int32)]
-                         where last = if d < c then minBound else maxBound
+    succ i
+      | i == maxBound = succError "Int32"
+      | otherwise     = i+1
+
+    pred i
+      | i == minBound = predError "Int32"
+      | otherwise     = i-1
+
+    toEnum x
+        -- with Int having the same range as Int32, the following test
+       -- shouldn't fail. However, having it here 
+      | x >= toInt (minBound::Int32) && x <= toInt (maxBound::Int32) 
+      = intToInt32 x
+      | otherwise
+      = toEnumError "Int32" x (minBound::Int32, maxBound::Int32)
+
+    fromEnum           = int32ToInt
+
+    enumFrom e1        = map toEnum [fromEnum e1 .. fromEnum (maxBound::Int32)]
+    enumFromThen e1 e2 = map toEnum [fromEnum e1, fromEnum e2 .. fromEnum (last::Int32)]
+                         where 
+                           last
+                            | e2 < e1   = minBound
+                            | otherwise = maxBound
 
 instance Read Int32 where
     readsPrec p s = [ (intToInt32 x,r) | (x,r) <- readsPrec p s ]
@@ -505,14 +604,14 @@ instance Bits Int32 where
   complement (I32# x)     = I32# (word2Int# ((int2Word# x) `xor#` (int2Word# (negateInt# 1#))))
 #endif
   shift (I32# x) i@(I# i#)
-       | i > 0     = I32# (intToInt32# (iShiftL# (int32ToInt# x)  i#))
-       | otherwise = I32# (intToInt32# (iShiftRA# (int32ToInt# x) (negateInt# i#)))
+       | i > 0     = I32# (intToInt32# (iShiftL# (i32ToInt# x)  i#))
+       | otherwise = I32# (intToInt32# (iShiftRA# (i32ToInt# x) (negateInt# i#)))
   i32@(I32# x)  `rotate` (I# i)
         | i ==# 0#    = i32
        | i ># 0#     = 
              -- ( (x<<i') | ((x&(0x100000000-2^i2))>>i2)
             I32# (intToInt32# ( word2Int# (
-                   (int2Word# (iShiftL# (int32ToInt# x) i')) 
+                   (int2Word# (iShiftL# (i32ToInt# x) i')) 
                          `or#`
                     (int2Word# (iShiftRA# (word2Int# (
                                              (int2Word# x) 
@@ -541,7 +640,7 @@ sizeofInt32 = 4
 
 \begin{code}
 #if WORD_SIZE_IN_BYTES == 8
-data Int64 = I64# Int#
+--data Int64 = I64# Int#
 
 int32ToInt64 :: Int32 -> Int64
 int32ToInt64 (I32# i#) = I64# i#
@@ -566,31 +665,29 @@ instance Num Int64 where
   negate w@(I64# x)   = I64# (negateInt# x)
   abs x               = absReal
   signum              = signumReal
-  fromInteger (J# a# s# d#) = case (integer2Int# a# s# d#) of { i# -> I64# i# }
+  fromInteger (S# i#)    = I64# i#
+  fromInteger (J# s# d#) = I64# (integer2Int# s# d#)
   fromInt       = intToInt64
 
 instance Bounded Int64 where
   minBound = integerToInt64 (-0x8000000000000000)
   maxBound = integerToInt64 0x7fffffffffffffff
 
-instance Real Int64 where
-  toRational x = toInteger x % 1
-
 instance Integral Int64 where
-    div x@(I64# x#) y@(I64# y#)
+    div x y
       | x > 0 && y < 0 = quotInt64 (x-y-1) y
       | x < 0 && y > 0 = quotInt64 (x-y+1) y
       | otherwise       = quotInt64 x y
 
     quot x@(I64# _) y@(I64# y#)
        | y# /=# 0# = x `quotInt64` y
-       | otherwise = error "Integral.Int64.quot: divide by 0\n"
+       | otherwise = divZeroError "quot{Int64}" x
 
     rem x@(I64# _) y@(I64# y#)
        | y# /=# 0# = x `remInt64` y
-       | otherwise = error "Integral.Int32.rem: divide by 0\n"
+       | otherwise = divZeroError "rem{Int64}" x
 
-    mod x@(I64# x#) y@(I64# y#)
+    mod x y
        | x > 0 && y < 0 || x < 0 && y > 0 = if r/=0 then r+y else 0
        | otherwise = r
        where r = remInt64 x y
@@ -599,20 +696,6 @@ instance Integral Int64 where
     toInteger (I64# i#) = toInteger (I# i#)
     toInt     (I64# i#) = I# i#
 
-instance Enum Int64 where
-    toEnum    (I# i)   = I64# i#
-    fromEnum  (I64# i) = I64# i#
-    enumFrom c         = map toEnum [fromEnum c .. fromEnum (maxBound::Int64)] -- a long list!
-    enumFromThen c d   = map toEnum [fromEnum c, fromEnum d .. fromEnum (last::Int64)]
-                      where last = if d < c then minBound else maxBound
-
-
-instance Read Int64 where
-    readsPrec p s = [ (intToInt64 x,r) | (x,r) <- readsPrec p s ]
-
-instance Show Int64 where
-    showsPrec p i64 = showsPrec p (int64ToInt i64)
-
 instance Bits Int64 where
   (I64# x) .&. (I64# y)   = I64# (word2Int# ((int2Word# x) `and#` (int2Word# y)))
   (I64# x) .|. (I64# y)   = I64# (word2Int# ((int2Word# x) `or#`  (int2Word# y)))
@@ -674,16 +757,13 @@ int64ToInt32 :: Int64 -> Int32
 int64ToInt32 (I64# i#) = I32# (int64ToInt# i#)
 
 int64ToInteger :: Int64 -> Integer
-int64ToInteger (I64# x#) = int64ToInteger# x#
+int64ToInteger (I64# x#) = 
+   case int64ToInteger# x# of
+     (# s#, p# #) -> J# s# p#
 
 integerToInt64 :: Integer -> Int64
-integerToInt64 (J# a# s# d#) = I64# (integerToInt64# a# s# d#)
-
-instance Show Int64 where
-  showsPrec p x = showsPrec p (int64ToInteger x)
-
-instance Read Int64 where
-  readsPrec p s = [ (integerToInt64 x,r) | (x,r) <- readDec s ]
+integerToInt64 (S# i#) = I64# (intToInt64# i#)
+integerToInt64 (J# s# d#) = I64# (integerToInt64# s# d#)
 
 instance Eq  Int64     where 
   (I64# x) == (I64# y) = x `eqInt64#` y
@@ -710,6 +790,7 @@ instance Num Int64 where
   fromInteger i       = integerToInt64 i
   fromInt     i       = intToInt64 i
 
+compareInt64# :: Int64# -> Int64# -> Ordering
 compareInt64# i# j# 
  | i# `ltInt64#` j# = LT
  | i# `eqInt64#` j# = EQ
@@ -719,24 +800,21 @@ instance Bounded Int64 where
   minBound = integerToInt64 (-0x8000000000000000)
   maxBound = integerToInt64 0x7fffffffffffffff
 
-instance Real Int64 where
-  toRational x = toInteger x % 1
-
 instance Integral Int64 where
-    div x@(I64# x#) y@(I64# y#)
+    div x y
       | x > 0 && y < 0 = quotInt64 (x-y-1) y
       | x < 0 && y > 0 = quotInt64 (x-y+1) y
       | otherwise       = quotInt64 x y
 
     quot x@(I64# _) y@(I64# y#)
        | y# `neInt64#` (intToInt64# 0#) = x `quotInt64` y
-       | otherwise = error "Integral.Int64.quot: divide by 0\n"
+       | otherwise = divZeroError "quot{Int64}" x
 
     rem x@(I64# _) y@(I64# y#)
        | y# `neInt64#` (intToInt64# 0#) = x `remInt64` y
-       | otherwise = error "Integral.Int32.rem: divide by 0\n"
+       | otherwise = divZeroError "rem{Int64}" x
 
-    mod x@(I64# x#) y@(I64# y#)
+    mod x y
        | x > 0 && y < 0 || x < 0 && y > 0 = if r/=0 then r+y else 0
        | otherwise = r
        where r = remInt64 x y
@@ -745,18 +823,6 @@ instance Integral Int64 where
     toInteger i         = int64ToInteger i
     toInt     i         = int64ToInt i
 
-instance Enum Int64 where
-    toEnum    (I# i)   = I64# (intToInt64# i)
-    fromEnum  (I64# w) = I# (int64ToInt# w)
-    enumFrom i              = eft64 i 1
-    enumFromTo   i1 i2      = eftt64 i1 1 (> i2)
-    enumFromThen i1 i2      = eftt64 i1 (i2 - i1) (>last)
-        where 
-        last
-         | i1 < i2   = maxBound::Int64
-         | otherwise = minBound
-
-
 instance Bits Int64 where
   (I64# x) .&. (I64# y)   = I64# (word64ToInt64# ((int64ToWord64# x) `and64#` (int64ToWord64# y)))
   (I64# x) .|. (I64# y)   = I64# (word64ToInt64# ((int64ToWord64# x) `or64#`  (int64ToWord64# y)))
@@ -787,6 +853,7 @@ instance Bits Int64 where
   bitSize  _    = 64
   isSigned _    = True
 
+remInt64, quotInt64 :: Int64 -> Int64 -> Int64
 remInt64  (I64# x) (I64# y) = I64# (x `remInt64#` y)
 quotInt64 (I64# x) (I64# y) = I64# (x `quotInt64#` y)
 
@@ -796,23 +863,6 @@ intToInt64 (I# i#) = I64# (intToInt64# i#)
 int64ToInt :: Int64 -> Int
 int64ToInt (I64# i#) = I# (int64ToInt# i#)
 
--- Enum Int64 helper funs:
-
-eftt64 :: Int64 -> Int64 -> (Int64->Bool) -> [Int64]
-eftt64 now step done = go now
-  where
-   go now
-     | done now  = []
-     | otherwise = now : go (now+step)
-
-eft64 :: Int64 -> Int64 -> [Int64]
-eft64 now step = go now
-  where 
-   go x
-    | x == maxBound = [x]
-    | otherwise     = x:go (x+step)
-
-
 -- Word64# primop wrappers:
 
 ltInt64# :: Int64# -> Int64# -> Bool
@@ -933,14 +983,14 @@ shiftRL64# a# b# =
     W64# w# -> w#
 
 int64ToInt# :: Int64# -> Int#
-int64ToInt# i# =
-  case (unsafePerformIO (_ccall_ stg_int64ToInt i#)) of
+int64ToInt# i64# =
+  case (unsafePerformIO (_ccall_ stg_int64ToInt i64#)) of
     I# i# -> i#
 
 wordToWord64# :: Word# -> Word64#
 wordToWord64# w# =
   case (unsafePerformIO (_ccall_ stg_wordToWord64 w#)) of
-    W64# w# -> w#
+    W64# w64# -> w64#
 
 word64ToInt64# :: Word64# -> Int64#
 word64ToInt64# w# =
@@ -948,20 +998,93 @@ word64ToInt64# w# =
     I64# i# -> i#
 
 int64ToWord64# :: Int64# -> Word64#
-int64ToWord64# w# =
-  case (unsafePerformIO (_ccall_ stg_int64ToWord64 w#)) of
+int64ToWord64# i# =
+  case (unsafePerformIO (_ccall_ stg_int64ToWord64 i#)) of
     W64# w# -> w#
 
 intToInt64# :: Int# -> Int64#
 intToInt64# i# =
   case (unsafePerformIO (_ccall_ stg_intToInt64 i#)) of
-    I64# i# -> i#
-      
+    I64# i64# -> i64#
 
 #endif
 
+--
+-- Code that's independent of Int64 rep.
+-- 
+instance Enum Int64 where
+    succ i
+      | i == maxBound = succError "Int64"
+      | otherwise     = i+1
+
+    pred i
+      | i == minBound = predError "Int64"
+      | otherwise     = i-1
+
+    toEnum    i = intToInt64 i
+    fromEnum  x
+      | x >= intToInt64 (minBound::Int) && x <= intToInt64 (maxBound::Int)
+      = int64ToInt x
+      | otherwise
+      = fromEnumError "Int64" x
+
+    enumFrom e1        = map integerToInt64 [int64ToInteger e1 .. int64ToInteger (maxBound::Int64)]
+    enumFromTo e1 e2   = map integerToInt64 [int64ToInteger e1 .. int64ToInteger e2]
+    enumFromThen e1 e2 = map integerToInt64 [int64ToInteger e1, int64ToInteger e2 .. int64ToInteger last]
+                      where 
+                         last :: Int64
+                         last 
+                          | e2 < e1   = minBound
+                          | otherwise = maxBound
+
+    enumFromThenTo e1 e2 e3 = map integerToInt64 [int64ToInteger e1, int64ToInteger e2 .. int64ToInteger e3]
+
+
+instance Show Int64 where
+    showsPrec p i64 = showsPrec p (int64ToInteger i64)
+
+instance Read Int64 where
+  readsPrec _ s = [ (integerToInt64 x,r) | (x,r) <- readDec s ]
+
+
+instance Ix Int64 where
+    range (m,n)          = [m..n]
+    index b@(m,_) i
+          | inRange b i = int64ToInt (i-m)
+          | otherwise   = indexError i b "Int64"
+    inRange (m,n) i      = m <= i && i <= n
+
+instance Real Int64 where
+  toRational x = toInteger x % 1
+
+
 sizeofInt64 :: Word32
 sizeofInt64 = 8
+
+int8ToInteger :: Int8 -> Integer
+int8ToInteger i = toInteger i
+
+int16ToInteger :: Int16 -> Integer
+int16ToInteger i = toInteger i
+
+int32ToInteger :: Int32 -> Integer
+int32ToInteger i = toInteger i
+
+int64ToInt8 :: Int64 -> Int8
+int64ToInt8 = int32ToInt8 . int64ToInt32
+
+int64ToInt16 :: Int64 -> Int16
+int64ToInt16 = int32ToInt16 . int64ToInt32
+
+integerToInt8 :: Integer -> Int8
+integerToInt8 = fromInteger
+
+integerToInt16 :: Integer -> Int16
+integerToInt16 = fromInteger
+
+integerToInt32 :: Integer -> Int32
+integerToInt32 = fromInteger
+
 \end{code}
 
 %
@@ -973,9 +1096,11 @@ sizeofInt64 = 8
 Code copied from the Prelude
 
 \begin{code}
+absReal :: (Ord a, Num a) => a -> a
 absReal x    | x >= 0    = x
             | otherwise = -x
 
+signumReal :: (Ord a, Num a) => a -> a
 signumReal x | x == 0    =  0
             | x > 0     =  1
             | otherwise = -1
@@ -1017,16 +1142,17 @@ indexInt64OffAddr (A# a#) (I# i#)
 #endif
 
 #ifndef __PARALLEL_HASKELL__
+
 indexInt8OffForeignObj  :: ForeignObj -> Int -> Int8
 indexInt8OffForeignObj (ForeignObj fo#) (I# i#) = intToInt8 (I# (ord# (indexCharOffForeignObj# fo# i#)))
 
 indexInt16OffForeignObj :: ForeignObj -> Int -> Int16
 indexInt16OffForeignObj fo i =
-#ifdef WORDS_BIGENDIAN
+# ifdef WORDS_BIGENDIAN
   intToInt16 ( int8ToInt l + (int8ToInt maxBound) * int8ToInt h)
-#else
+# else
   intToInt16 ( int8ToInt h + (int8ToInt maxBound) * int8ToInt l)
-#endif
+# endif
  where
    byte_idx = i * 2
    l = indexInt8OffForeignObj fo byte_idx
@@ -1037,19 +1163,19 @@ indexInt32OffForeignObj (ForeignObj fo#) i = intToInt32 (I# (indexIntOffForeignO
  where
    -- adjust index to be in Int units, not Int32 ones.
   (I# i'#) 
-#if WORD_SIZE_IN_BYTES==8
+# if WORD_SIZE_IN_BYTES==8
    = i `div` 2
-#else
+# else
    = i
-#endif
+# endif
 
 indexInt64OffForeignObj :: ForeignObj -> Int -> Int64
 indexInt64OffForeignObj (ForeignObj fo#) (I# i#)
-#if WORD_SIZE_IN_BYTES==8
+# if WORD_SIZE_IN_BYTES==8
  = I64# (indexIntOffForeignObj# fo# i#)
-#else
+# else
  = I64# (indexInt64OffForeignObj# fo# i#)
-#endif
+# endif
 
 #endif /* __PARALLEL_HASKELL__ */
 \end{code}
@@ -1074,6 +1200,7 @@ readInt64OffAddr a i = _casm_ `` %r=(StgInt64)(((StgInt64*)%0)[(StgInt)%1]); ''
 #endif
 
 #ifndef __PARALLEL_HASKELL__
+
 readInt8OffForeignObj :: ForeignObj -> Int -> IO Int8
 readInt8OffForeignObj fo i = _casm_ `` %r=(StgInt8)(((StgInt8*)%0)[(StgInt)%1]); '' fo i
 
@@ -1084,11 +1211,12 @@ readInt32OffForeignObj  :: ForeignObj -> Int -> IO Int32
 readInt32OffForeignObj fo i = _casm_ `` %r=(StgInt32)(((StgInt32*)%0)[(StgInt)%1]); '' fo i
 
 readInt64OffForeignObj  :: ForeignObj -> Int -> IO Int64
-#if WORD_SIZE_IN_BYTES==8
+# if WORD_SIZE_IN_BYTES==8
 readInt64OffForeignObj fo i = _casm_ `` %r=(StgInt)(((StgInt*)%0)[(StgInt)%1]); '' fo i
-#else
+# else
 readInt64OffForeignObj fo i = _casm_ `` %r=(StgInt64)(((StgInt64*)%0)[(StgInt)%1]); '' fo i
-#endif
+# endif
+
 #endif /* __PARALLEL_HASKELL__ */
 \end{code}
 
@@ -1110,6 +1238,7 @@ writeInt64OffAddr a i e = _casm_ `` (((StgInt64*)%0)[(StgInt)%1])=(StgInt64)%2;
 #endif
 
 #ifndef __PARALLEL_HASKELL__
+
 writeInt8OffForeignObj  :: ForeignObj -> Int -> Int8  -> IO ()
 writeInt8OffForeignObj fo i e = _casm_ `` (((StgInt8*)%0)[(StgInt)%1])=(StgInt8)%2; '' fo i e
 
@@ -1120,11 +1249,53 @@ writeInt32OffForeignObj :: ForeignObj -> Int -> Int32 -> IO ()
 writeInt32OffForeignObj fo i e = _casm_ `` (((StgInt32*)%0)[(StgInt)%1])=(StgInt32)%2; '' fo i e
 
 writeInt64OffForeignObj :: ForeignObj -> Int -> Int64 -> IO ()
-#if WORD_SIZE_IN_BYTES==8
+# if WORD_SIZE_IN_BYTES==8
 writeInt64OffForeignObj fo i e = _casm_ `` (((StgInt*)%0)[(StgInt)%1])=(StgInt)%2; '' fo i e
-#else
+# else
 writeInt64OffForeignObj fo i e = _casm_ `` (((StgInt64*)%0)[(StgInt)%1])=(StgInt64)%2; '' fo i e
-#endif
+# endif
+
 #endif /* __PARALLEL_HASKELL__ */
+
 \end{code}
 
+
+C&P'ed from Ix.lhs
+
+\begin{code}
+{-# NOINLINE indexError #-}
+indexError :: Show a => a -> (a,a) -> String -> b
+indexError i rng tp
+  = error (showString "Ix{" . showString tp . showString "}.index: Index " .
+           showParen True (showsPrec 0 i) .
+          showString " out of range " $
+          showParen True (showsPrec 0 rng) "")
+
+
+toEnumError :: (Show a,Show b) => String -> a -> (b,b) -> c
+toEnumError inst_ty tag bnds
+  = error ("Enum.toEnum{" ++ inst_ty ++ "}: tag " ++
+           (showParen True (showsPrec 0 tag) $
+            " is outside of bounds " ++
+            show bnds))
+
+fromEnumError :: (Show a,Show b) => String -> a -> b
+fromEnumError inst_ty tag
+  = error ("Enum.fromEnum{" ++ inst_ty ++ "}: value " ++
+           (showParen True (showsPrec 0 tag) $
+            " is outside of Int's bounds " ++
+            show (minBound::Int,maxBound::Int)))
+
+succError :: String -> a
+succError inst_ty
+  = error ("Enum.succ{" ++ inst_ty ++ "}: tried to take `succ' of maxBound")
+
+predError :: String -> a
+predError inst_ty
+  = error ("Enum.pred{" ++ inst_ty ++ "}: tried to take `pred' of minBound")
+
+divZeroError :: (Show a) => String -> a -> b
+divZeroError meth v 
+  = error ("Integral." ++ meth ++ ": divide by 0 (" ++ show v ++ " / 0)")
+
+\end{code}