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