[project @ 2002-03-19 11:24:51 by simonmar]
[haskell-directory.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_BITS == 31
136     maxBound = 0x7FFFFFFF
137 #elif WORD_SIZE_IN_BITS == 32
138     maxBound = 0xFFFFFFFF
139 #else
140     maxBound = 0xFFFFFFFFFFFFFFFF
141 #endif
142
143 instance Ix Word where
144     range (m,n)              = [m..n]
145     unsafeIndex b@(m,_) i    = fromIntegral (i - m)
146     inRange (m,n) i          = m <= i && i <= n
147     unsafeRangeSize b@(_l,h) = unsafeIndex b h + 1
148
149 instance Read Word where
150     readsPrec p s = [(fromInteger x, r) | (x, r) <- readsPrec p s]
151
152 instance Bits Word where
153     (W# x#) .&.   (W# y#)    = W# (x# `and#` y#)
154     (W# x#) .|.   (W# y#)    = W# (x# `or#`  y#)
155     (W# x#) `xor` (W# y#)    = W# (x# `xor#` y#)
156     complement (W# x#)       = W# (x# `xor#` mb#) where W# mb# = maxBound
157     (W# x#) `shift` (I# i#)
158         | i# >=# 0#          = W# (x# `shiftL#` i#)
159         | otherwise          = W# (x# `shiftRL#` negateInt# i#)
160     (W# x#) `rotate` (I# i#)
161         | i'# ==# 0# = W# x#
162         | otherwise  = W# ((x# `shiftL#` i'#) `or#` (x# `shiftRL#` (wsib -# i'#)))
163         where
164         i'# = word2Int# (int2Word# i# `and#` int2Word# (wsib -# 1#))
165         wsib = WORD_SIZE_IN_BITS#  {- work around preprocessor problem (??) -}
166     bitSize  _               = WORD_SIZE_IN_BITS
167     isSigned _               = False
168
169 {-# RULES
170 "fromIntegral/Int->Word"  fromIntegral = \(I# x#) -> W# (int2Word# x#)
171 "fromIntegral/Word->Int"  fromIntegral = \(W# x#) -> I# (word2Int# x#)
172 "fromIntegral/Word->Word" fromIntegral = id :: Word -> Word
173   #-}
174
175 ------------------------------------------------------------------------
176 -- type Word8
177 ------------------------------------------------------------------------
178
179 -- Word8 is represented in the same way as Word. Operations may assume
180 -- and must ensure that it holds only values from its logical range.
181
182 data Word8 = W8# Word# deriving (Eq, Ord)
183
184 instance CCallable Word8
185 instance CReturnable Word8
186
187 instance Show Word8 where
188     showsPrec p x = showsPrec p (fromIntegral x :: Int)
189
190 instance Num Word8 where
191     (W8# x#) + (W8# y#)    = W8# (narrow8Word# (x# `plusWord#` y#))
192     (W8# x#) - (W8# y#)    = W8# (narrow8Word# (x# `minusWord#` y#))
193     (W8# x#) * (W8# y#)    = W8# (narrow8Word# (x# `timesWord#` y#))
194     negate (W8# x#)        = W8# (narrow8Word# (int2Word# (negateInt# (word2Int# x#))))
195     abs x                  = x
196     signum 0               = 0
197     signum _               = 1
198     fromInteger (S# i#)    = W8# (narrow8Word# (int2Word# i#))
199     fromInteger (J# s# d#) = W8# (narrow8Word# (integer2Word# s# d#))
200
201 instance Real Word8 where
202     toRational x = toInteger x % 1
203
204 instance Enum Word8 where
205     succ x
206         | x /= maxBound = x + 1
207         | otherwise     = succError "Word8"
208     pred x
209         | x /= minBound = x - 1
210         | otherwise     = predError "Word8"
211     toEnum i@(I# i#)
212         | i >= 0 && i <= fromIntegral (maxBound::Word8)
213                         = W8# (int2Word# i#)
214         | otherwise     = toEnumError "Word8" i (minBound::Word8, maxBound::Word8)
215     fromEnum (W8# x#)   = I# (word2Int# x#)
216     enumFrom            = boundedEnumFrom
217     enumFromThen        = boundedEnumFromThen
218
219 instance Integral Word8 where
220     quot    x@(W8# x#) y@(W8# y#)
221         | y /= 0                  = W8# (x# `quotWord#` y#)
222         | otherwise               = divZeroError "quot{Word8}" x
223     rem     x@(W8# x#) y@(W8# y#)
224         | y /= 0                  = W8# (x# `remWord#` y#)
225         | otherwise               = divZeroError "rem{Word8}" x
226     div     x@(W8# x#) y@(W8# y#)
227         | y /= 0                  = W8# (x# `quotWord#` y#)
228         | otherwise               = divZeroError "div{Word8}" x
229     mod     x@(W8# x#) y@(W8# y#)
230         | y /= 0                  = W8# (x# `remWord#` y#)
231         | otherwise               = divZeroError "mod{Word8}" x
232     quotRem x@(W8# x#) y@(W8# y#)
233         | y /= 0                  = (W8# (x# `quotWord#` y#), W8# (x# `remWord#` y#))
234         | otherwise               = divZeroError "quotRem{Word8}" x
235     divMod  x@(W8# x#) y@(W8# y#)
236         | y /= 0                  = (W8# (x# `quotWord#` y#), W8# (x# `remWord#` y#))
237         | otherwise               = divZeroError "quotRem{Word8}" x
238     toInteger (W8# x#)            = S# (word2Int# x#)
239
240 instance Bounded Word8 where
241     minBound = 0
242     maxBound = 0xFF
243
244 instance Ix Word8 where
245     range (m,n)              = [m..n]
246     unsafeIndex b@(m,_) i    = fromIntegral (i - m)
247     inRange (m,n) i          = m <= i && i <= n
248     unsafeRangeSize b@(_l,h) = unsafeIndex b h + 1
249
250 instance Read Word8 where
251     readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
252
253 instance Bits Word8 where
254     (W8# x#) .&.   (W8# y#)   = W8# (x# `and#` y#)
255     (W8# x#) .|.   (W8# y#)   = W8# (x# `or#`  y#)
256     (W8# x#) `xor` (W8# y#)   = W8# (x# `xor#` y#)
257     complement (W8# x#)       = W8# (x# `xor#` mb#) where W8# mb# = maxBound
258     (W8# x#) `shift` (I# i#)
259         | i# >=# 0#           = W8# (narrow8Word# (x# `shiftL#` i#))
260         | otherwise           = W8# (x# `shiftRL#` negateInt# i#)
261     (W8# x#) `rotate` (I# i#)
262         | i'# ==# 0# = W8# x#
263         | otherwise  = W8# (narrow8Word# ((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# (narrow8Word# 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# (narrow16Word# (x# `plusWord#` y#))
294     (W16# x#) - (W16# y#)  = W16# (narrow16Word# (x# `minusWord#` y#))
295     (W16# x#) * (W16# y#)  = W16# (narrow16Word# (x# `timesWord#` y#))
296     negate (W16# x#)       = W16# (narrow16Word# (int2Word# (negateInt# (word2Int# x#))))
297     abs x                  = x
298     signum 0               = 0
299     signum _               = 1
300     fromInteger (S# i#)    = W16# (narrow16Word# (int2Word# i#))
301     fromInteger (J# s# d#) = W16# (narrow16Word# (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     unsafeIndex b@(m,_) i    = fromIntegral (i - m)
349     inRange (m,n) i          = m <= i && i <= n
350     unsafeRangeSize b@(_l,h) = unsafeIndex b h + 1
351
352 instance Read Word16 where
353     readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
354
355 instance Bits Word16 where
356     (W16# x#) .&.   (W16# y#)  = W16# (x# `and#` y#)
357     (W16# x#) .|.   (W16# y#)  = W16# (x# `or#`  y#)
358     (W16# x#) `xor` (W16# y#)  = W16# (x# `xor#` y#)
359     complement (W16# x#)       = W16# (x# `xor#` mb#) where W16# mb# = maxBound
360     (W16# x#) `shift` (I# i#)
361         | i# >=# 0#            = W16# (narrow16Word# (x# `shiftL#` i#))
362         | otherwise            = W16# (x# `shiftRL#` negateInt# i#)
363     (W16# x#) `rotate` (I# i#)
364         | i'# ==# 0# = W16# x#
365         | otherwise  = W16# (narrow16Word# ((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# (narrow16Word# x#)
377 "fromIntegral/Word16->a"       fromIntegral = \(W16# x#) -> fromIntegral (W# x#)
378   #-}
379
380 ------------------------------------------------------------------------
381 -- type Word32
382 ------------------------------------------------------------------------
383
384 #if WORD_SIZE_IN_BITS < 32
385
386 data Word32 = W32# Word32#
387
388 instance Eq Word32 where
389     (W32# x#) == (W32# y#) = x# `eqWord32#` y#
390     (W32# x#) /= (W32# y#) = x# `neWord32#` y#
391
392 instance Ord Word32 where
393     (W32# x#) <  (W32# y#) = x# `ltWord32#` y#
394     (W32# x#) <= (W32# y#) = x# `leWord32#` y#
395     (W32# x#) >  (W32# y#) = x# `gtWord32#` y#
396     (W32# x#) >= (W32# y#) = x# `geWord32#` y#
397
398 instance Num Word32 where
399     (W32# x#) + (W32# y#)  = W32# (int32ToWord32# (word32ToInt32# x# `plusInt32#` word32ToInt32# y#))
400     (W32# x#) - (W32# y#)  = W32# (int32ToWord32# (word32ToInt32# x# `minusInt32#` word32ToInt32# y#))
401     (W32# x#) * (W32# y#)  = W32# (int32ToWord32# (word32ToInt32# x# `timesInt32#` word32ToInt32# y#))
402     negate (W32# x#)       = W32# (int32ToWord32# (negateInt32# (word32ToInt32# x#)))
403     abs x                  = x
404     signum 0               = 0
405     signum _               = 1
406     fromInteger (S# i#)    = W32# (int32ToWord32# (intToInt32# i#))
407     fromInteger (J# s# d#) = W32# (integerToWord32# s# d#)
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        = W32# (wordToWord32# (int2Word# i#))
418         | otherwise     = toEnumError "Word32" i (minBound::Word32, maxBound::Word32)
419     fromEnum x@(W32# x#)
420         | x <= fromIntegral (maxBound::Int)
421                         = I# (word2Int# (word32ToWord# x#))
422         | otherwise     = fromEnumError "Word32" x
423     enumFrom            = integralEnumFrom
424     enumFromThen        = integralEnumFromThen
425     enumFromTo          = integralEnumFromTo
426     enumFromThenTo      = integralEnumFromThenTo
427
428 instance Integral Word32 where
429     quot    x@(W32# x#) y@(W32# y#)
430         | y /= 0                    = W32# (x# `quotWord32#` y#)
431         | otherwise                 = divZeroError "quot{Word32}" x
432     rem     x@(W32# x#) y@(W32# y#)
433         | y /= 0                    = W32# (x# `remWord32#` y#)
434         | otherwise                 = divZeroError "rem{Word32}" x
435     div     x@(W32# x#) y@(W32# y#)
436         | y /= 0                    = W32# (x# `quotWord32#` y#)
437         | otherwise                 = divZeroError "div{Word32}" x
438     mod     x@(W32# x#) y@(W32# y#)
439         | y /= 0                    = W32# (x# `remWord32#` y#)
440         | otherwise                 = divZeroError "mod{Word32}" x
441     quotRem x@(W32# x#) y@(W32# y#)
442         | y /= 0                    = (W32# (x# `quotWord32#` y#), W32# (x# `remWord32#` y#))
443         | otherwise                 = divZeroError "quotRem{Word32}" x
444     divMod  x@(W32# x#) y@(W32# y#)
445         | y /= 0                    = (W32# (x# `quotWord32#` y#), W32# (x# `remWord32#` y#))
446         | otherwise                 = divZeroError "quotRem{Word32}" x
447     toInteger x@(W32# x#)
448         | x <= fromIntegral (maxBound::Int)  = S# (word2Int# (word32ToWord# x#))
449         | otherwise                 = case word32ToInteger# x# of (# s, d #) -> J# s d
450
451 instance Bits Word32 where
452     (W32# x#) .&.   (W32# y#)  = W32# (x# `and32#` y#)
453     (W32# x#) .|.   (W32# y#)  = W32# (x# `or32#`  y#)
454     (W32# x#) `xor` (W32# y#)  = W32# (x# `xor32#` y#)
455     complement (W32# x#)       = W32# (not32# x#)
456     (W32# x#) `shift` (I# i#)
457         | i# >=# 0#            = W32# (x# `shiftL32#` i#)
458         | otherwise            = W32# (x# `shiftRL32#` negateInt# i#)
459     (W32# x#) `rotate` (I# i#)
460         | i'# ==# 0# = W32# x#
461         | otherwise  = W32# ((x# `shiftL32#` i'#) `or32#`
462                              (x# `shiftRL32#` (32# -# i'#)))
463         where
464         i'# = word2Int# (int2Word# i# `and#` int2Word# 31#)
465     bitSize  _                = 32
466     isSigned _                = False
467
468 foreign import unsafe "stg_eqWord32"      eqWord32#      :: Word32# -> Word32# -> Bool
469 foreign import unsafe "stg_neWord32"      neWord32#      :: Word32# -> Word32# -> Bool
470 foreign import unsafe "stg_ltWord32"      ltWord32#      :: Word32# -> Word32# -> Bool
471 foreign import unsafe "stg_leWord32"      leWord32#      :: Word32# -> Word32# -> Bool
472 foreign import unsafe "stg_gtWord32"      gtWord32#      :: Word32# -> Word32# -> Bool
473 foreign import unsafe "stg_geWord32"      geWord32#      :: Word32# -> Word32# -> Bool
474 foreign import unsafe "stg_int32ToWord32" int32ToWord32# :: Int32# -> Word32#
475 foreign import unsafe "stg_word32ToInt32" word32ToInt32# :: Word32# -> Int32#
476 foreign import unsafe "stg_intToInt32"    intToInt32#    :: Int# -> Int32#
477 foreign import unsafe "stg_wordToWord32"  wordToWord32#  :: Word# -> Word32#
478 foreign import unsafe "stg_word32ToWord"  word32ToWord#  :: Word32# -> Word#
479 foreign import unsafe "stg_plusInt32"     plusInt32#     :: Int32# -> Int32# -> Int32#
480 foreign import unsafe "stg_minusInt32"    minusInt32#    :: Int32# -> Int32# -> Int32#
481 foreign import unsafe "stg_timesInt32"    timesInt32#    :: Int32# -> Int32# -> Int32#
482 foreign import unsafe "stg_negateInt32"   negateInt32#   :: Int32# -> Int32#
483 foreign import unsafe "stg_quotWord32"    quotWord32#    :: Word32# -> Word32# -> Word32#
484 foreign import unsafe "stg_remWord32"     remWord32#     :: Word32# -> Word32# -> Word32#
485 foreign import unsafe "stg_and32"         and32#         :: Word32# -> Word32# -> Word32#
486 foreign import unsafe "stg_or32"          or32#          :: Word32# -> Word32# -> Word32#
487 foreign import unsafe "stg_xor32"         xor32#         :: Word32# -> Word32# -> Word32#
488 foreign import unsafe "stg_not32"         not32#         :: Word32# -> Word32#
489 foreign import unsafe "stg_shiftL32"      shiftL32#      :: Word32# -> Int# -> Word32#
490 foreign import unsafe "stg_shiftRL32"     shiftRL32#     :: Word32# -> Int# -> Word32#
491
492 {-# RULES
493 "fromIntegral/Int->Word32"    fromIntegral = \(I#   x#) -> W32# (int32ToWord32# (intToInt32# x#))
494 "fromIntegral/Word->Word32"   fromIntegral = \(W#   x#) -> W32# (wordToWord32# x#)
495 "fromIntegral/Word32->Int"    fromIntegral = \(W32# x#) -> I#   (word2Int# (word32ToWord# x#))
496 "fromIntegral/Word32->Word"   fromIntegral = \(W32# x#) -> W#   (word32ToWord# x#)
497 "fromIntegral/Word32->Word32" fromIntegral = id :: Word32 -> Word32
498   #-}
499
500 #else 
501
502 -- Word32 is represented in the same way as Word.
503 #if WORD_SIZE_IN_BITS > 32
504 -- Operations may assume and must ensure that it holds only values
505 -- from its logical range.
506 #endif
507
508 data Word32 = W32# Word# deriving (Eq, Ord)
509
510 instance Num Word32 where
511     (W32# x#) + (W32# y#)  = W32# (narrow32Word# (x# `plusWord#` y#))
512     (W32# x#) - (W32# y#)  = W32# (narrow32Word# (x# `minusWord#` y#))
513     (W32# x#) * (W32# y#)  = W32# (narrow32Word# (x# `timesWord#` y#))
514     negate (W32# x#)       = W32# (narrow32Word# (int2Word# (negateInt# (word2Int# x#))))
515     abs x                  = x
516     signum 0               = 0
517     signum _               = 1
518     fromInteger (S# i#)    = W32# (narrow32Word# (int2Word# i#))
519     fromInteger (J# s# d#) = W32# (narrow32Word# (integer2Word# s# d#))
520
521 instance Enum Word32 where
522     succ x
523         | x /= maxBound = x + 1
524         | otherwise     = succError "Word32"
525     pred x
526         | x /= minBound = x - 1
527         | otherwise     = predError "Word32"
528     toEnum i@(I# i#)
529         | i >= 0
530 #if WORD_SIZE_IN_BITS > 32
531           && i <= fromIntegral (maxBound::Word32)
532 #endif
533                         = W32# (int2Word# i#)
534         | otherwise     = toEnumError "Word32" i (minBound::Word32, maxBound::Word32)
535 #if WORD_SIZE_IN_BITS == 32
536     fromEnum x@(W32# x#)
537         | x <= fromIntegral (maxBound::Int)
538                         = I# (word2Int# x#)
539         | otherwise     = fromEnumError "Word32" x
540     enumFrom            = integralEnumFrom
541     enumFromThen        = integralEnumFromThen
542     enumFromTo          = integralEnumFromTo
543     enumFromThenTo      = integralEnumFromThenTo
544 #else
545     fromEnum (W32# x#)  = I# (word2Int# x#)
546     enumFrom            = boundedEnumFrom
547     enumFromThen        = boundedEnumFromThen
548 #endif
549
550 instance Integral Word32 where
551     quot    x@(W32# x#) y@(W32# y#)
552         | y /= 0                    = W32# (x# `quotWord#` y#)
553         | otherwise                 = divZeroError "quot{Word32}" x
554     rem     x@(W32# x#) y@(W32# y#)
555         | y /= 0                    = W32# (x# `remWord#` y#)
556         | otherwise                 = divZeroError "rem{Word32}" x
557     div     x@(W32# x#) y@(W32# y#)
558         | y /= 0                    = W32# (x# `quotWord#` y#)
559         | otherwise                 = divZeroError "div{Word32}" x
560     mod     x@(W32# x#) y@(W32# y#)
561         | y /= 0                    = W32# (x# `remWord#` y#)
562         | otherwise                 = divZeroError "mod{Word32}" x
563     quotRem x@(W32# x#) y@(W32# y#)
564         | y /= 0                    = (W32# (x# `quotWord#` y#), W32# (x# `remWord#` y#))
565         | otherwise                 = divZeroError "quotRem{Word32}" x
566     divMod  x@(W32# x#) y@(W32# y#)
567         | y /= 0                    = (W32# (x# `quotWord#` y#), W32# (x# `remWord#` y#))
568         | otherwise                 = divZeroError "quotRem{Word32}" x
569     toInteger (W32# x#)
570 #if WORD_SIZE_IN_BITS == 32
571         | i# >=# 0#                 = S# i#
572         | otherwise                 = case word2Integer# x# of (# s, d #) -> J# s d
573         where
574         i# = word2Int# x#
575 #else
576                                     = S# (word2Int# x#)
577 #endif
578
579 instance Bits Word32 where
580     (W32# x#) .&.   (W32# y#)  = W32# (x# `and#` y#)
581     (W32# x#) .|.   (W32# y#)  = W32# (x# `or#`  y#)
582     (W32# x#) `xor` (W32# y#)  = W32# (x# `xor#` y#)
583     complement (W32# x#)       = W32# (x# `xor#` mb#) where W32# mb# = maxBound
584     (W32# x#) `shift` (I# i#)
585         | i# >=# 0#            = W32# (narrow32Word# (x# `shiftL#` i#))
586         | otherwise            = W32# (x# `shiftRL#` negateInt# i#)
587     (W32# x#) `rotate` (I# i#)
588         | i'# ==# 0# = W32# x#
589         | otherwise  = W32# (narrow32Word# ((x# `shiftL#` i'#) `or#`
590                                             (x# `shiftRL#` (32# -# i'#))))
591         where
592         i'# = word2Int# (int2Word# i# `and#` int2Word# 31#)
593     bitSize  _                = 32
594     isSigned _                = False
595
596 {-# RULES
597 "fromIntegral/Word8->Word32"   fromIntegral = \(W8# x#) -> W32# x#
598 "fromIntegral/Word16->Word32"  fromIntegral = \(W16# x#) -> W32# x#
599 "fromIntegral/Word32->Word32"  fromIntegral = id :: Word32 -> Word32
600 "fromIntegral/Word32->Integer" fromIntegral = toInteger :: Word32 -> Integer
601 "fromIntegral/a->Word32"       fromIntegral = \x -> case fromIntegral x of W# x# -> W32# (narrow32Word# x#)
602 "fromIntegral/Word32->a"       fromIntegral = \(W32# x#) -> fromIntegral (W# x#)
603   #-}
604
605 #endif
606
607 instance CCallable Word32
608 instance CReturnable Word32
609
610 instance Show Word32 where
611 #if WORD_SIZE_IN_BITS < 33
612     showsPrec p x = showsPrec p (toInteger x)
613 #else
614     showsPrec p x = showsPrec p (fromIntegral x :: Int)
615 #endif
616
617
618 instance Real Word32 where
619     toRational x = toInteger x % 1
620
621 instance Bounded Word32 where
622     minBound = 0
623     maxBound = 0xFFFFFFFF
624
625 instance Ix Word32 where
626     range (m,n)              = [m..n]
627     unsafeIndex b@(m,_) i    = fromIntegral (i - m)
628     inRange (m,n) i          = m <= i && i <= n
629     unsafeRangeSize b@(_l,h) = unsafeIndex b h + 1
630
631 instance Read Word32 where  
632 #if WORD_SIZE_IN_BITS < 33
633     readsPrec p s = [(fromInteger x, r) | (x, r) <- readsPrec p s]
634 #else
635     readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
636 #endif
637
638 ------------------------------------------------------------------------
639 -- type Word64
640 ------------------------------------------------------------------------
641
642 #if WORD_SIZE_IN_BITS < 64
643
644 data Word64 = W64# Word64#
645
646 instance Eq Word64 where
647     (W64# x#) == (W64# y#) = x# `eqWord64#` y#
648     (W64# x#) /= (W64# y#) = x# `neWord64#` y#
649
650 instance Ord Word64 where
651     (W64# x#) <  (W64# y#) = x# `ltWord64#` y#
652     (W64# x#) <= (W64# y#) = x# `leWord64#` y#
653     (W64# x#) >  (W64# y#) = x# `gtWord64#` y#
654     (W64# x#) >= (W64# y#) = x# `geWord64#` y#
655
656 instance Num Word64 where
657     (W64# x#) + (W64# y#)  = W64# (int64ToWord64# (word64ToInt64# x# `plusInt64#` word64ToInt64# y#))
658     (W64# x#) - (W64# y#)  = W64# (int64ToWord64# (word64ToInt64# x# `minusInt64#` word64ToInt64# y#))
659     (W64# x#) * (W64# y#)  = W64# (int64ToWord64# (word64ToInt64# x# `timesInt64#` word64ToInt64# y#))
660     negate (W64# x#)       = W64# (int64ToWord64# (negateInt64# (word64ToInt64# x#)))
661     abs x                  = x
662     signum 0               = 0
663     signum _               = 1
664     fromInteger (S# i#)    = W64# (int64ToWord64# (intToInt64# i#))
665     fromInteger (J# s# d#) = W64# (integerToWord64# s# d#)
666
667 instance Enum Word64 where
668     succ x
669         | x /= maxBound = x + 1
670         | otherwise     = succError "Word64"
671     pred x
672         | x /= minBound = x - 1
673         | otherwise     = predError "Word64"
674     toEnum i@(I# i#)
675         | i >= 0        = W64# (wordToWord64# (int2Word# i#))
676         | otherwise     = toEnumError "Word64" i (minBound::Word64, maxBound::Word64)
677     fromEnum x@(W64# x#)
678         | x <= fromIntegral (maxBound::Int)
679                         = I# (word2Int# (word64ToWord# x#))
680         | otherwise     = fromEnumError "Word64" x
681     enumFrom            = integralEnumFrom
682     enumFromThen        = integralEnumFromThen
683     enumFromTo          = integralEnumFromTo
684     enumFromThenTo      = integralEnumFromThenTo
685
686 instance Integral Word64 where
687     quot    x@(W64# x#) y@(W64# y#)
688         | y /= 0                    = W64# (x# `quotWord64#` y#)
689         | otherwise                 = divZeroError "quot{Word64}" x
690     rem     x@(W64# x#) y@(W64# y#)
691         | y /= 0                    = W64# (x# `remWord64#` y#)
692         | otherwise                 = divZeroError "rem{Word64}" x
693     div     x@(W64# x#) y@(W64# y#)
694         | y /= 0                    = W64# (x# `quotWord64#` y#)
695         | otherwise                 = divZeroError "div{Word64}" x
696     mod     x@(W64# x#) y@(W64# y#)
697         | y /= 0                    = W64# (x# `remWord64#` y#)
698         | otherwise                 = divZeroError "mod{Word64}" x
699     quotRem x@(W64# x#) y@(W64# y#)
700         | y /= 0                    = (W64# (x# `quotWord64#` y#), W64# (x# `remWord64#` y#))
701         | otherwise                 = divZeroError "quotRem{Word64}" x
702     divMod  x@(W64# x#) y@(W64# y#)
703         | y /= 0                    = (W64# (x# `quotWord64#` y#), W64# (x# `remWord64#` y#))
704         | otherwise                 = divZeroError "quotRem{Word64}" x
705     toInteger x@(W64# x#)
706         | x <= 0x7FFFFFFF           = S# (word2Int# (word64ToWord# x#))
707         | otherwise                 = case word64ToInteger# x# of (# s, d #) -> J# s d
708
709 instance Bits Word64 where
710     (W64# x#) .&.   (W64# y#)  = W64# (x# `and64#` y#)
711     (W64# x#) .|.   (W64# y#)  = W64# (x# `or64#`  y#)
712     (W64# x#) `xor` (W64# y#)  = W64# (x# `xor64#` y#)
713     complement (W64# x#)       = W64# (not64# x#)
714     (W64# x#) `shift` (I# i#)
715         | i# >=# 0#            = W64# (x# `shiftL64#` i#)
716         | otherwise            = W64# (x# `shiftRL64#` negateInt# i#)
717     (W64# x#) `rotate` (I# i#)
718         | i'# ==# 0# = W64# x#
719         | otherwise  = W64# ((x# `uncheckedShiftL64#` i'#) `or64#`
720                              (x# `uncheckedShiftRL64#` (64# -# i'#)))
721         where
722         i'# = word2Int# (int2Word# i# `and#` int2Word# 63#)
723     bitSize  _                = 64
724     isSigned _                = False
725
726 -- give the 64-bit shift operations the same treatment as the 32-bit
727 -- ones (see GHC.Base), namely we wrap them in tests to catch the
728 -- cases when we're shifting more than 64 bits to avoid unspecified
729 -- behaviour in the C shift operations.
730
731 shiftL64#, shiftRL64# :: Word64# -> Int# -> Word64#
732
733 a `shiftL64#` b  | b >=# 64#  = wordToWord64# (int2Word# 0#)
734                  | otherwise  = a `uncheckedShiftL64#` b
735
736 a `shiftRL64#` b | b >=# 64#  = wordToWord64# (int2Word# 0#)
737                  | otherwise  = a `uncheckedShiftRL64#` b
738
739
740 foreign import ccall unsafe "stg_eqWord64"      eqWord64#      :: Word64# -> Word64# -> Bool
741 foreign import ccall unsafe "stg_neWord64"      neWord64#      :: Word64# -> Word64# -> Bool
742 foreign import ccall unsafe "stg_ltWord64"      ltWord64#      :: Word64# -> Word64# -> Bool
743 foreign import ccall unsafe "stg_leWord64"      leWord64#      :: Word64# -> Word64# -> Bool
744 foreign import ccall unsafe "stg_gtWord64"      gtWord64#      :: Word64# -> Word64# -> Bool
745 foreign import ccall unsafe "stg_geWord64"      geWord64#      :: Word64# -> Word64# -> Bool
746 foreign import ccall unsafe "stg_int64ToWord64" int64ToWord64# :: Int64# -> Word64#
747 foreign import ccall unsafe "stg_word64ToInt64" word64ToInt64# :: Word64# -> Int64#
748 foreign import ccall unsafe "stg_intToInt64"    intToInt64#    :: Int# -> Int64#
749 foreign import ccall unsafe "stg_wordToWord64"  wordToWord64#  :: Word# -> Word64#
750 foreign import ccall unsafe "stg_word64ToWord"  word64ToWord#  :: Word64# -> Word#
751 foreign import ccall unsafe "stg_plusInt64"     plusInt64#     :: Int64# -> Int64# -> Int64#
752 foreign import ccall unsafe "stg_minusInt64"    minusInt64#    :: Int64# -> Int64# -> Int64#
753 foreign import ccall unsafe "stg_timesInt64"    timesInt64#    :: Int64# -> Int64# -> Int64#
754 foreign import ccall unsafe "stg_negateInt64"   negateInt64#   :: Int64# -> Int64#
755 foreign import ccall unsafe "stg_quotWord64"    quotWord64#    :: Word64# -> Word64# -> Word64#
756 foreign import ccall unsafe "stg_remWord64"     remWord64#     :: Word64# -> Word64# -> Word64#
757 foreign import ccall unsafe "stg_and64"         and64#         :: Word64# -> Word64# -> Word64#
758 foreign import ccall unsafe "stg_or64"          or64#          :: Word64# -> Word64# -> Word64#
759 foreign import ccall unsafe "stg_xor64"         xor64#         :: Word64# -> Word64# -> Word64#
760 foreign import ccall unsafe "stg_not64"         not64#         :: Word64# -> Word64#
761 foreign import ccall unsafe "stg_uncheckedShiftL64"      uncheckedShiftL64#      :: Word64# -> Int# -> Word64#
762 foreign import ccall unsafe "stg_uncheckedShiftRL64"     uncheckedShiftRL64#     :: Word64# -> Int# -> Word64#
763
764 foreign import ccall unsafe "stg_integerToWord64" integerToWord64# :: Int# -> ByteArray# -> Word64#
765
766
767 {-# RULES
768 "fromIntegral/Int->Word64"    fromIntegral = \(I#   x#) -> W64# (int64ToWord64# (intToInt64# x#))
769 "fromIntegral/Word->Word64"   fromIntegral = \(W#   x#) -> W64# (wordToWord64# x#)
770 "fromIntegral/Word64->Int"    fromIntegral = \(W64# x#) -> I#   (word2Int# (word64ToWord# x#))
771 "fromIntegral/Word64->Word"   fromIntegral = \(W64# x#) -> W#   (word64ToWord# x#)
772 "fromIntegral/Word64->Word64" fromIntegral = id :: Word64 -> Word64
773   #-}
774
775 #else
776
777 -- Word64 is represented in the same way as Word.
778 -- Operations may assume and must ensure that it holds only values
779 -- from its logical range.
780
781 data Word64 = W64# Word# deriving (Eq, Ord)
782
783 instance Num Word64 where
784     (W64# x#) + (W64# y#)  = W64# (x# `plusWord#` y#)
785     (W64# x#) - (W64# y#)  = W64# (x# `minusWord#` y#)
786     (W64# x#) * (W64# y#)  = W64# (x# `timesWord#` y#)
787     negate (W64# x#)       = W64# (int2Word# (negateInt# (word2Int# x#)))
788     abs x                  = x
789     signum 0               = 0
790     signum _               = 1
791     fromInteger (S# i#)    = W64# (int2Word# i#)
792     fromInteger (J# s# d#) = W64# (integer2Word# s# d#)
793
794 instance Enum Word64 where
795     succ x
796         | x /= maxBound = x + 1
797         | otherwise     = succError "Word64"
798     pred x
799         | x /= minBound = x - 1
800         | otherwise     = predError "Word64"
801     toEnum i@(I# i#)
802         | i >= 0        = W64# (int2Word# i#)
803         | otherwise     = toEnumError "Word64" i (minBound::Word64, maxBound::Word64)
804     fromEnum x@(W64# x#)
805         | x <= fromIntegral (maxBound::Int)
806                         = I# (word2Int# x#)
807         | otherwise     = fromEnumError "Word64" x
808     enumFrom            = integralEnumFrom
809     enumFromThen        = integralEnumFromThen
810     enumFromTo          = integralEnumFromTo
811     enumFromThenTo      = integralEnumFromThenTo
812
813 instance Integral Word64 where
814     quot    x@(W64# x#) y@(W64# y#)
815         | y /= 0                    = W64# (x# `quotWord#` y#)
816         | otherwise                 = divZeroError "quot{Word64}" x
817     rem     x@(W64# x#) y@(W64# y#)
818         | y /= 0                    = W64# (x# `remWord#` y#)
819         | otherwise                 = divZeroError "rem{Word64}" x
820     div     x@(W64# x#) y@(W64# y#)
821         | y /= 0                    = W64# (x# `quotWord#` y#)
822         | otherwise                 = divZeroError "div{Word64}" x
823     mod     x@(W64# x#) y@(W64# y#)
824         | y /= 0                    = W64# (x# `remWord#` y#)
825         | otherwise                 = divZeroError "mod{Word64}" x
826     quotRem x@(W64# x#) y@(W64# y#)
827         | y /= 0                    = (W64# (x# `quotWord#` y#), W64# (x# `remWord#` y#))
828         | otherwise                 = divZeroError "quotRem{Word64}" x
829     divMod  x@(W64# x#) y@(W64# y#)
830         | y /= 0                    = (W64# (x# `quotWord#` y#), W64# (x# `remWord#` y#))
831         | otherwise                 = divZeroError "quotRem{Word64}" x
832     toInteger (W64# x#)
833         | i# >=# 0#                 = S# i#
834         | otherwise                 = case word2Integer# x# of (# s, d #) -> J# s d
835         where
836         i# = word2Int# x#
837
838 instance Bits Word64 where
839     (W64# x#) .&.   (W64# y#)  = W64# (x# `and#` y#)
840     (W64# x#) .|.   (W64# y#)  = W64# (x# `or#`  y#)
841     (W64# x#) `xor` (W64# y#)  = W64# (x# `xor#` y#)
842     complement (W64# x#)       = W64# (x# `xor#` mb#) where W64# mb# = maxBound
843     (W64# x#) `shift` (I# i#)
844         | i# >=# 0#            = W64# (x# `shiftL#` i#)
845         | otherwise            = W64# (x# `shiftRL#` negateInt# i#)
846     (W64# x#) `rotate` (I# i#)
847         | i'# ==# 0# = W64# x#
848         | otherwise  = W64# ((x# `shiftL#` i'#) `or#`
849                              (x# `shiftRL#` (64# -# i'#)))
850         where
851         i'# = word2Int# (int2Word# i# `and#` int2Word# 63#)
852     bitSize  _                = 64
853     isSigned _                = False
854
855 {-# RULES
856 "fromIntegral/a->Word64" fromIntegral = \x -> case fromIntegral x of W# x# -> W64# x#
857 "fromIntegral/Word64->a" fromIntegral = \(W64# x#) -> fromIntegral (W# x#)
858   #-}
859
860 #endif
861
862 instance CCallable Word64
863 instance CReturnable Word64
864
865 instance Show Word64 where
866     showsPrec p x = showsPrec p (toInteger x)
867
868 instance Real Word64 where
869     toRational x = toInteger x % 1
870
871 instance Bounded Word64 where
872     minBound = 0
873     maxBound = 0xFFFFFFFFFFFFFFFF
874
875 instance Ix Word64 where
876     range (m,n)              = [m..n]
877     unsafeIndex b@(m,_) i    = fromIntegral (i - m)
878     inRange (m,n) i          = m <= i && i <= n
879     unsafeRangeSize b@(_l,h) = unsafeIndex b h + 1
880
881 instance Read Word64 where
882     readsPrec p s = [(fromInteger x, r) | (x, r) <- readsPrec p s]
883 \end{code}