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