[commit: ghc] master: Move the Enum Word instance into GHC.Enum (3436333)

git at git.haskell.org git at git.haskell.org
Thu Aug 28 11:12:00 UTC 2014


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/343633307f5a24c741b80bbbc952919d9947f56c/ghc

>---------------------------------------------------------------

commit 343633307f5a24c741b80bbbc952919d9947f56c
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Mon May 12 10:54:30 2014 +0100

    Move the Enum Word instance into GHC.Enum
    
    This just avoids an unnecessary orphan instance.
    All the other instances for "earlier" types are in GHC.Enum already.


>---------------------------------------------------------------

343633307f5a24c741b80bbbc952919d9947f56c
 libraries/base/GHC/Enum.lhs | 35 +++++++++++++++++++++++++++++++++++
 libraries/base/GHC/Real.lhs | 25 +------------------------
 2 files changed, 36 insertions(+), 24 deletions(-)

diff --git a/libraries/base/GHC/Enum.lhs b/libraries/base/GHC/Enum.lhs
index d94e2ec..a6dae7a 100644
--- a/libraries/base/GHC/Enum.lhs
+++ b/libraries/base/GHC/Enum.lhs
@@ -650,6 +650,41 @@ instance Bounded Word where
 #else
 #error Unhandled value for WORD_SIZE_IN_BITS
 #endif
+
+instance Enum Word where
+    succ x
+        | x /= maxBound = x + 1
+        | otherwise     = succError "Word"
+    pred x
+        | x /= minBound = x - 1
+        | otherwise     = predError "Word"
+    toEnum i@(I# i#)
+        | i >= 0        = W# (int2Word# i#)
+        | otherwise     = toEnumError "Word" i (minBound::Word, maxBound::Word)
+    fromEnum x@(W# x#)
+        | x <= maxIntWord = I# (word2Int# x#)
+        | otherwise       = fromEnumError "Word" x
+
+    enumFrom n             = map integerToWordX [wordToIntegerX n .. wordToIntegerX (maxBound :: Word)]
+    enumFromTo n1 n2       = map integerToWordX [wordToIntegerX n1 .. wordToIntegerX n2]
+    enumFromThenTo n1 n2 m = map integerToWordX [wordToIntegerX n1, wordToIntegerX n2 .. wordToIntegerX m]
+    enumFromThen n1 n2     = map integerToWordX [wordToIntegerX n1, wordToIntegerX n2 .. wordToIntegerX limit]
+      where
+         limit :: Word
+         limit  | n2 >= n1  = maxBound
+                | otherwise = minBound
+
+maxIntWord :: Word
+-- The biggest word representable as an Int
+maxIntWord = W# (case maxInt of I# i -> int2Word# i)
+
+-- For some reason integerToWord and wordToInteger (GHC.Integer.Type)
+-- work over Word#
+integerToWordX :: Integer -> Word
+integerToWordX i = W# (integerToWord i)
+
+wordToIntegerX :: Word -> Integer
+wordToIntegerX (W# x#) = wordToInteger x#
 \end{code}
 
 
diff --git a/libraries/base/GHC/Real.lhs b/libraries/base/GHC/Real.lhs
index d70dd81..a54818f 100644
--- a/libraries/base/GHC/Real.lhs
+++ b/libraries/base/GHC/Real.lhs
@@ -345,30 +345,7 @@ instance Integral Word where
     divMod  (W# x#) y@(W# y#)
         | y /= 0                = (W# (x# `quotWord#` y#), W# (x# `remWord#` y#))
         | otherwise             = divZeroError
-    toInteger (W# x#)
-        | isTrue# (i# >=# 0#)   = smallInteger i#
-        | otherwise             = wordToInteger x#
-        where
-        !i# = word2Int# x#
-
-instance Enum Word where
-    succ x
-        | x /= maxBound = x + 1
-        | otherwise     = succError "Word"
-    pred x
-        | x /= minBound = x - 1
-        | otherwise     = predError "Word"
-    toEnum i@(I# i#)
-        | i >= 0        = W# (int2Word# i#)
-        | otherwise     = toEnumError "Word" i (minBound::Word, maxBound::Word)
-    fromEnum x@(W# x#)
-        | x <= fromIntegral (maxBound::Int)
-                        = I# (word2Int# x#)
-        | otherwise     = fromEnumError "Word" x
-    enumFrom            = integralEnumFrom
-    enumFromThen        = integralEnumFromThen
-    enumFromTo          = integralEnumFromTo
-    enumFromThenTo      = integralEnumFromThenTo
+    toInteger (W# x#)           = wordToInteger x#
 \end{code}
 
 



More information about the ghc-commits mailing list