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