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