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