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