Hide standalone deriving clauses from haddock
[ghc-base.git] / GHC / Word.hs
index 4e35965..99b25ba 100644 (file)
@@ -1,4 +1,4 @@
-{-# OPTIONS_GHC -fno-implicit-prelude #-}
+{-# OPTIONS_GHC -XNoImplicitPrelude #-}
 {-# OPTIONS_HADDOCK hide #-}
 -----------------------------------------------------------------------------
 -- |
@@ -27,6 +27,13 @@ module GHC.Word (
 
 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
@@ -83,8 +90,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
@@ -128,8 +134,8 @@ instance Integral Word where
         | y /= 0                = (W# (x# `quotWord#` y#), W# (x# `remWord#` y#))
         | 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#
 
@@ -169,10 +175,14 @@ instance Bits Word where
         | 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#)
@@ -200,8 +210,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
@@ -240,7 +249,7 @@ instance Integral Word8 where
     divMod  x@(W8# x#) y@(W8# y#)
         | y /= 0                  = (W8# (x# `quotWord#` y#), W8# (x# `remWord#` y#))
         | otherwise               = divZeroError
-    toInteger (W8# x#)            = S# (word2Int# x#)
+    toInteger (W8# x#)            = smallInteger (word2Int# x#)
 
 instance Bounded Word8 where
     minBound = 0
@@ -273,6 +282,10 @@ instance Bits Word8 where
     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
@@ -301,8 +314,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
@@ -341,7 +353,7 @@ instance Integral Word16 where
     divMod  x@(W16# x#) y@(W16# y#)
         | y /= 0                    = (W16# (x# `quotWord#` y#), W16# (x# `remWord#` y#))
         | otherwise                 = divZeroError
-    toInteger (W16# x#)             = S# (word2Int# x#)
+    toInteger (W16# x#)             = smallInteger (word2Int# x#)
 
 instance Bounded Word16 where
     minBound = 0
@@ -374,6 +386,10 @@ instance Bits Word16 where
     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
@@ -473,29 +489,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#))
@@ -524,8 +520,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
@@ -577,12 +572,12 @@ instance Integral Word32 where
         | 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
@@ -604,6 +599,10 @@ instance Bits Word32 where
     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#
@@ -669,8 +668,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
@@ -710,9 +708,7 @@ instance Integral Word64 where
     divMod  x@(W64# x#) y@(W64# y#)
         | y /= 0                    = (W64# (x# `quotWord64#` y#), W64# (x# `remWord64#` y#))
         | otherwise                 = divZeroError
-    toInteger x@(W64# x#)
-        | x <= 0x7FFFFFFF           = S# (word2Int# (word64ToWord# x#))
-        | otherwise                 = case word64ToInteger# x# of (# s, d #) -> J# s d
+    toInteger (W64# x#)             = word64ToInteger x#
 
 instance Bits Word64 where
     {-# INLINE shift #-}
@@ -733,6 +729,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
@@ -741,38 +741,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 "hs_eqWord64"      eqWord64#      :: Word64# -> Word64# -> Bool
-foreign import ccall unsafe "hs_neWord64"      neWord64#      :: Word64# -> Word64# -> Bool
-foreign import ccall unsafe "hs_ltWord64"      ltWord64#      :: Word64# -> Word64# -> Bool
-foreign import ccall unsafe "hs_leWord64"      leWord64#      :: Word64# -> Word64# -> Bool
-foreign import ccall unsafe "hs_gtWord64"      gtWord64#      :: Word64# -> Word64# -> Bool
-foreign import ccall unsafe "hs_geWord64"      geWord64#      :: Word64# -> Word64# -> Bool
-foreign import ccall unsafe "hs_int64ToWord64" int64ToWord64# :: Int64# -> Word64#
-foreign import ccall unsafe "hs_word64ToInt64" word64ToInt64# :: Word64# -> Int64#
-foreign import ccall unsafe "hs_intToInt64"    intToInt64#    :: Int# -> Int64#
-foreign import ccall unsafe "hs_wordToWord64"  wordToWord64#  :: Word# -> Word64#
-foreign import ccall unsafe "hs_word64ToWord"  word64ToWord#  :: Word64# -> Word#
-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_quotWord64"    quotWord64#    :: Word64# -> Word64# -> Word64#
-foreign import ccall unsafe "hs_remWord64"     remWord64#     :: Word64# -> Word64# -> Word64#
-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_integerToWord64" integerToWord64# :: Int# -> ByteArray# -> Word64#
-
+                 | otherwise  = a `uncheckedShiftRL64#` b
 
 {-# RULES
 "fromIntegral/Int->Word64"    fromIntegral = \(I#   x#) -> W64# (int64ToWord64# (intToInt64# x#))
@@ -799,8 +771,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
@@ -841,8 +812,8 @@ instance Integral Word64 where
         | y /= 0                    = (W64# (x# `quotWord#` y#), W64# (x# `remWord#` y#))
         | 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#
 
@@ -865,6 +836,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)
+
 {-# RULES
 "fromIntegral/a->Word64" fromIntegral = \x -> case fromIntegral x of W# x# -> W64# x#
 "fromIntegral/Word64->a" fromIntegral = \(W64# x#) -> fromIntegral (W# x#)