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