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