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