Move Integer out into its own package
[ghc-base.git] / GHC / Word.hs
1 {-# OPTIONS_GHC -fno-implicit-prelude #-}
2 {-# OPTIONS_HADDOCK hide #-}
3 -----------------------------------------------------------------------------
4 -- |
5 -- Module      :  GHC.Word
6 -- Copyright   :  (c) The University of Glasgow, 1997-2002
7 -- License     :  see libraries/base/LICENSE
8 -- 
9 -- Maintainer  :  cvs-ghc@haskell.org
10 -- Stability   :  internal
11 -- Portability :  non-portable (GHC Extensions)
12 --
13 -- Sized unsigned integral types: 'Word', 'Word8', 'Word16', 'Word32', and
14 -- 'Word64'.
15 --
16 -----------------------------------------------------------------------------
17
18 #include "MachDeps.h"
19
20 -- #hide
21 module GHC.Word (
22     Word(..), Word8(..), Word16(..), Word32(..), Word64(..),
23     toEnumError, fromEnumError, succError, predError,
24     uncheckedShiftL64#,
25     uncheckedShiftRL64#
26     ) where
27
28 import Data.Bits
29
30 import GHC.Base
31 import GHC.Enum
32 import GHC.Num
33 import GHC.Real
34 import GHC.Read
35 import GHC.Arr
36 import GHC.Show
37
38 ------------------------------------------------------------------------
39 -- Helper functions
40 ------------------------------------------------------------------------
41
42 {-# NOINLINE toEnumError #-}
43 toEnumError :: (Show a) => String -> Int -> (a,a) -> b
44 toEnumError inst_ty i bnds =
45     error $ "Enum.toEnum{" ++ inst_ty ++ "}: tag (" ++
46             show i ++
47             ") is outside of bounds " ++
48             show bnds
49
50 {-# NOINLINE fromEnumError #-}
51 fromEnumError :: (Show a) => String -> a -> b
52 fromEnumError inst_ty x =
53     error $ "Enum.fromEnum{" ++ inst_ty ++ "}: value (" ++
54             show x ++
55             ") is outside of Int's bounds " ++
56             show (minBound::Int, maxBound::Int)
57
58 {-# NOINLINE succError #-}
59 succError :: String -> a
60 succError inst_ty =
61     error $ "Enum.succ{" ++ inst_ty ++ "}: tried to take `succ' of maxBound"
62
63 {-# NOINLINE predError #-}
64 predError :: String -> a
65 predError inst_ty =
66     error $ "Enum.pred{" ++ inst_ty ++ "}: tried to take `pred' of minBound"
67
68 ------------------------------------------------------------------------
69 -- type Word
70 ------------------------------------------------------------------------
71
72 -- |A 'Word' is an unsigned integral type, with the same size as 'Int'.
73 data Word = W# Word# deriving (Eq, Ord)
74
75 instance Show Word where
76     showsPrec p x = showsPrec p (toInteger x)
77
78 instance Num Word where
79     (W# x#) + (W# y#)      = W# (x# `plusWord#` y#)
80     (W# x#) - (W# y#)      = W# (x# `minusWord#` y#)
81     (W# x#) * (W# y#)      = W# (x# `timesWord#` y#)
82     negate (W# x#)         = W# (int2Word# (negateInt# (word2Int# x#)))
83     abs x                  = x
84     signum 0               = 0
85     signum _               = 1
86     fromInteger i          = W# (integerToWord i)
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#             = smallInteger i#
131         | otherwise             = wordToInteger x#
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 i          = W8# (narrow8Word# (integerToWord i))
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#)            = smallInteger (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 i          = W16# (narrow16Word# (integerToWord i))
303
304 instance Real Word16 where
305     toRational x = toInteger x % 1
306
307 instance Enum Word16 where
308     succ x
309         | x /= maxBound = x + 1
310         | otherwise     = succError "Word16"
311     pred x
312         | x /= minBound = x - 1
313         | otherwise     = predError "Word16"
314     toEnum i@(I# i#)
315         | i >= 0 && i <= fromIntegral (maxBound::Word16)
316                         = W16# (int2Word# i#)
317         | otherwise     = toEnumError "Word16" i (minBound::Word16, maxBound::Word16)
318     fromEnum (W16# x#)  = I# (word2Int# x#)
319     enumFrom            = boundedEnumFrom
320     enumFromThen        = boundedEnumFromThen
321
322 instance Integral Word16 where
323     quot    x@(W16# x#) y@(W16# y#)
324         | y /= 0                    = W16# (x# `quotWord#` y#)
325         | otherwise                 = divZeroError
326     rem     x@(W16# x#) y@(W16# y#)
327         | y /= 0                    = W16# (x# `remWord#` y#)
328         | otherwise                 = divZeroError
329     div     x@(W16# x#) y@(W16# y#)
330         | y /= 0                    = W16# (x# `quotWord#` y#)
331         | otherwise                 = divZeroError
332     mod     x@(W16# x#) y@(W16# y#)
333         | y /= 0                    = W16# (x# `remWord#` y#)
334         | otherwise                 = divZeroError
335     quotRem x@(W16# x#) y@(W16# y#)
336         | y /= 0                    = (W16# (x# `quotWord#` y#), W16# (x# `remWord#` y#))
337         | otherwise                 = divZeroError
338     divMod  x@(W16# x#) y@(W16# y#)
339         | y /= 0                    = (W16# (x# `quotWord#` y#), W16# (x# `remWord#` y#))
340         | otherwise                 = divZeroError
341     toInteger (W16# x#)             = smallInteger (word2Int# x#)
342
343 instance Bounded Word16 where
344     minBound = 0
345     maxBound = 0xFFFF
346
347 instance Ix Word16 where
348     range (m,n)              = [m..n]
349     unsafeIndex b@(m,_) i    = fromIntegral (i - m)
350     inRange (m,n) i          = m <= i && i <= n
351
352 instance Read Word16 where
353     readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
354
355 instance Bits Word16 where
356     {-# INLINE shift #-}
357
358     (W16# x#) .&.   (W16# y#)  = W16# (x# `and#` y#)
359     (W16# x#) .|.   (W16# y#)  = W16# (x# `or#`  y#)
360     (W16# x#) `xor` (W16# y#)  = W16# (x# `xor#` y#)
361     complement (W16# x#)       = W16# (x# `xor#` mb#) where W16# mb# = maxBound
362     (W16# x#) `shift` (I# i#)
363         | i# >=# 0#            = W16# (narrow16Word# (x# `shiftL#` i#))
364         | otherwise            = W16# (x# `shiftRL#` negateInt# i#)
365     (W16# x#) `rotate` (I# i#)
366         | i'# ==# 0# = W16# x#
367         | otherwise  = W16# (narrow16Word# ((x# `uncheckedShiftL#` i'#) `or#`
368                                             (x# `uncheckedShiftRL#` (16# -# i'#))))
369         where
370         i'# = word2Int# (int2Word# i# `and#` int2Word# 15#)
371     bitSize  _                = 16
372     isSigned _                = False
373
374 {-# RULES
375 "fromIntegral/Word8->Word16"   fromIntegral = \(W8# x#) -> W16# x#
376 "fromIntegral/Word16->Word16"  fromIntegral = id :: Word16 -> Word16
377 "fromIntegral/Word16->Integer" fromIntegral = toInteger :: Word16 -> Integer
378 "fromIntegral/a->Word16"       fromIntegral = \x -> case fromIntegral x of W# x# -> W16# (narrow16Word# x#)
379 "fromIntegral/Word16->a"       fromIntegral = \(W16# x#) -> fromIntegral (W# x#)
380   #-}
381
382 ------------------------------------------------------------------------
383 -- type Word32
384 ------------------------------------------------------------------------
385
386 #if WORD_SIZE_IN_BITS < 32
387
388 data Word32 = W32# Word32#
389 -- ^ 32-bit unsigned integer type
390
391 instance Eq Word32 where
392     (W32# x#) == (W32# y#) = x# `eqWord32#` y#
393     (W32# x#) /= (W32# y#) = x# `neWord32#` y#
394
395 instance Ord Word32 where
396     (W32# x#) <  (W32# y#) = x# `ltWord32#` y#
397     (W32# x#) <= (W32# y#) = x# `leWord32#` y#
398     (W32# x#) >  (W32# y#) = x# `gtWord32#` y#
399     (W32# x#) >= (W32# y#) = x# `geWord32#` y#
400
401 instance Num Word32 where
402     (W32# x#) + (W32# y#)  = W32# (int32ToWord32# (word32ToInt32# x# `plusInt32#` word32ToInt32# y#))
403     (W32# x#) - (W32# y#)  = W32# (int32ToWord32# (word32ToInt32# x# `minusInt32#` word32ToInt32# y#))
404     (W32# x#) * (W32# y#)  = W32# (int32ToWord32# (word32ToInt32# x# `timesInt32#` word32ToInt32# y#))
405     negate (W32# x#)       = W32# (int32ToWord32# (negateInt32# (word32ToInt32# x#)))
406     abs x                  = x
407     signum 0               = 0
408     signum _               = 1
409     fromInteger (S# i#)    = W32# (int32ToWord32# (intToInt32# i#))
410     fromInteger (J# s# d#) = W32# (integerToWord32# s# d#)
411
412 instance Enum Word32 where
413     succ x
414         | x /= maxBound = x + 1
415         | otherwise     = succError "Word32"
416     pred x
417         | x /= minBound = x - 1
418         | otherwise     = predError "Word32"
419     toEnum i@(I# i#)
420         | i >= 0        = W32# (wordToWord32# (int2Word# i#))
421         | otherwise     = toEnumError "Word32" i (minBound::Word32, maxBound::Word32)
422     fromEnum x@(W32# x#)
423         | x <= fromIntegral (maxBound::Int)
424                         = I# (word2Int# (word32ToWord# x#))
425         | otherwise     = fromEnumError "Word32" x
426     enumFrom            = integralEnumFrom
427     enumFromThen        = integralEnumFromThen
428     enumFromTo          = integralEnumFromTo
429     enumFromThenTo      = integralEnumFromThenTo
430
431 instance Integral Word32 where
432     quot    x@(W32# x#) y@(W32# y#)
433         | y /= 0                    = W32# (x# `quotWord32#` y#)
434         | otherwise                 = divZeroError
435     rem     x@(W32# x#) y@(W32# y#)
436         | y /= 0                    = W32# (x# `remWord32#` y#)
437         | otherwise                 = divZeroError
438     div     x@(W32# x#) y@(W32# y#)
439         | y /= 0                    = W32# (x# `quotWord32#` y#)
440         | otherwise                 = divZeroError
441     mod     x@(W32# x#) y@(W32# y#)
442         | y /= 0                    = W32# (x# `remWord32#` y#)
443         | otherwise                 = divZeroError
444     quotRem x@(W32# x#) y@(W32# y#)
445         | y /= 0                    = (W32# (x# `quotWord32#` y#), W32# (x# `remWord32#` y#))
446         | otherwise                 = divZeroError
447     divMod  x@(W32# x#) y@(W32# y#)
448         | y /= 0                    = (W32# (x# `quotWord32#` y#), W32# (x# `remWord32#` y#))
449         | otherwise                 = divZeroError
450     toInteger x@(W32# x#)
451         | x <= fromIntegral (maxBound::Int)  = S# (word2Int# (word32ToWord# x#))
452         | otherwise                 = case word32ToInteger# x# of (# s, d #) -> J# s d
453
454 instance Bits Word32 where
455     {-# INLINE shift #-}
456
457     (W32# x#) .&.   (W32# y#)  = W32# (x# `and32#` y#)
458     (W32# x#) .|.   (W32# y#)  = W32# (x# `or32#`  y#)
459     (W32# x#) `xor` (W32# y#)  = W32# (x# `xor32#` y#)
460     complement (W32# x#)       = W32# (not32# x#)
461     (W32# x#) `shift` (I# i#)
462         | i# >=# 0#            = W32# (x# `shiftL32#` i#)
463         | otherwise            = W32# (x# `shiftRL32#` negateInt# i#)
464     (W32# x#) `rotate` (I# i#)
465         | i'# ==# 0# = W32# x#
466         | otherwise  = W32# ((x# `shiftL32#` i'#) `or32#`
467                              (x# `shiftRL32#` (32# -# i'#)))
468         where
469         i'# = word2Int# (int2Word# i# `and#` int2Word# 31#)
470     bitSize  _                = 32
471     isSigned _                = False
472
473 foreign import unsafe "stg_eqWord32"      eqWord32#      :: Word32# -> Word32# -> Bool
474 foreign import unsafe "stg_neWord32"      neWord32#      :: Word32# -> Word32# -> Bool
475 foreign import unsafe "stg_ltWord32"      ltWord32#      :: Word32# -> Word32# -> Bool
476 foreign import unsafe "stg_leWord32"      leWord32#      :: Word32# -> Word32# -> Bool
477 foreign import unsafe "stg_gtWord32"      gtWord32#      :: Word32# -> Word32# -> Bool
478 foreign import unsafe "stg_geWord32"      geWord32#      :: Word32# -> Word32# -> Bool
479 foreign import unsafe "stg_int32ToWord32" int32ToWord32# :: Int32# -> Word32#
480 foreign import unsafe "stg_word32ToInt32" word32ToInt32# :: Word32# -> Int32#
481 foreign import unsafe "stg_intToInt32"    intToInt32#    :: Int# -> Int32#
482 foreign import unsafe "stg_wordToWord32"  wordToWord32#  :: Word# -> Word32#
483 foreign import unsafe "stg_word32ToWord"  word32ToWord#  :: Word32# -> Word#
484 foreign import unsafe "stg_plusInt32"     plusInt32#     :: Int32# -> Int32# -> Int32#
485 foreign import unsafe "stg_minusInt32"    minusInt32#    :: Int32# -> Int32# -> Int32#
486 foreign import unsafe "stg_timesInt32"    timesInt32#    :: Int32# -> Int32# -> Int32#
487 foreign import unsafe "stg_negateInt32"   negateInt32#   :: Int32# -> Int32#
488 foreign import unsafe "stg_quotWord32"    quotWord32#    :: Word32# -> Word32# -> Word32#
489 foreign import unsafe "stg_remWord32"     remWord32#     :: Word32# -> Word32# -> Word32#
490 foreign import unsafe "stg_and32"         and32#         :: Word32# -> Word32# -> Word32#
491 foreign import unsafe "stg_or32"          or32#          :: Word32# -> Word32# -> Word32#
492 foreign import unsafe "stg_xor32"         xor32#         :: Word32# -> Word32# -> Word32#
493 foreign import unsafe "stg_not32"         not32#         :: Word32# -> Word32#
494 foreign import unsafe "stg_shiftL32"      shiftL32#      :: Word32# -> Int# -> Word32#
495 foreign import unsafe "stg_shiftRL32"     shiftRL32#     :: Word32# -> Int# -> Word32#
496
497 {-# RULES
498 "fromIntegral/Int->Word32"    fromIntegral = \(I#   x#) -> W32# (int32ToWord32# (intToInt32# x#))
499 "fromIntegral/Word->Word32"   fromIntegral = \(W#   x#) -> W32# (wordToWord32# x#)
500 "fromIntegral/Word32->Int"    fromIntegral = \(W32# x#) -> I#   (word2Int# (word32ToWord# x#))
501 "fromIntegral/Word32->Word"   fromIntegral = \(W32# x#) -> W#   (word32ToWord# x#)
502 "fromIntegral/Word32->Word32" fromIntegral = id :: Word32 -> Word32
503   #-}
504
505 #else 
506
507 -- Word32 is represented in the same way as Word.
508 #if WORD_SIZE_IN_BITS > 32
509 -- Operations may assume and must ensure that it holds only values
510 -- from its logical range.
511 #endif
512
513 data Word32 = W32# Word# deriving (Eq, Ord)
514 -- ^ 32-bit unsigned integer type
515
516 instance Num Word32 where
517     (W32# x#) + (W32# y#)  = W32# (narrow32Word# (x# `plusWord#` y#))
518     (W32# x#) - (W32# y#)  = W32# (narrow32Word# (x# `minusWord#` y#))
519     (W32# x#) * (W32# y#)  = W32# (narrow32Word# (x# `timesWord#` y#))
520     negate (W32# x#)       = W32# (narrow32Word# (int2Word# (negateInt# (word2Int# x#))))
521     abs x                  = x
522     signum 0               = 0
523     signum _               = 1
524     fromInteger i          = W32# (narrow32Word# (integerToWord i))
525
526 instance Enum Word32 where
527     succ x
528         | x /= maxBound = x + 1
529         | otherwise     = succError "Word32"
530     pred x
531         | x /= minBound = x - 1
532         | otherwise     = predError "Word32"
533     toEnum i@(I# i#)
534         | i >= 0
535 #if WORD_SIZE_IN_BITS > 32
536           && i <= fromIntegral (maxBound::Word32)
537 #endif
538                         = W32# (int2Word# i#)
539         | otherwise     = toEnumError "Word32" i (minBound::Word32, maxBound::Word32)
540 #if WORD_SIZE_IN_BITS == 32
541     fromEnum x@(W32# x#)
542         | x <= fromIntegral (maxBound::Int)
543                         = I# (word2Int# x#)
544         | otherwise     = fromEnumError "Word32" x
545     enumFrom            = integralEnumFrom
546     enumFromThen        = integralEnumFromThen
547     enumFromTo          = integralEnumFromTo
548     enumFromThenTo      = integralEnumFromThenTo
549 #else
550     fromEnum (W32# x#)  = I# (word2Int# x#)
551     enumFrom            = boundedEnumFrom
552     enumFromThen        = boundedEnumFromThen
553 #endif
554
555 instance Integral Word32 where
556     quot    x@(W32# x#) y@(W32# y#)
557         | y /= 0                    = W32# (x# `quotWord#` y#)
558         | otherwise                 = divZeroError
559     rem     x@(W32# x#) y@(W32# y#)
560         | y /= 0                    = W32# (x# `remWord#` y#)
561         | otherwise                 = divZeroError
562     div     x@(W32# x#) y@(W32# y#)
563         | y /= 0                    = W32# (x# `quotWord#` y#)
564         | otherwise                 = divZeroError
565     mod     x@(W32# x#) y@(W32# y#)
566         | y /= 0                    = W32# (x# `remWord#` y#)
567         | otherwise                 = divZeroError
568     quotRem x@(W32# x#) y@(W32# y#)
569         | y /= 0                    = (W32# (x# `quotWord#` y#), W32# (x# `remWord#` y#))
570         | otherwise                 = divZeroError
571     divMod  x@(W32# x#) y@(W32# y#)
572         | y /= 0                    = (W32# (x# `quotWord#` y#), W32# (x# `remWord#` y#))
573         | otherwise                 = divZeroError
574     toInteger (W32# x#)
575 #if WORD_SIZE_IN_BITS == 32
576         | i# >=# 0#                 = smallInteger i#
577         | otherwise                 = word2Integer x#
578         where
579         i# = word2Int# x#
580 #else
581                                     = smallInteger (word2Int# x#)
582 #endif
583
584 instance Bits Word32 where
585     {-# INLINE shift #-}
586
587     (W32# x#) .&.   (W32# y#)  = W32# (x# `and#` y#)
588     (W32# x#) .|.   (W32# y#)  = W32# (x# `or#`  y#)
589     (W32# x#) `xor` (W32# y#)  = W32# (x# `xor#` y#)
590     complement (W32# x#)       = W32# (x# `xor#` mb#) where W32# mb# = maxBound
591     (W32# x#) `shift` (I# i#)
592         | i# >=# 0#            = W32# (narrow32Word# (x# `shiftL#` i#))
593         | otherwise            = W32# (x# `shiftRL#` negateInt# i#)
594     (W32# x#) `rotate` (I# i#)
595         | i'# ==# 0# = W32# x#
596         | otherwise  = W32# (narrow32Word# ((x# `uncheckedShiftL#` i'#) `or#`
597                                             (x# `uncheckedShiftRL#` (32# -# i'#))))
598         where
599         i'# = word2Int# (int2Word# i# `and#` int2Word# 31#)
600     bitSize  _                = 32
601     isSigned _                = False
602
603 {-# RULES
604 "fromIntegral/Word8->Word32"   fromIntegral = \(W8# x#) -> W32# x#
605 "fromIntegral/Word16->Word32"  fromIntegral = \(W16# x#) -> W32# x#
606 "fromIntegral/Word32->Word32"  fromIntegral = id :: Word32 -> Word32
607 "fromIntegral/Word32->Integer" fromIntegral = toInteger :: Word32 -> Integer
608 "fromIntegral/a->Word32"       fromIntegral = \x -> case fromIntegral x of W# x# -> W32# (narrow32Word# x#)
609 "fromIntegral/Word32->a"       fromIntegral = \(W32# x#) -> fromIntegral (W# x#)
610   #-}
611
612 #endif
613
614 instance Show Word32 where
615 #if WORD_SIZE_IN_BITS < 33
616     showsPrec p x = showsPrec p (toInteger x)
617 #else
618     showsPrec p x = showsPrec p (fromIntegral x :: Int)
619 #endif
620
621
622 instance Real Word32 where
623     toRational x = toInteger x % 1
624
625 instance Bounded Word32 where
626     minBound = 0
627     maxBound = 0xFFFFFFFF
628
629 instance Ix Word32 where
630     range (m,n)              = [m..n]
631     unsafeIndex b@(m,_) i    = fromIntegral (i - m)
632     inRange (m,n) i          = m <= i && i <= n
633
634 instance Read Word32 where  
635 #if WORD_SIZE_IN_BITS < 33
636     readsPrec p s = [(fromInteger x, r) | (x, r) <- readsPrec p s]
637 #else
638     readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
639 #endif
640
641 ------------------------------------------------------------------------
642 -- type Word64
643 ------------------------------------------------------------------------
644
645 #if WORD_SIZE_IN_BITS < 64
646
647 data Word64 = W64# Word64#
648 -- ^ 64-bit unsigned integer type
649
650 instance Eq Word64 where
651     (W64# x#) == (W64# y#) = x# `eqWord64#` y#
652     (W64# x#) /= (W64# y#) = x# `neWord64#` y#
653
654 instance Ord Word64 where
655     (W64# x#) <  (W64# y#) = x# `ltWord64#` y#
656     (W64# x#) <= (W64# y#) = x# `leWord64#` y#
657     (W64# x#) >  (W64# y#) = x# `gtWord64#` y#
658     (W64# x#) >= (W64# y#) = x# `geWord64#` y#
659
660 instance Num Word64 where
661     (W64# x#) + (W64# y#)  = W64# (int64ToWord64# (word64ToInt64# x# `plusInt64#` word64ToInt64# y#))
662     (W64# x#) - (W64# y#)  = W64# (int64ToWord64# (word64ToInt64# x# `minusInt64#` word64ToInt64# y#))
663     (W64# x#) * (W64# y#)  = W64# (int64ToWord64# (word64ToInt64# x# `timesInt64#` word64ToInt64# y#))
664     negate (W64# x#)       = W64# (int64ToWord64# (negateInt64# (word64ToInt64# x#)))
665     abs x                  = x
666     signum 0               = 0
667     signum _               = 1
668     fromInteger (S# i#)    = W64# (int64ToWord64# (intToInt64# i#))
669     fromInteger (J# s# d#) = W64# (integerToWord64# s# d#)
670
671 instance Enum Word64 where
672     succ x
673         | x /= maxBound = x + 1
674         | otherwise     = succError "Word64"
675     pred x
676         | x /= minBound = x - 1
677         | otherwise     = predError "Word64"
678     toEnum i@(I# i#)
679         | i >= 0        = W64# (wordToWord64# (int2Word# i#))
680         | otherwise     = toEnumError "Word64" i (minBound::Word64, maxBound::Word64)
681     fromEnum x@(W64# x#)
682         | x <= fromIntegral (maxBound::Int)
683                         = I# (word2Int# (word64ToWord# x#))
684         | otherwise     = fromEnumError "Word64" x
685     enumFrom            = integralEnumFrom
686     enumFromThen        = integralEnumFromThen
687     enumFromTo          = integralEnumFromTo
688     enumFromThenTo      = integralEnumFromThenTo
689
690 instance Integral Word64 where
691     quot    x@(W64# x#) y@(W64# y#)
692         | y /= 0                    = W64# (x# `quotWord64#` y#)
693         | otherwise                 = divZeroError
694     rem     x@(W64# x#) y@(W64# y#)
695         | y /= 0                    = W64# (x# `remWord64#` y#)
696         | otherwise                 = divZeroError
697     div     x@(W64# x#) y@(W64# y#)
698         | y /= 0                    = W64# (x# `quotWord64#` y#)
699         | otherwise                 = divZeroError
700     mod     x@(W64# x#) y@(W64# y#)
701         | y /= 0                    = W64# (x# `remWord64#` y#)
702         | otherwise                 = divZeroError
703     quotRem x@(W64# x#) y@(W64# y#)
704         | y /= 0                    = (W64# (x# `quotWord64#` y#), W64# (x# `remWord64#` y#))
705         | otherwise                 = divZeroError
706     divMod  x@(W64# x#) y@(W64# y#)
707         | y /= 0                    = (W64# (x# `quotWord64#` y#), W64# (x# `remWord64#` y#))
708         | otherwise                 = divZeroError
709     toInteger x@(W64# x#)
710         | x <= 0x7FFFFFFF           = S# (word2Int# (word64ToWord# x#))
711         | otherwise                 = case word64ToInteger# x# of (# s, d #) -> J# s d
712
713 instance Bits Word64 where
714     {-# INLINE shift #-}
715
716     (W64# x#) .&.   (W64# y#)  = W64# (x# `and64#` y#)
717     (W64# x#) .|.   (W64# y#)  = W64# (x# `or64#`  y#)
718     (W64# x#) `xor` (W64# y#)  = W64# (x# `xor64#` y#)
719     complement (W64# x#)       = W64# (not64# x#)
720     (W64# x#) `shift` (I# i#)
721         | i# >=# 0#            = W64# (x# `shiftL64#` i#)
722         | otherwise            = W64# (x# `shiftRL64#` negateInt# i#)
723     (W64# x#) `rotate` (I# i#)
724         | i'# ==# 0# = W64# x#
725         | otherwise  = W64# ((x# `uncheckedShiftL64#` i'#) `or64#`
726                              (x# `uncheckedShiftRL64#` (64# -# i'#)))
727         where
728         i'# = word2Int# (int2Word# i# `and#` int2Word# 63#)
729     bitSize  _                = 64
730     isSigned _                = False
731
732 -- give the 64-bit shift operations the same treatment as the 32-bit
733 -- ones (see GHC.Base), namely we wrap them in tests to catch the
734 -- cases when we're shifting more than 64 bits to avoid unspecified
735 -- behaviour in the C shift operations.
736
737 shiftL64#, shiftRL64# :: Word64# -> Int# -> Word64#
738
739 a `shiftL64#` b  | b >=# 64#  = wordToWord64# (int2Word# 0#)
740                  | otherwise  = a `uncheckedShiftL64#` b
741
742 a `shiftRL64#` b | b >=# 64#  = wordToWord64# (int2Word# 0#)
743                  | otherwise  = a `uncheckedShiftRL64#` b
744
745
746 foreign import ccall unsafe "hs_eqWord64"      eqWord64#      :: Word64# -> Word64# -> Bool
747 foreign import ccall unsafe "hs_neWord64"      neWord64#      :: Word64# -> Word64# -> Bool
748 foreign import ccall unsafe "hs_ltWord64"      ltWord64#      :: Word64# -> Word64# -> Bool
749 foreign import ccall unsafe "hs_leWord64"      leWord64#      :: Word64# -> Word64# -> Bool
750 foreign import ccall unsafe "hs_gtWord64"      gtWord64#      :: Word64# -> Word64# -> Bool
751 foreign import ccall unsafe "hs_geWord64"      geWord64#      :: Word64# -> Word64# -> Bool
752 foreign import ccall unsafe "hs_int64ToWord64" int64ToWord64# :: Int64# -> Word64#
753 foreign import ccall unsafe "hs_word64ToInt64" word64ToInt64# :: Word64# -> Int64#
754 foreign import ccall unsafe "hs_intToInt64"    intToInt64#    :: Int# -> Int64#
755 foreign import ccall unsafe "hs_wordToWord64"  wordToWord64#  :: Word# -> Word64#
756 foreign import ccall unsafe "hs_word64ToWord"  word64ToWord#  :: Word64# -> Word#
757 foreign import ccall unsafe "hs_plusInt64"     plusInt64#     :: Int64# -> Int64# -> Int64#
758 foreign import ccall unsafe "hs_minusInt64"    minusInt64#    :: Int64# -> Int64# -> Int64#
759 foreign import ccall unsafe "hs_timesInt64"    timesInt64#    :: Int64# -> Int64# -> Int64#
760 foreign import ccall unsafe "hs_negateInt64"   negateInt64#   :: Int64# -> Int64#
761 foreign import ccall unsafe "hs_quotWord64"    quotWord64#    :: Word64# -> Word64# -> Word64#
762 foreign import ccall unsafe "hs_remWord64"     remWord64#     :: Word64# -> Word64# -> Word64#
763 foreign import ccall unsafe "hs_and64"         and64#         :: Word64# -> Word64# -> Word64#
764 foreign import ccall unsafe "hs_or64"          or64#          :: Word64# -> Word64# -> Word64#
765 foreign import ccall unsafe "hs_xor64"         xor64#         :: Word64# -> Word64# -> Word64#
766 foreign import ccall unsafe "hs_not64"         not64#         :: Word64# -> Word64#
767 foreign import ccall unsafe "hs_uncheckedShiftL64"      uncheckedShiftL64#      :: Word64# -> Int# -> Word64#
768 foreign import ccall unsafe "hs_uncheckedShiftRL64"     uncheckedShiftRL64#     :: Word64# -> Int# -> Word64#
769
770 foreign import ccall unsafe "hs_integerToWord64" integerToWord64# :: Int# -> ByteArray# -> Word64#
771
772
773 {-# RULES
774 "fromIntegral/Int->Word64"    fromIntegral = \(I#   x#) -> W64# (int64ToWord64# (intToInt64# x#))
775 "fromIntegral/Word->Word64"   fromIntegral = \(W#   x#) -> W64# (wordToWord64# x#)
776 "fromIntegral/Word64->Int"    fromIntegral = \(W64# x#) -> I#   (word2Int# (word64ToWord# x#))
777 "fromIntegral/Word64->Word"   fromIntegral = \(W64# x#) -> W#   (word64ToWord# x#)
778 "fromIntegral/Word64->Word64" fromIntegral = id :: Word64 -> Word64
779   #-}
780
781 #else
782
783 -- Word64 is represented in the same way as Word.
784 -- Operations may assume and must ensure that it holds only values
785 -- from its logical range.
786
787 data Word64 = W64# Word# deriving (Eq, Ord)
788 -- ^ 64-bit unsigned integer type
789
790 instance Num Word64 where
791     (W64# x#) + (W64# y#)  = W64# (x# `plusWord#` y#)
792     (W64# x#) - (W64# y#)  = W64# (x# `minusWord#` y#)
793     (W64# x#) * (W64# y#)  = W64# (x# `timesWord#` y#)
794     negate (W64# x#)       = W64# (int2Word# (negateInt# (word2Int# x#)))
795     abs x                  = x
796     signum 0               = 0
797     signum _               = 1
798     fromInteger i          = W64# (integerToWord i)
799
800 instance Enum Word64 where
801     succ x
802         | x /= maxBound = x + 1
803         | otherwise     = succError "Word64"
804     pred x
805         | x /= minBound = x - 1
806         | otherwise     = predError "Word64"
807     toEnum i@(I# i#)
808         | i >= 0        = W64# (int2Word# i#)
809         | otherwise     = toEnumError "Word64" i (minBound::Word64, maxBound::Word64)
810     fromEnum x@(W64# x#)
811         | x <= fromIntegral (maxBound::Int)
812                         = I# (word2Int# x#)
813         | otherwise     = fromEnumError "Word64" x
814     enumFrom            = integralEnumFrom
815     enumFromThen        = integralEnumFromThen
816     enumFromTo          = integralEnumFromTo
817     enumFromThenTo      = integralEnumFromThenTo
818
819 instance Integral Word64 where
820     quot    x@(W64# x#) y@(W64# y#)
821         | y /= 0                    = W64# (x# `quotWord#` y#)
822         | otherwise                 = divZeroError
823     rem     x@(W64# x#) y@(W64# y#)
824         | y /= 0                    = W64# (x# `remWord#` y#)
825         | otherwise                 = divZeroError
826     div     x@(W64# x#) y@(W64# y#)
827         | y /= 0                    = W64# (x# `quotWord#` y#)
828         | otherwise                 = divZeroError
829     mod     x@(W64# x#) y@(W64# y#)
830         | y /= 0                    = W64# (x# `remWord#` y#)
831         | otherwise                 = divZeroError
832     quotRem x@(W64# x#) y@(W64# y#)
833         | y /= 0                    = (W64# (x# `quotWord#` y#), W64# (x# `remWord#` y#))
834         | otherwise                 = divZeroError
835     divMod  x@(W64# x#) y@(W64# y#)
836         | y /= 0                    = (W64# (x# `quotWord#` y#), W64# (x# `remWord#` y#))
837         | otherwise                 = divZeroError
838     toInteger (W64# x#)
839         | i# >=# 0#                 = smallInteger i#
840         | otherwise                 = wordToInteger x#
841         where
842         i# = word2Int# x#
843
844 instance Bits Word64 where
845     {-# INLINE shift #-}
846
847     (W64# x#) .&.   (W64# y#)  = W64# (x# `and#` y#)
848     (W64# x#) .|.   (W64# y#)  = W64# (x# `or#`  y#)
849     (W64# x#) `xor` (W64# y#)  = W64# (x# `xor#` y#)
850     complement (W64# x#)       = W64# (x# `xor#` mb#) where W64# mb# = maxBound
851     (W64# x#) `shift` (I# i#)
852         | i# >=# 0#            = W64# (x# `shiftL#` i#)
853         | otherwise            = W64# (x# `shiftRL#` negateInt# i#)
854     (W64# x#) `rotate` (I# i#)
855         | i'# ==# 0# = W64# x#
856         | otherwise  = W64# ((x# `uncheckedShiftL#` i'#) `or#`
857                              (x# `uncheckedShiftRL#` (64# -# i'#)))
858         where
859         i'# = word2Int# (int2Word# i# `and#` int2Word# 63#)
860     bitSize  _                = 64
861     isSigned _                = False
862
863 {-# RULES
864 "fromIntegral/a->Word64" fromIntegral = \x -> case fromIntegral x of W# x# -> W64# x#
865 "fromIntegral/Word64->a" fromIntegral = \(W64# x#) -> fromIntegral (W# x#)
866   #-}
867
868 uncheckedShiftL64#  = uncheckedShiftL#
869 uncheckedShiftRL64# = uncheckedShiftRL#
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]