add GHC.HetMet.{hetmet_kappa,hetmet_kappa_app}
[ghc-base.git] / GHC / Int.hs
index 2bb7d5c..27ee990 100644 (file)
@@ -1,4 +1,6 @@
-{-# OPTIONS_GHC -fno-implicit-prelude #-}
+{-# LANGUAGE CPP, NoImplicitPrelude, BangPatterns, MagicHash, 
+             StandaloneDeriving #-}
+{-# OPTIONS_HADDOCK hide #-}
 -----------------------------------------------------------------------------
 -- |
 -- Module      :  GHC.Int
 
 -- #hide
 module GHC.Int (
-    Int8(..), Int16(..), Int32(..), Int64(..))
-    where
+    Int8(..), Int16(..), Int32(..), Int64(..),
+    uncheckedIShiftL64#, uncheckedIShiftRA64#
+    ) where
 
 import Data.Bits
 
-import {-# SOURCE #-} GHC.Err
+#if WORD_SIZE_IN_BITS < 32
+import GHC.IntWord32
+#endif
+#if WORD_SIZE_IN_BITS < 64
+import GHC.IntWord64
+#endif
+
 import GHC.Base
 import GHC.Enum
 import GHC.Num
 import GHC.Real
 import GHC.Read
 import GHC.Arr
-import GHC.Word
+import GHC.Err
+import GHC.Word hiding (uncheckedShiftL64#, uncheckedShiftRL64#)
 import GHC.Show
+import GHC.Float ()     -- for RealFrac methods
+
 
 ------------------------------------------------------------------------
 -- type Int8
@@ -55,8 +67,7 @@ instance Num Int8 where
     signum x | x > 0       = 1
     signum 0               = 0
     signum _               = -1
-    fromInteger (S# i#)    = I8# (narrow8Int# i#)
-    fromInteger (J# s# d#) = I8# (narrow8Int# (integer2Int# s# d#))
+    fromInteger i          = I8# (narrow8Int# (toInt# i))
 
 instance Real Int8 where
     toRational x = toInteger x % 1
@@ -79,40 +90,40 @@ instance Enum Int8 where
 instance Integral Int8 where
     quot    x@(I8# x#) y@(I8# y#)
         | y == 0                     = divZeroError
-        | x == minBound && y == (-1) = overflowError
+        | y == (-1) && x == minBound = overflowError -- Note [Order of tests]
         | otherwise                  = I8# (narrow8Int# (x# `quotInt#` y#))
     rem     x@(I8# x#) y@(I8# y#)
         | y == 0                     = divZeroError
-        | x == minBound && y == (-1) = overflowError
+        | y == (-1) && x == minBound = overflowError -- Note [Order of tests]
         | otherwise                  = I8# (narrow8Int# (x# `remInt#` y#))
     div     x@(I8# x#) y@(I8# y#)
         | y == 0                     = divZeroError
-        | x == minBound && y == (-1) = overflowError
+        | y == (-1) && x == minBound = overflowError -- Note [Order of tests]
         | otherwise                  = I8# (narrow8Int# (x# `divInt#` y#))
     mod     x@(I8# x#) y@(I8# y#)
         | y == 0                     = divZeroError
-        | x == minBound && y == (-1) = overflowError
+        | y == (-1) && x == minBound = overflowError -- Note [Order of tests]
         | otherwise                  = I8# (narrow8Int# (x# `modInt#` y#))
     quotRem x@(I8# x#) y@(I8# y#)
         | y == 0                     = divZeroError
-        | x == minBound && y == (-1) = overflowError
+        | y == (-1) && x == minBound = overflowError -- Note [Order of tests]
         | otherwise                  = (I8# (narrow8Int# (x# `quotInt#` y#)),
                                        I8# (narrow8Int# (x# `remInt#` y#)))
     divMod  x@(I8# x#) y@(I8# y#)
         | y == 0                     = divZeroError
-        | x == minBound && y == (-1) = overflowError
+        | y == (-1) && x == minBound = overflowError -- Note [Order of tests]
         | otherwise                  = (I8# (narrow8Int# (x# `divInt#` y#)),
                                        I8# (narrow8Int# (x# `modInt#` y#)))
-    toInteger (I8# x#)               = S# x#
+    toInteger (I8# x#)               = smallInteger x#
 
 instance Bounded Int8 where
     minBound = -0x80
     maxBound =  0x7F
 
 instance Ix Int8 where
-    range (m,n)              = [m..n]
-    unsafeIndex b@(m,_) i    = fromIntegral i - fromIntegral m
-    inRange (m,n) i          = m <= i && i <= n
+    range (m,n)         = [m..n]
+    unsafeIndex (m,_) i = fromIntegral i - fromIntegral m
+    inRange (m,n) i     = m <= i && i <= n
 
 instance Read Int8 where
     readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
@@ -134,8 +145,8 @@ instance Bits Int8 where
         = I8# (narrow8Int# (word2Int# ((x'# `uncheckedShiftL#` i'#) `or#`
                                        (x'# `uncheckedShiftRL#` (8# -# i'#)))))
         where
-        x'# = narrow8Word# (int2Word# x#)
-        i'# = word2Int# (int2Word# i# `and#` int2Word# 7#)
+        !x'# = narrow8Word# (int2Word# x#)
+        !i'# = word2Int# (int2Word# i# `and#` int2Word# 7#)
     bitSize  _                = 8
     isSigned _                = True
 
@@ -145,6 +156,36 @@ instance Bits Int8 where
 "fromIntegral/Int8->a"    fromIntegral = \(I8# x#) -> fromIntegral (I# x#)
   #-}
 
+{-# RULES
+"properFraction/Float->(Int8,Float)"
+    forall x. properFraction (x :: Float) =
+                      case properFraction x of {
+                        (n, y) -> ((fromIntegral :: Int -> Int8) n, y) }
+"truncate/Float->Int8"
+    forall x. truncate (x :: Float) = (fromIntegral :: Int -> Int8) (truncate x)
+"floor/Float->Int8"
+    forall x. floor    (x :: Float) = (fromIntegral :: Int -> Int8) (floor x)
+"ceiling/Float->Int8"
+    forall x. ceiling  (x :: Float) = (fromIntegral :: Int -> Int8) (ceiling x)
+"round/Float->Int8"
+    forall x. round    (x :: Float) = (fromIntegral :: Int -> Int8) (round x)
+  #-}
+
+{-# RULES
+"properFraction/Double->(Int8,Double)"
+    forall x. properFraction (x :: Double) =
+                      case properFraction x of {
+                        (n, y) -> ((fromIntegral :: Int -> Int8) n, y) }
+"truncate/Double->Int8"
+    forall x. truncate (x :: Double) = (fromIntegral :: Int -> Int8) (truncate x)
+"floor/Double->Int8"
+    forall x. floor    (x :: Double) = (fromIntegral :: Int -> Int8) (floor x)
+"ceiling/Double->Int8"
+    forall x. ceiling  (x :: Double) = (fromIntegral :: Int -> Int8) (ceiling x)
+"round/Double->Int8"
+    forall x. round    (x :: Double) = (fromIntegral :: Int -> Int8) (round x)
+  #-}
+
 ------------------------------------------------------------------------
 -- type Int16
 ------------------------------------------------------------------------
@@ -168,8 +209,7 @@ instance Num Int16 where
     signum x | x > 0       = 1
     signum 0               = 0
     signum _               = -1
-    fromInteger (S# i#)    = I16# (narrow16Int# i#)
-    fromInteger (J# s# d#) = I16# (narrow16Int# (integer2Int# s# d#))
+    fromInteger i          = I16# (narrow16Int# (toInt# i))
 
 instance Real Int16 where
     toRational x = toInteger x % 1
@@ -192,40 +232,40 @@ instance Enum Int16 where
 instance Integral Int16 where
     quot    x@(I16# x#) y@(I16# y#)
         | y == 0                     = divZeroError
-        | x == minBound && y == (-1) = overflowError
+        | y == (-1) && x == minBound = overflowError -- Note [Order of tests]
         | otherwise                  = I16# (narrow16Int# (x# `quotInt#` y#))
     rem     x@(I16# x#) y@(I16# y#)
         | y == 0                     = divZeroError
-        | x == minBound && y == (-1) = overflowError
+        | y == (-1) && x == minBound = overflowError -- Note [Order of tests]
         | otherwise                  = I16# (narrow16Int# (x# `remInt#` y#))
     div     x@(I16# x#) y@(I16# y#)
         | y == 0                     = divZeroError
-        | x == minBound && y == (-1) = overflowError
+        | y == (-1) && x == minBound = overflowError -- Note [Order of tests]
         | otherwise                  = I16# (narrow16Int# (x# `divInt#` y#))
     mod     x@(I16# x#) y@(I16# y#)
         | y == 0                     = divZeroError
-        | x == minBound && y == (-1) = overflowError
+        | y == (-1) && x == minBound = overflowError -- Note [Order of tests]
         | otherwise                  = I16# (narrow16Int# (x# `modInt#` y#))
     quotRem x@(I16# x#) y@(I16# y#)
         | y == 0                     = divZeroError
-        | x == minBound && y == (-1) = overflowError
+        | y == (-1) && x == minBound = overflowError -- Note [Order of tests]
         | otherwise                  = (I16# (narrow16Int# (x# `quotInt#` y#)),
                                         I16# (narrow16Int# (x# `remInt#` y#)))
     divMod  x@(I16# x#) y@(I16# y#)
         | y == 0                     = divZeroError
-        | x == minBound && y == (-1) = overflowError
+        | y == (-1) && x == minBound = overflowError -- Note [Order of tests]
         | otherwise                  = (I16# (narrow16Int# (x# `divInt#` y#)),
                                         I16# (narrow16Int# (x# `modInt#` y#)))
-    toInteger (I16# x#)              = S# x#
+    toInteger (I16# x#)              = smallInteger x#
 
 instance Bounded Int16 where
     minBound = -0x8000
     maxBound =  0x7FFF
 
 instance Ix Int16 where
-    range (m,n)              = [m..n]
-    unsafeIndex b@(m,_) i    = fromIntegral i - fromIntegral m
-    inRange (m,n) i          = m <= i && i <= n
+    range (m,n)         = [m..n]
+    unsafeIndex (m,_) i = fromIntegral i - fromIntegral m
+    inRange (m,n) i     = m <= i && i <= n
 
 instance Read Int16 where
     readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
@@ -247,11 +287,12 @@ instance Bits Int16 where
         = I16# (narrow16Int# (word2Int# ((x'# `uncheckedShiftL#` i'#) `or#`
                                          (x'# `uncheckedShiftRL#` (16# -# i'#)))))
         where
-        x'# = narrow16Word# (int2Word# x#)
-        i'# = word2Int# (int2Word# i# `and#` int2Word# 15#)
+        !x'# = narrow16Word# (int2Word# x#)
+        !i'# = word2Int# (int2Word# i# `and#` int2Word# 15#)
     bitSize  _                 = 16
     isSigned _                 = True
 
+
 {-# RULES
 "fromIntegral/Word8->Int16"  fromIntegral = \(W8# x#) -> I16# (word2Int# x#)
 "fromIntegral/Int8->Int16"   fromIntegral = \(I8# x#) -> I16# x#
@@ -260,6 +301,36 @@ instance Bits Int16 where
 "fromIntegral/Int16->a"      fromIntegral = \(I16# x#) -> fromIntegral (I# x#)
   #-}
 
+{-# RULES
+"properFraction/Float->(Int16,Float)"
+    forall x. properFraction (x :: Float) =
+                      case properFraction x of {
+                        (n, y) -> ((fromIntegral :: Int -> Int16) n, y) }
+"truncate/Float->Int16"
+    forall x. truncate (x :: Float) = (fromIntegral :: Int -> Int16) (truncate x)
+"floor/Float->Int16"
+    forall x. floor    (x :: Float) = (fromIntegral :: Int -> Int16) (floor x)
+"ceiling/Float->Int16"
+    forall x. ceiling  (x :: Float) = (fromIntegral :: Int -> Int16) (ceiling x)
+"round/Float->Int16"
+    forall x. round    (x :: Float) = (fromIntegral :: Int -> Int16) (round x)
+  #-}
+
+{-# RULES
+"properFraction/Double->(Int16,Double)"
+    forall x. properFraction (x :: Double) =
+                      case properFraction x of {
+                        (n, y) -> ((fromIntegral :: Int -> Int16) n, y) }
+"truncate/Double->Int16"
+    forall x. truncate (x :: Double) = (fromIntegral :: Int -> Int16) (truncate x)
+"floor/Double->Int16"
+    forall x. floor    (x :: Double) = (fromIntegral :: Int -> Int16) (floor x)
+"ceiling/Double->Int16"
+    forall x. ceiling  (x :: Double) = (fromIntegral :: Int -> Int16) (ceiling x)
+"round/Double->Int16"
+    forall x. round    (x :: Double) = (fromIntegral :: Int -> Int16) (round x)
+  #-}
+
 ------------------------------------------------------------------------
 -- type Int32
 ------------------------------------------------------------------------
@@ -315,33 +386,33 @@ instance Enum Int32 where
 instance Integral Int32 where
     quot    x@(I32# x#) y@(I32# y#)
         | y == 0                     = divZeroError
-        | x == minBound && y == (-1) = overflowError
+        | y == (-1) && x == minBound = overflowError -- Note [Order of tests]
         | otherwise                  = I32# (x# `quotInt32#` y#)
     rem     x@(I32# x#) y@(I32# y#)
         | y == 0                  = divZeroError
-        | x == minBound && y == (-1) = overflowError
+        | y == (-1) && x == minBound = overflowError -- Note [Order of tests]
         | otherwise               = I32# (x# `remInt32#` y#)
     div     x@(I32# x#) y@(I32# y#)
         | y == 0                  = divZeroError
-        | x == minBound && y == (-1) = overflowError
+        | y == (-1) && x == minBound = overflowError -- Note [Order of tests]
         | otherwise               = I32# (x# `divInt32#` y#)
     mod     x@(I32# x#) y@(I32# y#)
         | y == 0                  = divZeroError
-        | x == minBound && y == (-1) = overflowError
+        | y == (-1) && x == minBound = overflowError -- Note [Order of tests]
         | otherwise               = I32# (x# `modInt32#` y#)
     quotRem x@(I32# x#) y@(I32# y#)
         | y == 0                  = divZeroError
-        | x == minBound && y == (-1) = overflowError
+        | y == (-1) && x == minBound = overflowError -- Note [Order of tests]
         | otherwise               = (I32# (x# `quotInt32#` y#),
                                      I32# (x# `remInt32#` y#))
     divMod  x@(I32# x#) y@(I32# y#)
         | y == 0                  = divZeroError
-        | x == minBound && y == (-1) = overflowError
+        | y == (-1) && x == minBound = overflowError -- Note [Order of tests]
         | otherwise               = (I32# (x# `divInt32#` y#),
                                      I32# (x# `modInt32#` y#))
     toInteger x@(I32# x#)
        | x >= fromIntegral (minBound::Int) && x <= fromIntegral (maxBound::Int)
-                                  = S# (int32ToInt# x#)
+                                  = smallInteger (int32ToInt# x#)
         | otherwise               = case int32ToInteger# x# of (# s, d #) -> J# s d
 
 divInt32#, modInt32# :: Int32# -> Int32# -> Int32#
@@ -384,31 +455,6 @@ instance Bits Int32 where
     bitSize  _                 = 32
     isSigned _                 = True
 
-foreign import "stg_eqInt32"       unsafe eqInt32#       :: Int32# -> Int32# -> Bool
-foreign import "stg_neInt32"       unsafe neInt32#       :: Int32# -> Int32# -> Bool
-foreign import "stg_ltInt32"       unsafe ltInt32#       :: Int32# -> Int32# -> Bool
-foreign import "stg_leInt32"       unsafe leInt32#       :: Int32# -> Int32# -> Bool
-foreign import "stg_gtInt32"       unsafe gtInt32#       :: Int32# -> Int32# -> Bool
-foreign import "stg_geInt32"       unsafe geInt32#       :: Int32# -> Int32# -> Bool
-foreign import "stg_plusInt32"     unsafe plusInt32#     :: Int32# -> Int32# -> Int32#
-foreign import "stg_minusInt32"    unsafe minusInt32#    :: Int32# -> Int32# -> Int32#
-foreign import "stg_timesInt32"    unsafe timesInt32#    :: Int32# -> Int32# -> Int32#
-foreign import "stg_negateInt32"   unsafe negateInt32#   :: Int32# -> Int32#
-foreign import "stg_quotInt32"     unsafe quotInt32#     :: Int32# -> Int32# -> Int32#
-foreign import "stg_remInt32"      unsafe remInt32#      :: Int32# -> Int32# -> Int32#
-foreign import "stg_intToInt32"    unsafe intToInt32#    :: Int# -> Int32#
-foreign import "stg_int32ToInt"    unsafe int32ToInt#    :: Int32# -> Int#
-foreign import "stg_wordToWord32"  unsafe wordToWord32#  :: Word# -> Word32#
-foreign import "stg_int32ToWord32" unsafe int32ToWord32# :: Int32# -> Word32#
-foreign import "stg_word32ToInt32" unsafe word32ToInt32# :: Word32# -> Int32#
-foreign import "stg_and32"         unsafe and32#         :: Word32# -> Word32# -> Word32#
-foreign import "stg_or32"          unsafe or32#          :: Word32# -> Word32# -> Word32#
-foreign import "stg_xor32"         unsafe xor32#         :: Word32# -> Word32# -> Word32#
-foreign import "stg_not32"         unsafe not32#         :: Word32# -> Word32#
-foreign import "stg_iShiftL32"     unsafe iShiftL32#     :: Int32# -> Int# -> Int32#
-foreign import "stg_iShiftRA32"    unsafe iShiftRA32#    :: Int32# -> Int# -> Int32#
-foreign import "stg_shiftL32"      unsafe shiftL32#      :: Word32# -> Int# -> Word32#
-foreign import "stg_shiftRL32"     unsafe shiftRL32#     :: Word32# -> Int# -> Word32#
 
 {-# RULES
 "fromIntegral/Int->Int32"    fromIntegral = \(I#   x#) -> I32# (intToInt32# x#)
@@ -420,7 +466,8 @@ foreign import "stg_shiftRL32"     unsafe shiftRL32#     :: Word32# -> Int# -> W
 "fromIntegral/Int32->Int32"  fromIntegral = id :: Int32 -> Int32
   #-}
 
-#else 
+-- No rules for RealFrac methods if Int32 is larger than Int
+#else
 
 -- Int32 is represented in the same way as Int.
 #if WORD_SIZE_IN_BITS > 32
@@ -444,8 +491,7 @@ instance Num Int32 where
     signum x | x > 0       = 1
     signum 0               = 0
     signum _               = -1
-    fromInteger (S# i#)    = I32# (narrow32Int# i#)
-    fromInteger (J# s# d#) = I32# (narrow32Int# (integer2Int# s# d#))
+    fromInteger i          = I32# (narrow32Int# (toInt# i))
 
 instance Enum Int32 where
     succ x
@@ -469,31 +515,31 @@ instance Enum Int32 where
 instance Integral Int32 where
     quot    x@(I32# x#) y@(I32# y#)
         | y == 0                     = divZeroError
-        | x == minBound && y == (-1) = overflowError
+        | y == (-1) && x == minBound = overflowError -- Note [Order of tests]
         | otherwise                  = I32# (narrow32Int# (x# `quotInt#` y#))
     rem     x@(I32# x#) y@(I32# y#)
         | y == 0                     = divZeroError
-        | x == minBound && y == (-1) = overflowError
+        | y == (-1) && x == minBound = overflowError -- Note [Order of tests]
         | otherwise                  = I32# (narrow32Int# (x# `remInt#` y#))
     div     x@(I32# x#) y@(I32# y#)
         | y == 0                     = divZeroError
-        | x == minBound && y == (-1) = overflowError
+        | y == (-1) && x == minBound = overflowError -- Note [Order of tests]
         | otherwise                  = I32# (narrow32Int# (x# `divInt#` y#))
     mod     x@(I32# x#) y@(I32# y#)
         | y == 0                     = divZeroError
-        | x == minBound && y == (-1) = overflowError
+        | y == (-1) && x == minBound = overflowError -- Note [Order of tests]
         | otherwise                  = I32# (narrow32Int# (x# `modInt#` y#))
     quotRem x@(I32# x#) y@(I32# y#)
         | y == 0                     = divZeroError
-        | x == minBound && y == (-1) = overflowError
+        | y == (-1) && x == minBound = overflowError -- Note [Order of tests]
         | otherwise                  = (I32# (narrow32Int# (x# `quotInt#` y#)),
                                      I32# (narrow32Int# (x# `remInt#` y#)))
     divMod  x@(I32# x#) y@(I32# y#)
         | y == 0                     = divZeroError
-        | x == minBound && y == (-1) = overflowError
+        | y == (-1) && x == minBound = overflowError -- Note [Order of tests]
         | otherwise                  = (I32# (narrow32Int# (x# `divInt#` y#)),
                                      I32# (narrow32Int# (x# `modInt#` y#)))
-    toInteger (I32# x#)              = S# x#
+    toInteger (I32# x#)              = smallInteger x#
 
 instance Read Int32 where
     readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
@@ -515,8 +561,8 @@ instance Bits Int32 where
         = I32# (narrow32Int# (word2Int# ((x'# `uncheckedShiftL#` i'#) `or#`
                                          (x'# `uncheckedShiftRL#` (32# -# i'#)))))
         where
-        x'# = narrow32Word# (int2Word# x#)
-        i'# = word2Int# (int2Word# i# `and#` int2Word# 31#)
+        !x'# = narrow32Word# (int2Word# x#)
+        !i'# = word2Int# (int2Word# i# `and#` int2Word# 31#)
     bitSize  _                 = 32
     isSigned _                 = True
 
@@ -530,7 +576,37 @@ instance Bits Int32 where
 "fromIntegral/Int32->a"      fromIntegral = \(I32# x#) -> fromIntegral (I# x#)
   #-}
 
-#endif 
+{-# RULES
+"properFraction/Float->(Int32,Float)"
+    forall x. properFraction (x :: Float) =
+                      case properFraction x of {
+                        (n, y) -> ((fromIntegral :: Int -> Int32) n, y) }
+"truncate/Float->Int32"
+    forall x. truncate (x :: Float) = (fromIntegral :: Int -> Int32) (truncate x)
+"floor/Float->Int32"
+    forall x. floor    (x :: Float) = (fromIntegral :: Int -> Int32) (floor x)
+"ceiling/Float->Int32"
+    forall x. ceiling  (x :: Float) = (fromIntegral :: Int -> Int32) (ceiling x)
+"round/Float->Int32"
+    forall x. round    (x :: Float) = (fromIntegral :: Int -> Int32) (round x)
+  #-}
+
+{-# RULES
+"properFraction/Double->(Int32,Double)"
+    forall x. properFraction (x :: Double) =
+                      case properFraction x of {
+                        (n, y) -> ((fromIntegral :: Int -> Int32) n, y) }
+"truncate/Double->Int32"
+    forall x. truncate (x :: Double) = (fromIntegral :: Int -> Int32) (truncate x)
+"floor/Double->Int32"
+    forall x. floor    (x :: Double) = (fromIntegral :: Int -> Int32) (floor x)
+"ceiling/Double->Int32"
+    forall x. ceiling  (x :: Double) = (fromIntegral :: Int -> Int32) (ceiling x)
+"round/Double->Int32"
+    forall x. round    (x :: Double) = (fromIntegral :: Int -> Int32) (round x)
+  #-}
+
+#endif
 
 instance Real Int32 where
     toRational x = toInteger x % 1
@@ -540,9 +616,9 @@ instance Bounded Int32 where
     maxBound =  0x7FFFFFFF
 
 instance Ix Int32 where
-    range (m,n)              = [m..n]
-    unsafeIndex b@(m,_) i    = fromIntegral i - fromIntegral m
-    inRange (m,n) i          = m <= i && i <= n
+    range (m,n)         = [m..n]
+    unsafeIndex (m,_) i = fromIntegral i - fromIntegral m
+    inRange (m,n) i     = m <= i && i <= n
 
 ------------------------------------------------------------------------
 -- type Int64
@@ -576,8 +652,7 @@ instance Num Int64 where
     signum x | x > 0       = 1
     signum 0               = 0
     signum _               = -1
-    fromInteger (S# i#)    = I64# (intToInt64# i#)
-    fromInteger (J# s# d#) = I64# (integerToInt64# s# d#)
+    fromInteger i          = I64# (integerToInt64 i)
 
 instance Enum Int64 where
     succ x
@@ -599,36 +674,31 @@ instance Enum Int64 where
 instance Integral Int64 where
     quot    x@(I64# x#) y@(I64# y#)
         | y == 0                     = divZeroError
-        | x == minBound && y == (-1) = overflowError
+        | y == (-1) && x == minBound = overflowError -- Note [Order of tests]
         | otherwise                  = I64# (x# `quotInt64#` y#)
     rem     x@(I64# x#) y@(I64# y#)
         | y == 0                     = divZeroError
-        | x == minBound && y == (-1) = overflowError
+        | y == (-1) && x == minBound = overflowError -- Note [Order of tests]
         | otherwise                  = I64# (x# `remInt64#` y#)
     div     x@(I64# x#) y@(I64# y#)
         | y == 0                     = divZeroError
-        | x == minBound && y == (-1) = overflowError
+        | y == (-1) && x == minBound = overflowError -- Note [Order of tests]
         | otherwise                  = I64# (x# `divInt64#` y#)
     mod     x@(I64# x#) y@(I64# y#)
         | y == 0                     = divZeroError
-        | x == minBound && y == (-1) = overflowError
+        | y == (-1) && x == minBound = overflowError -- Note [Order of tests]
         | otherwise                  = I64# (x# `modInt64#` y#)
     quotRem x@(I64# x#) y@(I64# y#)
         | y == 0                     = divZeroError
-        | x == minBound && y == (-1) = overflowError
+        | y == (-1) && x == minBound = overflowError -- Note [Order of tests]
         | otherwise                  = (I64# (x# `quotInt64#` y#),
                                         I64# (x# `remInt64#` y#))
     divMod  x@(I64# x#) y@(I64# y#)
         | y == 0                     = divZeroError
-        | x == minBound && y == (-1) = overflowError
+        | y == (-1) && x == minBound = overflowError -- Note [Order of tests]
         | 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
+    toInteger (I64# x)               = int64ToInteger x
 
 
 divInt64#, modInt64# :: Int64# -> Int64# -> Int64#
@@ -644,7 +714,7 @@ x# `modInt64#` y#
         = if r# `neInt64#` intToInt64# 0# then r# `plusInt64#` y# else intToInt64# 0#
     | otherwise = r#
     where
-    r# = x# `remInt64#` y#
+    !r# = x# `remInt64#` y#
 
 instance Read Int64 where
     readsPrec p s = [(fromInteger x, r) | (x, r) <- readsPrec p s]
@@ -666,12 +736,11 @@ instance Bits Int64 where
         = I64# (word64ToInt64# ((x'# `uncheckedShiftL64#` i'#) `or64#`
                                 (x'# `uncheckedShiftRL64#` (64# -# i'#))))
         where
-        x'# = int64ToWord64# x#
-        i'# = word2Int# (int2Word# i# `and#` int2Word# 63#)
+        !x'# = int64ToWord64# x#
+        !i'# = word2Int# (int2Word# i# `and#` int2Word# 63#)
     bitSize  _                 = 64
     isSigned _                 = True
 
-
 -- give the 64-bit shift operations the same treatment as the 32-bit
 -- ones (see GHC.Base), namely we wrap them in tests to catch the
 -- cases when we're shifting more than 64 bits to avoid unspecified
@@ -687,35 +756,6 @@ a `iShiftRA64#` b | b >=# 64# = if a `ltInt64#` (intToInt64# 0#)
                                        else intToInt64# 0#
                  | otherwise = a `uncheckedIShiftRA64#` b
 
-
-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#)
 "fromIntegral/Word->Int64"   fromIntegral = \(W#   x#) -> I64# (word64ToInt64# (wordToWord64# x#))
@@ -726,7 +766,9 @@ foreign import ccall unsafe "hs_integerToInt64"  integerToInt64#  :: Int# -> Byt
 "fromIntegral/Int64->Int64"  fromIntegral = id :: Int64 -> Int64
   #-}
 
-#else 
+-- No RULES for RealFrac methods if Int is smaller than Int64, we can't
+-- go through Int and whether going through Integer is faster is uncertain.
+#else
 
 -- Int64 is represented in the same way as Int.
 -- Operations may assume and must ensure that it holds only values
@@ -748,8 +790,7 @@ instance Num Int64 where
     signum x | x > 0       = 1
     signum 0               = 0
     signum _               = -1
-    fromInteger (S# i#)    = I64# i#
-    fromInteger (J# s# d#) = I64# (integer2Int# s# d#)
+    fromInteger i          = I64# (toInt# i)
 
 instance Enum Int64 where
     succ x
@@ -766,29 +807,29 @@ instance Enum Int64 where
 instance Integral Int64 where
     quot    x@(I64# x#) y@(I64# y#)
         | y == 0                     = divZeroError
-        | x == minBound && y == (-1) = overflowError
+        | y == (-1) && x == minBound = overflowError -- Note [Order of tests]
         | otherwise                  = I64# (x# `quotInt#` y#)
     rem     x@(I64# x#) y@(I64# y#)
         | y == 0                     = divZeroError
-        | x == minBound && y == (-1) = overflowError
+        | y == (-1) && x == minBound = overflowError -- Note [Order of tests]
         | otherwise                  = I64# (x# `remInt#` y#)
     div     x@(I64# x#) y@(I64# y#)
         | y == 0                     = divZeroError
-        | x == minBound && y == (-1) = overflowError
+        | y == (-1) && x == minBound = overflowError -- Note [Order of tests]
         | otherwise                  = I64# (x# `divInt#` y#)
     mod     x@(I64# x#) y@(I64# y#)
         | y == 0                     = divZeroError
-        | x == minBound && y == (-1) = overflowError
+        | y == (-1) && x == minBound = overflowError -- Note [Order of tests]
         | otherwise                  = I64# (x# `modInt#` y#)
     quotRem x@(I64# x#) y@(I64# y#)
         | y == 0                     = divZeroError
-        | x == minBound && y == (-1) = overflowError
+        | y == (-1) && x == minBound = overflowError -- Note [Order of tests]
         | otherwise                  = (I64# (x# `quotInt#` y#), I64# (x# `remInt#` y#))
     divMod  x@(I64# x#) y@(I64# y#)
         | y == 0                     = divZeroError
-        | x == minBound && y == (-1) = overflowError
+        | y == (-1) && x == minBound = overflowError -- Note [Order of tests]
         | otherwise                  = (I64# (x# `divInt#` y#), I64# (x# `modInt#` y#))
-    toInteger (I64# x#)              = S# x#
+    toInteger (I64# x#)              = smallInteger x#
 
 instance Read Int64 where
     readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
@@ -810,8 +851,8 @@ instance Bits Int64 where
         = I64# (word2Int# ((x'# `uncheckedShiftL#` i'#) `or#`
                            (x'# `uncheckedShiftRL#` (64# -# i'#))))
         where
-        x'# = int2Word# x#
-        i'# = word2Int# (int2Word# i# `and#` int2Word# 63#)
+        !x'# = int2Word# x#
+        !i'# = word2Int# (int2Word# i# `and#` int2Word# 63#)
     bitSize  _                 = 64
     isSigned _                 = True
 
@@ -820,6 +861,41 @@ instance Bits Int64 where
 "fromIntegral/Int64->a" fromIntegral = \(I64# x#) -> fromIntegral (I# x#)
   #-}
 
+{-# RULES
+"properFraction/Float->(Int64,Float)"
+    forall x. properFraction (x :: Float) =
+                      case properFraction x of {
+                        (n, y) -> ((fromIntegral :: Int -> Int64) n, y) }
+"truncate/Float->Int64"
+    forall x. truncate (x :: Float) = (fromIntegral :: Int -> Int64) (truncate x)
+"floor/Float->Int64"
+    forall x. floor    (x :: Float) = (fromIntegral :: Int -> Int64) (floor x)
+"ceiling/Float->Int64"
+    forall x. ceiling  (x :: Float) = (fromIntegral :: Int -> Int64) (ceiling x)
+"round/Float->Int64"
+    forall x. round    (x :: Float) = (fromIntegral :: Int -> Int64) (round x)
+  #-}
+
+{-# RULES
+"properFraction/Double->(Int64,Double)"
+    forall x. properFraction (x :: Double) =
+                      case properFraction x of {
+                        (n, y) -> ((fromIntegral :: Int -> Int64) n, y) }
+"truncate/Double->Int64"
+    forall x. truncate (x :: Double) = (fromIntegral :: Int -> Int64) (truncate x)
+"floor/Double->Int64"
+    forall x. floor    (x :: Double) = (fromIntegral :: Int -> Int64) (floor x)
+"ceiling/Double->Int64"
+    forall x. ceiling  (x :: Double) = (fromIntegral :: Int -> Int64) (ceiling x)
+"round/Double->Int64"
+    forall x. round    (x :: Double) = (fromIntegral :: Int -> Int64) (round x)
+  #-}
+
+uncheckedIShiftL64# :: Int# -> Int# -> Int#
+uncheckedIShiftL64#  = uncheckedIShiftL#
+
+uncheckedIShiftRA64# :: Int# -> Int# -> Int#
+uncheckedIShiftRA64# = uncheckedIShiftRA#
 #endif
 
 instance Real Int64 where
@@ -830,6 +906,131 @@ instance Bounded Int64 where
     maxBound =  0x7FFFFFFFFFFFFFFF
 
 instance Ix Int64 where
-    range (m,n)              = [m..n]
-    unsafeIndex b@(m,_) i    = fromIntegral i - fromIntegral m
-    inRange (m,n) i          = m <= i && i <= n
+    range (m,n)         = [m..n]
+    unsafeIndex (m,_) i = fromIntegral i - fromIntegral m
+    inRange (m,n) i     = m <= i && i <= n
+
+
+{-
+Note [Order of tests]
+
+Suppose we had a definition like:
+
+    quot x y
+     | y == 0                     = divZeroError
+     | x == minBound && y == (-1) = overflowError
+     | otherwise                  = x `primQuot` y
+
+Note in particular that the
+    x == minBound
+test comes before the
+    y == (-1)
+test.
+
+this expands to something like:
+
+    case y of
+    0 -> divZeroError
+    _ -> case x of
+         -9223372036854775808 ->
+             case y of
+             -1 -> overflowError
+             _ -> x `primQuot` y
+         _ -> x `primQuot` y
+
+Now if we have the call (x `quot` 2), and quot gets inlined, then we get:
+
+    case 2 of
+    0 -> divZeroError
+    _ -> case x of
+         -9223372036854775808 ->
+             case 2 of
+             -1 -> overflowError
+             _ -> x `primQuot` 2
+         _ -> x `primQuot` 2
+
+which simplifies to:
+
+    case x of
+    -9223372036854775808 -> x `primQuot` 2
+    _                    -> x `primQuot` 2
+
+Now we have a case with two identical branches, which would be
+eliminated (assuming it doesn't affect strictness, which it doesn't in
+this case), leaving the desired:
+
+    x `primQuot` 2
+
+except in the minBound branch we know what x is, and GHC cleverly does
+the division at compile time, giving:
+
+    case x of
+    -9223372036854775808 -> -4611686018427387904
+    _                    -> x `primQuot` 2
+
+So instead we use a definition like:
+
+    quot x y
+     | y == 0                     = divZeroError
+     | y == (-1) && x == minBound = overflowError
+     | otherwise                  = x `primQuot` y
+
+which gives us:
+
+    case y of
+    0 -> divZeroError
+    -1 ->
+        case x of
+        -9223372036854775808 -> overflowError
+        _ -> x `primQuot` y
+    _ -> x `primQuot` y
+
+for which our call (x `quot` 2) expands to:
+
+    case 2 of
+    0 -> divZeroError
+    -1 ->
+        case x of
+        -9223372036854775808 -> overflowError
+        _ -> x `primQuot` 2
+    _ -> x `primQuot` 2
+
+which simplifies to:
+
+    x `primQuot` 2
+
+as required.
+
+
+
+But we now have the same problem with a constant numerator: the call
+(2 `quot` y) expands to
+
+    case y of
+    0 -> divZeroError
+    -1 ->
+        case 2 of
+        -9223372036854775808 -> overflowError
+        _ -> 2 `primQuot` y
+    _ -> 2 `primQuot` y
+
+which simplifies to:
+
+    case y of
+    0 -> divZeroError
+    -1 -> 2 `primQuot` y
+    _ -> 2 `primQuot` y
+
+which simplifies to:
+
+    case y of
+    0 -> divZeroError
+    -1 -> -2
+    _ -> 2 `primQuot` y
+
+
+However, constant denominators are more common than constant numerators,
+so the
+    y == (-1) && x == minBound
+order gives us better code in the common case.
+-}