[project @ 2001-03-28 22:14:02 by qrczak]
[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 #include "MachDeps.h"
8
9 module PrelWord (
10     Word(..), Word8(..), Word16(..), Word32(..), Word64(..),
11     divZeroError, toEnumError, fromEnumError, succError, predError)
12     where
13
14 import PrelBase
15 import PrelEnum
16 import PrelNum
17 import PrelReal
18 import PrelRead
19 import PrelArr
20 import PrelBits
21
22 ------------------------------------------------------------------------
23 -- Helper functions
24 ------------------------------------------------------------------------
25
26 {-# NOINLINE divZeroError #-}
27 divZeroError :: (Show a) => String -> a -> b
28 divZeroError meth x =
29     error $ "Integral." ++ meth ++ ": divide by 0 (" ++ show x ++ " / 0)"
30
31 {-# NOINLINE toEnumError #-}
32 toEnumError :: (Show a) => String -> Int -> (a,a) -> b
33 toEnumError inst_ty i bnds =
34     error $ "Enum.toEnum{" ++ inst_ty ++ "}: tag (" ++
35             show i ++
36             ") is outside of bounds " ++
37             show bnds
38
39 {-# NOINLINE fromEnumError #-}
40 fromEnumError :: (Show a) => String -> a -> b
41 fromEnumError inst_ty x =
42     error $ "Enum.fromEnum{" ++ inst_ty ++ "}: value (" ++
43             show x ++
44             ") is outside of Int's bounds " ++
45             show (minBound::Int, maxBound::Int)
46
47 {-# NOINLINE succError #-}
48 succError :: String -> a
49 succError inst_ty =
50     error $ "Enum.succ{" ++ inst_ty ++ "}: tried to take `succ' of maxBound"
51
52 {-# NOINLINE predError #-}
53 predError :: String -> a
54 predError inst_ty =
55     error $ "Enum.pred{" ++ inst_ty ++ "}: tried to take `pred' of minBound"
56
57 ------------------------------------------------------------------------
58 -- type Word
59 ------------------------------------------------------------------------
60
61 -- A Word is an unsigned integral type, with the same size as Int.
62
63 data Word = W# Word# deriving (Eq, Ord)
64
65 instance CCallable Word
66 instance CReturnable Word
67
68 instance Show Word where
69     showsPrec p x = showsPrec p (toInteger x)
70
71 instance Num Word where
72     (W# x#) + (W# y#)      = W# (x# `plusWord#` y#)
73     (W# x#) - (W# y#)      = W# (x# `minusWord#` y#)
74     (W# x#) * (W# y#)      = W# (x# `timesWord#` y#)
75     negate (W# x#)         = W# (int2Word# (negateInt# (word2Int# x#)))
76     abs x                  = x
77     signum 0               = 0
78     signum _               = 1
79     fromInteger (S# i#)    = W# (int2Word# i#)
80     fromInteger (J# s# d#) = W# (integer2Word# s# d#)
81
82 instance Real Word where
83     toRational x = toInteger x % 1
84
85 instance Enum Word where
86     succ x
87         | x /= maxBound = x + 1
88         | otherwise     = succError "Word"
89     pred x
90         | x /= minBound = x - 1
91         | otherwise     = predError "Word"
92     toEnum i@(I# i#)
93         | i >= 0        = W# (int2Word# i#)
94         | otherwise     = toEnumError "Word" i (minBound::Word, maxBound::Word)
95     fromEnum x@(W# x#)
96         | x <= fromIntegral (maxBound::Int)
97                         = I# (word2Int# x#)
98         | otherwise     = fromEnumError "Word" x
99     enumFrom            = integralEnumFrom
100     enumFromThen        = integralEnumFromThen
101     enumFromTo          = integralEnumFromTo
102     enumFromThenTo      = integralEnumFromThenTo
103
104 instance Integral Word where
105     quot    x@(W# x#) y@(W# y#)
106         | y /= 0                = W# (x# `quotWord#` y#)
107         | otherwise             = divZeroError "quot{Word}" x
108     rem     x@(W# x#) y@(W# y#)
109         | y /= 0                = W# (x# `remWord#` y#)
110         | otherwise             = divZeroError "rem{Word}" x
111     div     x@(W# x#) y@(W# y#)
112         | y /= 0                = W# (x# `quotWord#` y#)
113         | otherwise             = divZeroError "div{Word}" x
114     mod     x@(W# x#) y@(W# y#)
115         | y /= 0                = W# (x# `remWord#` y#)
116         | otherwise             = divZeroError "mod{Word}" x
117     quotRem x@(W# x#) y@(W# y#)
118         | y /= 0                = (W# (x# `quotWord#` y#), W# (x# `remWord#` y#))
119         | otherwise             = divZeroError "quotRem{Word}" x
120     divMod  x@(W# x#) y@(W# y#)
121         | y /= 0                = (W# (x# `quotWord#` y#), W# (x# `remWord#` y#))
122         | otherwise             = divZeroError "divMod{Word}" x
123     toInteger (W# x#)
124         | i# >=# 0#             = S# i#
125         | otherwise             = case word2Integer# x# of (# s, d #) -> J# s d
126         where
127         i# = word2Int# x#
128
129 instance Bounded Word where
130     minBound = 0
131 #if WORD_SIZE_IN_BYTES == 4
132     maxBound = 0xFFFFFFFF
133 #else
134     maxBound = 0xFFFFFFFFFFFFFFFF
135 #endif
136
137 instance Ix Word where
138     range (m,n)       = [m..n]
139     index b@(m,_) i
140         | inRange b i = fromIntegral (i - m)
141         | otherwise   = indexError b i "Word"
142     inRange (m,n) i   = m <= i && i <= n
143
144 instance Read Word where
145     readsPrec p s = [(fromInteger x, r) | (x, r) <- readsPrec p s]
146
147 instance Bits Word where
148     (W# x#) .&.   (W# y#)    = W# (x# `and#` y#)
149     (W# x#) .|.   (W# y#)    = W# (x# `or#`  y#)
150     (W# x#) `xor` (W# y#)    = W# (x# `xor#` y#)
151     complement (W# x#)       = W# (x# `xor#` mb#) where W# mb# = maxBound
152     (W# x#) `shift` (I# i#)
153         | i# >=# 0#          = W# (x# `shiftL#` i#)
154         | otherwise          = W# (x# `shiftRL#` negateInt# i#)
155 #if WORD_SIZE_IN_BYTES == 4
156     (W# x#) `rotate` (I# i#) = W# ((x# `shiftL#` i'#) `or#` (x# `shiftRL#` (32# -# i'#)))
157         where
158         i'# = word2Int# (int2Word# i# `and#` int2Word# 31#)
159 #else
160     (W# x#) `rotate` (I# i#) = W# ((x# `shiftL#` i'#) `or#` (x# `shiftRL#` (64# -# i'#)))
161         where
162         i'# = word2Int# (int2Word# i# `and#` int2Word# 63#)
163 #endif
164     bitSize  _               = WORD_SIZE_IN_BYTES * 8
165     isSigned _               = False
166
167 {-# RULES
168 "fromIntegral/Int->Word"  fromIntegral = \(I# x#) -> W# (int2Word# x#)
169 "fromIntegral/Word->Int"  fromIntegral = \(W# x#) -> I# (word2Int# x#)
170 "fromIntegral/Word->Word" fromIntegral = id :: Word -> Word
171     #-}
172
173 ------------------------------------------------------------------------
174 -- type Word8
175 ------------------------------------------------------------------------
176
177 -- Word8 is represented in the same way as Word. Operations may assume
178 -- and must ensure that it holds only values from its logical range.
179
180 data Word8 = W8# Word# deriving (Eq, Ord)
181
182 instance CCallable Word8
183 instance CReturnable Word8
184
185 instance Show Word8 where
186     showsPrec p x = showsPrec p (fromIntegral x :: Int)
187
188 instance Num Word8 where
189     (W8# x#) + (W8# y#)    = W8# (wordToWord8# (x# `plusWord#` y#))
190     (W8# x#) - (W8# y#)    = W8# (wordToWord8# (x# `minusWord#` y#))
191     (W8# x#) * (W8# y#)    = W8# (wordToWord8# (x# `timesWord#` y#))
192     negate (W8# x#)        = W8# (wordToWord8# (int2Word# (negateInt# (word2Int# x#))))
193     abs x                  = x
194     signum 0               = 0
195     signum _               = 1
196     fromInteger (S# i#)    = W8# (wordToWord8# (int2Word# i#))
197     fromInteger (J# s# d#) = W8# (wordToWord8# (integer2Word# s# d#))
198
199 instance Real Word8 where
200     toRational x = toInteger x % 1
201
202 instance Enum Word8 where
203     succ x
204         | x /= maxBound = x + 1
205         | otherwise     = succError "Word8"
206     pred x
207         | x /= minBound = x - 1
208         | otherwise     = predError "Word8"
209     toEnum i@(I# i#)
210         | i >= 0 && i <= fromIntegral (maxBound::Word8)
211                         = W8# (int2Word# i#)
212         | otherwise     = toEnumError "Word8" i (minBound::Word8, maxBound::Word8)
213     fromEnum (W8# x#)   = I# (word2Int# x#)
214     enumFrom            = boundedEnumFrom
215     enumFromThen        = boundedEnumFromThen
216
217 instance Integral Word8 where
218     quot    x@(W8# x#) y@(W8# y#)
219         | y /= 0                  = W8# (x# `quotWord#` y#)
220         | otherwise               = divZeroError "quot{Word8}" x
221     rem     x@(W8# x#) y@(W8# y#)
222         | y /= 0                  = W8# (x# `remWord#` y#)
223         | otherwise               = divZeroError "rem{Word8}" x
224     div     x@(W8# x#) y@(W8# y#)
225         | y /= 0                  = W8# (x# `quotWord#` y#)
226         | otherwise               = divZeroError "div{Word8}" x
227     mod     x@(W8# x#) y@(W8# y#)
228         | y /= 0                  = W8# (x# `remWord#` y#)
229         | otherwise               = divZeroError "mod{Word8}" x
230     quotRem x@(W8# x#) y@(W8# y#)
231         | y /= 0                  = (W8# (x# `quotWord#` y#), W8# (x# `remWord#` y#))
232         | otherwise               = divZeroError "quotRem{Word8}" x
233     divMod  x@(W8# x#) y@(W8# y#)
234         | y /= 0                  = (W8# (x# `quotWord#` y#), W8# (x# `remWord#` y#))
235         | otherwise               = divZeroError "quotRem{Word8}" x
236     toInteger (W8# x#)            = S# (word2Int# x#)
237
238 instance Bounded Word8 where
239     minBound = 0
240     maxBound = 0xFF
241
242 instance Ix Word8 where
243     range (m,n)       = [m..n]
244     index b@(m,_) i
245         | inRange b i = fromIntegral (i - m)
246         | otherwise   = indexError b i "Word8"
247     inRange (m,n) i   = m <= i && i <= n
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# (wordToWord8# (x# `shiftL#` i#))
259         | otherwise           = W8# (x# `shiftRL#` negateInt# i#)
260     (W8# x#) `rotate` (I# i#) = W8# (wordToWord8# ((x# `shiftL#` i'#) `or#`
261                                                    (x# `shiftRL#` (8# -# i'#))))
262         where
263         i'# = word2Int# (int2Word# i# `and#` int2Word# 7#)
264     bitSize  _                = 8
265     isSigned _                = False
266
267 {-# RULES
268 "fromIntegral/a->Word8" fromIntegral = \x -> case fromIntegral x of W# x# -> W8# (wordToWord8# 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# (wordToWord16# (x# `plusWord#` y#))
289     (W16# x#) - (W16# y#)  = W16# (wordToWord16# (x# `minusWord#` y#))
290     (W16# x#) * (W16# y#)  = W16# (wordToWord16# (x# `timesWord#` y#))
291     negate (W16# x#)       = W16# (wordToWord16# (int2Word# (negateInt# (word2Int# x#))))
292     abs x                  = x
293     signum 0               = 0
294     signum _               = 1
295     fromInteger (S# i#)    = W16# (wordToWord16# (int2Word# i#))
296     fromInteger (J# s# d#) = W16# (wordToWord16# (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     index b@(m,_) i
344         | inRange b i = fromIntegral (i - m)
345         | otherwise   = indexError b i "Word16"
346     inRange (m,n) i   = m <= i && i <= n
347
348 instance Read Word16 where
349     readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
350
351 instance Bits Word16 where
352     (W16# x#) .&.   (W16# y#)  = W16# (x# `and#` y#)
353     (W16# x#) .|.   (W16# y#)  = W16# (x# `or#`  y#)
354     (W16# x#) `xor` (W16# y#)  = W16# (x# `xor#` y#)
355     complement (W16# x#)       = W16# (x# `xor#` mb#) where W16# mb# = maxBound
356     (W16# x#) `shift` (I# i#)
357         | i# >=# 0#            = W16# (wordToWord16# (x# `shiftL#` i#))
358         | otherwise            = W16# (x# `shiftRL#` negateInt# i#)
359     (W16# x#) `rotate` (I# i#) = W16# (wordToWord16# ((x# `shiftL#` i'#) `or#`
360                                                       (x# `shiftRL#` (16# -# i'#))))
361         where
362         i'# = word2Int# (int2Word# i# `and#` int2Word# 15#)
363     bitSize  _                = 16
364     isSigned _                = False
365
366 {-# RULES
367 "fromIntegral/a->Word16" fromIntegral = \x -> case fromIntegral x of W# x# -> W16# (wordToWord16# x#)
368 "fromIntegral/Word16->a" fromIntegral = \(W16# x#) -> fromIntegral (W# x#)
369     #-}
370
371 ------------------------------------------------------------------------
372 -- type Word32
373 ------------------------------------------------------------------------
374
375 -- Word32 is represented in the same way as Word.
376 #if WORD_SIZE_IN_BYTES == 8
377 -- Operations may assume and must ensure that it holds only values
378 -- from its logical range.
379 #endif
380
381 data Word32 = W32# Word# deriving (Eq, Ord)
382
383 #if WORD_SIZE_IN_BYTES == 4
384 {-# RULES "wordToWord32#" forall x#. wordToWord32# x# = x# #-}
385 #endif
386
387 instance CCallable Word32
388 instance CReturnable Word32
389
390 instance Show Word32 where
391 #if WORD_SIZE_IN_BYTES == 4
392     showsPrec p x = showsPrec p (toInteger x)
393 #else
394     showsPrec p x = showsPrec p (fromIntegral x :: Int)
395 #endif
396
397 instance Num Word32 where
398     (W32# x#) + (W32# y#)  = W32# (wordToWord32# (x# `plusWord#` y#))
399     (W32# x#) - (W32# y#)  = W32# (wordToWord32# (x# `minusWord#` y#))
400     (W32# x#) * (W32# y#)  = W32# (wordToWord32# (x# `timesWord#` y#))
401     negate (W32# x#)       = W32# (wordToWord32# (int2Word# (negateInt# (word2Int# x#))))
402     abs x                  = x
403     signum 0               = 0
404     signum _               = 1
405     fromInteger (S# i#)    = W32# (wordToWord32# (int2Word# i#))
406     fromInteger (J# s# d#) = W32# (wordToWord32# (integer2Word# s# d#))
407
408 instance Real Word32 where
409     toRational x = toInteger x % 1
410
411 instance Enum Word32 where
412     succ x
413         | x /= maxBound = x + 1
414         | otherwise     = succError "Word32"
415     pred x
416         | x /= minBound = x - 1
417         | otherwise     = predError "Word32"
418     toEnum i@(I# i#)
419         | i >= 0
420 #if WORD_SIZE_IN_BYTES == 8
421           && i <= fromIntegral (maxBound::Word32)
422 #endif
423                         = W32# (int2Word# i#)
424         | otherwise     = toEnumError "Word32" i (minBound::Word32, maxBound::Word32)
425 #if WORD_SIZE_IN_BYTES == 4
426     fromEnum x@(W32# x#)
427         | x <= fromIntegral (maxBound::Int)
428                         = I# (word2Int# x#)
429         | otherwise     = fromEnumError "Word32" x
430     enumFrom            = integralEnumFrom
431     enumFromThen        = integralEnumFromThen
432     enumFromTo          = integralEnumFromTo
433     enumFromThenTo      = integralEnumFromThenTo
434 #else
435     fromEnum (W32# x#)  = I# (word2Int# x#)
436     enumFrom            = boundedEnumFrom
437     enumFromThen        = boundedEnumFromThen
438 #endif
439
440 instance Integral Word32 where
441     quot    x@(W32# x#) y@(W32# y#)
442         | y /= 0                    = W32# (x# `quotWord#` y#)
443         | otherwise                 = divZeroError "quot{Word32}" x
444     rem     x@(W32# x#) y@(W32# y#)
445         | y /= 0                    = W32# (x# `remWord#` y#)
446         | otherwise                 = divZeroError "rem{Word32}" x
447     div     x@(W32# x#) y@(W32# y#)
448         | y /= 0                    = W32# (x# `quotWord#` y#)
449         | otherwise                 = divZeroError "div{Word32}" x
450     mod     x@(W32# x#) y@(W32# y#)
451         | y /= 0                    = W32# (x# `remWord#` y#)
452         | otherwise                 = divZeroError "mod{Word32}" x
453     quotRem x@(W32# x#) y@(W32# y#)
454         | y /= 0                    = (W32# (x# `quotWord#` y#), W32# (x# `remWord#` y#))
455         | otherwise                 = divZeroError "quotRem{Word32}" x
456     divMod  x@(W32# x#) y@(W32# y#)
457         | y /= 0                    = (W32# (x# `quotWord#` y#), W32# (x# `remWord#` y#))
458         | otherwise                 = divZeroError "quotRem{Word32}" x
459     toInteger (W32# x#)
460 #if WORD_SIZE_IN_BYTES == 4
461         | i# >=# 0#                 = S# i#
462         | otherwise                 = case word2Integer# x# of (# s, d #) -> J# s d
463         where
464         i# = word2Int# x#
465 #else
466                                     = S# (word2Int# x#)
467 #endif
468
469 instance Bounded Word32 where
470     minBound = 0
471     maxBound = 0xFFFFFFFF
472
473 instance Ix Word32 where
474     range (m,n)       = [m..n]
475     index b@(m,_) i
476         | inRange b i = fromIntegral (i - m)
477         | otherwise   = indexError b i "Word32"
478     inRange (m,n) i   = m <= i && i <= n
479
480 instance Read Word32 where
481 #if WORD_SIZE_IN_BYTES == 4
482     readsPrec p s = [(fromInteger x, r) | (x, r) <- readsPrec p s]
483 #else
484     readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
485 #endif
486
487 instance Bits Word32 where
488     (W32# x#) .&.   (W32# y#)  = W32# (x# `and#` y#)
489     (W32# x#) .|.   (W32# y#)  = W32# (x# `or#`  y#)
490     (W32# x#) `xor` (W32# y#)  = W32# (x# `xor#` y#)
491     complement (W32# x#)       = W32# (x# `xor#` mb#) where W32# mb# = maxBound
492     (W32# x#) `shift` (I# i#)
493         | i# >=# 0#            = W32# (wordToWord32# (x# `shiftL#` i#))
494         | otherwise            = W32# (x# `shiftRL#` negateInt# i#)
495     (W32# x#) `rotate` (I# i#) = W32# (wordToWord32# ((x# `shiftL#` i'#) `or#`
496                                                       (x# `shiftRL#` (32# -# i'#))))
497         where
498         i'# = word2Int# (int2Word# i# `and#` int2Word# 31#)
499     bitSize  _                = 32
500     isSigned _                = False
501
502 {-# RULES
503 "fromIntegral/a->Word32" fromIntegral = \x -> case fromIntegral x of W# x# -> W32# (wordToWord32# x#)
504 "fromIntegral/Word32->a" fromIntegral = \(W32# x#) -> fromIntegral (W# x#)
505     #-}
506
507 ------------------------------------------------------------------------
508 -- type Word64
509 ------------------------------------------------------------------------
510
511 #if WORD_SIZE_IN_BYTES == 4
512
513 data Word64 = W64# Word64#
514
515 instance Eq Word64 where
516     (W64# x#) == (W64# y#) = x# `eqWord64#` y#
517     (W64# x#) /= (W64# y#) = x# `neWord64#` y#
518
519 instance Ord Word64 where
520     (W64# x#) <  (W64# y#) = x# `ltWord64#` y#
521     (W64# x#) <= (W64# y#) = x# `leWord64#` y#
522     (W64# x#) >  (W64# y#) = x# `gtWord64#` y#
523     (W64# x#) >= (W64# y#) = x# `geWord64#` y#
524
525 instance Num Word64 where
526     (W64# x#) + (W64# y#)  = W64# (int64ToWord64# (word64ToInt64# x# `plusInt64#` word64ToInt64# y#))
527     (W64# x#) - (W64# y#)  = W64# (int64ToWord64# (word64ToInt64# x# `minusInt64#` word64ToInt64# y#))
528     (W64# x#) * (W64# y#)  = W64# (int64ToWord64# (word64ToInt64# x# `timesInt64#` word64ToInt64# y#))
529     negate (W64# x#)       = W64# (int64ToWord64# (negateInt64# (word64ToInt64# x#)))
530     abs x                  = x
531     signum 0               = 0
532     signum _               = 1
533     fromInteger (S# i#)    = W64# (int64ToWord64# (intToInt64# i#))
534     fromInteger (J# s# d#) = W64# (integerToWord64# s# d#)
535
536 instance Enum Word64 where
537     succ x
538         | x /= maxBound = x + 1
539         | otherwise     = succError "Word64"
540     pred x
541         | x /= minBound = x - 1
542         | otherwise     = predError "Word64"
543     toEnum i@(I# i#)
544         | i >= 0        = W64# (wordToWord64# (int2Word# i#))
545         | otherwise     = toEnumError "Word64" i (minBound::Word64, maxBound::Word64)
546     fromEnum x@(W64# x#)
547         | x <= fromIntegral (maxBound::Int)
548                         = I# (word2Int# (word64ToWord# x#))
549         | otherwise     = fromEnumError "Word64" x
550     enumFrom            = integralEnumFrom
551     enumFromThen        = integralEnumFromThen
552     enumFromTo          = integralEnumFromTo
553     enumFromThenTo      = integralEnumFromThenTo
554
555 instance Integral Word64 where
556     quot    x@(W64# x#) y@(W64# y#)
557         | y /= 0                    = W64# (x# `quotWord64#` y#)
558         | otherwise                 = divZeroError "quot{Word64}" x
559     rem     x@(W64# x#) y@(W64# y#)
560         | y /= 0                    = W64# (x# `remWord64#` y#)
561         | otherwise                 = divZeroError "rem{Word64}" x
562     div     x@(W64# x#) y@(W64# y#)
563         | y /= 0                    = W64# (x# `quotWord64#` y#)
564         | otherwise                 = divZeroError "div{Word64}" x
565     mod     x@(W64# x#) y@(W64# y#)
566         | y /= 0                    = W64# (x# `remWord64#` y#)
567         | otherwise                 = divZeroError "mod{Word64}" x
568     quotRem x@(W64# x#) y@(W64# y#)
569         | y /= 0                    = (W64# (x# `quotWord64#` y#), W64# (x# `remWord64#` y#))
570         | otherwise                 = divZeroError "quotRem{Word64}" x
571     divMod  x@(W64# x#) y@(W64# y#)
572         | y /= 0                    = (W64# (x# `quotWord64#` y#), W64# (x# `remWord64#` y#))
573         | otherwise                 = divZeroError "quotRem{Word64}" x
574     toInteger x@(W64# x#)
575         | x <= 0x7FFFFFFF           = S# (word2Int# (word64ToWord# x#))
576         | otherwise                 = case word64ToInteger# x# of (# s, d #) -> J# s d
577
578 instance Bits Word64 where
579     (W64# x#) .&.   (W64# y#)  = W64# (x# `and64#` y#)
580     (W64# x#) .|.   (W64# y#)  = W64# (x# `or64#`  y#)
581     (W64# x#) `xor` (W64# y#)  = W64# (x# `xor64#` y#)
582     complement (W64# x#)       = W64# (not64# x#)
583     (W64# x#) `shift` (I# i#)
584         | i# >=# 0#            = W64# (x# `shiftL64#` i#)
585         | otherwise            = W64# (x# `shiftRL64#` negateInt# i#)
586     (W64# x#) `rotate` (I# i#) = W64# ((x# `shiftL64#` i'#) `or64#`
587                                        (x# `shiftRL64#` (64# -# i'#)))
588         where
589         i'# = word2Int# (int2Word# i# `and#` int2Word# 63#)
590     bitSize  _                = 64
591     isSigned _                = False
592
593 foreign import "stg_eqWord64"      unsafe eqWord64#      :: Word64# -> Word64# -> Bool
594 foreign import "stg_neWord64"      unsafe neWord64#      :: Word64# -> Word64# -> Bool
595 foreign import "stg_ltWord64"      unsafe ltWord64#      :: Word64# -> Word64# -> Bool
596 foreign import "stg_leWord64"      unsafe leWord64#      :: Word64# -> Word64# -> Bool
597 foreign import "stg_gtWord64"      unsafe gtWord64#      :: Word64# -> Word64# -> Bool
598 foreign import "stg_geWord64"      unsafe geWord64#      :: Word64# -> Word64# -> Bool
599 foreign import "stg_int64ToWord64" unsafe int64ToWord64# :: Int64# -> Word64#
600 foreign import "stg_word64ToInt64" unsafe word64ToInt64# :: Word64# -> Int64#
601 foreign import "stg_plusInt64"     unsafe plusInt64#     :: Int64# -> Int64# -> Int64#
602 foreign import "stg_minusInt64"    unsafe minusInt64#    :: Int64# -> Int64# -> Int64#
603 foreign import "stg_timesInt64"    unsafe timesInt64#    :: Int64# -> Int64# -> Int64#
604 foreign import "stg_negateInt64"   unsafe negateInt64#   :: Int64# -> Int64#
605 foreign import "stg_intToInt64"    unsafe intToInt64#    :: Int# -> Int64#
606 foreign import "stg_wordToWord64"  unsafe wordToWord64#  :: Word# -> Word64#
607 foreign import "stg_word64ToWord"  unsafe word64ToWord#  :: Word64# -> Word#
608 foreign import "stg_quotWord64"    unsafe quotWord64#    :: Word64# -> Word64# -> Word64#
609 foreign import "stg_remWord64"     unsafe remWord64#     :: Word64# -> Word64# -> Word64#
610 foreign import "stg_and64"         unsafe and64#         :: Word64# -> Word64# -> Word64#
611 foreign import "stg_or64"          unsafe or64#          :: Word64# -> Word64# -> Word64#
612 foreign import "stg_xor64"         unsafe xor64#         :: Word64# -> Word64# -> Word64#
613 foreign import "stg_not64"         unsafe not64#         :: Word64# -> Word64#
614 foreign import "stg_shiftL64"      unsafe shiftL64#      :: Word64# -> Int# -> Word64#
615 foreign import "stg_shiftRL64"     unsafe shiftRL64#     :: Word64# -> Int# -> Word64#
616
617 {-# RULES
618 "fromIntegral/Int->Word64"    fromIntegral = \(I#   x#) -> W64# (int64ToWord64# (intToInt64# x#))
619 "fromIntegral/Word->Word64"   fromIntegral = \(W#   x#) -> W64# (wordToWord64# x#)
620 "fromIntegral/Word64->Int"    fromIntegral = \(W64# x#) -> I#   (word2Int# (word64ToWord# x#))
621 "fromIntegral/Word64->Word"   fromIntegral = \(W64# x#) -> W#   (word64ToWord# x#)
622 "fromIntegral/Word64->Word64" fromIntegral = id :: Word64 -> Word64
623     #-}
624
625 #else
626
627 data Word32 = W64# Word# deriving (Eq, Ord)
628
629 instance Num Word64 where
630     (W64# x#) + (W64# y#)  = W64# (x# `plusWord#` y#)
631     (W64# x#) - (W64# y#)  = W64# (x# `minusWord#` y#)
632     (W64# x#) * (W64# y#)  = W64# (x# `timesWord#` y#)
633     negate (W64# x#)       = W64# (int2Word# (negateInt# (word2Int# x#)))
634     abs x                  = x
635     signum 0               = 0
636     signum _               = 1
637     fromInteger (S# i#)    = W64# (int2Word# i#)
638     fromInteger (J# s# d#) = W64# (integer2Word# s# d#)
639
640 instance Enum Word64 where
641     succ x
642         | x /= maxBound = x + 1
643         | otherwise     = succError "Word64"
644     pred x
645         | x /= minBound = x - 1
646         | otherwise     = predError "Word64"
647     toEnum i@(I# i#)
648         | i >= 0        = W64# (int2Word# i#)
649         | otherwise     = toEnumError "Word64" i (minBound::Word64, maxBound::Word64)
650     fromEnum x@(W64# x#)
651         | x <= fromIntegral (maxBound::Int)
652                         = I# (word2Int# x#)
653         | otherwise     = fromEnumError "Word64" x
654     enumFrom            = integralEnumFrom
655     enumFromThen        = integralEnumFromThen
656     enumFromTo          = integralEnumFromTo
657     enumFromThenTo      = integralEnumFromThenTo
658
659 instance Integral Word64 where
660     quot    x@(W64# x#) y@(W64# y#)
661         | y /= 0                    = W64# (x# `quotWord#` y#)
662         | otherwise                 = divZeroError "quot{Word64}" x
663     rem     x@(W64# x#) y@(W64# y#)
664         | y /= 0                    = W64# (x# `remWord#` y#)
665         | otherwise                 = divZeroError "rem{Word64}" x
666     div     x@(W64# x#) y@(W64# y#)
667         | y /= 0                    = W64# (x# `quotWord#` y#)
668         | otherwise                 = divZeroError "div{Word64}" x
669     mod     x@(W64# x#) y@(W64# y#)
670         | y /= 0                    = W64# (x# `remWord#` y#)
671         | otherwise                 = divZeroError "mod{Word64}" x
672     quotRem x@(W64# x#) y@(W64# y#)
673         | y /= 0                    = (W64# (x# `quotWord#` y#), W64# (x# `remWord#` y#))
674         | otherwise                 = divZeroError "quotRem{Word64}" x
675     divMod  x@(W64# x#) y@(W64# y#)
676         | y /= 0                    = (W64# (x# `quotWord#` y#), W64# (x# `remWord#` y#))
677         | otherwise                 = divZeroError "quotRem{Word64}" x
678     toInteger (W64# x#)
679         | i# >=# 0#                 = S# i#
680         | otherwise                 = case word2Integer# x# of (# s, d #) -> J# s d
681         where
682         i# = word2Int# x#
683
684 instance Bits Word64 where
685     (W64# x#) .&.   (W64# y#)  = W64# (x# `and#` y#)
686     (W64# x#) .|.   (W64# y#)  = W64# (x# `or#`  y#)
687     (W64# x#) `xor` (W64# y#)  = W64# (x# `xor#` y#)
688     complement (W64# x#)       = W64# (x# `xor#` mb#) where W64# mb# = maxBound
689     (W64# x#) `shift` (I# i#)
690         | i# >=# 0#            = W64# (x# `shiftL#` i#)
691         | otherwise            = W64# (x# `shiftRL#` negateInt# i#)
692     (W64# x#) `rotate` (I# i#) = W64# ((x# `shiftL#` i'#) `or#`
693                                        (x# `shiftRL#` (64# -# i'#)))
694         where
695         i'# = word2Int# (int2Word# i# `and#` int2Word# 63#)
696     bitSize  _                = 64
697     isSigned _                = False
698
699 {-# RULES
700 "fromIntegral/a->Word64" fromIntegral = \x -> case fromIntegral x of W# x# -> W64# x#
701 "fromIntegral/Word64->a" fromIntegral = \(W64# x#) -> fromIntegral (W# x#)
702     #-}
703
704 #endif
705
706 instance CCallable Word64
707 instance CReturnable Word64
708
709 instance Show Word64 where
710     showsPrec p x = showsPrec p (toInteger x)
711
712 instance Real Word64 where
713     toRational x = toInteger x % 1
714
715 instance Bounded Word64 where
716     minBound = 0
717     maxBound = 0xFFFFFFFFFFFFFFFF
718
719 instance Ix Word64 where
720     range (m,n)       = [m..n]
721     index b@(m,_) i
722         | inRange b i = fromIntegral (i - m)
723         | otherwise   = indexError b i "Word64"
724     inRange (m,n) i   = m <= i && i <= n
725
726 instance Read Word64 where
727     readsPrec p s = [(fromInteger x, r) | (x, r) <- readsPrec p s]
728 \end{code}