Add tests from testsuite/tests/h98
[ghc-base.git] / GHC / Word.hs
index a56c2de..9d3e1a6 100644 (file)
@@ -1,5 +1,6 @@
-{-# OPTIONS_GHC -XNoImplicitPrelude #-}
+{-# LANGUAGE CPP, NoImplicitPrelude, BangPatterns, MagicHash #-}
 {-# OPTIONS_HADDOCK hide #-}
+
 -----------------------------------------------------------------------------
 -- |
 -- Module      :  GHC.Word
@@ -42,6 +43,7 @@ import GHC.Read
 import GHC.Arr
 import GHC.Show
 import GHC.Err
+import GHC.Float ()     -- for RealFrac methods
 
 ------------------------------------------------------------------------
 -- Helper functions
@@ -181,16 +183,16 @@ instance Bits Word where
     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#)
 "fromIntegral/Word->Word" fromIntegral = id :: Word -> Word
   #-}
 
+-- No RULES for RealFrac unfortunately.
+-- Going through Int isn't possible because Word's range is not
+-- included in Int's, going through Integer may or may not be slower.
+
 ------------------------------------------------------------------------
 -- type Word8
 ------------------------------------------------------------------------
@@ -285,10 +287,6 @@ 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
@@ -296,6 +294,36 @@ instance Bits Word8 where
 "fromIntegral/Word8->a"       fromIntegral = \(W8# x#) -> fromIntegral (W# x#)
   #-}
 
+{-# RULES
+"properFraction/Float->(Word8,Float)"
+    forall x. properFraction (x :: Float) =
+                      case properFraction x of {
+                        (n, y) -> ((fromIntegral :: Int -> Word8) n, y) }
+"truncate/Float->Word8"
+    forall x. truncate (x :: Float) = (fromIntegral :: Int -> Word8) (truncate x)
+"floor/Float->Word8"
+    forall x. floor    (x :: Float) = (fromIntegral :: Int -> Word8) (floor x)
+"ceiling/Float->Word8"
+    forall x. ceiling  (x :: Float) = (fromIntegral :: Int -> Word8) (ceiling x)
+"round/Float->Word8"
+    forall x. round    (x :: Float) = (fromIntegral :: Int -> Word8) (round x)
+  #-}
+
+{-# RULES
+"properFraction/Double->(Word8,Double)"
+    forall x. properFraction (x :: Double) =
+                      case properFraction x of {
+                        (n, y) -> ((fromIntegral :: Int -> Word8) n, y) }
+"truncate/Double->Word8"
+    forall x. truncate (x :: Double) = (fromIntegral :: Int -> Word8) (truncate x)
+"floor/Double->Word8"
+    forall x. floor    (x :: Double) = (fromIntegral :: Int -> Word8) (floor x)
+"ceiling/Double->Word8"
+    forall x. ceiling  (x :: Double) = (fromIntegral :: Int -> Word8) (ceiling x)
+"round/Double->Word8"
+    forall x. round    (x :: Double) = (fromIntegral :: Int -> Word8) (round x)
+  #-}
+
 ------------------------------------------------------------------------
 -- type Word16
 ------------------------------------------------------------------------
@@ -390,10 +418,6 @@ 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
@@ -402,6 +426,36 @@ instance Bits Word16 where
 "fromIntegral/Word16->a"       fromIntegral = \(W16# x#) -> fromIntegral (W# x#)
   #-}
 
+{-# RULES
+"properFraction/Float->(Word16,Float)"
+    forall x. properFraction (x :: Float) =
+                      case properFraction x of {
+                        (n, y) -> ((fromIntegral :: Int -> Word16) n, y) }
+"truncate/Float->Word16"
+    forall x. truncate (x :: Float) = (fromIntegral :: Int -> Word16) (truncate x)
+"floor/Float->Word16"
+    forall x. floor    (x :: Float) = (fromIntegral :: Int -> Word16) (floor x)
+"ceiling/Float->Word16"
+    forall x. ceiling  (x :: Float) = (fromIntegral :: Int -> Word16) (ceiling x)
+"round/Float->Word16"
+    forall x. round    (x :: Float) = (fromIntegral :: Int -> Word16) (round x)
+  #-}
+
+{-# RULES
+"properFraction/Double->(Word16,Double)"
+    forall x. properFraction (x :: Double) =
+                      case properFraction x of {
+                        (n, y) -> ((fromIntegral :: Int -> Word16) n, y) }
+"truncate/Double->Word16"
+    forall x. truncate (x :: Double) = (fromIntegral :: Int -> Word16) (truncate x)
+"floor/Double->Word16"
+    forall x. floor    (x :: Double) = (fromIntegral :: Int -> Word16) (floor x)
+"ceiling/Double->Word16"
+    forall x. ceiling  (x :: Double) = (fromIntegral :: Int -> Word16) (ceiling x)
+"round/Double->Word16"
+    forall x. round    (x :: Double) = (fromIntegral :: Int -> Word16) (round x)
+  #-}
+
 ------------------------------------------------------------------------
 -- type Word32
 ------------------------------------------------------------------------
@@ -493,10 +547,6 @@ 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/Int->Word32"    fromIntegral = \(I#   x#) -> W32# (int32ToWord32# (intToInt32# x#))
 "fromIntegral/Word->Word32"   fromIntegral = \(W#   x#) -> W32# (wordToWord32# x#)
@@ -511,6 +561,39 @@ instance Bits Word32 where
 #if WORD_SIZE_IN_BITS > 32
 -- Operations may assume and must ensure that it holds only values
 -- from its logical range.
+
+-- We can use rewrite rules for the RealFrac methods
+
+{-# RULES
+"properFraction/Float->(Word32,Float)"
+    forall x. properFraction (x :: Float) =
+                      case properFraction x of {
+                        (n, y) -> ((fromIntegral :: Int -> Word32) n, y) }
+"truncate/Float->Word32"
+    forall x. truncate (x :: Float) = (fromIntegral :: Int -> Word32) (truncate x)
+"floor/Float->Word32"
+    forall x. floor    (x :: Float) = (fromIntegral :: Int -> Word32) (floor x)
+"ceiling/Float->Word32"
+    forall x. ceiling  (x :: Float) = (fromIntegral :: Int -> Word32) (ceiling x)
+"round/Float->Word32"
+    forall x. round    (x :: Float) = (fromIntegral :: Int -> Word32) (round x)
+  #-}
+
+{-# RULES
+"properFraction/Double->(Word32,Double)"
+    forall x. properFraction (x :: Double) =
+                      case properFraction x of {
+                        (n, y) -> ((fromIntegral :: Int -> Word32) n, y) }
+"truncate/Double->Word32"
+    forall x. truncate (x :: Double) = (fromIntegral :: Int -> Word32) (truncate x)
+"floor/Double->Word32"
+    forall x. floor    (x :: Double) = (fromIntegral :: Int -> Word32) (floor x)
+"ceiling/Double->Word32"
+    forall x. ceiling  (x :: Double) = (fromIntegral :: Int -> Word32) (ceiling x)
+"round/Double->Word32"
+    forall x. round    (x :: Double) = (fromIntegral :: Int -> Word32) (round x)
+  #-}
+
 #endif
 
 data Word32 = W32# Word# deriving (Eq, Ord)
@@ -579,7 +662,7 @@ instance Integral Word32 where
         | i# >=# 0#                 = smallInteger i#
         | otherwise                 = wordToInteger x#
         where
-        i# = word2Int# x#
+        !i# = word2Int# x#
 #else
                                     = smallInteger (word2Int# x#)
 #endif
@@ -604,10 +687,6 @@ 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#
@@ -730,14 +809,10 @@ instance Bits Word64 where
         | otherwise  = W64# ((x# `uncheckedShiftL64#` i'#) `or64#`
                              (x# `uncheckedShiftRL64#` (64# -# i'#)))
         where
-        i'# = word2Int# (int2Word# i# `and#` int2Word# 63#)
+        !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)
-
 -- 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
@@ -842,10 +917,6 @@ 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#)