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