d2e44debd77bd097beafb7e95ce682693434361b
[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/Word8->Word8"   fromIntegral = id :: Word8 -> Word8
269 "fromIntegral/Word8->Integer" fromIntegral = toInteger :: Word8 -> Integer
270 "fromIntegral/a->Word8"       fromIntegral = \x -> case fromIntegral x of W# x# -> W8# (wordToWord8# x#)
271 "fromIntegral/Word8->a"       fromIntegral = \(W8# x#) -> fromIntegral (W# x#)
272   #-}
273
274 ------------------------------------------------------------------------
275 -- type Word16
276 ------------------------------------------------------------------------
277
278 -- Word16 is represented in the same way as Word. Operations may assume
279 -- and must ensure that it holds only values from its logical range.
280
281 data Word16 = W16# Word# deriving (Eq, Ord)
282
283 instance CCallable Word16
284 instance CReturnable Word16
285
286 instance Show Word16 where
287     showsPrec p x = showsPrec p (fromIntegral x :: Int)
288
289 instance Num Word16 where
290     (W16# x#) + (W16# y#)  = W16# (wordToWord16# (x# `plusWord#` y#))
291     (W16# x#) - (W16# y#)  = W16# (wordToWord16# (x# `minusWord#` y#))
292     (W16# x#) * (W16# y#)  = W16# (wordToWord16# (x# `timesWord#` y#))
293     negate (W16# x#)       = W16# (wordToWord16# (int2Word# (negateInt# (word2Int# x#))))
294     abs x                  = x
295     signum 0               = 0
296     signum _               = 1
297     fromInteger (S# i#)    = W16# (wordToWord16# (int2Word# i#))
298     fromInteger (J# s# d#) = W16# (wordToWord16# (integer2Word# s# d#))
299
300 instance Real Word16 where
301     toRational x = toInteger x % 1
302
303 instance Enum Word16 where
304     succ x
305         | x /= maxBound = x + 1
306         | otherwise     = succError "Word16"
307     pred x
308         | x /= minBound = x - 1
309         | otherwise     = predError "Word16"
310     toEnum i@(I# i#)
311         | i >= 0 && i <= fromIntegral (maxBound::Word16)
312                         = W16# (int2Word# i#)
313         | otherwise     = toEnumError "Word16" i (minBound::Word16, maxBound::Word16)
314     fromEnum (W16# x#)  = I# (word2Int# x#)
315     enumFrom            = boundedEnumFrom
316     enumFromThen        = boundedEnumFromThen
317
318 instance Integral Word16 where
319     quot    x@(W16# x#) y@(W16# y#)
320         | y /= 0                    = W16# (x# `quotWord#` y#)
321         | otherwise                 = divZeroError "quot{Word16}" x
322     rem     x@(W16# x#) y@(W16# y#)
323         | y /= 0                    = W16# (x# `remWord#` y#)
324         | otherwise                 = divZeroError "rem{Word16}" x
325     div     x@(W16# x#) y@(W16# y#)
326         | y /= 0                    = W16# (x# `quotWord#` y#)
327         | otherwise                 = divZeroError "div{Word16}" x
328     mod     x@(W16# x#) y@(W16# y#)
329         | y /= 0                    = W16# (x# `remWord#` y#)
330         | otherwise                 = divZeroError "mod{Word16}" x
331     quotRem x@(W16# x#) y@(W16# y#)
332         | y /= 0                    = (W16# (x# `quotWord#` y#), W16# (x# `remWord#` y#))
333         | otherwise                 = divZeroError "quotRem{Word16}" x
334     divMod  x@(W16# x#) y@(W16# y#)
335         | y /= 0                    = (W16# (x# `quotWord#` y#), W16# (x# `remWord#` y#))
336         | otherwise                 = divZeroError "quotRem{Word16}" x
337     toInteger (W16# x#)             = S# (word2Int# x#)
338
339 instance Bounded Word16 where
340     minBound = 0
341     maxBound = 0xFFFF
342
343 instance Ix Word16 where
344     range (m,n)       = [m..n]
345     index b@(m,_) i
346         | inRange b i = fromIntegral (i - m)
347         | otherwise   = indexError b i "Word16"
348     inRange (m,n) i   = m <= i && i <= n
349
350 instance Read Word16 where
351     readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
352
353 instance Bits Word16 where
354     (W16# x#) .&.   (W16# y#)  = W16# (x# `and#` y#)
355     (W16# x#) .|.   (W16# y#)  = W16# (x# `or#`  y#)
356     (W16# x#) `xor` (W16# y#)  = W16# (x# `xor#` y#)
357     complement (W16# x#)       = W16# (x# `xor#` mb#) where W16# mb# = maxBound
358     (W16# x#) `shift` (I# i#)
359         | i# >=# 0#            = W16# (wordToWord16# (x# `shiftL#` i#))
360         | otherwise            = W16# (x# `shiftRL#` negateInt# i#)
361     (W16# x#) `rotate` (I# i#) = W16# (wordToWord16# ((x# `shiftL#` i'#) `or#`
362                                                       (x# `shiftRL#` (16# -# i'#))))
363         where
364         i'# = word2Int# (int2Word# i# `and#` int2Word# 15#)
365     bitSize  _                = 16
366     isSigned _                = False
367
368 {-# RULES
369 "fromIntegral/Word8->Word16"   fromIntegral = \(W8# x#) -> W16# x#
370 "fromIntegral/Word16->Word16"  fromIntegral = id :: Word16 -> Word16
371 "fromIntegral/Word16->Integer" fromIntegral = toInteger :: Word16 -> Integer
372 "fromIntegral/a->Word16"       fromIntegral = \x -> case fromIntegral x of W# x# -> W16# (wordToWord16# x#)
373 "fromIntegral/Word16->a"       fromIntegral = \(W16# x#) -> fromIntegral (W# x#)
374   #-}
375
376 ------------------------------------------------------------------------
377 -- type Word32
378 ------------------------------------------------------------------------
379
380 -- Word32 is represented in the same way as Word.
381 #if WORD_SIZE_IN_BYTES == 8
382 -- Operations may assume and must ensure that it holds only values
383 -- from its logical range.
384 #endif
385
386 data Word32 = W32# Word# deriving (Eq, Ord)
387
388 instance CCallable Word32
389 instance CReturnable Word32
390
391 instance Show Word32 where
392 #if WORD_SIZE_IN_BYTES == 4
393     showsPrec p x = showsPrec p (toInteger x)
394 #else
395     showsPrec p x = showsPrec p (fromIntegral x :: Int)
396 #endif
397
398 instance Num Word32 where
399     (W32# x#) + (W32# y#)  = W32# (wordToWord32# (x# `plusWord#` y#))
400     (W32# x#) - (W32# y#)  = W32# (wordToWord32# (x# `minusWord#` y#))
401     (W32# x#) * (W32# y#)  = W32# (wordToWord32# (x# `timesWord#` y#))
402     negate (W32# x#)       = W32# (wordToWord32# (int2Word# (negateInt# (word2Int# x#))))
403     abs x                  = x
404     signum 0               = 0
405     signum _               = 1
406     fromInteger (S# i#)    = W32# (wordToWord32# (int2Word# i#))
407     fromInteger (J# s# d#) = W32# (wordToWord32# (integer2Word# s# d#))
408
409 instance Real Word32 where
410     toRational x = toInteger x % 1
411
412 instance Enum Word32 where
413     succ x
414         | x /= maxBound = x + 1
415         | otherwise     = succError "Word32"
416     pred x
417         | x /= minBound = x - 1
418         | otherwise     = predError "Word32"
419     toEnum i@(I# i#)
420         | i >= 0
421 #if WORD_SIZE_IN_BYTES == 8
422           && i <= fromIntegral (maxBound::Word32)
423 #endif
424                         = W32# (int2Word# i#)
425         | otherwise     = toEnumError "Word32" i (minBound::Word32, maxBound::Word32)
426 #if WORD_SIZE_IN_BYTES == 4
427     fromEnum x@(W32# x#)
428         | x <= fromIntegral (maxBound::Int)
429                         = I# (word2Int# x#)
430         | otherwise     = fromEnumError "Word32" x
431     enumFrom            = integralEnumFrom
432     enumFromThen        = integralEnumFromThen
433     enumFromTo          = integralEnumFromTo
434     enumFromThenTo      = integralEnumFromThenTo
435 #else
436     fromEnum (W32# x#)  = I# (word2Int# x#)
437     enumFrom            = boundedEnumFrom
438     enumFromThen        = boundedEnumFromThen
439 #endif
440
441 instance Integral Word32 where
442     quot    x@(W32# x#) y@(W32# y#)
443         | y /= 0                    = W32# (x# `quotWord#` y#)
444         | otherwise                 = divZeroError "quot{Word32}" x
445     rem     x@(W32# x#) y@(W32# y#)
446         | y /= 0                    = W32# (x# `remWord#` y#)
447         | otherwise                 = divZeroError "rem{Word32}" x
448     div     x@(W32# x#) y@(W32# y#)
449         | y /= 0                    = W32# (x# `quotWord#` y#)
450         | otherwise                 = divZeroError "div{Word32}" x
451     mod     x@(W32# x#) y@(W32# y#)
452         | y /= 0                    = W32# (x# `remWord#` y#)
453         | otherwise                 = divZeroError "mod{Word32}" x
454     quotRem x@(W32# x#) y@(W32# y#)
455         | y /= 0                    = (W32# (x# `quotWord#` y#), W32# (x# `remWord#` y#))
456         | otherwise                 = divZeroError "quotRem{Word32}" x
457     divMod  x@(W32# x#) y@(W32# y#)
458         | y /= 0                    = (W32# (x# `quotWord#` y#), W32# (x# `remWord#` y#))
459         | otherwise                 = divZeroError "quotRem{Word32}" x
460     toInteger (W32# x#)
461 #if WORD_SIZE_IN_BYTES == 4
462         | i# >=# 0#                 = S# i#
463         | otherwise                 = case word2Integer# x# of (# s, d #) -> J# s d
464         where
465         i# = word2Int# x#
466 #else
467                                     = S# (word2Int# x#)
468 #endif
469
470 instance Bounded Word32 where
471     minBound = 0
472     maxBound = 0xFFFFFFFF
473
474 instance Ix Word32 where
475     range (m,n)       = [m..n]
476     index b@(m,_) i
477         | inRange b i = fromIntegral (i - m)
478         | otherwise   = indexError b i "Word32"
479     inRange (m,n) i   = m <= i && i <= n
480
481 instance Read Word32 where
482 #if WORD_SIZE_IN_BYTES == 4
483     readsPrec p s = [(fromInteger x, r) | (x, r) <- readsPrec p s]
484 #else
485     readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
486 #endif
487
488 instance Bits Word32 where
489     (W32# x#) .&.   (W32# y#)  = W32# (x# `and#` y#)
490     (W32# x#) .|.   (W32# y#)  = W32# (x# `or#`  y#)
491     (W32# x#) `xor` (W32# y#)  = W32# (x# `xor#` y#)
492     complement (W32# x#)       = W32# (x# `xor#` mb#) where W32# mb# = maxBound
493     (W32# x#) `shift` (I# i#)
494         | i# >=# 0#            = W32# (wordToWord32# (x# `shiftL#` i#))
495         | otherwise            = W32# (x# `shiftRL#` negateInt# i#)
496     (W32# x#) `rotate` (I# i#) = W32# (wordToWord32# ((x# `shiftL#` i'#) `or#`
497                                                       (x# `shiftRL#` (32# -# i'#))))
498         where
499         i'# = word2Int# (int2Word# i# `and#` int2Word# 31#)
500     bitSize  _                = 32
501     isSigned _                = False
502
503 {-# RULES
504 "fromIntegral/Word8->Word32"   fromIntegral = \(W8# x#) -> W32# x#
505 "fromIntegral/Word16->Word32"  fromIntegral = \(W16# x#) -> W32# x#
506 "fromIntegral/Word32->Word32"  fromIntegral = id :: Word32 -> Word32
507 "fromIntegral/Word32->Integer" fromIntegral = toInteger :: Word32 -> Integer
508 "fromIntegral/a->Word32"       fromIntegral = \x -> case fromIntegral x of W# x# -> W32# (wordToWord32# x#)
509 "fromIntegral/Word32->a"       fromIntegral = \(W32# x#) -> fromIntegral (W# x#)
510   #-}
511
512 ------------------------------------------------------------------------
513 -- type Word64
514 ------------------------------------------------------------------------
515
516 #if WORD_SIZE_IN_BYTES == 4
517
518 data Word64 = W64# Word64#
519
520 instance Eq Word64 where
521     (W64# x#) == (W64# y#) = x# `eqWord64#` y#
522     (W64# x#) /= (W64# y#) = x# `neWord64#` y#
523
524 instance Ord Word64 where
525     (W64# x#) <  (W64# y#) = x# `ltWord64#` y#
526     (W64# x#) <= (W64# y#) = x# `leWord64#` y#
527     (W64# x#) >  (W64# y#) = x# `gtWord64#` y#
528     (W64# x#) >= (W64# y#) = x# `geWord64#` y#
529
530 instance Num Word64 where
531     (W64# x#) + (W64# y#)  = W64# (int64ToWord64# (word64ToInt64# x# `plusInt64#` word64ToInt64# y#))
532     (W64# x#) - (W64# y#)  = W64# (int64ToWord64# (word64ToInt64# x# `minusInt64#` word64ToInt64# y#))
533     (W64# x#) * (W64# y#)  = W64# (int64ToWord64# (word64ToInt64# x# `timesInt64#` word64ToInt64# y#))
534     negate (W64# x#)       = W64# (int64ToWord64# (negateInt64# (word64ToInt64# x#)))
535     abs x                  = x
536     signum 0               = 0
537     signum _               = 1
538     fromInteger (S# i#)    = W64# (int64ToWord64# (intToInt64# i#))
539     fromInteger (J# s# d#) = W64# (integerToWord64# s# d#)
540
541 instance Enum Word64 where
542     succ x
543         | x /= maxBound = x + 1
544         | otherwise     = succError "Word64"
545     pred x
546         | x /= minBound = x - 1
547         | otherwise     = predError "Word64"
548     toEnum i@(I# i#)
549         | i >= 0        = W64# (wordToWord64# (int2Word# i#))
550         | otherwise     = toEnumError "Word64" i (minBound::Word64, maxBound::Word64)
551     fromEnum x@(W64# x#)
552         | x <= fromIntegral (maxBound::Int)
553                         = I# (word2Int# (word64ToWord# x#))
554         | otherwise     = fromEnumError "Word64" x
555     enumFrom            = integralEnumFrom
556     enumFromThen        = integralEnumFromThen
557     enumFromTo          = integralEnumFromTo
558     enumFromThenTo      = integralEnumFromThenTo
559
560 instance Integral Word64 where
561     quot    x@(W64# x#) y@(W64# y#)
562         | y /= 0                    = W64# (x# `quotWord64#` y#)
563         | otherwise                 = divZeroError "quot{Word64}" x
564     rem     x@(W64# x#) y@(W64# y#)
565         | y /= 0                    = W64# (x# `remWord64#` y#)
566         | otherwise                 = divZeroError "rem{Word64}" x
567     div     x@(W64# x#) y@(W64# y#)
568         | y /= 0                    = W64# (x# `quotWord64#` y#)
569         | otherwise                 = divZeroError "div{Word64}" x
570     mod     x@(W64# x#) y@(W64# y#)
571         | y /= 0                    = W64# (x# `remWord64#` y#)
572         | otherwise                 = divZeroError "mod{Word64}" x
573     quotRem x@(W64# x#) y@(W64# y#)
574         | y /= 0                    = (W64# (x# `quotWord64#` y#), W64# (x# `remWord64#` y#))
575         | otherwise                 = divZeroError "quotRem{Word64}" x
576     divMod  x@(W64# x#) y@(W64# y#)
577         | y /= 0                    = (W64# (x# `quotWord64#` y#), W64# (x# `remWord64#` y#))
578         | otherwise                 = divZeroError "quotRem{Word64}" x
579     toInteger x@(W64# x#)
580         | x <= 0x7FFFFFFF           = S# (word2Int# (word64ToWord# x#))
581         | otherwise                 = case word64ToInteger# x# of (# s, d #) -> J# s d
582
583 instance Bits Word64 where
584     (W64# x#) .&.   (W64# y#)  = W64# (x# `and64#` y#)
585     (W64# x#) .|.   (W64# y#)  = W64# (x# `or64#`  y#)
586     (W64# x#) `xor` (W64# y#)  = W64# (x# `xor64#` y#)
587     complement (W64# x#)       = W64# (not64# x#)
588     (W64# x#) `shift` (I# i#)
589         | i# >=# 0#            = W64# (x# `shiftL64#` i#)
590         | otherwise            = W64# (x# `shiftRL64#` negateInt# i#)
591     (W64# x#) `rotate` (I# i#) = W64# ((x# `shiftL64#` i'#) `or64#`
592                                        (x# `shiftRL64#` (64# -# i'#)))
593         where
594         i'# = word2Int# (int2Word# i# `and#` int2Word# 63#)
595     bitSize  _                = 64
596     isSigned _                = False
597
598 foreign import "stg_eqWord64"      unsafe eqWord64#      :: Word64# -> Word64# -> Bool
599 foreign import "stg_neWord64"      unsafe neWord64#      :: Word64# -> Word64# -> Bool
600 foreign import "stg_ltWord64"      unsafe ltWord64#      :: Word64# -> Word64# -> Bool
601 foreign import "stg_leWord64"      unsafe leWord64#      :: Word64# -> Word64# -> Bool
602 foreign import "stg_gtWord64"      unsafe gtWord64#      :: Word64# -> Word64# -> Bool
603 foreign import "stg_geWord64"      unsafe geWord64#      :: Word64# -> Word64# -> Bool
604 foreign import "stg_int64ToWord64" unsafe int64ToWord64# :: Int64# -> Word64#
605 foreign import "stg_word64ToInt64" unsafe word64ToInt64# :: Word64# -> Int64#
606 foreign import "stg_plusInt64"     unsafe plusInt64#     :: Int64# -> Int64# -> Int64#
607 foreign import "stg_minusInt64"    unsafe minusInt64#    :: Int64# -> Int64# -> Int64#
608 foreign import "stg_timesInt64"    unsafe timesInt64#    :: Int64# -> Int64# -> Int64#
609 foreign import "stg_negateInt64"   unsafe negateInt64#   :: Int64# -> Int64#
610 foreign import "stg_intToInt64"    unsafe intToInt64#    :: Int# -> Int64#
611 foreign import "stg_wordToWord64"  unsafe wordToWord64#  :: Word# -> Word64#
612 foreign import "stg_word64ToWord"  unsafe word64ToWord#  :: Word64# -> Word#
613 foreign import "stg_quotWord64"    unsafe quotWord64#    :: Word64# -> Word64# -> Word64#
614 foreign import "stg_remWord64"     unsafe remWord64#     :: Word64# -> Word64# -> Word64#
615 foreign import "stg_and64"         unsafe and64#         :: Word64# -> Word64# -> Word64#
616 foreign import "stg_or64"          unsafe or64#          :: Word64# -> Word64# -> Word64#
617 foreign import "stg_xor64"         unsafe xor64#         :: Word64# -> Word64# -> Word64#
618 foreign import "stg_not64"         unsafe not64#         :: Word64# -> Word64#
619 foreign import "stg_shiftL64"      unsafe shiftL64#      :: Word64# -> Int# -> Word64#
620 foreign import "stg_shiftRL64"     unsafe shiftRL64#     :: Word64# -> Int# -> Word64#
621
622 {-# RULES
623 "fromIntegral/Int->Word64"    fromIntegral = \(I#   x#) -> W64# (int64ToWord64# (intToInt64# x#))
624 "fromIntegral/Word->Word64"   fromIntegral = \(W#   x#) -> W64# (wordToWord64# x#)
625 "fromIntegral/Word64->Int"    fromIntegral = \(W64# x#) -> I#   (word2Int# (word64ToWord# x#))
626 "fromIntegral/Word64->Word"   fromIntegral = \(W64# x#) -> W#   (word64ToWord# x#)
627 "fromIntegral/Word64->Word64" fromIntegral = id :: Word64 -> Word64
628   #-}
629
630 #else
631
632 data Word64 = W64# Word# deriving (Eq, Ord)
633
634 instance Num Word64 where
635     (W64# x#) + (W64# y#)  = W64# (x# `plusWord#` y#)
636     (W64# x#) - (W64# y#)  = W64# (x# `minusWord#` y#)
637     (W64# x#) * (W64# y#)  = W64# (x# `timesWord#` y#)
638     negate (W64# x#)       = W64# (int2Word# (negateInt# (word2Int# x#)))
639     abs x                  = x
640     signum 0               = 0
641     signum _               = 1
642     fromInteger (S# i#)    = W64# (int2Word# i#)
643     fromInteger (J# s# d#) = W64# (integer2Word# s# d#)
644
645 instance Enum Word64 where
646     succ x
647         | x /= maxBound = x + 1
648         | otherwise     = succError "Word64"
649     pred x
650         | x /= minBound = x - 1
651         | otherwise     = predError "Word64"
652     toEnum i@(I# i#)
653         | i >= 0        = W64# (int2Word# i#)
654         | otherwise     = toEnumError "Word64" i (minBound::Word64, maxBound::Word64)
655     fromEnum x@(W64# x#)
656         | x <= fromIntegral (maxBound::Int)
657                         = I# (word2Int# x#)
658         | otherwise     = fromEnumError "Word64" x
659     enumFrom            = integralEnumFrom
660     enumFromThen        = integralEnumFromThen
661     enumFromTo          = integralEnumFromTo
662     enumFromThenTo      = integralEnumFromThenTo
663
664 instance Integral Word64 where
665     quot    x@(W64# x#) y@(W64# y#)
666         | y /= 0                    = W64# (x# `quotWord#` y#)
667         | otherwise                 = divZeroError "quot{Word64}" x
668     rem     x@(W64# x#) y@(W64# y#)
669         | y /= 0                    = W64# (x# `remWord#` y#)
670         | otherwise                 = divZeroError "rem{Word64}" x
671     div     x@(W64# x#) y@(W64# y#)
672         | y /= 0                    = W64# (x# `quotWord#` y#)
673         | otherwise                 = divZeroError "div{Word64}" x
674     mod     x@(W64# x#) y@(W64# y#)
675         | y /= 0                    = W64# (x# `remWord#` y#)
676         | otherwise                 = divZeroError "mod{Word64}" x
677     quotRem x@(W64# x#) y@(W64# y#)
678         | y /= 0                    = (W64# (x# `quotWord#` y#), W64# (x# `remWord#` y#))
679         | otherwise                 = divZeroError "quotRem{Word64}" x
680     divMod  x@(W64# x#) y@(W64# y#)
681         | y /= 0                    = (W64# (x# `quotWord#` y#), W64# (x# `remWord#` y#))
682         | otherwise                 = divZeroError "quotRem{Word64}" x
683     toInteger (W64# x#)
684         | i# >=# 0#                 = S# i#
685         | otherwise                 = case word2Integer# x# of (# s, d #) -> J# s d
686         where
687         i# = word2Int# x#
688
689 instance Bits Word64 where
690     (W64# x#) .&.   (W64# y#)  = W64# (x# `and#` y#)
691     (W64# x#) .|.   (W64# y#)  = W64# (x# `or#`  y#)
692     (W64# x#) `xor` (W64# y#)  = W64# (x# `xor#` y#)
693     complement (W64# x#)       = W64# (x# `xor#` mb#) where W64# mb# = maxBound
694     (W64# x#) `shift` (I# i#)
695         | i# >=# 0#            = W64# (x# `shiftL#` i#)
696         | otherwise            = W64# (x# `shiftRL#` negateInt# i#)
697     (W64# x#) `rotate` (I# i#) = W64# ((x# `shiftL#` i'#) `or#`
698                                        (x# `shiftRL#` (64# -# i'#)))
699         where
700         i'# = word2Int# (int2Word# i# `and#` int2Word# 63#)
701     bitSize  _                = 64
702     isSigned _                = False
703
704 {-# RULES
705 "fromIntegral/a->Word64" fromIntegral = \x -> case fromIntegral x of W# x# -> W64# x#
706 "fromIntegral/Word64->a" fromIntegral = \(W64# x#) -> fromIntegral (W# x#)
707   #-}
708
709 #endif
710
711 instance CCallable Word64
712 instance CReturnable Word64
713
714 instance Show Word64 where
715     showsPrec p x = showsPrec p (toInteger x)
716
717 instance Real Word64 where
718     toRational x = toInteger x % 1
719
720 instance Bounded Word64 where
721     minBound = 0
722     maxBound = 0xFFFFFFFFFFFFFFFF
723
724 instance Ix Word64 where
725     range (m,n)       = [m..n]
726     index b@(m,_) i
727         | inRange b i = fromIntegral (i - m)
728         | otherwise   = indexError b i "Word64"
729     inRange (m,n) i   = m <= i && i <= n
730
731 instance Read Word64 where
732     readsPrec p s = [(fromInteger x, r) | (x, r) <- readsPrec p s]
733 \end{code}