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