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