[project @ 2002-09-16 11:24:36 by simonpj]
[ghc-base.git] / GHC / Word.hs
1 {-# OPTIONS -fno-implicit-prelude #-}
2 -----------------------------------------------------------------------------
3 -- |
4 -- Module      :  GHC.Word
5 -- Copyright   :  (c) The University of Glasgow, 1997-2002
6 -- License     :  see libraries/base/LICENSE
7 -- 
8 -- Maintainer  :  cvs-ghc@haskell.org
9 -- Stability   :  internal
10 -- Portability :  non-portable (GHC Extensions)
11 --
12 -- Sized unsigned integral types: 'Word', 'Word8', 'Word16', 'Word32', and
13 -- 'Word64'.
14 --
15 -----------------------------------------------------------------------------
16
17 #include "MachDeps.h"
18
19 module GHC.Word (
20     Word(..), Word8(..), Word16(..), Word32(..), Word64(..),
21     divZeroError, toEnumError, fromEnumError, succError, predError)
22     where
23
24 import Data.Bits
25
26 import GHC.Base
27 import GHC.Enum
28 import GHC.Num
29 import GHC.Real
30 import GHC.Read
31 import GHC.Arr
32 import GHC.Show
33
34 ------------------------------------------------------------------------
35 -- Helper functions
36 ------------------------------------------------------------------------
37
38 {-# NOINLINE divZeroError #-}
39 divZeroError :: (Show a) => String -> a -> b
40 divZeroError meth x =
41     error $ "Integral." ++ meth ++ ": divide by 0 (" ++ show x ++ " / 0)"
42
43 {-# NOINLINE toEnumError #-}
44 toEnumError :: (Show a) => String -> Int -> (a,a) -> b
45 toEnumError inst_ty i bnds =
46     error $ "Enum.toEnum{" ++ inst_ty ++ "}: tag (" ++
47             show i ++
48             ") is outside of bounds " ++
49             show bnds
50
51 {-# NOINLINE fromEnumError #-}
52 fromEnumError :: (Show a) => String -> a -> b
53 fromEnumError inst_ty x =
54     error $ "Enum.fromEnum{" ++ inst_ty ++ "}: value (" ++
55             show x ++
56             ") is outside of Int's bounds " ++
57             show (minBound::Int, maxBound::Int)
58
59 {-# NOINLINE succError #-}
60 succError :: String -> a
61 succError inst_ty =
62     error $ "Enum.succ{" ++ inst_ty ++ "}: tried to take `succ' of maxBound"
63
64 {-# NOINLINE predError #-}
65 predError :: String -> a
66 predError inst_ty =
67     error $ "Enum.pred{" ++ inst_ty ++ "}: tried to take `pred' of minBound"
68
69 ------------------------------------------------------------------------
70 -- type Word
71 ------------------------------------------------------------------------
72
73 -- |A 'Word' is an unsigned integral type, with the same size as 'Int'.
74 data Word = W# Word# deriving (Eq, Ord)
75
76 instance CCallable Word
77 instance CReturnable Word
78
79 instance Show Word where
80     showsPrec p x = showsPrec p (toInteger x)
81
82 instance Num Word where
83     (W# x#) + (W# y#)      = W# (x# `plusWord#` y#)
84     (W# x#) - (W# y#)      = W# (x# `minusWord#` y#)
85     (W# x#) * (W# y#)      = W# (x# `timesWord#` y#)
86     negate (W# x#)         = W# (int2Word# (negateInt# (word2Int# x#)))
87     abs x                  = x
88     signum 0               = 0
89     signum _               = 1
90     fromInteger (S# i#)    = W# (int2Word# i#)
91     fromInteger (J# s# d#) = W# (integer2Word# s# d#)
92
93 instance Real Word where
94     toRational x = toInteger x % 1
95
96 instance Enum Word where
97     succ x
98         | x /= maxBound = x + 1
99         | otherwise     = succError "Word"
100     pred x
101         | x /= minBound = x - 1
102         | otherwise     = predError "Word"
103     toEnum i@(I# i#)
104         | i >= 0        = W# (int2Word# i#)
105         | otherwise     = toEnumError "Word" i (minBound::Word, maxBound::Word)
106     fromEnum x@(W# x#)
107         | x <= fromIntegral (maxBound::Int)
108                         = I# (word2Int# x#)
109         | otherwise     = fromEnumError "Word" x
110     enumFrom            = integralEnumFrom
111     enumFromThen        = integralEnumFromThen
112     enumFromTo          = integralEnumFromTo
113     enumFromThenTo      = integralEnumFromThenTo
114
115 instance Integral Word where
116     quot    x@(W# x#) y@(W# y#)
117         | y /= 0                = W# (x# `quotWord#` y#)
118         | otherwise             = divZeroError "quot{Word}" x
119     rem     x@(W# x#) y@(W# y#)
120         | y /= 0                = W# (x# `remWord#` y#)
121         | otherwise             = divZeroError "rem{Word}" x
122     div     x@(W# x#) y@(W# y#)
123         | y /= 0                = W# (x# `quotWord#` y#)
124         | otherwise             = divZeroError "div{Word}" x
125     mod     x@(W# x#) y@(W# y#)
126         | y /= 0                = W# (x# `remWord#` y#)
127         | otherwise             = divZeroError "mod{Word}" x
128     quotRem x@(W# x#) y@(W# y#)
129         | y /= 0                = (W# (x# `quotWord#` y#), W# (x# `remWord#` y#))
130         | otherwise             = divZeroError "quotRem{Word}" x
131     divMod  x@(W# x#) y@(W# y#)
132         | y /= 0                = (W# (x# `quotWord#` y#), W# (x# `remWord#` y#))
133         | otherwise             = divZeroError "divMod{Word}" x
134     toInteger (W# x#)
135         | i# >=# 0#             = S# i#
136         | otherwise             = case word2Integer# x# of (# s, d #) -> J# s d
137         where
138         i# = word2Int# x#
139
140 instance Bounded Word where
141     minBound = 0
142 #if WORD_SIZE_IN_BITS == 31
143     maxBound = 0x7FFFFFFF
144 #elif WORD_SIZE_IN_BITS == 32
145     maxBound = 0xFFFFFFFF
146 #else
147     maxBound = 0xFFFFFFFFFFFFFFFF
148 #endif
149
150 instance Ix Word where
151     range (m,n)              = [m..n]
152     unsafeIndex b@(m,_) i    = fromIntegral (i - m)
153     inRange (m,n) i          = m <= i && i <= n
154     unsafeRangeSize b@(_l,h) = unsafeIndex b h + 1
155
156 instance Read Word where
157     readsPrec p s = [(fromInteger x, r) | (x, r) <- readsPrec p s]
158
159 instance Bits Word where
160     (W# x#) .&.   (W# y#)    = W# (x# `and#` y#)
161     (W# x#) .|.   (W# y#)    = W# (x# `or#`  y#)
162     (W# x#) `xor` (W# y#)    = W# (x# `xor#` y#)
163     complement (W# x#)       = W# (x# `xor#` mb#) where W# mb# = maxBound
164     (W# x#) `shift` (I# i#)
165         | i# >=# 0#          = W# (x# `shiftL#` i#)
166         | otherwise          = W# (x# `shiftRL#` negateInt# i#)
167     (W# x#) `rotate` (I# i#)
168         | i'# ==# 0# = W# x#
169         | otherwise  = W# ((x# `shiftL#` i'#) `or#` (x# `shiftRL#` (wsib -# i'#)))
170         where
171         i'# = word2Int# (int2Word# i# `and#` int2Word# (wsib -# 1#))
172         wsib = WORD_SIZE_IN_BITS#  {- work around preprocessor problem (??) -}
173     bitSize  _               = WORD_SIZE_IN_BITS
174     isSigned _               = False
175
176 {-# RULES
177 "fromIntegral/Int->Word"  fromIntegral = \(I# x#) -> W# (int2Word# x#)
178 "fromIntegral/Word->Int"  fromIntegral = \(W# x#) -> I# (word2Int# x#)
179 "fromIntegral/Word->Word" fromIntegral = id :: Word -> Word
180   #-}
181
182 ------------------------------------------------------------------------
183 -- type Word8
184 ------------------------------------------------------------------------
185
186 -- Word8 is represented in the same way as Word. Operations may assume
187 -- and must ensure that it holds only values from its logical range.
188
189 data Word8 = W8# Word# deriving (Eq, Ord)
190 -- ^ 8-bit unsigned integer type
191
192 instance CCallable Word8
193 instance CReturnable Word8
194
195 instance Show Word8 where
196     showsPrec p x = showsPrec p (fromIntegral x :: Int)
197
198 instance Num Word8 where
199     (W8# x#) + (W8# y#)    = W8# (narrow8Word# (x# `plusWord#` y#))
200     (W8# x#) - (W8# y#)    = W8# (narrow8Word# (x# `minusWord#` y#))
201     (W8# x#) * (W8# y#)    = W8# (narrow8Word# (x# `timesWord#` y#))
202     negate (W8# x#)        = W8# (narrow8Word# (int2Word# (negateInt# (word2Int# x#))))
203     abs x                  = x
204     signum 0               = 0
205     signum _               = 1
206     fromInteger (S# i#)    = W8# (narrow8Word# (int2Word# i#))
207     fromInteger (J# s# d#) = W8# (narrow8Word# (integer2Word# s# d#))
208
209 instance Real Word8 where
210     toRational x = toInteger x % 1
211
212 instance Enum Word8 where
213     succ x
214         | x /= maxBound = x + 1
215         | otherwise     = succError "Word8"
216     pred x
217         | x /= minBound = x - 1
218         | otherwise     = predError "Word8"
219     toEnum i@(I# i#)
220         | i >= 0 && i <= fromIntegral (maxBound::Word8)
221                         = W8# (int2Word# i#)
222         | otherwise     = toEnumError "Word8" i (minBound::Word8, maxBound::Word8)
223     fromEnum (W8# x#)   = I# (word2Int# x#)
224     enumFrom            = boundedEnumFrom
225     enumFromThen        = boundedEnumFromThen
226
227 instance Integral Word8 where
228     quot    x@(W8# x#) y@(W8# y#)
229         | y /= 0                  = W8# (x# `quotWord#` y#)
230         | otherwise               = divZeroError "quot{Word8}" x
231     rem     x@(W8# x#) y@(W8# y#)
232         | y /= 0                  = W8# (x# `remWord#` y#)
233         | otherwise               = divZeroError "rem{Word8}" x
234     div     x@(W8# x#) y@(W8# y#)
235         | y /= 0                  = W8# (x# `quotWord#` y#)
236         | otherwise               = divZeroError "div{Word8}" x
237     mod     x@(W8# x#) y@(W8# y#)
238         | y /= 0                  = W8# (x# `remWord#` y#)
239         | otherwise               = divZeroError "mod{Word8}" x
240     quotRem x@(W8# x#) y@(W8# y#)
241         | y /= 0                  = (W8# (x# `quotWord#` y#), W8# (x# `remWord#` y#))
242         | otherwise               = divZeroError "quotRem{Word8}" x
243     divMod  x@(W8# x#) y@(W8# y#)
244         | y /= 0                  = (W8# (x# `quotWord#` y#), W8# (x# `remWord#` y#))
245         | otherwise               = divZeroError "quotRem{Word8}" x
246     toInteger (W8# x#)            = S# (word2Int# x#)
247
248 instance Bounded Word8 where
249     minBound = 0
250     maxBound = 0xFF
251
252 instance Ix Word8 where
253     range (m,n)              = [m..n]
254     unsafeIndex b@(m,_) i    = fromIntegral (i - m)
255     inRange (m,n) i          = m <= i && i <= n
256     unsafeRangeSize b@(_l,h) = unsafeIndex b h + 1
257
258 instance Read Word8 where
259     readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
260
261 instance Bits Word8 where
262     (W8# x#) .&.   (W8# y#)   = W8# (x# `and#` y#)
263     (W8# x#) .|.   (W8# y#)   = W8# (x# `or#`  y#)
264     (W8# x#) `xor` (W8# y#)   = W8# (x# `xor#` y#)
265     complement (W8# x#)       = W8# (x# `xor#` mb#) where W8# mb# = maxBound
266     (W8# x#) `shift` (I# i#)
267         | i# >=# 0#           = W8# (narrow8Word# (x# `shiftL#` i#))
268         | otherwise           = W8# (x# `shiftRL#` negateInt# i#)
269     (W8# x#) `rotate` (I# i#)
270         | i'# ==# 0# = W8# x#
271         | otherwise  = W8# (narrow8Word# ((x# `shiftL#` i'#) `or#`
272                                           (x# `shiftRL#` (8# -# i'#))))
273         where
274         i'# = word2Int# (int2Word# i# `and#` int2Word# 7#)
275     bitSize  _                = 8
276     isSigned _                = False
277
278 {-# RULES
279 "fromIntegral/Word8->Word8"   fromIntegral = id :: Word8 -> Word8
280 "fromIntegral/Word8->Integer" fromIntegral = toInteger :: Word8 -> Integer
281 "fromIntegral/a->Word8"       fromIntegral = \x -> case fromIntegral x of W# x# -> W8# (narrow8Word# x#)
282 "fromIntegral/Word8->a"       fromIntegral = \(W8# x#) -> fromIntegral (W# x#)
283   #-}
284
285 ------------------------------------------------------------------------
286 -- type Word16
287 ------------------------------------------------------------------------
288
289 -- Word16 is represented in the same way as Word. Operations may assume
290 -- and must ensure that it holds only values from its logical range.
291
292 data Word16 = W16# Word# deriving (Eq, Ord)
293 -- ^ 16-bit unsigned integer type
294
295 instance CCallable Word16
296 instance CReturnable Word16
297
298 instance Show Word16 where
299     showsPrec p x = showsPrec p (fromIntegral x :: Int)
300
301 instance Num Word16 where
302     (W16# x#) + (W16# y#)  = W16# (narrow16Word# (x# `plusWord#` y#))
303     (W16# x#) - (W16# y#)  = W16# (narrow16Word# (x# `minusWord#` y#))
304     (W16# x#) * (W16# y#)  = W16# (narrow16Word# (x# `timesWord#` y#))
305     negate (W16# x#)       = W16# (narrow16Word# (int2Word# (negateInt# (word2Int# x#))))
306     abs x                  = x
307     signum 0               = 0
308     signum _               = 1
309     fromInteger (S# i#)    = W16# (narrow16Word# (int2Word# i#))
310     fromInteger (J# s# d#) = W16# (narrow16Word# (integer2Word# s# d#))
311
312 instance Real Word16 where
313     toRational x = toInteger x % 1
314
315 instance Enum Word16 where
316     succ x
317         | x /= maxBound = x + 1
318         | otherwise     = succError "Word16"
319     pred x
320         | x /= minBound = x - 1
321         | otherwise     = predError "Word16"
322     toEnum i@(I# i#)
323         | i >= 0 && i <= fromIntegral (maxBound::Word16)
324                         = W16# (int2Word# i#)
325         | otherwise     = toEnumError "Word16" i (minBound::Word16, maxBound::Word16)
326     fromEnum (W16# x#)  = I# (word2Int# x#)
327     enumFrom            = boundedEnumFrom
328     enumFromThen        = boundedEnumFromThen
329
330 instance Integral Word16 where
331     quot    x@(W16# x#) y@(W16# y#)
332         | y /= 0                    = W16# (x# `quotWord#` y#)
333         | otherwise                 = divZeroError "quot{Word16}" x
334     rem     x@(W16# x#) y@(W16# y#)
335         | y /= 0                    = W16# (x# `remWord#` y#)
336         | otherwise                 = divZeroError "rem{Word16}" x
337     div     x@(W16# x#) y@(W16# y#)
338         | y /= 0                    = W16# (x# `quotWord#` y#)
339         | otherwise                 = divZeroError "div{Word16}" x
340     mod     x@(W16# x#) y@(W16# y#)
341         | y /= 0                    = W16# (x# `remWord#` y#)
342         | otherwise                 = divZeroError "mod{Word16}" x
343     quotRem x@(W16# x#) y@(W16# y#)
344         | y /= 0                    = (W16# (x# `quotWord#` y#), W16# (x# `remWord#` y#))
345         | otherwise                 = divZeroError "quotRem{Word16}" x
346     divMod  x@(W16# x#) y@(W16# y#)
347         | y /= 0                    = (W16# (x# `quotWord#` y#), W16# (x# `remWord#` y#))
348         | otherwise                 = divZeroError "quotRem{Word16}" x
349     toInteger (W16# x#)             = S# (word2Int# x#)
350
351 instance Bounded Word16 where
352     minBound = 0
353     maxBound = 0xFFFF
354
355 instance Ix Word16 where
356     range (m,n)              = [m..n]
357     unsafeIndex b@(m,_) i    = fromIntegral (i - m)
358     inRange (m,n) i          = m <= i && i <= n
359     unsafeRangeSize b@(_l,h) = unsafeIndex b h + 1
360
361 instance Read Word16 where
362     readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
363
364 instance Bits Word16 where
365     (W16# x#) .&.   (W16# y#)  = W16# (x# `and#` y#)
366     (W16# x#) .|.   (W16# y#)  = W16# (x# `or#`  y#)
367     (W16# x#) `xor` (W16# y#)  = W16# (x# `xor#` y#)
368     complement (W16# x#)       = W16# (x# `xor#` mb#) where W16# mb# = maxBound
369     (W16# x#) `shift` (I# i#)
370         | i# >=# 0#            = W16# (narrow16Word# (x# `shiftL#` i#))
371         | otherwise            = W16# (x# `shiftRL#` negateInt# i#)
372     (W16# x#) `rotate` (I# i#)
373         | i'# ==# 0# = W16# x#
374         | otherwise  = W16# (narrow16Word# ((x# `shiftL#` i'#) `or#`
375                                             (x# `shiftRL#` (16# -# i'#))))
376         where
377         i'# = word2Int# (int2Word# i# `and#` int2Word# 15#)
378     bitSize  _                = 16
379     isSigned _                = False
380
381 {-# RULES
382 "fromIntegral/Word8->Word16"   fromIntegral = \(W8# x#) -> W16# x#
383 "fromIntegral/Word16->Word16"  fromIntegral = id :: Word16 -> Word16
384 "fromIntegral/Word16->Integer" fromIntegral = toInteger :: Word16 -> Integer
385 "fromIntegral/a->Word16"       fromIntegral = \x -> case fromIntegral x of W# x# -> W16# (narrow16Word# x#)
386 "fromIntegral/Word16->a"       fromIntegral = \(W16# x#) -> fromIntegral (W# x#)
387   #-}
388
389 ------------------------------------------------------------------------
390 -- type Word32
391 ------------------------------------------------------------------------
392
393 #if WORD_SIZE_IN_BITS < 32
394
395 data Word32 = W32# Word32#
396 -- ^ 32-bit unsigned integer type
397
398 instance Eq Word32 where
399     (W32# x#) == (W32# y#) = x# `eqWord32#` y#
400     (W32# x#) /= (W32# y#) = x# `neWord32#` y#
401
402 instance Ord Word32 where
403     (W32# x#) <  (W32# y#) = x# `ltWord32#` y#
404     (W32# x#) <= (W32# y#) = x# `leWord32#` y#
405     (W32# x#) >  (W32# y#) = x# `gtWord32#` y#
406     (W32# x#) >= (W32# y#) = x# `geWord32#` y#
407
408 instance Num Word32 where
409     (W32# x#) + (W32# y#)  = W32# (int32ToWord32# (word32ToInt32# x# `plusInt32#` word32ToInt32# y#))
410     (W32# x#) - (W32# y#)  = W32# (int32ToWord32# (word32ToInt32# x# `minusInt32#` word32ToInt32# y#))
411     (W32# x#) * (W32# y#)  = W32# (int32ToWord32# (word32ToInt32# x# `timesInt32#` word32ToInt32# y#))
412     negate (W32# x#)       = W32# (int32ToWord32# (negateInt32# (word32ToInt32# x#)))
413     abs x                  = x
414     signum 0               = 0
415     signum _               = 1
416     fromInteger (S# i#)    = W32# (int32ToWord32# (intToInt32# i#))
417     fromInteger (J# s# d#) = W32# (integerToWord32# s# d#)
418
419 instance Enum Word32 where
420     succ x
421         | x /= maxBound = x + 1
422         | otherwise     = succError "Word32"
423     pred x
424         | x /= minBound = x - 1
425         | otherwise     = predError "Word32"
426     toEnum i@(I# i#)
427         | i >= 0        = W32# (wordToWord32# (int2Word# i#))
428         | otherwise     = toEnumError "Word32" i (minBound::Word32, maxBound::Word32)
429     fromEnum x@(W32# x#)
430         | x <= fromIntegral (maxBound::Int)
431                         = I# (word2Int# (word32ToWord# x#))
432         | otherwise     = fromEnumError "Word32" x
433     enumFrom            = integralEnumFrom
434     enumFromThen        = integralEnumFromThen
435     enumFromTo          = integralEnumFromTo
436     enumFromThenTo      = integralEnumFromThenTo
437
438 instance Integral Word32 where
439     quot    x@(W32# x#) y@(W32# y#)
440         | y /= 0                    = W32# (x# `quotWord32#` y#)
441         | otherwise                 = divZeroError "quot{Word32}" x
442     rem     x@(W32# x#) y@(W32# y#)
443         | y /= 0                    = W32# (x# `remWord32#` y#)
444         | otherwise                 = divZeroError "rem{Word32}" x
445     div     x@(W32# x#) y@(W32# y#)
446         | y /= 0                    = W32# (x# `quotWord32#` y#)
447         | otherwise                 = divZeroError "div{Word32}" x
448     mod     x@(W32# x#) y@(W32# y#)
449         | y /= 0                    = W32# (x# `remWord32#` y#)
450         | otherwise                 = divZeroError "mod{Word32}" x
451     quotRem x@(W32# x#) y@(W32# y#)
452         | y /= 0                    = (W32# (x# `quotWord32#` y#), W32# (x# `remWord32#` y#))
453         | otherwise                 = divZeroError "quotRem{Word32}" x
454     divMod  x@(W32# x#) y@(W32# y#)
455         | y /= 0                    = (W32# (x# `quotWord32#` y#), W32# (x# `remWord32#` y#))
456         | otherwise                 = divZeroError "quotRem{Word32}" x
457     toInteger x@(W32# x#)
458         | x <= fromIntegral (maxBound::Int)  = S# (word2Int# (word32ToWord# x#))
459         | otherwise                 = case word32ToInteger# x# of (# s, d #) -> J# s d
460
461 instance Bits Word32 where
462     (W32# x#) .&.   (W32# y#)  = W32# (x# `and32#` y#)
463     (W32# x#) .|.   (W32# y#)  = W32# (x# `or32#`  y#)
464     (W32# x#) `xor` (W32# y#)  = W32# (x# `xor32#` y#)
465     complement (W32# x#)       = W32# (not32# x#)
466     (W32# x#) `shift` (I# i#)
467         | i# >=# 0#            = W32# (x# `shiftL32#` i#)
468         | otherwise            = W32# (x# `shiftRL32#` negateInt# i#)
469     (W32# x#) `rotate` (I# i#)
470         | i'# ==# 0# = W32# x#
471         | otherwise  = W32# ((x# `shiftL32#` i'#) `or32#`
472                              (x# `shiftRL32#` (32# -# i'#)))
473         where
474         i'# = word2Int# (int2Word# i# `and#` int2Word# 31#)
475     bitSize  _                = 32
476     isSigned _                = False
477
478 foreign import unsafe "stg_eqWord32"      eqWord32#      :: Word32# -> Word32# -> Bool
479 foreign import unsafe "stg_neWord32"      neWord32#      :: Word32# -> Word32# -> Bool
480 foreign import unsafe "stg_ltWord32"      ltWord32#      :: Word32# -> Word32# -> Bool
481 foreign import unsafe "stg_leWord32"      leWord32#      :: Word32# -> Word32# -> Bool
482 foreign import unsafe "stg_gtWord32"      gtWord32#      :: Word32# -> Word32# -> Bool
483 foreign import unsafe "stg_geWord32"      geWord32#      :: Word32# -> Word32# -> Bool
484 foreign import unsafe "stg_int32ToWord32" int32ToWord32# :: Int32# -> Word32#
485 foreign import unsafe "stg_word32ToInt32" word32ToInt32# :: Word32# -> Int32#
486 foreign import unsafe "stg_intToInt32"    intToInt32#    :: Int# -> Int32#
487 foreign import unsafe "stg_wordToWord32"  wordToWord32#  :: Word# -> Word32#
488 foreign import unsafe "stg_word32ToWord"  word32ToWord#  :: Word32# -> Word#
489 foreign import unsafe "stg_plusInt32"     plusInt32#     :: Int32# -> Int32# -> Int32#
490 foreign import unsafe "stg_minusInt32"    minusInt32#    :: Int32# -> Int32# -> Int32#
491 foreign import unsafe "stg_timesInt32"    timesInt32#    :: Int32# -> Int32# -> Int32#
492 foreign import unsafe "stg_negateInt32"   negateInt32#   :: Int32# -> Int32#
493 foreign import unsafe "stg_quotWord32"    quotWord32#    :: Word32# -> Word32# -> Word32#
494 foreign import unsafe "stg_remWord32"     remWord32#     :: Word32# -> Word32# -> Word32#
495 foreign import unsafe "stg_and32"         and32#         :: Word32# -> Word32# -> Word32#
496 foreign import unsafe "stg_or32"          or32#          :: Word32# -> Word32# -> Word32#
497 foreign import unsafe "stg_xor32"         xor32#         :: Word32# -> Word32# -> Word32#
498 foreign import unsafe "stg_not32"         not32#         :: Word32# -> Word32#
499 foreign import unsafe "stg_shiftL32"      shiftL32#      :: Word32# -> Int# -> Word32#
500 foreign import unsafe "stg_shiftRL32"     shiftRL32#     :: Word32# -> Int# -> Word32#
501
502 {-# RULES
503 "fromIntegral/Int->Word32"    fromIntegral = \(I#   x#) -> W32# (int32ToWord32# (intToInt32# x#))
504 "fromIntegral/Word->Word32"   fromIntegral = \(W#   x#) -> W32# (wordToWord32# x#)
505 "fromIntegral/Word32->Int"    fromIntegral = \(W32# x#) -> I#   (word2Int# (word32ToWord# x#))
506 "fromIntegral/Word32->Word"   fromIntegral = \(W32# x#) -> W#   (word32ToWord# x#)
507 "fromIntegral/Word32->Word32" fromIntegral = id :: Word32 -> Word32
508   #-}
509
510 #else 
511
512 -- Word32 is represented in the same way as Word.
513 #if WORD_SIZE_IN_BITS > 32
514 -- Operations may assume and must ensure that it holds only values
515 -- from its logical range.
516 #endif
517
518 data Word32 = W32# Word# deriving (Eq, Ord)
519 -- ^ 32-bit unsigned integer type
520
521 instance Num Word32 where
522     (W32# x#) + (W32# y#)  = W32# (narrow32Word# (x# `plusWord#` y#))
523     (W32# x#) - (W32# y#)  = W32# (narrow32Word# (x# `minusWord#` y#))
524     (W32# x#) * (W32# y#)  = W32# (narrow32Word# (x# `timesWord#` y#))
525     negate (W32# x#)       = W32# (narrow32Word# (int2Word# (negateInt# (word2Int# x#))))
526     abs x                  = x
527     signum 0               = 0
528     signum _               = 1
529     fromInteger (S# i#)    = W32# (narrow32Word# (int2Word# i#))
530     fromInteger (J# s# d#) = W32# (narrow32Word# (integer2Word# s# d#))
531
532 instance Enum Word32 where
533     succ x
534         | x /= maxBound = x + 1
535         | otherwise     = succError "Word32"
536     pred x
537         | x /= minBound = x - 1
538         | otherwise     = predError "Word32"
539     toEnum i@(I# i#)
540         | i >= 0
541 #if WORD_SIZE_IN_BITS > 32
542           && i <= fromIntegral (maxBound::Word32)
543 #endif
544                         = W32# (int2Word# i#)
545         | otherwise     = toEnumError "Word32" i (minBound::Word32, maxBound::Word32)
546 #if WORD_SIZE_IN_BITS == 32
547     fromEnum x@(W32# x#)
548         | x <= fromIntegral (maxBound::Int)
549                         = I# (word2Int# x#)
550         | otherwise     = fromEnumError "Word32" x
551     enumFrom            = integralEnumFrom
552     enumFromThen        = integralEnumFromThen
553     enumFromTo          = integralEnumFromTo
554     enumFromThenTo      = integralEnumFromThenTo
555 #else
556     fromEnum (W32# x#)  = I# (word2Int# x#)
557     enumFrom            = boundedEnumFrom
558     enumFromThen        = boundedEnumFromThen
559 #endif
560
561 instance Integral Word32 where
562     quot    x@(W32# x#) y@(W32# y#)
563         | y /= 0                    = W32# (x# `quotWord#` y#)
564         | otherwise                 = divZeroError "quot{Word32}" x
565     rem     x@(W32# x#) y@(W32# y#)
566         | y /= 0                    = W32# (x# `remWord#` y#)
567         | otherwise                 = divZeroError "rem{Word32}" x
568     div     x@(W32# x#) y@(W32# y#)
569         | y /= 0                    = W32# (x# `quotWord#` y#)
570         | otherwise                 = divZeroError "div{Word32}" x
571     mod     x@(W32# x#) y@(W32# y#)
572         | y /= 0                    = W32# (x# `remWord#` y#)
573         | otherwise                 = divZeroError "mod{Word32}" x
574     quotRem x@(W32# x#) y@(W32# y#)
575         | y /= 0                    = (W32# (x# `quotWord#` y#), W32# (x# `remWord#` y#))
576         | otherwise                 = divZeroError "quotRem{Word32}" x
577     divMod  x@(W32# x#) y@(W32# y#)
578         | y /= 0                    = (W32# (x# `quotWord#` y#), W32# (x# `remWord#` y#))
579         | otherwise                 = divZeroError "quotRem{Word32}" x
580     toInteger (W32# x#)
581 #if WORD_SIZE_IN_BITS == 32
582         | i# >=# 0#                 = S# i#
583         | otherwise                 = case word2Integer# x# of (# s, d #) -> J# s d
584         where
585         i# = word2Int# x#
586 #else
587                                     = S# (word2Int# x#)
588 #endif
589
590 instance Bits Word32 where
591     (W32# x#) .&.   (W32# y#)  = W32# (x# `and#` y#)
592     (W32# x#) .|.   (W32# y#)  = W32# (x# `or#`  y#)
593     (W32# x#) `xor` (W32# y#)  = W32# (x# `xor#` y#)
594     complement (W32# x#)       = W32# (x# `xor#` mb#) where W32# mb# = maxBound
595     (W32# x#) `shift` (I# i#)
596         | i# >=# 0#            = W32# (narrow32Word# (x# `shiftL#` i#))
597         | otherwise            = W32# (x# `shiftRL#` negateInt# i#)
598     (W32# x#) `rotate` (I# i#)
599         | i'# ==# 0# = W32# x#
600         | otherwise  = W32# (narrow32Word# ((x# `shiftL#` i'#) `or#`
601                                             (x# `shiftRL#` (32# -# i'#))))
602         where
603         i'# = word2Int# (int2Word# i# `and#` int2Word# 31#)
604     bitSize  _                = 32
605     isSigned _                = False
606
607 {-# RULES
608 "fromIntegral/Word8->Word32"   fromIntegral = \(W8# x#) -> W32# x#
609 "fromIntegral/Word16->Word32"  fromIntegral = \(W16# x#) -> W32# x#
610 "fromIntegral/Word32->Word32"  fromIntegral = id :: Word32 -> Word32
611 "fromIntegral/Word32->Integer" fromIntegral = toInteger :: Word32 -> Integer
612 "fromIntegral/a->Word32"       fromIntegral = \x -> case fromIntegral x of W# x# -> W32# (narrow32Word# x#)
613 "fromIntegral/Word32->a"       fromIntegral = \(W32# x#) -> fromIntegral (W# x#)
614   #-}
615
616 #endif
617
618 instance CCallable Word32
619 instance CReturnable Word32
620
621 instance Show Word32 where
622 #if WORD_SIZE_IN_BITS < 33
623     showsPrec p x = showsPrec p (toInteger x)
624 #else
625     showsPrec p x = showsPrec p (fromIntegral x :: Int)
626 #endif
627
628
629 instance Real Word32 where
630     toRational x = toInteger x % 1
631
632 instance Bounded Word32 where
633     minBound = 0
634     maxBound = 0xFFFFFFFF
635
636 instance Ix Word32 where
637     range (m,n)              = [m..n]
638     unsafeIndex b@(m,_) i    = fromIntegral (i - m)
639     inRange (m,n) i          = m <= i && i <= n
640     unsafeRangeSize b@(_l,h) = unsafeIndex b h + 1
641
642 instance Read Word32 where  
643 #if WORD_SIZE_IN_BITS < 33
644     readsPrec p s = [(fromInteger x, r) | (x, r) <- readsPrec p s]
645 #else
646     readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
647 #endif
648
649 ------------------------------------------------------------------------
650 -- type Word64
651 ------------------------------------------------------------------------
652
653 #if WORD_SIZE_IN_BITS < 64
654
655 data Word64 = W64# Word64#
656 -- ^ 64-bit unsigned integer type
657
658 instance Eq Word64 where
659     (W64# x#) == (W64# y#) = x# `eqWord64#` y#
660     (W64# x#) /= (W64# y#) = x# `neWord64#` y#
661
662 instance Ord Word64 where
663     (W64# x#) <  (W64# y#) = x# `ltWord64#` y#
664     (W64# x#) <= (W64# y#) = x# `leWord64#` y#
665     (W64# x#) >  (W64# y#) = x# `gtWord64#` y#
666     (W64# x#) >= (W64# y#) = x# `geWord64#` y#
667
668 instance Num Word64 where
669     (W64# x#) + (W64# y#)  = W64# (int64ToWord64# (word64ToInt64# x# `plusInt64#` word64ToInt64# y#))
670     (W64# x#) - (W64# y#)  = W64# (int64ToWord64# (word64ToInt64# x# `minusInt64#` word64ToInt64# y#))
671     (W64# x#) * (W64# y#)  = W64# (int64ToWord64# (word64ToInt64# x# `timesInt64#` word64ToInt64# y#))
672     negate (W64# x#)       = W64# (int64ToWord64# (negateInt64# (word64ToInt64# x#)))
673     abs x                  = x
674     signum 0               = 0
675     signum _               = 1
676     fromInteger (S# i#)    = W64# (int64ToWord64# (intToInt64# i#))
677     fromInteger (J# s# d#) = W64# (integerToWord64# s# d#)
678
679 instance Enum Word64 where
680     succ x
681         | x /= maxBound = x + 1
682         | otherwise     = succError "Word64"
683     pred x
684         | x /= minBound = x - 1
685         | otherwise     = predError "Word64"
686     toEnum i@(I# i#)
687         | i >= 0        = W64# (wordToWord64# (int2Word# i#))
688         | otherwise     = toEnumError "Word64" i (minBound::Word64, maxBound::Word64)
689     fromEnum x@(W64# x#)
690         | x <= fromIntegral (maxBound::Int)
691                         = I# (word2Int# (word64ToWord# x#))
692         | otherwise     = fromEnumError "Word64" x
693     enumFrom            = integralEnumFrom
694     enumFromThen        = integralEnumFromThen
695     enumFromTo          = integralEnumFromTo
696     enumFromThenTo      = integralEnumFromThenTo
697
698 instance Integral Word64 where
699     quot    x@(W64# x#) y@(W64# y#)
700         | y /= 0                    = W64# (x# `quotWord64#` y#)
701         | otherwise                 = divZeroError "quot{Word64}" x
702     rem     x@(W64# x#) y@(W64# y#)
703         | y /= 0                    = W64# (x# `remWord64#` y#)
704         | otherwise                 = divZeroError "rem{Word64}" x
705     div     x@(W64# x#) y@(W64# y#)
706         | y /= 0                    = W64# (x# `quotWord64#` y#)
707         | otherwise                 = divZeroError "div{Word64}" x
708     mod     x@(W64# x#) y@(W64# y#)
709         | y /= 0                    = W64# (x# `remWord64#` y#)
710         | otherwise                 = divZeroError "mod{Word64}" x
711     quotRem x@(W64# x#) y@(W64# y#)
712         | y /= 0                    = (W64# (x# `quotWord64#` y#), W64# (x# `remWord64#` y#))
713         | otherwise                 = divZeroError "quotRem{Word64}" x
714     divMod  x@(W64# x#) y@(W64# y#)
715         | y /= 0                    = (W64# (x# `quotWord64#` y#), W64# (x# `remWord64#` y#))
716         | otherwise                 = divZeroError "quotRem{Word64}" x
717     toInteger x@(W64# x#)
718         | x <= 0x7FFFFFFF           = S# (word2Int# (word64ToWord# x#))
719         | otherwise                 = case word64ToInteger# x# of (# s, d #) -> J# s d
720
721 instance Bits Word64 where
722     (W64# x#) .&.   (W64# y#)  = W64# (x# `and64#` y#)
723     (W64# x#) .|.   (W64# y#)  = W64# (x# `or64#`  y#)
724     (W64# x#) `xor` (W64# y#)  = W64# (x# `xor64#` y#)
725     complement (W64# x#)       = W64# (not64# x#)
726     (W64# x#) `shift` (I# i#)
727         | i# >=# 0#            = W64# (x# `shiftL64#` i#)
728         | otherwise            = W64# (x# `shiftRL64#` negateInt# i#)
729     (W64# x#) `rotate` (I# i#)
730         | i'# ==# 0# = W64# x#
731         | otherwise  = W64# ((x# `uncheckedShiftL64#` i'#) `or64#`
732                              (x# `uncheckedShiftRL64#` (64# -# i'#)))
733         where
734         i'# = word2Int# (int2Word# i# `and#` int2Word# 63#)
735     bitSize  _                = 64
736     isSigned _                = False
737
738 -- give the 64-bit shift operations the same treatment as the 32-bit
739 -- ones (see GHC.Base), namely we wrap them in tests to catch the
740 -- cases when we're shifting more than 64 bits to avoid unspecified
741 -- behaviour in the C shift operations.
742
743 shiftL64#, shiftRL64# :: Word64# -> Int# -> Word64#
744
745 a `shiftL64#` b  | b >=# 64#  = wordToWord64# (int2Word# 0#)
746                  | otherwise  = a `uncheckedShiftL64#` b
747
748 a `shiftRL64#` b | b >=# 64#  = wordToWord64# (int2Word# 0#)
749                  | otherwise  = a `uncheckedShiftRL64#` b
750
751
752 foreign import ccall unsafe "stg_eqWord64"      eqWord64#      :: Word64# -> Word64# -> Bool
753 foreign import ccall unsafe "stg_neWord64"      neWord64#      :: Word64# -> Word64# -> Bool
754 foreign import ccall unsafe "stg_ltWord64"      ltWord64#      :: Word64# -> Word64# -> Bool
755 foreign import ccall unsafe "stg_leWord64"      leWord64#      :: Word64# -> Word64# -> Bool
756 foreign import ccall unsafe "stg_gtWord64"      gtWord64#      :: Word64# -> Word64# -> Bool
757 foreign import ccall unsafe "stg_geWord64"      geWord64#      :: Word64# -> Word64# -> Bool
758 foreign import ccall unsafe "stg_int64ToWord64" int64ToWord64# :: Int64# -> Word64#
759 foreign import ccall unsafe "stg_word64ToInt64" word64ToInt64# :: Word64# -> Int64#
760 foreign import ccall unsafe "stg_intToInt64"    intToInt64#    :: Int# -> Int64#
761 foreign import ccall unsafe "stg_wordToWord64"  wordToWord64#  :: Word# -> Word64#
762 foreign import ccall unsafe "stg_word64ToWord"  word64ToWord#  :: Word64# -> Word#
763 foreign import ccall unsafe "stg_plusInt64"     plusInt64#     :: Int64# -> Int64# -> Int64#
764 foreign import ccall unsafe "stg_minusInt64"    minusInt64#    :: Int64# -> Int64# -> Int64#
765 foreign import ccall unsafe "stg_timesInt64"    timesInt64#    :: Int64# -> Int64# -> Int64#
766 foreign import ccall unsafe "stg_negateInt64"   negateInt64#   :: Int64# -> Int64#
767 foreign import ccall unsafe "stg_quotWord64"    quotWord64#    :: Word64# -> Word64# -> Word64#
768 foreign import ccall unsafe "stg_remWord64"     remWord64#     :: Word64# -> Word64# -> Word64#
769 foreign import ccall unsafe "stg_and64"         and64#         :: Word64# -> Word64# -> Word64#
770 foreign import ccall unsafe "stg_or64"          or64#          :: Word64# -> Word64# -> Word64#
771 foreign import ccall unsafe "stg_xor64"         xor64#         :: Word64# -> Word64# -> Word64#
772 foreign import ccall unsafe "stg_not64"         not64#         :: Word64# -> Word64#
773 foreign import ccall unsafe "stg_uncheckedShiftL64"      uncheckedShiftL64#      :: Word64# -> Int# -> Word64#
774 foreign import ccall unsafe "stg_uncheckedShiftRL64"     uncheckedShiftRL64#     :: Word64# -> Int# -> Word64#
775
776 foreign import ccall unsafe "stg_integerToWord64" integerToWord64# :: Int# -> ByteArray# -> Word64#
777
778
779 {-# RULES
780 "fromIntegral/Int->Word64"    fromIntegral = \(I#   x#) -> W64# (int64ToWord64# (intToInt64# x#))
781 "fromIntegral/Word->Word64"   fromIntegral = \(W#   x#) -> W64# (wordToWord64# x#)
782 "fromIntegral/Word64->Int"    fromIntegral = \(W64# x#) -> I#   (word2Int# (word64ToWord# x#))
783 "fromIntegral/Word64->Word"   fromIntegral = \(W64# x#) -> W#   (word64ToWord# x#)
784 "fromIntegral/Word64->Word64" fromIntegral = id :: Word64 -> Word64
785   #-}
786
787 #else
788
789 -- Word64 is represented in the same way as Word.
790 -- Operations may assume and must ensure that it holds only values
791 -- from its logical range.
792
793 data Word64 = W64# Word# deriving (Eq, Ord)
794 -- ^ 64-bit unsigned integer type
795
796 instance Num Word64 where
797     (W64# x#) + (W64# y#)  = W64# (x# `plusWord#` y#)
798     (W64# x#) - (W64# y#)  = W64# (x# `minusWord#` y#)
799     (W64# x#) * (W64# y#)  = W64# (x# `timesWord#` y#)
800     negate (W64# x#)       = W64# (int2Word# (negateInt# (word2Int# x#)))
801     abs x                  = x
802     signum 0               = 0
803     signum _               = 1
804     fromInteger (S# i#)    = W64# (int2Word# i#)
805     fromInteger (J# s# d#) = W64# (integer2Word# s# d#)
806
807 instance Enum Word64 where
808     succ x
809         | x /= maxBound = x + 1
810         | otherwise     = succError "Word64"
811     pred x
812         | x /= minBound = x - 1
813         | otherwise     = predError "Word64"
814     toEnum i@(I# i#)
815         | i >= 0        = W64# (int2Word# i#)
816         | otherwise     = toEnumError "Word64" i (minBound::Word64, maxBound::Word64)
817     fromEnum x@(W64# x#)
818         | x <= fromIntegral (maxBound::Int)
819                         = I# (word2Int# x#)
820         | otherwise     = fromEnumError "Word64" x
821     enumFrom            = integralEnumFrom
822     enumFromThen        = integralEnumFromThen
823     enumFromTo          = integralEnumFromTo
824     enumFromThenTo      = integralEnumFromThenTo
825
826 instance Integral Word64 where
827     quot    x@(W64# x#) y@(W64# y#)
828         | y /= 0                    = W64# (x# `quotWord#` y#)
829         | otherwise                 = divZeroError "quot{Word64}" x
830     rem     x@(W64# x#) y@(W64# y#)
831         | y /= 0                    = W64# (x# `remWord#` y#)
832         | otherwise                 = divZeroError "rem{Word64}" x
833     div     x@(W64# x#) y@(W64# y#)
834         | y /= 0                    = W64# (x# `quotWord#` y#)
835         | otherwise                 = divZeroError "div{Word64}" x
836     mod     x@(W64# x#) y@(W64# y#)
837         | y /= 0                    = W64# (x# `remWord#` y#)
838         | otherwise                 = divZeroError "mod{Word64}" x
839     quotRem x@(W64# x#) y@(W64# y#)
840         | y /= 0                    = (W64# (x# `quotWord#` y#), W64# (x# `remWord#` y#))
841         | otherwise                 = divZeroError "quotRem{Word64}" x
842     divMod  x@(W64# x#) y@(W64# y#)
843         | y /= 0                    = (W64# (x# `quotWord#` y#), W64# (x# `remWord#` y#))
844         | otherwise                 = divZeroError "quotRem{Word64}" x
845     toInteger (W64# x#)
846         | i# >=# 0#                 = S# i#
847         | otherwise                 = case word2Integer# x# of (# s, d #) -> J# s d
848         where
849         i# = word2Int# x#
850
851 instance Bits Word64 where
852     (W64# x#) .&.   (W64# y#)  = W64# (x# `and#` y#)
853     (W64# x#) .|.   (W64# y#)  = W64# (x# `or#`  y#)
854     (W64# x#) `xor` (W64# y#)  = W64# (x# `xor#` y#)
855     complement (W64# x#)       = W64# (x# `xor#` mb#) where W64# mb# = maxBound
856     (W64# x#) `shift` (I# i#)
857         | i# >=# 0#            = W64# (x# `shiftL#` i#)
858         | otherwise            = W64# (x# `shiftRL#` negateInt# i#)
859     (W64# x#) `rotate` (I# i#)
860         | i'# ==# 0# = W64# x#
861         | otherwise  = W64# ((x# `shiftL#` i'#) `or#`
862                              (x# `shiftRL#` (64# -# i'#)))
863         where
864         i'# = word2Int# (int2Word# i# `and#` int2Word# 63#)
865     bitSize  _                = 64
866     isSigned _                = False
867
868 {-# RULES
869 "fromIntegral/a->Word64" fromIntegral = \x -> case fromIntegral x of W# x# -> W64# x#
870 "fromIntegral/Word64->a" fromIntegral = \(W64# x#) -> fromIntegral (W# x#)
871   #-}
872
873 #endif
874
875 instance CCallable Word64
876 instance CReturnable Word64
877
878 instance Show Word64 where
879     showsPrec p x = showsPrec p (toInteger x)
880
881 instance Real Word64 where
882     toRational x = toInteger x % 1
883
884 instance Bounded Word64 where
885     minBound = 0
886     maxBound = 0xFFFFFFFFFFFFFFFF
887
888 instance Ix Word64 where
889     range (m,n)              = [m..n]
890     unsafeIndex b@(m,_) i    = fromIntegral (i - m)
891     inRange (m,n) i          = m <= i && i <= n
892     unsafeRangeSize b@(_l,h) = unsafeIndex b h + 1
893
894 instance Read Word64 where
895     readsPrec p s = [(fromInteger x, r) | (x, r) <- readsPrec p s]