Import GHC.Err so we see bottoming functions properly
[ghc-base.git] / GHC / Word.hs
index 1850161..8d63e11 100644 (file)
@@ -1,4 +1,5 @@
-{-# OPTIONS -fno-implicit-prelude #-}
+{-# OPTIONS_GHC -XNoImplicitPrelude #-}
+{-# OPTIONS_HADDOCK hide #-}
 -----------------------------------------------------------------------------
 -- |
 -- Module      :  GHC.Word
 
 #include "MachDeps.h"
 
+-- #hide
 module GHC.Word (
     Word(..), Word8(..), Word16(..), Word32(..), Word64(..),
-    divZeroError, toEnumError, fromEnumError, succError, predError)
-    where
+    toEnumError, fromEnumError, succError, predError,
+    uncheckedShiftL64#,
+    uncheckedShiftRL64#
+    ) where
 
 import Data.Bits
 
+#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
@@ -30,16 +41,12 @@ import GHC.Real
 import GHC.Read
 import GHC.Arr
 import GHC.Show
+import GHC.Err
 
 ------------------------------------------------------------------------
 -- Helper functions
 ------------------------------------------------------------------------
 
-{-# NOINLINE divZeroError #-}
-divZeroError :: (Show a) => String -> a -> b
-divZeroError meth x =
-    error $ "Integral." ++ meth ++ ": divide by 0 (" ++ show x ++ " / 0)"
-
 {-# NOINLINE toEnumError #-}
 toEnumError :: (Show a) => String -> Int -> (a,a) -> b
 toEnumError inst_ty i bnds =
@@ -70,13 +77,9 @@ predError inst_ty =
 -- type Word
 ------------------------------------------------------------------------
 
--- A Word is an unsigned integral type, with the same size as Int.
-
+-- |A 'Word' is an unsigned integral type, with the same size as 'Int'.
 data Word = W# Word# deriving (Eq, Ord)
 
-instance CCallable Word
-instance CReturnable Word
-
 instance Show Word where
     showsPrec p x = showsPrec p (toInteger x)
 
@@ -88,8 +91,7 @@ instance Num Word where
     abs x                  = x
     signum 0               = 0
     signum _               = 1
-    fromInteger (S# i#)    = W# (int2Word# i#)
-    fromInteger (J# s# d#) = W# (integer2Word# s# d#)
+    fromInteger i          = W# (integerToWord i)
 
 instance Real Word where
     toRational x = toInteger x % 1
@@ -114,50 +116,54 @@ instance Enum Word where
     enumFromThenTo      = integralEnumFromThenTo
 
 instance Integral Word where
-    quot    x@(W# x#) y@(W# y#)
+    quot    (W# x#) y@(W# y#)
         | y /= 0                = W# (x# `quotWord#` y#)
-        | otherwise             = divZeroError "quot{Word}" x
-    rem     x@(W# x#) y@(W# y#)
+        | otherwise             = divZeroError
+    rem     (W# x#) y@(W# y#)
         | y /= 0                = W# (x# `remWord#` y#)
-        | otherwise             = divZeroError "rem{Word}" x
-    div     x@(W# x#) y@(W# y#)
+        | otherwise             = divZeroError
+    div     (W# x#) y@(W# y#)
         | y /= 0                = W# (x# `quotWord#` y#)
-        | otherwise             = divZeroError "div{Word}" x
-    mod     x@(W# x#) y@(W# y#)
+        | otherwise             = divZeroError
+    mod     (W# x#) y@(W# y#)
         | y /= 0                = W# (x# `remWord#` y#)
-        | otherwise             = divZeroError "mod{Word}" x
-    quotRem x@(W# x#) y@(W# y#)
+        | otherwise             = divZeroError
+    quotRem (W# x#) y@(W# y#)
         | y /= 0                = (W# (x# `quotWord#` y#), W# (x# `remWord#` y#))
-        | otherwise             = divZeroError "quotRem{Word}" x
-    divMod  x@(W# x#) y@(W# y#)
+        | otherwise             = divZeroError
+    divMod  (W# x#) y@(W# y#)
         | y /= 0                = (W# (x# `quotWord#` y#), W# (x# `remWord#` y#))
-        | otherwise             = divZeroError "divMod{Word}" x
+        | otherwise             = divZeroError
     toInteger (W# x#)
-        | i# >=# 0#             = S# i#
-        | otherwise             = case word2Integer# x# of (# s, d #) -> J# s d
+        | i# >=# 0#             = smallInteger i#
+        | otherwise             = wordToInteger x#
         where
         i# = word2Int# x#
 
 instance Bounded Word where
     minBound = 0
+
+    -- use unboxed literals for maxBound, because GHC doesn't optimise
+    -- (fromInteger 0xffffffff :: Word).
 #if WORD_SIZE_IN_BITS == 31
-    maxBound = 0x7FFFFFFF
+    maxBound = W# (int2Word# 0x7FFFFFFF#)
 #elif WORD_SIZE_IN_BITS == 32
-    maxBound = 0xFFFFFFFF
+    maxBound = W# (int2Word# 0xFFFFFFFF#)
 #else
-    maxBound = 0xFFFFFFFFFFFFFFFF
+    maxBound = W# (int2Word# 0xFFFFFFFFFFFFFFFF#)
 #endif
 
 instance Ix Word where
-    range (m,n)              = [m..n]
-    unsafeIndex b@(m,_) i    = fromIntegral (i - m)
-    inRange (m,n) i          = m <= i && i <= n
-    unsafeRangeSize b@(_l,h) = unsafeIndex b h + 1
+    range (m,n)         = [m..n]
+    unsafeIndex (m,_) i = fromIntegral (i - m)
+    inRange (m,n) i     = m <= i && i <= n
 
 instance Read Word where
     readsPrec p s = [(fromInteger x, r) | (x, r) <- readsPrec p s]
 
 instance Bits Word where
+    {-# INLINE shift #-}
+
     (W# x#) .&.   (W# y#)    = W# (x# `and#` y#)
     (W# x#) .|.   (W# y#)    = W# (x# `or#`  y#)
     (W# x#) `xor` (W# y#)    = W# (x# `xor#` y#)
@@ -167,13 +173,17 @@ instance Bits Word where
         | otherwise          = W# (x# `shiftRL#` negateInt# i#)
     (W# x#) `rotate` (I# i#)
         | i'# ==# 0# = W# x#
-        | otherwise  = W# ((x# `shiftL#` i'#) `or#` (x# `shiftRL#` (wsib -# i'#)))
+        | otherwise  = W# ((x# `uncheckedShiftL#` i'#) `or#` (x# `uncheckedShiftRL#` (wsib -# i'#)))
         where
         i'# = word2Int# (int2Word# i# `and#` int2Word# (wsib -# 1#))
-       wsib = WORD_SIZE_IN_BITS#  {- work around preprocessor problem (??) -}
+        wsib = WORD_SIZE_IN_BITS#  {- work around preprocessor problem (??) -}
     bitSize  _               = WORD_SIZE_IN_BITS
     isSigned _               = False
 
+    {-# INLINE shiftR #-}
+    -- same as the default definition, but we want it inlined (#2376)
+    x `shiftR`  i = x `shift`  (-i)
+
 {-# RULES
 "fromIntegral/Int->Word"  fromIntegral = \(I# x#) -> W# (int2Word# x#)
 "fromIntegral/Word->Int"  fromIntegral = \(W# x#) -> I# (word2Int# x#)
@@ -188,9 +198,7 @@ instance Bits Word where
 -- and must ensure that it holds only values from its logical range.
 
 data Word8 = W8# Word# deriving (Eq, Ord)
-
-instance CCallable Word8
-instance CReturnable Word8
+-- ^ 8-bit unsigned integer type
 
 instance Show Word8 where
     showsPrec p x = showsPrec p (fromIntegral x :: Int)
@@ -203,8 +211,7 @@ instance Num Word8 where
     abs x                  = x
     signum 0               = 0
     signum _               = 1
-    fromInteger (S# i#)    = W8# (narrow8Word# (int2Word# i#))
-    fromInteger (J# s# d#) = W8# (narrow8Word# (integer2Word# s# d#))
+    fromInteger i          = W8# (narrow8Word# (integerToWord i))
 
 instance Real Word8 where
     toRational x = toInteger x % 1
@@ -225,40 +232,41 @@ instance Enum Word8 where
     enumFromThen        = boundedEnumFromThen
 
 instance Integral Word8 where
-    quot    x@(W8# x#) y@(W8# y#)
+    quot    (W8# x#) y@(W8# y#)
         | y /= 0                  = W8# (x# `quotWord#` y#)
-        | otherwise               = divZeroError "quot{Word8}" x
-    rem     x@(W8# x#) y@(W8# y#)
+        | otherwise               = divZeroError
+    rem     (W8# x#) y@(W8# y#)
         | y /= 0                  = W8# (x# `remWord#` y#)
-        | otherwise               = divZeroError "rem{Word8}" x
-    div     x@(W8# x#) y@(W8# y#)
+        | otherwise               = divZeroError
+    div     (W8# x#) y@(W8# y#)
         | y /= 0                  = W8# (x# `quotWord#` y#)
-        | otherwise               = divZeroError "div{Word8}" x
-    mod     x@(W8# x#) y@(W8# y#)
+        | otherwise               = divZeroError
+    mod     (W8# x#) y@(W8# y#)
         | y /= 0                  = W8# (x# `remWord#` y#)
-        | otherwise               = divZeroError "mod{Word8}" x
-    quotRem x@(W8# x#) y@(W8# y#)
+        | otherwise               = divZeroError
+    quotRem (W8# x#) y@(W8# y#)
         | y /= 0                  = (W8# (x# `quotWord#` y#), W8# (x# `remWord#` y#))
-        | otherwise               = divZeroError "quotRem{Word8}" x
-    divMod  x@(W8# x#) y@(W8# y#)
+        | otherwise               = divZeroError
+    divMod  (W8# x#) y@(W8# y#)
         | y /= 0                  = (W8# (x# `quotWord#` y#), W8# (x# `remWord#` y#))
-        | otherwise               = divZeroError "quotRem{Word8}" x
-    toInteger (W8# x#)            = S# (word2Int# x#)
+        | otherwise               = divZeroError
+    toInteger (W8# x#)            = smallInteger (word2Int# x#)
 
 instance Bounded Word8 where
     minBound = 0
     maxBound = 0xFF
 
 instance Ix Word8 where
-    range (m,n)              = [m..n]
-    unsafeIndex b@(m,_) i    = fromIntegral (i - m)
-    inRange (m,n) i          = m <= i && i <= n
-    unsafeRangeSize b@(_l,h) = unsafeIndex b h + 1
+    range (m,n)         = [m..n]
+    unsafeIndex (m,_) i = fromIntegral (i - m)
+    inRange (m,n) i     = m <= i && i <= n
 
 instance Read Word8 where
     readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
 
 instance Bits Word8 where
+    {-# INLINE shift #-}
+
     (W8# x#) .&.   (W8# y#)   = W8# (x# `and#` y#)
     (W8# x#) .|.   (W8# y#)   = W8# (x# `or#`  y#)
     (W8# x#) `xor` (W8# y#)   = W8# (x# `xor#` y#)
@@ -268,13 +276,17 @@ instance Bits Word8 where
         | otherwise           = W8# (x# `shiftRL#` negateInt# i#)
     (W8# x#) `rotate` (I# i#)
         | i'# ==# 0# = W8# x#
-        | otherwise  = W8# (narrow8Word# ((x# `shiftL#` i'#) `or#`
-                                          (x# `shiftRL#` (8# -# i'#))))
+        | otherwise  = W8# (narrow8Word# ((x# `uncheckedShiftL#` i'#) `or#`
+                                          (x# `uncheckedShiftRL#` (8# -# i'#))))
         where
         i'# = word2Int# (int2Word# i# `and#` int2Word# 7#)
     bitSize  _                = 8
     isSigned _                = False
 
+    {-# INLINE shiftR #-}
+    -- same as the default definition, but we want it inlined (#2376)
+    x `shiftR`  i = x `shift`  (-i)
+
 {-# RULES
 "fromIntegral/Word8->Word8"   fromIntegral = id :: Word8 -> Word8
 "fromIntegral/Word8->Integer" fromIntegral = toInteger :: Word8 -> Integer
@@ -290,9 +302,7 @@ instance Bits Word8 where
 -- and must ensure that it holds only values from its logical range.
 
 data Word16 = W16# Word# deriving (Eq, Ord)
-
-instance CCallable Word16
-instance CReturnable Word16
+-- ^ 16-bit unsigned integer type
 
 instance Show Word16 where
     showsPrec p x = showsPrec p (fromIntegral x :: Int)
@@ -305,8 +315,7 @@ instance Num Word16 where
     abs x                  = x
     signum 0               = 0
     signum _               = 1
-    fromInteger (S# i#)    = W16# (narrow16Word# (int2Word# i#))
-    fromInteger (J# s# d#) = W16# (narrow16Word# (integer2Word# s# d#))
+    fromInteger i          = W16# (narrow16Word# (integerToWord i))
 
 instance Real Word16 where
     toRational x = toInteger x % 1
@@ -327,40 +336,41 @@ instance Enum Word16 where
     enumFromThen        = boundedEnumFromThen
 
 instance Integral Word16 where
-    quot    x@(W16# x#) y@(W16# y#)
+    quot    (W16# x#) y@(W16# y#)
         | y /= 0                    = W16# (x# `quotWord#` y#)
-        | otherwise                 = divZeroError "quot{Word16}" x
-    rem     x@(W16# x#) y@(W16# y#)
+        | otherwise                 = divZeroError
+    rem     (W16# x#) y@(W16# y#)
         | y /= 0                    = W16# (x# `remWord#` y#)
-        | otherwise                 = divZeroError "rem{Word16}" x
-    div     x@(W16# x#) y@(W16# y#)
+        | otherwise                 = divZeroError
+    div     (W16# x#) y@(W16# y#)
         | y /= 0                    = W16# (x# `quotWord#` y#)
-        | otherwise                 = divZeroError "div{Word16}" x
-    mod     x@(W16# x#) y@(W16# y#)
+        | otherwise                 = divZeroError
+    mod     (W16# x#) y@(W16# y#)
         | y /= 0                    = W16# (x# `remWord#` y#)
-        | otherwise                 = divZeroError "mod{Word16}" x
-    quotRem x@(W16# x#) y@(W16# y#)
+        | otherwise                 = divZeroError
+    quotRem (W16# x#) y@(W16# y#)
         | y /= 0                    = (W16# (x# `quotWord#` y#), W16# (x# `remWord#` y#))
-        | otherwise                 = divZeroError "quotRem{Word16}" x
-    divMod  x@(W16# x#) y@(W16# y#)
+        | otherwise                 = divZeroError
+    divMod  (W16# x#) y@(W16# y#)
         | y /= 0                    = (W16# (x# `quotWord#` y#), W16# (x# `remWord#` y#))
-        | otherwise                 = divZeroError "quotRem{Word16}" x
-    toInteger (W16# x#)             = S# (word2Int# x#)
+        | otherwise                 = divZeroError
+    toInteger (W16# x#)             = smallInteger (word2Int# x#)
 
 instance Bounded Word16 where
     minBound = 0
     maxBound = 0xFFFF
 
 instance Ix Word16 where
-    range (m,n)              = [m..n]
-    unsafeIndex b@(m,_) i    = fromIntegral (i - m)
-    inRange (m,n) i          = m <= i && i <= n
-    unsafeRangeSize b@(_l,h) = unsafeIndex b h + 1
+    range (m,n)         = [m..n]
+    unsafeIndex (m,_) i = fromIntegral (i - m)
+    inRange (m,n) i     = m <= i && i <= n
 
 instance Read Word16 where
     readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
 
 instance Bits Word16 where
+    {-# INLINE shift #-}
+
     (W16# x#) .&.   (W16# y#)  = W16# (x# `and#` y#)
     (W16# x#) .|.   (W16# y#)  = W16# (x# `or#`  y#)
     (W16# x#) `xor` (W16# y#)  = W16# (x# `xor#` y#)
@@ -370,13 +380,17 @@ instance Bits Word16 where
         | otherwise            = W16# (x# `shiftRL#` negateInt# i#)
     (W16# x#) `rotate` (I# i#)
         | i'# ==# 0# = W16# x#
-        | otherwise  = W16# (narrow16Word# ((x# `shiftL#` i'#) `or#`
-                                            (x# `shiftRL#` (16# -# i'#))))
+        | otherwise  = W16# (narrow16Word# ((x# `uncheckedShiftL#` i'#) `or#`
+                                            (x# `uncheckedShiftRL#` (16# -# i'#))))
         where
         i'# = word2Int# (int2Word# i# `and#` int2Word# 15#)
     bitSize  _                = 16
     isSigned _                = False
 
+    {-# INLINE shiftR #-}
+    -- same as the default definition, but we want it inlined (#2376)
+    x `shiftR`  i = x `shift`  (-i)
+
 {-# RULES
 "fromIntegral/Word8->Word16"   fromIntegral = \(W8# x#) -> W16# x#
 "fromIntegral/Word16->Word16"  fromIntegral = id :: Word16 -> Word16
@@ -392,6 +406,7 @@ instance Bits Word16 where
 #if WORD_SIZE_IN_BITS < 32
 
 data Word32 = W32# Word32#
+-- ^ 32-bit unsigned integer type
 
 instance Eq Word32 where
     (W32# x#) == (W32# y#) = x# `eqWord32#` y#
@@ -436,27 +451,29 @@ instance Enum Word32 where
 instance Integral Word32 where
     quot    x@(W32# x#) y@(W32# y#)
         | y /= 0                    = W32# (x# `quotWord32#` y#)
-        | otherwise                 = divZeroError "quot{Word32}" x
+        | otherwise                 = divZeroError
     rem     x@(W32# x#) y@(W32# y#)
         | y /= 0                    = W32# (x# `remWord32#` y#)
-        | otherwise                 = divZeroError "rem{Word32}" x
+        | otherwise                 = divZeroError
     div     x@(W32# x#) y@(W32# y#)
         | y /= 0                    = W32# (x# `quotWord32#` y#)
-        | otherwise                 = divZeroError "div{Word32}" x
+        | otherwise                 = divZeroError
     mod     x@(W32# x#) y@(W32# y#)
         | y /= 0                    = W32# (x# `remWord32#` y#)
-        | otherwise                 = divZeroError "mod{Word32}" x
+        | otherwise                 = divZeroError
     quotRem x@(W32# x#) y@(W32# y#)
         | y /= 0                    = (W32# (x# `quotWord32#` y#), W32# (x# `remWord32#` y#))
-        | otherwise                 = divZeroError "quotRem{Word32}" x
+        | otherwise                 = divZeroError
     divMod  x@(W32# x#) y@(W32# y#)
         | y /= 0                    = (W32# (x# `quotWord32#` y#), W32# (x# `remWord32#` y#))
-        | otherwise                 = divZeroError "quotRem{Word32}" x
+        | otherwise                 = divZeroError
     toInteger x@(W32# x#)
         | x <= fromIntegral (maxBound::Int)  = S# (word2Int# (word32ToWord# x#))
         | otherwise                 = case word32ToInteger# x# of (# s, d #) -> J# s d
 
 instance Bits Word32 where
+    {-# INLINE shift #-}
+
     (W32# x#) .&.   (W32# y#)  = W32# (x# `and32#` y#)
     (W32# x#) .|.   (W32# y#)  = W32# (x# `or32#`  y#)
     (W32# x#) `xor` (W32# y#)  = W32# (x# `xor32#` y#)
@@ -473,29 +490,9 @@ instance Bits Word32 where
     bitSize  _                = 32
     isSigned _                = False
 
-foreign import unsafe "stg_eqWord32"      eqWord32#      :: Word32# -> Word32# -> Bool
-foreign import unsafe "stg_neWord32"      neWord32#      :: Word32# -> Word32# -> Bool
-foreign import unsafe "stg_ltWord32"      ltWord32#      :: Word32# -> Word32# -> Bool
-foreign import unsafe "stg_leWord32"      leWord32#      :: Word32# -> Word32# -> Bool
-foreign import unsafe "stg_gtWord32"      gtWord32#      :: Word32# -> Word32# -> Bool
-foreign import unsafe "stg_geWord32"      geWord32#      :: Word32# -> Word32# -> Bool
-foreign import unsafe "stg_int32ToWord32" int32ToWord32# :: Int32# -> Word32#
-foreign import unsafe "stg_word32ToInt32" word32ToInt32# :: Word32# -> Int32#
-foreign import unsafe "stg_intToInt32"    intToInt32#    :: Int# -> Int32#
-foreign import unsafe "stg_wordToWord32"  wordToWord32#  :: Word# -> Word32#
-foreign import unsafe "stg_word32ToWord"  word32ToWord#  :: Word32# -> Word#
-foreign import unsafe "stg_plusInt32"     plusInt32#     :: Int32# -> Int32# -> Int32#
-foreign import unsafe "stg_minusInt32"    minusInt32#    :: Int32# -> Int32# -> Int32#
-foreign import unsafe "stg_timesInt32"    timesInt32#    :: Int32# -> Int32# -> Int32#
-foreign import unsafe "stg_negateInt32"   negateInt32#   :: Int32# -> Int32#
-foreign import unsafe "stg_quotWord32"    quotWord32#    :: Word32# -> Word32# -> Word32#
-foreign import unsafe "stg_remWord32"     remWord32#     :: Word32# -> Word32# -> Word32#
-foreign import unsafe "stg_and32"         and32#         :: Word32# -> Word32# -> Word32#
-foreign import unsafe "stg_or32"          or32#          :: Word32# -> Word32# -> Word32#
-foreign import unsafe "stg_xor32"         xor32#         :: Word32# -> Word32# -> Word32#
-foreign import unsafe "stg_not32"         not32#         :: Word32# -> Word32#
-foreign import unsafe "stg_shiftL32"      shiftL32#      :: Word32# -> Int# -> Word32#
-foreign import unsafe "stg_shiftRL32"     shiftRL32#     :: Word32# -> Int# -> Word32#
+    {-# INLINE shiftR #-}
+    -- same as the default definition, but we want it inlined (#2376)
+    x `shiftR`  i = x `shift`  (-i)
 
 {-# RULES
 "fromIntegral/Int->Word32"    fromIntegral = \(I#   x#) -> W32# (int32ToWord32# (intToInt32# x#))
@@ -514,6 +511,7 @@ foreign import unsafe "stg_shiftRL32"     shiftRL32#     :: Word32# -> Int# -> W
 #endif
 
 data Word32 = W32# Word# deriving (Eq, Ord)
+-- ^ 32-bit unsigned integer type
 
 instance Num Word32 where
     (W32# x#) + (W32# y#)  = W32# (narrow32Word# (x# `plusWord#` y#))
@@ -523,8 +521,7 @@ instance Num Word32 where
     abs x                  = x
     signum 0               = 0
     signum _               = 1
-    fromInteger (S# i#)    = W32# (narrow32Word# (int2Word# i#))
-    fromInteger (J# s# d#) = W32# (narrow32Word# (integer2Word# s# d#))
+    fromInteger i          = W32# (narrow32Word# (integerToWord i))
 
 instance Enum Word32 where
     succ x
@@ -556,35 +553,37 @@ instance Enum Word32 where
 #endif
 
 instance Integral Word32 where
-    quot    x@(W32# x#) y@(W32# y#)
+    quot    (W32# x#) y@(W32# y#)
         | y /= 0                    = W32# (x# `quotWord#` y#)
-        | otherwise                 = divZeroError "quot{Word32}" x
-    rem     x@(W32# x#) y@(W32# y#)
+        | otherwise                 = divZeroError
+    rem     (W32# x#) y@(W32# y#)
         | y /= 0                    = W32# (x# `remWord#` y#)
-        | otherwise                 = divZeroError "rem{Word32}" x
-    div     x@(W32# x#) y@(W32# y#)
+        | otherwise                 = divZeroError
+    div     (W32# x#) y@(W32# y#)
         | y /= 0                    = W32# (x# `quotWord#` y#)
-        | otherwise                 = divZeroError "div{Word32}" x
-    mod     x@(W32# x#) y@(W32# y#)
+        | otherwise                 = divZeroError
+    mod     (W32# x#) y@(W32# y#)
         | y /= 0                    = W32# (x# `remWord#` y#)
-        | otherwise                 = divZeroError "mod{Word32}" x
-    quotRem x@(W32# x#) y@(W32# y#)
+        | otherwise                 = divZeroError
+    quotRem (W32# x#) y@(W32# y#)
         | y /= 0                    = (W32# (x# `quotWord#` y#), W32# (x# `remWord#` y#))
-        | otherwise                 = divZeroError "quotRem{Word32}" x
-    divMod  x@(W32# x#) y@(W32# y#)
+        | otherwise                 = divZeroError
+    divMod  (W32# x#) y@(W32# y#)
         | y /= 0                    = (W32# (x# `quotWord#` y#), W32# (x# `remWord#` y#))
-        | otherwise                 = divZeroError "quotRem{Word32}" x
+        | otherwise                 = divZeroError
     toInteger (W32# x#)
 #if WORD_SIZE_IN_BITS == 32
-        | i# >=# 0#                 = S# i#
-        | otherwise                 = case word2Integer# x# of (# s, d #) -> J# s d
+        | i# >=# 0#                 = smallInteger i#
+        | otherwise                 = wordToInteger x#
         where
         i# = word2Int# x#
 #else
-                                    = S# (word2Int# x#)
+                                    = smallInteger (word2Int# x#)
 #endif
 
 instance Bits Word32 where
+    {-# INLINE shift #-}
+
     (W32# x#) .&.   (W32# y#)  = W32# (x# `and#` y#)
     (W32# x#) .|.   (W32# y#)  = W32# (x# `or#`  y#)
     (W32# x#) `xor` (W32# y#)  = W32# (x# `xor#` y#)
@@ -594,13 +593,17 @@ instance Bits Word32 where
         | otherwise            = W32# (x# `shiftRL#` negateInt# i#)
     (W32# x#) `rotate` (I# i#)
         | i'# ==# 0# = W32# x#
-        | otherwise  = W32# (narrow32Word# ((x# `shiftL#` i'#) `or#`
-                                            (x# `shiftRL#` (32# -# i'#))))
+        | otherwise  = W32# (narrow32Word# ((x# `uncheckedShiftL#` i'#) `or#`
+                                            (x# `uncheckedShiftRL#` (32# -# i'#))))
         where
         i'# = word2Int# (int2Word# i# `and#` int2Word# 31#)
     bitSize  _                = 32
     isSigned _                = False
 
+    {-# INLINE shiftR #-}
+    -- same as the default definition, but we want it inlined (#2376)
+    x `shiftR`  i = x `shift`  (-i)
+
 {-# RULES
 "fromIntegral/Word8->Word32"   fromIntegral = \(W8# x#) -> W32# x#
 "fromIntegral/Word16->Word32"  fromIntegral = \(W16# x#) -> W32# x#
@@ -612,9 +615,6 @@ instance Bits Word32 where
 
 #endif
 
-instance CCallable Word32
-instance CReturnable Word32
-
 instance Show Word32 where
 #if WORD_SIZE_IN_BITS < 33
     showsPrec p x = showsPrec p (toInteger x)
@@ -631,10 +631,9 @@ instance Bounded Word32 where
     maxBound = 0xFFFFFFFF
 
 instance Ix Word32 where
-    range (m,n)              = [m..n]
-    unsafeIndex b@(m,_) i    = fromIntegral (i - m)
-    inRange (m,n) i          = m <= i && i <= n
-    unsafeRangeSize b@(_l,h) = unsafeIndex b h + 1
+    range (m,n)         = [m..n]
+    unsafeIndex (m,_) i = fromIntegral (i - m)
+    inRange (m,n) i     = m <= i && i <= n
 
 instance Read Word32 where  
 #if WORD_SIZE_IN_BITS < 33
@@ -650,6 +649,7 @@ instance Read Word32 where
 #if WORD_SIZE_IN_BITS < 64
 
 data Word64 = W64# Word64#
+-- ^ 64-bit unsigned integer type
 
 instance Eq Word64 where
     (W64# x#) == (W64# y#) = x# `eqWord64#` y#
@@ -669,8 +669,7 @@ instance Num Word64 where
     abs x                  = x
     signum 0               = 0
     signum _               = 1
-    fromInteger (S# i#)    = W64# (int64ToWord64# (intToInt64# i#))
-    fromInteger (J# s# d#) = W64# (integerToWord64# s# d#)
+    fromInteger i          = W64# (integerToWord64 i)
 
 instance Enum Word64 where
     succ x
@@ -692,29 +691,29 @@ instance Enum Word64 where
     enumFromThenTo      = integralEnumFromThenTo
 
 instance Integral Word64 where
-    quot    x@(W64# x#) y@(W64# y#)
+    quot    (W64# x#) y@(W64# y#)
         | y /= 0                    = W64# (x# `quotWord64#` y#)
-        | otherwise                 = divZeroError "quot{Word64}" x
-    rem     x@(W64# x#) y@(W64# y#)
+        | otherwise                 = divZeroError
+    rem     (W64# x#) y@(W64# y#)
         | y /= 0                    = W64# (x# `remWord64#` y#)
-        | otherwise                 = divZeroError "rem{Word64}" x
-    div     x@(W64# x#) y@(W64# y#)
+        | otherwise                 = divZeroError
+    div     (W64# x#) y@(W64# y#)
         | y /= 0                    = W64# (x# `quotWord64#` y#)
-        | otherwise                 = divZeroError "div{Word64}" x
-    mod     x@(W64# x#) y@(W64# y#)
+        | otherwise                 = divZeroError
+    mod     (W64# x#) y@(W64# y#)
         | y /= 0                    = W64# (x# `remWord64#` y#)
-        | otherwise                 = divZeroError "mod{Word64}" x
-    quotRem x@(W64# x#) y@(W64# y#)
+        | otherwise                 = divZeroError
+    quotRem (W64# x#) y@(W64# y#)
         | y /= 0                    = (W64# (x# `quotWord64#` y#), W64# (x# `remWord64#` y#))
-        | otherwise                 = divZeroError "quotRem{Word64}" x
-    divMod  x@(W64# x#) y@(W64# y#)
+        | otherwise                 = divZeroError
+    divMod  (W64# x#) y@(W64# y#)
         | y /= 0                    = (W64# (x# `quotWord64#` y#), W64# (x# `remWord64#` y#))
-        | otherwise                 = divZeroError "quotRem{Word64}" x
-    toInteger x@(W64# x#)
-        | x <= 0x7FFFFFFF           = S# (word2Int# (word64ToWord# x#))
-        | otherwise                 = case word64ToInteger# x# of (# s, d #) -> J# s d
+        | otherwise                 = divZeroError
+    toInteger (W64# x#)             = word64ToInteger x#
 
 instance Bits Word64 where
+    {-# INLINE shift #-}
+
     (W64# x#) .&.   (W64# y#)  = W64# (x# `and64#` y#)
     (W64# x#) .|.   (W64# y#)  = W64# (x# `or64#`  y#)
     (W64# x#) `xor` (W64# y#)  = W64# (x# `xor64#` y#)
@@ -731,6 +730,10 @@ instance Bits Word64 where
     bitSize  _                = 64
     isSigned _                = False
 
+    {-# INLINE shiftR #-}
+    -- same as the default definition, but we want it inlined (#2376)
+    x `shiftR`  i = x `shift`  (-i)
+
 -- 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
@@ -739,38 +742,10 @@ instance Bits Word64 where
 shiftL64#, shiftRL64# :: Word64# -> Int# -> Word64#
 
 a `shiftL64#` b  | b >=# 64#  = wordToWord64# (int2Word# 0#)
-                | otherwise  = a `uncheckedShiftL64#` b
+                 | otherwise  = a `uncheckedShiftL64#` b
 
 a `shiftRL64#` b | b >=# 64#  = wordToWord64# (int2Word# 0#)
-                | otherwise  = a `uncheckedShiftRL64#` b
-
-
-foreign import ccall unsafe "stg_eqWord64"      eqWord64#      :: Word64# -> Word64# -> Bool
-foreign import ccall unsafe "stg_neWord64"      neWord64#      :: Word64# -> Word64# -> Bool
-foreign import ccall unsafe "stg_ltWord64"      ltWord64#      :: Word64# -> Word64# -> Bool
-foreign import ccall unsafe "stg_leWord64"      leWord64#      :: Word64# -> Word64# -> Bool
-foreign import ccall unsafe "stg_gtWord64"      gtWord64#      :: Word64# -> Word64# -> Bool
-foreign import ccall unsafe "stg_geWord64"      geWord64#      :: Word64# -> Word64# -> Bool
-foreign import ccall unsafe "stg_int64ToWord64" int64ToWord64# :: Int64# -> Word64#
-foreign import ccall unsafe "stg_word64ToInt64" word64ToInt64# :: Word64# -> Int64#
-foreign import ccall unsafe "stg_intToInt64"    intToInt64#    :: Int# -> Int64#
-foreign import ccall unsafe "stg_wordToWord64"  wordToWord64#  :: Word# -> Word64#
-foreign import ccall unsafe "stg_word64ToWord"  word64ToWord#  :: Word64# -> Word#
-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_quotWord64"    quotWord64#    :: Word64# -> Word64# -> Word64#
-foreign import ccall unsafe "stg_remWord64"     remWord64#     :: Word64# -> Word64# -> Word64#
-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_integerToWord64" integerToWord64# :: Int# -> ByteArray# -> Word64#
-
+                 | otherwise  = a `uncheckedShiftRL64#` b
 
 {-# RULES
 "fromIntegral/Int->Word64"    fromIntegral = \(I#   x#) -> W64# (int64ToWord64# (intToInt64# x#))
@@ -787,6 +762,7 @@ foreign import ccall unsafe "stg_integerToWord64" integerToWord64# :: Int# -> By
 -- from its logical range.
 
 data Word64 = W64# Word# deriving (Eq, Ord)
+-- ^ 64-bit unsigned integer type
 
 instance Num Word64 where
     (W64# x#) + (W64# y#)  = W64# (x# `plusWord#` y#)
@@ -796,8 +772,7 @@ instance Num Word64 where
     abs x                  = x
     signum 0               = 0
     signum _               = 1
-    fromInteger (S# i#)    = W64# (int2Word# i#)
-    fromInteger (J# s# d#) = W64# (integer2Word# s# d#)
+    fromInteger i          = W64# (integerToWord i)
 
 instance Enum Word64 where
     succ x
@@ -819,31 +794,33 @@ instance Enum Word64 where
     enumFromThenTo      = integralEnumFromThenTo
 
 instance Integral Word64 where
-    quot    x@(W64# x#) y@(W64# y#)
+    quot    (W64# x#) y@(W64# y#)
         | y /= 0                    = W64# (x# `quotWord#` y#)
-        | otherwise                 = divZeroError "quot{Word64}" x
-    rem     x@(W64# x#) y@(W64# y#)
+        | otherwise                 = divZeroError
+    rem     (W64# x#) y@(W64# y#)
         | y /= 0                    = W64# (x# `remWord#` y#)
-        | otherwise                 = divZeroError "rem{Word64}" x
-    div     x@(W64# x#) y@(W64# y#)
+        | otherwise                 = divZeroError
+    div     (W64# x#) y@(W64# y#)
         | y /= 0                    = W64# (x# `quotWord#` y#)
-        | otherwise                 = divZeroError "div{Word64}" x
-    mod     x@(W64# x#) y@(W64# y#)
+        | otherwise                 = divZeroError
+    mod     (W64# x#) y@(W64# y#)
         | y /= 0                    = W64# (x# `remWord#` y#)
-        | otherwise                 = divZeroError "mod{Word64}" x
-    quotRem x@(W64# x#) y@(W64# y#)
+        | otherwise                 = divZeroError
+    quotRem (W64# x#) y@(W64# y#)
         | y /= 0                    = (W64# (x# `quotWord#` y#), W64# (x# `remWord#` y#))
-        | otherwise                 = divZeroError "quotRem{Word64}" x
-    divMod  x@(W64# x#) y@(W64# y#)
+        | otherwise                 = divZeroError
+    divMod  (W64# x#) y@(W64# y#)
         | y /= 0                    = (W64# (x# `quotWord#` y#), W64# (x# `remWord#` y#))
-        | otherwise                 = divZeroError "quotRem{Word64}" x
+        | otherwise                 = divZeroError
     toInteger (W64# x#)
-        | i# >=# 0#                 = S# i#
-        | otherwise                 = case word2Integer# x# of (# s, d #) -> J# s d
+        | i# >=# 0#                 = smallInteger i#
+        | otherwise                 = wordToInteger x#
         where
         i# = word2Int# x#
 
 instance Bits Word64 where
+    {-# INLINE shift #-}
+
     (W64# x#) .&.   (W64# y#)  = W64# (x# `and#` y#)
     (W64# x#) .|.   (W64# y#)  = W64# (x# `or#`  y#)
     (W64# x#) `xor` (W64# y#)  = W64# (x# `xor#` y#)
@@ -853,22 +830,29 @@ instance Bits Word64 where
         | otherwise            = W64# (x# `shiftRL#` negateInt# i#)
     (W64# x#) `rotate` (I# i#)
         | i'# ==# 0# = W64# x#
-        | otherwise  = W64# ((x# `shiftL#` i'#) `or#`
-                             (x# `shiftRL#` (64# -# i'#)))
+        | otherwise  = W64# ((x# `uncheckedShiftL#` i'#) `or#`
+                             (x# `uncheckedShiftRL#` (64# -# i'#)))
         where
         i'# = word2Int# (int2Word# i# `and#` int2Word# 63#)
     bitSize  _                = 64
     isSigned _                = False
 
+    {-# INLINE shiftR #-}
+    -- same as the default definition, but we want it inlined (#2376)
+    x `shiftR`  i = x `shift`  (-i)
+
 {-# RULES
 "fromIntegral/a->Word64" fromIntegral = \x -> case fromIntegral x of W# x# -> W64# x#
 "fromIntegral/Word64->a" fromIntegral = \(W64# x#) -> fromIntegral (W# x#)
   #-}
 
-#endif
+uncheckedShiftL64# :: Word# -> Int# -> Word#
+uncheckedShiftL64#  = uncheckedShiftL#
 
-instance CCallable Word64
-instance CReturnable Word64
+uncheckedShiftRL64# :: Word# -> Int# -> Word#
+uncheckedShiftRL64# = uncheckedShiftRL#
+
+#endif
 
 instance Show Word64 where
     showsPrec p x = showsPrec p (toInteger x)
@@ -881,10 +865,9 @@ instance Bounded Word64 where
     maxBound = 0xFFFFFFFFFFFFFFFF
 
 instance Ix Word64 where
-    range (m,n)              = [m..n]
-    unsafeIndex b@(m,_) i    = fromIntegral (i - m)
-    inRange (m,n) i          = m <= i && i <= n
-    unsafeRangeSize b@(_l,h) = unsafeIndex b h + 1
+    range (m,n)         = [m..n]
+    unsafeIndex (m,_) i = fromIntegral (i - m)
+    inRange (m,n) i     = m <= i && i <= n
 
 instance Read Word64 where
     readsPrec p s = [(fromInteger x, r) | (x, r) <- readsPrec p s]