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