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