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