Avoid using deprecated flags
[ghc-base.git] / GHC / Word.hs
1 {-# OPTIONS_GHC -XNoImplicitPrelude #-}
2 {-# OPTIONS_HADDOCK hide #-}
3 -----------------------------------------------------------------------------
4 -- |
5 -- Module      :  GHC.Word
6 -- Copyright   :  (c) The University of Glasgow, 1997-2002
7 -- License     :  see libraries/base/LICENSE
8 -- 
9 -- Maintainer  :  cvs-ghc@haskell.org
10 -- Stability   :  internal
11 -- Portability :  non-portable (GHC Extensions)
12 --
13 -- Sized unsigned integral types: 'Word', 'Word8', 'Word16', 'Word32', and
14 -- 'Word64'.
15 --
16 -----------------------------------------------------------------------------
17
18 #include "MachDeps.h"
19
20 -- #hide
21 module GHC.Word (
22     Word(..), Word8(..), Word16(..), Word32(..), Word64(..),
23     toEnumError, fromEnumError, succError, predError,
24     uncheckedShiftL64#,
25     uncheckedShiftRL64#
26     ) where
27
28 import Data.Bits
29
30 #if WORD_SIZE_IN_BITS < 32
31 import GHC.IntWord32
32 #endif
33 #if WORD_SIZE_IN_BITS < 64
34 import GHC.IntWord64
35 #endif
36
37 import GHC.Base
38 import GHC.Enum
39 import GHC.Num
40 import GHC.Real
41 import GHC.Read
42 import GHC.Arr
43 import GHC.Show
44
45 ------------------------------------------------------------------------
46 -- Helper functions
47 ------------------------------------------------------------------------
48
49 {-# NOINLINE toEnumError #-}
50 toEnumError :: (Show a) => String -> Int -> (a,a) -> b
51 toEnumError inst_ty i bnds =
52     error $ "Enum.toEnum{" ++ inst_ty ++ "}: tag (" ++
53             show i ++
54             ") is outside of bounds " ++
55             show bnds
56
57 {-# NOINLINE fromEnumError #-}
58 fromEnumError :: (Show a) => String -> a -> b
59 fromEnumError inst_ty x =
60     error $ "Enum.fromEnum{" ++ inst_ty ++ "}: value (" ++
61             show x ++
62             ") is outside of Int's bounds " ++
63             show (minBound::Int, maxBound::Int)
64
65 {-# NOINLINE succError #-}
66 succError :: String -> a
67 succError inst_ty =
68     error $ "Enum.succ{" ++ inst_ty ++ "}: tried to take `succ' of maxBound"
69
70 {-# NOINLINE predError #-}
71 predError :: String -> a
72 predError inst_ty =
73     error $ "Enum.pred{" ++ inst_ty ++ "}: tried to take `pred' of minBound"
74
75 ------------------------------------------------------------------------
76 -- type Word
77 ------------------------------------------------------------------------
78
79 -- |A 'Word' is an unsigned integral type, with the same size as 'Int'.
80 data Word = W# Word# deriving (Eq, Ord)
81
82 instance Show Word where
83     showsPrec p x = showsPrec p (toInteger x)
84
85 instance Num Word where
86     (W# x#) + (W# y#)      = W# (x# `plusWord#` y#)
87     (W# x#) - (W# y#)      = W# (x# `minusWord#` y#)
88     (W# x#) * (W# y#)      = W# (x# `timesWord#` y#)
89     negate (W# x#)         = W# (int2Word# (negateInt# (word2Int# x#)))
90     abs x                  = x
91     signum 0               = 0
92     signum _               = 1
93     fromInteger i          = W# (integerToWord i)
94
95 instance Real Word where
96     toRational x = toInteger x % 1
97
98 instance Enum Word where
99     succ x
100         | x /= maxBound = x + 1
101         | otherwise     = succError "Word"
102     pred x
103         | x /= minBound = x - 1
104         | otherwise     = predError "Word"
105     toEnum i@(I# i#)
106         | i >= 0        = W# (int2Word# i#)
107         | otherwise     = toEnumError "Word" i (minBound::Word, maxBound::Word)
108     fromEnum x@(W# x#)
109         | x <= fromIntegral (maxBound::Int)
110                         = I# (word2Int# x#)
111         | otherwise     = fromEnumError "Word" x
112     enumFrom            = integralEnumFrom
113     enumFromThen        = integralEnumFromThen
114     enumFromTo          = integralEnumFromTo
115     enumFromThenTo      = integralEnumFromThenTo
116
117 instance Integral Word where
118     quot    x@(W# x#) y@(W# y#)
119         | y /= 0                = W# (x# `quotWord#` y#)
120         | otherwise             = divZeroError
121     rem     x@(W# x#) y@(W# y#)
122         | y /= 0                = W# (x# `remWord#` y#)
123         | otherwise             = divZeroError
124     div     x@(W# x#) y@(W# y#)
125         | y /= 0                = W# (x# `quotWord#` y#)
126         | otherwise             = divZeroError
127     mod     x@(W# x#) y@(W# y#)
128         | y /= 0                = W# (x# `remWord#` y#)
129         | otherwise             = divZeroError
130     quotRem x@(W# x#) y@(W# y#)
131         | y /= 0                = (W# (x# `quotWord#` y#), W# (x# `remWord#` y#))
132         | otherwise             = divZeroError
133     divMod  x@(W# x#) y@(W# y#)
134         | y /= 0                = (W# (x# `quotWord#` y#), W# (x# `remWord#` y#))
135         | otherwise             = divZeroError
136     toInteger (W# x#)
137         | i# >=# 0#             = smallInteger i#
138         | otherwise             = wordToInteger x#
139         where
140         i# = word2Int# x#
141
142 instance Bounded Word where
143     minBound = 0
144
145     -- use unboxed literals for maxBound, because GHC doesn't optimise
146     -- (fromInteger 0xffffffff :: Word).
147 #if WORD_SIZE_IN_BITS == 31
148     maxBound = W# (int2Word# 0x7FFFFFFF#)
149 #elif WORD_SIZE_IN_BITS == 32
150     maxBound = W# (int2Word# 0xFFFFFFFF#)
151 #else
152     maxBound = W# (int2Word# 0xFFFFFFFFFFFFFFFF#)
153 #endif
154
155 instance Ix Word where
156     range (m,n)              = [m..n]
157     unsafeIndex b@(m,_) i    = fromIntegral (i - m)
158     inRange (m,n) i          = m <= i && i <= n
159
160 instance Read Word where
161     readsPrec p s = [(fromInteger x, r) | (x, r) <- readsPrec p s]
162
163 instance Bits Word where
164     {-# INLINE shift #-}
165
166     (W# x#) .&.   (W# y#)    = W# (x# `and#` y#)
167     (W# x#) .|.   (W# y#)    = W# (x# `or#`  y#)
168     (W# x#) `xor` (W# y#)    = W# (x# `xor#` y#)
169     complement (W# x#)       = W# (x# `xor#` mb#) where W# mb# = maxBound
170     (W# x#) `shift` (I# i#)
171         | i# >=# 0#          = W# (x# `shiftL#` i#)
172         | otherwise          = W# (x# `shiftRL#` negateInt# i#)
173     (W# x#) `rotate` (I# i#)
174         | i'# ==# 0# = W# x#
175         | otherwise  = W# ((x# `uncheckedShiftL#` i'#) `or#` (x# `uncheckedShiftRL#` (wsib -# i'#)))
176         where
177         i'# = word2Int# (int2Word# i# `and#` int2Word# (wsib -# 1#))
178         wsib = WORD_SIZE_IN_BITS#  {- work around preprocessor problem (??) -}
179     bitSize  _               = WORD_SIZE_IN_BITS
180     isSigned _               = False
181
182 {-# RULES
183 "fromIntegral/Int->Word"  fromIntegral = \(I# x#) -> W# (int2Word# x#)
184 "fromIntegral/Word->Int"  fromIntegral = \(W# x#) -> I# (word2Int# x#)
185 "fromIntegral/Word->Word" fromIntegral = id :: Word -> Word
186   #-}
187
188 ------------------------------------------------------------------------
189 -- type Word8
190 ------------------------------------------------------------------------
191
192 -- Word8 is represented in the same way as Word. Operations may assume
193 -- and must ensure that it holds only values from its logical range.
194
195 data Word8 = W8# Word# deriving (Eq, Ord)
196 -- ^ 8-bit unsigned integer type
197
198 instance Show Word8 where
199     showsPrec p x = showsPrec p (fromIntegral x :: Int)
200
201 instance Num Word8 where
202     (W8# x#) + (W8# y#)    = W8# (narrow8Word# (x# `plusWord#` y#))
203     (W8# x#) - (W8# y#)    = W8# (narrow8Word# (x# `minusWord#` y#))
204     (W8# x#) * (W8# y#)    = W8# (narrow8Word# (x# `timesWord#` y#))
205     negate (W8# x#)        = W8# (narrow8Word# (int2Word# (negateInt# (word2Int# x#))))
206     abs x                  = x
207     signum 0               = 0
208     signum _               = 1
209     fromInteger i          = W8# (narrow8Word# (integerToWord i))
210
211 instance Real Word8 where
212     toRational x = toInteger x % 1
213
214 instance Enum Word8 where
215     succ x
216         | x /= maxBound = x + 1
217         | otherwise     = succError "Word8"
218     pred x
219         | x /= minBound = x - 1
220         | otherwise     = predError "Word8"
221     toEnum i@(I# i#)
222         | i >= 0 && i <= fromIntegral (maxBound::Word8)
223                         = W8# (int2Word# i#)
224         | otherwise     = toEnumError "Word8" i (minBound::Word8, maxBound::Word8)
225     fromEnum (W8# x#)   = I# (word2Int# x#)
226     enumFrom            = boundedEnumFrom
227     enumFromThen        = boundedEnumFromThen
228
229 instance Integral Word8 where
230     quot    x@(W8# x#) y@(W8# y#)
231         | y /= 0                  = W8# (x# `quotWord#` y#)
232         | otherwise               = divZeroError
233     rem     x@(W8# x#) y@(W8# y#)
234         | y /= 0                  = W8# (x# `remWord#` y#)
235         | otherwise               = divZeroError
236     div     x@(W8# x#) y@(W8# y#)
237         | y /= 0                  = W8# (x# `quotWord#` y#)
238         | otherwise               = divZeroError
239     mod     x@(W8# x#) y@(W8# y#)
240         | y /= 0                  = W8# (x# `remWord#` y#)
241         | otherwise               = divZeroError
242     quotRem x@(W8# x#) y@(W8# y#)
243         | y /= 0                  = (W8# (x# `quotWord#` y#), W8# (x# `remWord#` y#))
244         | otherwise               = divZeroError
245     divMod  x@(W8# x#) y@(W8# y#)
246         | y /= 0                  = (W8# (x# `quotWord#` y#), W8# (x# `remWord#` y#))
247         | otherwise               = divZeroError
248     toInteger (W8# x#)            = smallInteger (word2Int# x#)
249
250 instance Bounded Word8 where
251     minBound = 0
252     maxBound = 0xFF
253
254 instance Ix Word8 where
255     range (m,n)              = [m..n]
256     unsafeIndex b@(m,_) i    = fromIntegral (i - m)
257     inRange (m,n) i          = m <= i && i <= n
258
259 instance Read Word8 where
260     readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
261
262 instance Bits Word8 where
263     {-# INLINE shift #-}
264
265     (W8# x#) .&.   (W8# y#)   = W8# (x# `and#` y#)
266     (W8# x#) .|.   (W8# y#)   = W8# (x# `or#`  y#)
267     (W8# x#) `xor` (W8# y#)   = W8# (x# `xor#` y#)
268     complement (W8# x#)       = W8# (x# `xor#` mb#) where W8# mb# = maxBound
269     (W8# x#) `shift` (I# i#)
270         | i# >=# 0#           = W8# (narrow8Word# (x# `shiftL#` i#))
271         | otherwise           = W8# (x# `shiftRL#` negateInt# i#)
272     (W8# x#) `rotate` (I# i#)
273         | i'# ==# 0# = W8# x#
274         | otherwise  = W8# (narrow8Word# ((x# `uncheckedShiftL#` i'#) `or#`
275                                           (x# `uncheckedShiftRL#` (8# -# i'#))))
276         where
277         i'# = word2Int# (int2Word# i# `and#` int2Word# 7#)
278     bitSize  _                = 8
279     isSigned _                = False
280
281 {-# RULES
282 "fromIntegral/Word8->Word8"   fromIntegral = id :: Word8 -> Word8
283 "fromIntegral/Word8->Integer" fromIntegral = toInteger :: Word8 -> Integer
284 "fromIntegral/a->Word8"       fromIntegral = \x -> case fromIntegral x of W# x# -> W8# (narrow8Word# x#)
285 "fromIntegral/Word8->a"       fromIntegral = \(W8# x#) -> fromIntegral (W# x#)
286   #-}
287
288 ------------------------------------------------------------------------
289 -- type Word16
290 ------------------------------------------------------------------------
291
292 -- Word16 is represented in the same way as Word. Operations may assume
293 -- and must ensure that it holds only values from its logical range.
294
295 data Word16 = W16# Word# deriving (Eq, Ord)
296 -- ^ 16-bit unsigned integer type
297
298 instance Show Word16 where
299     showsPrec p x = showsPrec p (fromIntegral x :: Int)
300
301 instance Num Word16 where
302     (W16# x#) + (W16# y#)  = W16# (narrow16Word# (x# `plusWord#` y#))
303     (W16# x#) - (W16# y#)  = W16# (narrow16Word# (x# `minusWord#` y#))
304     (W16# x#) * (W16# y#)  = W16# (narrow16Word# (x# `timesWord#` y#))
305     negate (W16# x#)       = W16# (narrow16Word# (int2Word# (negateInt# (word2Int# x#))))
306     abs x                  = x
307     signum 0               = 0
308     signum _               = 1
309     fromInteger i          = W16# (narrow16Word# (integerToWord i))
310
311 instance Real Word16 where
312     toRational x = toInteger x % 1
313
314 instance Enum Word16 where
315     succ x
316         | x /= maxBound = x + 1
317         | otherwise     = succError "Word16"
318     pred x
319         | x /= minBound = x - 1
320         | otherwise     = predError "Word16"
321     toEnum i@(I# i#)
322         | i >= 0 && i <= fromIntegral (maxBound::Word16)
323                         = W16# (int2Word# i#)
324         | otherwise     = toEnumError "Word16" i (minBound::Word16, maxBound::Word16)
325     fromEnum (W16# x#)  = I# (word2Int# x#)
326     enumFrom            = boundedEnumFrom
327     enumFromThen        = boundedEnumFromThen
328
329 instance Integral Word16 where
330     quot    x@(W16# x#) y@(W16# y#)
331         | y /= 0                    = W16# (x# `quotWord#` y#)
332         | otherwise                 = divZeroError
333     rem     x@(W16# x#) y@(W16# y#)
334         | y /= 0                    = W16# (x# `remWord#` y#)
335         | otherwise                 = divZeroError
336     div     x@(W16# x#) y@(W16# y#)
337         | y /= 0                    = W16# (x# `quotWord#` y#)
338         | otherwise                 = divZeroError
339     mod     x@(W16# x#) y@(W16# y#)
340         | y /= 0                    = W16# (x# `remWord#` y#)
341         | otherwise                 = divZeroError
342     quotRem x@(W16# x#) y@(W16# y#)
343         | y /= 0                    = (W16# (x# `quotWord#` y#), W16# (x# `remWord#` y#))
344         | otherwise                 = divZeroError
345     divMod  x@(W16# x#) y@(W16# y#)
346         | y /= 0                    = (W16# (x# `quotWord#` y#), W16# (x# `remWord#` y#))
347         | otherwise                 = divZeroError
348     toInteger (W16# x#)             = smallInteger (word2Int# x#)
349
350 instance Bounded Word16 where
351     minBound = 0
352     maxBound = 0xFFFF
353
354 instance Ix Word16 where
355     range (m,n)              = [m..n]
356     unsafeIndex b@(m,_) i    = fromIntegral (i - m)
357     inRange (m,n) i          = m <= i && i <= n
358
359 instance Read Word16 where
360     readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
361
362 instance Bits Word16 where
363     {-# INLINE shift #-}
364
365     (W16# x#) .&.   (W16# y#)  = W16# (x# `and#` y#)
366     (W16# x#) .|.   (W16# y#)  = W16# (x# `or#`  y#)
367     (W16# x#) `xor` (W16# y#)  = W16# (x# `xor#` y#)
368     complement (W16# x#)       = W16# (x# `xor#` mb#) where W16# mb# = maxBound
369     (W16# x#) `shift` (I# i#)
370         | i# >=# 0#            = W16# (narrow16Word# (x# `shiftL#` i#))
371         | otherwise            = W16# (x# `shiftRL#` negateInt# i#)
372     (W16# x#) `rotate` (I# i#)
373         | i'# ==# 0# = W16# x#
374         | otherwise  = W16# (narrow16Word# ((x# `uncheckedShiftL#` i'#) `or#`
375                                             (x# `uncheckedShiftRL#` (16# -# i'#))))
376         where
377         i'# = word2Int# (int2Word# i# `and#` int2Word# 15#)
378     bitSize  _                = 16
379     isSigned _                = False
380
381 {-# RULES
382 "fromIntegral/Word8->Word16"   fromIntegral = \(W8# x#) -> W16# x#
383 "fromIntegral/Word16->Word16"  fromIntegral = id :: Word16 -> Word16
384 "fromIntegral/Word16->Integer" fromIntegral = toInteger :: Word16 -> Integer
385 "fromIntegral/a->Word16"       fromIntegral = \x -> case fromIntegral x of W# x# -> W16# (narrow16Word# x#)
386 "fromIntegral/Word16->a"       fromIntegral = \(W16# x#) -> fromIntegral (W# x#)
387   #-}
388
389 ------------------------------------------------------------------------
390 -- type Word32
391 ------------------------------------------------------------------------
392
393 #if WORD_SIZE_IN_BITS < 32
394
395 data Word32 = W32# Word32#
396 -- ^ 32-bit unsigned integer type
397
398 instance Eq Word32 where
399     (W32# x#) == (W32# y#) = x# `eqWord32#` y#
400     (W32# x#) /= (W32# y#) = x# `neWord32#` y#
401
402 instance Ord Word32 where
403     (W32# x#) <  (W32# y#) = x# `ltWord32#` y#
404     (W32# x#) <= (W32# y#) = x# `leWord32#` y#
405     (W32# x#) >  (W32# y#) = x# `gtWord32#` y#
406     (W32# x#) >= (W32# y#) = x# `geWord32#` y#
407
408 instance Num Word32 where
409     (W32# x#) + (W32# y#)  = W32# (int32ToWord32# (word32ToInt32# x# `plusInt32#` word32ToInt32# y#))
410     (W32# x#) - (W32# y#)  = W32# (int32ToWord32# (word32ToInt32# x# `minusInt32#` word32ToInt32# y#))
411     (W32# x#) * (W32# y#)  = W32# (int32ToWord32# (word32ToInt32# x# `timesInt32#` word32ToInt32# y#))
412     negate (W32# x#)       = W32# (int32ToWord32# (negateInt32# (word32ToInt32# x#)))
413     abs x                  = x
414     signum 0               = 0
415     signum _               = 1
416     fromInteger (S# i#)    = W32# (int32ToWord32# (intToInt32# i#))
417     fromInteger (J# s# d#) = W32# (integerToWord32# s# d#)
418
419 instance Enum Word32 where
420     succ x
421         | x /= maxBound = x + 1
422         | otherwise     = succError "Word32"
423     pred x
424         | x /= minBound = x - 1
425         | otherwise     = predError "Word32"
426     toEnum i@(I# i#)
427         | i >= 0        = W32# (wordToWord32# (int2Word# i#))
428         | otherwise     = toEnumError "Word32" i (minBound::Word32, maxBound::Word32)
429     fromEnum x@(W32# x#)
430         | x <= fromIntegral (maxBound::Int)
431                         = I# (word2Int# (word32ToWord# x#))
432         | otherwise     = fromEnumError "Word32" x
433     enumFrom            = integralEnumFrom
434     enumFromThen        = integralEnumFromThen
435     enumFromTo          = integralEnumFromTo
436     enumFromThenTo      = integralEnumFromThenTo
437
438 instance Integral Word32 where
439     quot    x@(W32# x#) y@(W32# y#)
440         | y /= 0                    = W32# (x# `quotWord32#` y#)
441         | otherwise                 = divZeroError
442     rem     x@(W32# x#) y@(W32# y#)
443         | y /= 0                    = W32# (x# `remWord32#` y#)
444         | otherwise                 = divZeroError
445     div     x@(W32# x#) y@(W32# y#)
446         | y /= 0                    = W32# (x# `quotWord32#` y#)
447         | otherwise                 = divZeroError
448     mod     x@(W32# x#) y@(W32# y#)
449         | y /= 0                    = W32# (x# `remWord32#` y#)
450         | otherwise                 = divZeroError
451     quotRem x@(W32# x#) y@(W32# y#)
452         | y /= 0                    = (W32# (x# `quotWord32#` y#), W32# (x# `remWord32#` y#))
453         | otherwise                 = divZeroError
454     divMod  x@(W32# x#) y@(W32# y#)
455         | y /= 0                    = (W32# (x# `quotWord32#` y#), W32# (x# `remWord32#` y#))
456         | otherwise                 = divZeroError
457     toInteger x@(W32# x#)
458         | x <= fromIntegral (maxBound::Int)  = S# (word2Int# (word32ToWord# x#))
459         | otherwise                 = case word32ToInteger# x# of (# s, d #) -> J# s d
460
461 instance Bits Word32 where
462     {-# INLINE shift #-}
463
464     (W32# x#) .&.   (W32# y#)  = W32# (x# `and32#` y#)
465     (W32# x#) .|.   (W32# y#)  = W32# (x# `or32#`  y#)
466     (W32# x#) `xor` (W32# y#)  = W32# (x# `xor32#` y#)
467     complement (W32# x#)       = W32# (not32# x#)
468     (W32# x#) `shift` (I# i#)
469         | i# >=# 0#            = W32# (x# `shiftL32#` i#)
470         | otherwise            = W32# (x# `shiftRL32#` negateInt# i#)
471     (W32# x#) `rotate` (I# i#)
472         | i'# ==# 0# = W32# x#
473         | otherwise  = W32# ((x# `shiftL32#` i'#) `or32#`
474                              (x# `shiftRL32#` (32# -# i'#)))
475         where
476         i'# = word2Int# (int2Word# i# `and#` int2Word# 31#)
477     bitSize  _                = 32
478     isSigned _                = False
479
480 {-# RULES
481 "fromIntegral/Int->Word32"    fromIntegral = \(I#   x#) -> W32# (int32ToWord32# (intToInt32# x#))
482 "fromIntegral/Word->Word32"   fromIntegral = \(W#   x#) -> W32# (wordToWord32# x#)
483 "fromIntegral/Word32->Int"    fromIntegral = \(W32# x#) -> I#   (word2Int# (word32ToWord# x#))
484 "fromIntegral/Word32->Word"   fromIntegral = \(W32# x#) -> W#   (word32ToWord# x#)
485 "fromIntegral/Word32->Word32" fromIntegral = id :: Word32 -> Word32
486   #-}
487
488 #else 
489
490 -- Word32 is represented in the same way as Word.
491 #if WORD_SIZE_IN_BITS > 32
492 -- Operations may assume and must ensure that it holds only values
493 -- from its logical range.
494 #endif
495
496 data Word32 = W32# Word# deriving (Eq, Ord)
497 -- ^ 32-bit unsigned integer type
498
499 instance Num Word32 where
500     (W32# x#) + (W32# y#)  = W32# (narrow32Word# (x# `plusWord#` y#))
501     (W32# x#) - (W32# y#)  = W32# (narrow32Word# (x# `minusWord#` y#))
502     (W32# x#) * (W32# y#)  = W32# (narrow32Word# (x# `timesWord#` y#))
503     negate (W32# x#)       = W32# (narrow32Word# (int2Word# (negateInt# (word2Int# x#))))
504     abs x                  = x
505     signum 0               = 0
506     signum _               = 1
507     fromInteger i          = W32# (narrow32Word# (integerToWord i))
508
509 instance Enum Word32 where
510     succ x
511         | x /= maxBound = x + 1
512         | otherwise     = succError "Word32"
513     pred x
514         | x /= minBound = x - 1
515         | otherwise     = predError "Word32"
516     toEnum i@(I# i#)
517         | i >= 0
518 #if WORD_SIZE_IN_BITS > 32
519           && i <= fromIntegral (maxBound::Word32)
520 #endif
521                         = W32# (int2Word# i#)
522         | otherwise     = toEnumError "Word32" i (minBound::Word32, maxBound::Word32)
523 #if WORD_SIZE_IN_BITS == 32
524     fromEnum x@(W32# x#)
525         | x <= fromIntegral (maxBound::Int)
526                         = I# (word2Int# x#)
527         | otherwise     = fromEnumError "Word32" x
528     enumFrom            = integralEnumFrom
529     enumFromThen        = integralEnumFromThen
530     enumFromTo          = integralEnumFromTo
531     enumFromThenTo      = integralEnumFromThenTo
532 #else
533     fromEnum (W32# x#)  = I# (word2Int# x#)
534     enumFrom            = boundedEnumFrom
535     enumFromThen        = boundedEnumFromThen
536 #endif
537
538 instance Integral Word32 where
539     quot    x@(W32# x#) y@(W32# y#)
540         | y /= 0                    = W32# (x# `quotWord#` y#)
541         | otherwise                 = divZeroError
542     rem     x@(W32# x#) y@(W32# y#)
543         | y /= 0                    = W32# (x# `remWord#` y#)
544         | otherwise                 = divZeroError
545     div     x@(W32# x#) y@(W32# y#)
546         | y /= 0                    = W32# (x# `quotWord#` y#)
547         | otherwise                 = divZeroError
548     mod     x@(W32# x#) y@(W32# y#)
549         | y /= 0                    = W32# (x# `remWord#` y#)
550         | otherwise                 = divZeroError
551     quotRem x@(W32# x#) y@(W32# y#)
552         | y /= 0                    = (W32# (x# `quotWord#` y#), W32# (x# `remWord#` y#))
553         | otherwise                 = divZeroError
554     divMod  x@(W32# x#) y@(W32# y#)
555         | y /= 0                    = (W32# (x# `quotWord#` y#), W32# (x# `remWord#` y#))
556         | otherwise                 = divZeroError
557     toInteger (W32# x#)
558 #if WORD_SIZE_IN_BITS == 32
559         | i# >=# 0#                 = smallInteger i#
560         | otherwise                 = wordToInteger x#
561         where
562         i# = word2Int# x#
563 #else
564                                     = smallInteger (word2Int# x#)
565 #endif
566
567 instance Bits Word32 where
568     {-# INLINE shift #-}
569
570     (W32# x#) .&.   (W32# y#)  = W32# (x# `and#` y#)
571     (W32# x#) .|.   (W32# y#)  = W32# (x# `or#`  y#)
572     (W32# x#) `xor` (W32# y#)  = W32# (x# `xor#` y#)
573     complement (W32# x#)       = W32# (x# `xor#` mb#) where W32# mb# = maxBound
574     (W32# x#) `shift` (I# i#)
575         | i# >=# 0#            = W32# (narrow32Word# (x# `shiftL#` i#))
576         | otherwise            = W32# (x# `shiftRL#` negateInt# i#)
577     (W32# x#) `rotate` (I# i#)
578         | i'# ==# 0# = W32# x#
579         | otherwise  = W32# (narrow32Word# ((x# `uncheckedShiftL#` i'#) `or#`
580                                             (x# `uncheckedShiftRL#` (32# -# i'#))))
581         where
582         i'# = word2Int# (int2Word# i# `and#` int2Word# 31#)
583     bitSize  _                = 32
584     isSigned _                = False
585
586 {-# RULES
587 "fromIntegral/Word8->Word32"   fromIntegral = \(W8# x#) -> W32# x#
588 "fromIntegral/Word16->Word32"  fromIntegral = \(W16# x#) -> W32# x#
589 "fromIntegral/Word32->Word32"  fromIntegral = id :: Word32 -> Word32
590 "fromIntegral/Word32->Integer" fromIntegral = toInteger :: Word32 -> Integer
591 "fromIntegral/a->Word32"       fromIntegral = \x -> case fromIntegral x of W# x# -> W32# (narrow32Word# x#)
592 "fromIntegral/Word32->a"       fromIntegral = \(W32# x#) -> fromIntegral (W# x#)
593   #-}
594
595 #endif
596
597 instance Show Word32 where
598 #if WORD_SIZE_IN_BITS < 33
599     showsPrec p x = showsPrec p (toInteger x)
600 #else
601     showsPrec p x = showsPrec p (fromIntegral x :: Int)
602 #endif
603
604
605 instance Real Word32 where
606     toRational x = toInteger x % 1
607
608 instance Bounded Word32 where
609     minBound = 0
610     maxBound = 0xFFFFFFFF
611
612 instance Ix Word32 where
613     range (m,n)              = [m..n]
614     unsafeIndex b@(m,_) i    = fromIntegral (i - m)
615     inRange (m,n) i          = m <= i && i <= n
616
617 instance Read Word32 where  
618 #if WORD_SIZE_IN_BITS < 33
619     readsPrec p s = [(fromInteger x, r) | (x, r) <- readsPrec p s]
620 #else
621     readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
622 #endif
623
624 ------------------------------------------------------------------------
625 -- type Word64
626 ------------------------------------------------------------------------
627
628 #if WORD_SIZE_IN_BITS < 64
629
630 data Word64 = W64# Word64#
631 -- ^ 64-bit unsigned integer type
632
633 instance Eq Word64 where
634     (W64# x#) == (W64# y#) = x# `eqWord64#` y#
635     (W64# x#) /= (W64# y#) = x# `neWord64#` y#
636
637 instance Ord Word64 where
638     (W64# x#) <  (W64# y#) = x# `ltWord64#` y#
639     (W64# x#) <= (W64# y#) = x# `leWord64#` y#
640     (W64# x#) >  (W64# y#) = x# `gtWord64#` y#
641     (W64# x#) >= (W64# y#) = x# `geWord64#` y#
642
643 instance Num Word64 where
644     (W64# x#) + (W64# y#)  = W64# (int64ToWord64# (word64ToInt64# x# `plusInt64#` word64ToInt64# y#))
645     (W64# x#) - (W64# y#)  = W64# (int64ToWord64# (word64ToInt64# x# `minusInt64#` word64ToInt64# y#))
646     (W64# x#) * (W64# y#)  = W64# (int64ToWord64# (word64ToInt64# x# `timesInt64#` word64ToInt64# y#))
647     negate (W64# x#)       = W64# (int64ToWord64# (negateInt64# (word64ToInt64# x#)))
648     abs x                  = x
649     signum 0               = 0
650     signum _               = 1
651     fromInteger i          = W64# (integerToWord64 i)
652
653 instance Enum Word64 where
654     succ x
655         | x /= maxBound = x + 1
656         | otherwise     = succError "Word64"
657     pred x
658         | x /= minBound = x - 1
659         | otherwise     = predError "Word64"
660     toEnum i@(I# i#)
661         | i >= 0        = W64# (wordToWord64# (int2Word# i#))
662         | otherwise     = toEnumError "Word64" i (minBound::Word64, maxBound::Word64)
663     fromEnum x@(W64# x#)
664         | x <= fromIntegral (maxBound::Int)
665                         = I# (word2Int# (word64ToWord# x#))
666         | otherwise     = fromEnumError "Word64" x
667     enumFrom            = integralEnumFrom
668     enumFromThen        = integralEnumFromThen
669     enumFromTo          = integralEnumFromTo
670     enumFromThenTo      = integralEnumFromThenTo
671
672 instance Integral Word64 where
673     quot    x@(W64# x#) y@(W64# y#)
674         | y /= 0                    = W64# (x# `quotWord64#` y#)
675         | otherwise                 = divZeroError
676     rem     x@(W64# x#) y@(W64# y#)
677         | y /= 0                    = W64# (x# `remWord64#` y#)
678         | otherwise                 = divZeroError
679     div     x@(W64# x#) y@(W64# y#)
680         | y /= 0                    = W64# (x# `quotWord64#` y#)
681         | otherwise                 = divZeroError
682     mod     x@(W64# x#) y@(W64# y#)
683         | y /= 0                    = W64# (x# `remWord64#` y#)
684         | otherwise                 = divZeroError
685     quotRem x@(W64# x#) y@(W64# y#)
686         | y /= 0                    = (W64# (x# `quotWord64#` y#), W64# (x# `remWord64#` y#))
687         | otherwise                 = divZeroError
688     divMod  x@(W64# x#) y@(W64# y#)
689         | y /= 0                    = (W64# (x# `quotWord64#` y#), W64# (x# `remWord64#` y#))
690         | otherwise                 = divZeroError
691     toInteger (W64# x#)             = word64ToInteger x#
692
693 instance Bits Word64 where
694     {-# INLINE shift #-}
695
696     (W64# x#) .&.   (W64# y#)  = W64# (x# `and64#` y#)
697     (W64# x#) .|.   (W64# y#)  = W64# (x# `or64#`  y#)
698     (W64# x#) `xor` (W64# y#)  = W64# (x# `xor64#` y#)
699     complement (W64# x#)       = W64# (not64# x#)
700     (W64# x#) `shift` (I# i#)
701         | i# >=# 0#            = W64# (x# `shiftL64#` i#)
702         | otherwise            = W64# (x# `shiftRL64#` negateInt# i#)
703     (W64# x#) `rotate` (I# i#)
704         | i'# ==# 0# = W64# x#
705         | otherwise  = W64# ((x# `uncheckedShiftL64#` i'#) `or64#`
706                              (x# `uncheckedShiftRL64#` (64# -# i'#)))
707         where
708         i'# = word2Int# (int2Word# i# `and#` int2Word# 63#)
709     bitSize  _                = 64
710     isSigned _                = False
711
712 -- give the 64-bit shift operations the same treatment as the 32-bit
713 -- ones (see GHC.Base), namely we wrap them in tests to catch the
714 -- cases when we're shifting more than 64 bits to avoid unspecified
715 -- behaviour in the C shift operations.
716
717 shiftL64#, shiftRL64# :: Word64# -> Int# -> Word64#
718
719 a `shiftL64#` b  | b >=# 64#  = wordToWord64# (int2Word# 0#)
720                  | otherwise  = a `uncheckedShiftL64#` b
721
722 a `shiftRL64#` b | b >=# 64#  = wordToWord64# (int2Word# 0#)
723                  | otherwise  = a `uncheckedShiftRL64#` b
724
725 {-# RULES
726 "fromIntegral/Int->Word64"    fromIntegral = \(I#   x#) -> W64# (int64ToWord64# (intToInt64# x#))
727 "fromIntegral/Word->Word64"   fromIntegral = \(W#   x#) -> W64# (wordToWord64# x#)
728 "fromIntegral/Word64->Int"    fromIntegral = \(W64# x#) -> I#   (word2Int# (word64ToWord# x#))
729 "fromIntegral/Word64->Word"   fromIntegral = \(W64# x#) -> W#   (word64ToWord# x#)
730 "fromIntegral/Word64->Word64" fromIntegral = id :: Word64 -> Word64
731   #-}
732
733 #else
734
735 -- Word64 is represented in the same way as Word.
736 -- Operations may assume and must ensure that it holds only values
737 -- from its logical range.
738
739 data Word64 = W64# Word# deriving (Eq, Ord)
740 -- ^ 64-bit unsigned integer type
741
742 instance Num Word64 where
743     (W64# x#) + (W64# y#)  = W64# (x# `plusWord#` y#)
744     (W64# x#) - (W64# y#)  = W64# (x# `minusWord#` y#)
745     (W64# x#) * (W64# y#)  = W64# (x# `timesWord#` y#)
746     negate (W64# x#)       = W64# (int2Word# (negateInt# (word2Int# x#)))
747     abs x                  = x
748     signum 0               = 0
749     signum _               = 1
750     fromInteger i          = W64# (integerToWord i)
751
752 instance Enum Word64 where
753     succ x
754         | x /= maxBound = x + 1
755         | otherwise     = succError "Word64"
756     pred x
757         | x /= minBound = x - 1
758         | otherwise     = predError "Word64"
759     toEnum i@(I# i#)
760         | i >= 0        = W64# (int2Word# i#)
761         | otherwise     = toEnumError "Word64" i (minBound::Word64, maxBound::Word64)
762     fromEnum x@(W64# x#)
763         | x <= fromIntegral (maxBound::Int)
764                         = I# (word2Int# x#)
765         | otherwise     = fromEnumError "Word64" x
766     enumFrom            = integralEnumFrom
767     enumFromThen        = integralEnumFromThen
768     enumFromTo          = integralEnumFromTo
769     enumFromThenTo      = integralEnumFromThenTo
770
771 instance Integral Word64 where
772     quot    x@(W64# x#) y@(W64# y#)
773         | y /= 0                    = W64# (x# `quotWord#` y#)
774         | otherwise                 = divZeroError
775     rem     x@(W64# x#) y@(W64# y#)
776         | y /= 0                    = W64# (x# `remWord#` y#)
777         | otherwise                 = divZeroError
778     div     x@(W64# x#) y@(W64# y#)
779         | y /= 0                    = W64# (x# `quotWord#` y#)
780         | otherwise                 = divZeroError
781     mod     x@(W64# x#) y@(W64# y#)
782         | y /= 0                    = W64# (x# `remWord#` y#)
783         | otherwise                 = divZeroError
784     quotRem x@(W64# x#) y@(W64# y#)
785         | y /= 0                    = (W64# (x# `quotWord#` y#), W64# (x# `remWord#` y#))
786         | otherwise                 = divZeroError
787     divMod  x@(W64# x#) y@(W64# y#)
788         | y /= 0                    = (W64# (x# `quotWord#` y#), W64# (x# `remWord#` y#))
789         | otherwise                 = divZeroError
790     toInteger (W64# x#)
791         | i# >=# 0#                 = smallInteger i#
792         | otherwise                 = wordToInteger x#
793         where
794         i# = word2Int# x#
795
796 instance Bits Word64 where
797     {-# INLINE shift #-}
798
799     (W64# x#) .&.   (W64# y#)  = W64# (x# `and#` y#)
800     (W64# x#) .|.   (W64# y#)  = W64# (x# `or#`  y#)
801     (W64# x#) `xor` (W64# y#)  = W64# (x# `xor#` y#)
802     complement (W64# x#)       = W64# (x# `xor#` mb#) where W64# mb# = maxBound
803     (W64# x#) `shift` (I# i#)
804         | i# >=# 0#            = W64# (x# `shiftL#` i#)
805         | otherwise            = W64# (x# `shiftRL#` negateInt# i#)
806     (W64# x#) `rotate` (I# i#)
807         | i'# ==# 0# = W64# x#
808         | otherwise  = W64# ((x# `uncheckedShiftL#` i'#) `or#`
809                              (x# `uncheckedShiftRL#` (64# -# i'#)))
810         where
811         i'# = word2Int# (int2Word# i# `and#` int2Word# 63#)
812     bitSize  _                = 64
813     isSigned _                = False
814
815 {-# RULES
816 "fromIntegral/a->Word64" fromIntegral = \x -> case fromIntegral x of W# x# -> W64# x#
817 "fromIntegral/Word64->a" fromIntegral = \(W64# x#) -> fromIntegral (W# x#)
818   #-}
819
820 uncheckedShiftL64#  = uncheckedShiftL#
821 uncheckedShiftRL64# = uncheckedShiftRL#
822
823 #endif
824
825 instance Show Word64 where
826     showsPrec p x = showsPrec p (toInteger x)
827
828 instance Real Word64 where
829     toRational x = toInteger x % 1
830
831 instance Bounded Word64 where
832     minBound = 0
833     maxBound = 0xFFFFFFFFFFFFFFFF
834
835 instance Ix Word64 where
836     range (m,n)              = [m..n]
837     unsafeIndex b@(m,_) i    = fromIntegral (i - m)
838     inRange (m,n) i          = m <= i && i <= n
839
840 instance Read Word64 where
841     readsPrec p s = [(fromInteger x, r) | (x, r) <- readsPrec p s]