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