1 {-# OPTIONS_GHC -fno-implicit-prelude #-}
2 -----------------------------------------------------------------------------
5 -- Copyright : (c) The University of Glasgow, 1997-2002
6 -- License : see libraries/base/LICENSE
8 -- Maintainer : cvs-ghc@haskell.org
9 -- Stability : internal
10 -- Portability : non-portable (GHC Extensions)
12 -- Sized unsigned integral types: 'Word', 'Word8', 'Word16', 'Word32', and
15 -----------------------------------------------------------------------------
21 Word(..), Word8(..), Word16(..), Word32(..), Word64(..),
22 toEnumError, fromEnumError, succError, predError)
27 import {-# SOURCE #-} GHC.Err
36 ------------------------------------------------------------------------
38 ------------------------------------------------------------------------
40 {-# NOINLINE toEnumError #-}
41 toEnumError :: (Show a) => String -> Int -> (a,a) -> b
42 toEnumError inst_ty i bnds =
43 error $ "Enum.toEnum{" ++ inst_ty ++ "}: tag (" ++
45 ") is outside of bounds " ++
48 {-# NOINLINE fromEnumError #-}
49 fromEnumError :: (Show a) => String -> a -> b
50 fromEnumError inst_ty x =
51 error $ "Enum.fromEnum{" ++ inst_ty ++ "}: value (" ++
53 ") is outside of Int's bounds " ++
54 show (minBound::Int, maxBound::Int)
56 {-# NOINLINE succError #-}
57 succError :: String -> a
59 error $ "Enum.succ{" ++ inst_ty ++ "}: tried to take `succ' of maxBound"
61 {-# NOINLINE predError #-}
62 predError :: String -> a
64 error $ "Enum.pred{" ++ inst_ty ++ "}: tried to take `pred' of minBound"
66 ------------------------------------------------------------------------
68 ------------------------------------------------------------------------
70 -- |A 'Word' is an unsigned integral type, with the same size as 'Int'.
71 data Word = W# Word# deriving (Eq, Ord)
73 instance Show Word where
74 showsPrec p x = showsPrec p (toInteger x)
76 instance Num Word where
77 (W# x#) + (W# y#) = W# (x# `plusWord#` y#)
78 (W# x#) - (W# y#) = W# (x# `minusWord#` y#)
79 (W# x#) * (W# y#) = W# (x# `timesWord#` y#)
80 negate (W# x#) = W# (int2Word# (negateInt# (word2Int# x#)))
84 fromInteger (S# i#) = W# (int2Word# i#)
85 fromInteger (J# s# d#) = W# (integer2Word# s# d#)
87 instance Real Word where
88 toRational x = toInteger x % 1
90 instance Enum Word where
92 | x /= maxBound = x + 1
93 | otherwise = succError "Word"
95 | x /= minBound = x - 1
96 | otherwise = predError "Word"
98 | i >= 0 = W# (int2Word# i#)
99 | otherwise = toEnumError "Word" i (minBound::Word, maxBound::Word)
101 | x <= fromIntegral (maxBound::Int)
103 | otherwise = fromEnumError "Word" x
104 enumFrom = integralEnumFrom
105 enumFromThen = integralEnumFromThen
106 enumFromTo = integralEnumFromTo
107 enumFromThenTo = integralEnumFromThenTo
109 instance Integral Word where
110 quot x@(W# x#) y@(W# y#)
111 | y /= 0 = W# (x# `quotWord#` y#)
112 | otherwise = divZeroError
113 rem x@(W# x#) y@(W# y#)
114 | y /= 0 = W# (x# `remWord#` y#)
115 | otherwise = divZeroError
116 div x@(W# x#) y@(W# y#)
117 | y /= 0 = W# (x# `quotWord#` y#)
118 | otherwise = divZeroError
119 mod x@(W# x#) y@(W# y#)
120 | y /= 0 = W# (x# `remWord#` y#)
121 | otherwise = divZeroError
122 quotRem x@(W# x#) y@(W# y#)
123 | y /= 0 = (W# (x# `quotWord#` y#), W# (x# `remWord#` y#))
124 | otherwise = divZeroError
125 divMod x@(W# x#) y@(W# y#)
126 | y /= 0 = (W# (x# `quotWord#` y#), W# (x# `remWord#` y#))
127 | otherwise = divZeroError
130 | otherwise = case word2Integer# x# of (# s, d #) -> J# s d
134 instance Bounded Word where
137 -- use unboxed literals for maxBound, because GHC doesn't optimise
138 -- (fromInteger 0xffffffff :: Word).
139 #if WORD_SIZE_IN_BITS == 31
140 maxBound = W# (int2Word# 0x7FFFFFFF#)
141 #elif WORD_SIZE_IN_BITS == 32
142 maxBound = W# (int2Word# 0xFFFFFFFF#)
144 maxBound = W# (int2Word# 0xFFFFFFFFFFFFFFFF#)
147 instance Ix Word where
149 unsafeIndex b@(m,_) i = fromIntegral (i - m)
150 inRange (m,n) i = m <= i && i <= n
152 instance Read Word where
153 readsPrec p s = [(fromInteger x, r) | (x, r) <- readsPrec p s]
155 instance Bits Word where
156 (W# x#) .&. (W# y#) = W# (x# `and#` y#)
157 (W# x#) .|. (W# y#) = W# (x# `or#` y#)
158 (W# x#) `xor` (W# y#) = W# (x# `xor#` y#)
159 complement (W# x#) = W# (x# `xor#` mb#) where W# mb# = maxBound
160 (W# x#) `shift` (I# i#)
161 | i# >=# 0# = W# (x# `shiftL#` i#)
162 | otherwise = W# (x# `shiftRL#` negateInt# i#)
163 (W# x#) `rotate` (I# i#)
165 | otherwise = W# ((x# `shiftL#` i'#) `or#` (x# `shiftRL#` (wsib -# i'#)))
167 i'# = word2Int# (int2Word# i# `and#` int2Word# (wsib -# 1#))
168 wsib = WORD_SIZE_IN_BITS# {- work around preprocessor problem (??) -}
169 bitSize _ = WORD_SIZE_IN_BITS
173 "fromIntegral/Int->Word" fromIntegral = \(I# x#) -> W# (int2Word# x#)
174 "fromIntegral/Word->Int" fromIntegral = \(W# x#) -> I# (word2Int# x#)
175 "fromIntegral/Word->Word" fromIntegral = id :: Word -> Word
178 ------------------------------------------------------------------------
180 ------------------------------------------------------------------------
182 -- Word8 is represented in the same way as Word. Operations may assume
183 -- and must ensure that it holds only values from its logical range.
185 data Word8 = W8# Word# deriving (Eq, Ord)
186 -- ^ 8-bit unsigned integer type
188 instance Show Word8 where
189 showsPrec p x = showsPrec p (fromIntegral x :: Int)
191 instance Num Word8 where
192 (W8# x#) + (W8# y#) = W8# (narrow8Word# (x# `plusWord#` y#))
193 (W8# x#) - (W8# y#) = W8# (narrow8Word# (x# `minusWord#` y#))
194 (W8# x#) * (W8# y#) = W8# (narrow8Word# (x# `timesWord#` y#))
195 negate (W8# x#) = W8# (narrow8Word# (int2Word# (negateInt# (word2Int# x#))))
199 fromInteger (S# i#) = W8# (narrow8Word# (int2Word# i#))
200 fromInteger (J# s# d#) = W8# (narrow8Word# (integer2Word# s# d#))
202 instance Real Word8 where
203 toRational x = toInteger x % 1
205 instance Enum Word8 where
207 | x /= maxBound = x + 1
208 | otherwise = succError "Word8"
210 | x /= minBound = x - 1
211 | otherwise = predError "Word8"
213 | i >= 0 && i <= fromIntegral (maxBound::Word8)
215 | otherwise = toEnumError "Word8" i (minBound::Word8, maxBound::Word8)
216 fromEnum (W8# x#) = I# (word2Int# x#)
217 enumFrom = boundedEnumFrom
218 enumFromThen = boundedEnumFromThen
220 instance Integral Word8 where
221 quot x@(W8# x#) y@(W8# y#)
222 | y /= 0 = W8# (x# `quotWord#` y#)
223 | otherwise = divZeroError
224 rem x@(W8# x#) y@(W8# y#)
225 | y /= 0 = W8# (x# `remWord#` y#)
226 | otherwise = divZeroError
227 div x@(W8# x#) y@(W8# y#)
228 | y /= 0 = W8# (x# `quotWord#` y#)
229 | otherwise = divZeroError
230 mod x@(W8# x#) y@(W8# y#)
231 | y /= 0 = W8# (x# `remWord#` y#)
232 | otherwise = divZeroError
233 quotRem x@(W8# x#) y@(W8# y#)
234 | y /= 0 = (W8# (x# `quotWord#` y#), W8# (x# `remWord#` y#))
235 | otherwise = divZeroError
236 divMod x@(W8# x#) y@(W8# y#)
237 | y /= 0 = (W8# (x# `quotWord#` y#), W8# (x# `remWord#` y#))
238 | otherwise = divZeroError
239 toInteger (W8# x#) = S# (word2Int# x#)
241 instance Bounded Word8 where
245 instance Ix Word8 where
247 unsafeIndex b@(m,_) i = fromIntegral (i - m)
248 inRange (m,n) i = m <= i && i <= n
250 instance Read Word8 where
251 readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
253 instance Bits Word8 where
254 (W8# x#) .&. (W8# y#) = W8# (x# `and#` y#)
255 (W8# x#) .|. (W8# y#) = W8# (x# `or#` y#)
256 (W8# x#) `xor` (W8# y#) = W8# (x# `xor#` y#)
257 complement (W8# x#) = W8# (x# `xor#` mb#) where W8# mb# = maxBound
258 (W8# x#) `shift` (I# i#)
259 | i# >=# 0# = W8# (narrow8Word# (x# `shiftL#` i#))
260 | otherwise = W8# (x# `shiftRL#` negateInt# i#)
261 (W8# x#) `rotate` (I# i#)
262 | i'# ==# 0# = W8# x#
263 | otherwise = W8# (narrow8Word# ((x# `shiftL#` i'#) `or#`
264 (x# `shiftRL#` (8# -# i'#))))
266 i'# = word2Int# (int2Word# i# `and#` int2Word# 7#)
271 "fromIntegral/Word8->Word8" fromIntegral = id :: Word8 -> Word8
272 "fromIntegral/Word8->Integer" fromIntegral = toInteger :: Word8 -> Integer
273 "fromIntegral/a->Word8" fromIntegral = \x -> case fromIntegral x of W# x# -> W8# (narrow8Word# x#)
274 "fromIntegral/Word8->a" fromIntegral = \(W8# x#) -> fromIntegral (W# x#)
277 ------------------------------------------------------------------------
279 ------------------------------------------------------------------------
281 -- Word16 is represented in the same way as Word. Operations may assume
282 -- and must ensure that it holds only values from its logical range.
284 data Word16 = W16# Word# deriving (Eq, Ord)
285 -- ^ 16-bit unsigned integer type
287 instance Show Word16 where
288 showsPrec p x = showsPrec p (fromIntegral x :: Int)
290 instance Num Word16 where
291 (W16# x#) + (W16# y#) = W16# (narrow16Word# (x# `plusWord#` y#))
292 (W16# x#) - (W16# y#) = W16# (narrow16Word# (x# `minusWord#` y#))
293 (W16# x#) * (W16# y#) = W16# (narrow16Word# (x# `timesWord#` y#))
294 negate (W16# x#) = W16# (narrow16Word# (int2Word# (negateInt# (word2Int# x#))))
298 fromInteger (S# i#) = W16# (narrow16Word# (int2Word# i#))
299 fromInteger (J# s# d#) = W16# (narrow16Word# (integer2Word# s# d#))
301 instance Real Word16 where
302 toRational x = toInteger x % 1
304 instance Enum Word16 where
306 | x /= maxBound = x + 1
307 | otherwise = succError "Word16"
309 | x /= minBound = x - 1
310 | otherwise = predError "Word16"
312 | i >= 0 && i <= fromIntegral (maxBound::Word16)
313 = W16# (int2Word# i#)
314 | otherwise = toEnumError "Word16" i (minBound::Word16, maxBound::Word16)
315 fromEnum (W16# x#) = I# (word2Int# x#)
316 enumFrom = boundedEnumFrom
317 enumFromThen = boundedEnumFromThen
319 instance Integral Word16 where
320 quot x@(W16# x#) y@(W16# y#)
321 | y /= 0 = W16# (x# `quotWord#` y#)
322 | otherwise = divZeroError
323 rem x@(W16# x#) y@(W16# y#)
324 | y /= 0 = W16# (x# `remWord#` y#)
325 | otherwise = divZeroError
326 div x@(W16# x#) y@(W16# y#)
327 | y /= 0 = W16# (x# `quotWord#` y#)
328 | otherwise = divZeroError
329 mod x@(W16# x#) y@(W16# y#)
330 | y /= 0 = W16# (x# `remWord#` y#)
331 | otherwise = divZeroError
332 quotRem x@(W16# x#) y@(W16# y#)
333 | y /= 0 = (W16# (x# `quotWord#` y#), W16# (x# `remWord#` y#))
334 | otherwise = divZeroError
335 divMod x@(W16# x#) y@(W16# y#)
336 | y /= 0 = (W16# (x# `quotWord#` y#), W16# (x# `remWord#` y#))
337 | otherwise = divZeroError
338 toInteger (W16# x#) = S# (word2Int# x#)
340 instance Bounded Word16 where
344 instance Ix Word16 where
346 unsafeIndex b@(m,_) i = fromIntegral (i - m)
347 inRange (m,n) i = m <= i && i <= n
349 instance Read Word16 where
350 readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
352 instance Bits Word16 where
353 (W16# x#) .&. (W16# y#) = W16# (x# `and#` y#)
354 (W16# x#) .|. (W16# y#) = W16# (x# `or#` y#)
355 (W16# x#) `xor` (W16# y#) = W16# (x# `xor#` y#)
356 complement (W16# x#) = W16# (x# `xor#` mb#) where W16# mb# = maxBound
357 (W16# x#) `shift` (I# i#)
358 | i# >=# 0# = W16# (narrow16Word# (x# `shiftL#` i#))
359 | otherwise = W16# (x# `shiftRL#` negateInt# i#)
360 (W16# x#) `rotate` (I# i#)
361 | i'# ==# 0# = W16# x#
362 | otherwise = W16# (narrow16Word# ((x# `shiftL#` i'#) `or#`
363 (x# `shiftRL#` (16# -# i'#))))
365 i'# = word2Int# (int2Word# i# `and#` int2Word# 15#)
370 "fromIntegral/Word8->Word16" fromIntegral = \(W8# x#) -> W16# x#
371 "fromIntegral/Word16->Word16" fromIntegral = id :: Word16 -> Word16
372 "fromIntegral/Word16->Integer" fromIntegral = toInteger :: Word16 -> Integer
373 "fromIntegral/a->Word16" fromIntegral = \x -> case fromIntegral x of W# x# -> W16# (narrow16Word# x#)
374 "fromIntegral/Word16->a" fromIntegral = \(W16# x#) -> fromIntegral (W# x#)
377 ------------------------------------------------------------------------
379 ------------------------------------------------------------------------
381 #if WORD_SIZE_IN_BITS < 32
383 data Word32 = W32# Word32#
384 -- ^ 32-bit unsigned integer type
386 instance Eq Word32 where
387 (W32# x#) == (W32# y#) = x# `eqWord32#` y#
388 (W32# x#) /= (W32# y#) = x# `neWord32#` y#
390 instance Ord Word32 where
391 (W32# x#) < (W32# y#) = x# `ltWord32#` y#
392 (W32# x#) <= (W32# y#) = x# `leWord32#` y#
393 (W32# x#) > (W32# y#) = x# `gtWord32#` y#
394 (W32# x#) >= (W32# y#) = x# `geWord32#` y#
396 instance Num Word32 where
397 (W32# x#) + (W32# y#) = W32# (int32ToWord32# (word32ToInt32# x# `plusInt32#` word32ToInt32# y#))
398 (W32# x#) - (W32# y#) = W32# (int32ToWord32# (word32ToInt32# x# `minusInt32#` word32ToInt32# y#))
399 (W32# x#) * (W32# y#) = W32# (int32ToWord32# (word32ToInt32# x# `timesInt32#` word32ToInt32# y#))
400 negate (W32# x#) = W32# (int32ToWord32# (negateInt32# (word32ToInt32# x#)))
404 fromInteger (S# i#) = W32# (int32ToWord32# (intToInt32# i#))
405 fromInteger (J# s# d#) = W32# (integerToWord32# s# d#)
407 instance Enum Word32 where
409 | x /= maxBound = x + 1
410 | otherwise = succError "Word32"
412 | x /= minBound = x - 1
413 | otherwise = predError "Word32"
415 | i >= 0 = W32# (wordToWord32# (int2Word# i#))
416 | otherwise = toEnumError "Word32" i (minBound::Word32, maxBound::Word32)
418 | x <= fromIntegral (maxBound::Int)
419 = I# (word2Int# (word32ToWord# x#))
420 | otherwise = fromEnumError "Word32" x
421 enumFrom = integralEnumFrom
422 enumFromThen = integralEnumFromThen
423 enumFromTo = integralEnumFromTo
424 enumFromThenTo = integralEnumFromThenTo
426 instance Integral Word32 where
427 quot x@(W32# x#) y@(W32# y#)
428 | y /= 0 = W32# (x# `quotWord32#` y#)
429 | otherwise = divZeroError
430 rem x@(W32# x#) y@(W32# y#)
431 | y /= 0 = W32# (x# `remWord32#` y#)
432 | otherwise = divZeroError
433 div x@(W32# x#) y@(W32# y#)
434 | y /= 0 = W32# (x# `quotWord32#` y#)
435 | otherwise = divZeroError
436 mod x@(W32# x#) y@(W32# y#)
437 | y /= 0 = W32# (x# `remWord32#` y#)
438 | otherwise = divZeroError
439 quotRem x@(W32# x#) y@(W32# y#)
440 | y /= 0 = (W32# (x# `quotWord32#` y#), W32# (x# `remWord32#` y#))
441 | otherwise = divZeroError
442 divMod x@(W32# x#) y@(W32# y#)
443 | y /= 0 = (W32# (x# `quotWord32#` y#), W32# (x# `remWord32#` y#))
444 | otherwise = divZeroError
445 toInteger x@(W32# x#)
446 | x <= fromIntegral (maxBound::Int) = S# (word2Int# (word32ToWord# x#))
447 | otherwise = case word32ToInteger# x# of (# s, d #) -> J# s d
449 instance Bits Word32 where
450 (W32# x#) .&. (W32# y#) = W32# (x# `and32#` y#)
451 (W32# x#) .|. (W32# y#) = W32# (x# `or32#` y#)
452 (W32# x#) `xor` (W32# y#) = W32# (x# `xor32#` y#)
453 complement (W32# x#) = W32# (not32# x#)
454 (W32# x#) `shift` (I# i#)
455 | i# >=# 0# = W32# (x# `shiftL32#` i#)
456 | otherwise = W32# (x# `shiftRL32#` negateInt# i#)
457 (W32# x#) `rotate` (I# i#)
458 | i'# ==# 0# = W32# x#
459 | otherwise = W32# ((x# `shiftL32#` i'#) `or32#`
460 (x# `shiftRL32#` (32# -# i'#)))
462 i'# = word2Int# (int2Word# i# `and#` int2Word# 31#)
466 foreign import unsafe "stg_eqWord32" eqWord32# :: Word32# -> Word32# -> Bool
467 foreign import unsafe "stg_neWord32" neWord32# :: Word32# -> Word32# -> Bool
468 foreign import unsafe "stg_ltWord32" ltWord32# :: Word32# -> Word32# -> Bool
469 foreign import unsafe "stg_leWord32" leWord32# :: Word32# -> Word32# -> Bool
470 foreign import unsafe "stg_gtWord32" gtWord32# :: Word32# -> Word32# -> Bool
471 foreign import unsafe "stg_geWord32" geWord32# :: Word32# -> Word32# -> Bool
472 foreign import unsafe "stg_int32ToWord32" int32ToWord32# :: Int32# -> Word32#
473 foreign import unsafe "stg_word32ToInt32" word32ToInt32# :: Word32# -> Int32#
474 foreign import unsafe "stg_intToInt32" intToInt32# :: Int# -> Int32#
475 foreign import unsafe "stg_wordToWord32" wordToWord32# :: Word# -> Word32#
476 foreign import unsafe "stg_word32ToWord" word32ToWord# :: Word32# -> Word#
477 foreign import unsafe "stg_plusInt32" plusInt32# :: Int32# -> Int32# -> Int32#
478 foreign import unsafe "stg_minusInt32" minusInt32# :: Int32# -> Int32# -> Int32#
479 foreign import unsafe "stg_timesInt32" timesInt32# :: Int32# -> Int32# -> Int32#
480 foreign import unsafe "stg_negateInt32" negateInt32# :: Int32# -> Int32#
481 foreign import unsafe "stg_quotWord32" quotWord32# :: Word32# -> Word32# -> Word32#
482 foreign import unsafe "stg_remWord32" remWord32# :: Word32# -> Word32# -> Word32#
483 foreign import unsafe "stg_and32" and32# :: Word32# -> Word32# -> Word32#
484 foreign import unsafe "stg_or32" or32# :: Word32# -> Word32# -> Word32#
485 foreign import unsafe "stg_xor32" xor32# :: Word32# -> Word32# -> Word32#
486 foreign import unsafe "stg_not32" not32# :: Word32# -> Word32#
487 foreign import unsafe "stg_shiftL32" shiftL32# :: Word32# -> Int# -> Word32#
488 foreign import unsafe "stg_shiftRL32" shiftRL32# :: Word32# -> Int# -> Word32#
491 "fromIntegral/Int->Word32" fromIntegral = \(I# x#) -> W32# (int32ToWord32# (intToInt32# x#))
492 "fromIntegral/Word->Word32" fromIntegral = \(W# x#) -> W32# (wordToWord32# x#)
493 "fromIntegral/Word32->Int" fromIntegral = \(W32# x#) -> I# (word2Int# (word32ToWord# x#))
494 "fromIntegral/Word32->Word" fromIntegral = \(W32# x#) -> W# (word32ToWord# x#)
495 "fromIntegral/Word32->Word32" fromIntegral = id :: Word32 -> Word32
500 -- Word32 is represented in the same way as Word.
501 #if WORD_SIZE_IN_BITS > 32
502 -- Operations may assume and must ensure that it holds only values
503 -- from its logical range.
506 data Word32 = W32# Word# deriving (Eq, Ord)
507 -- ^ 32-bit unsigned integer type
509 instance Num Word32 where
510 (W32# x#) + (W32# y#) = W32# (narrow32Word# (x# `plusWord#` y#))
511 (W32# x#) - (W32# y#) = W32# (narrow32Word# (x# `minusWord#` y#))
512 (W32# x#) * (W32# y#) = W32# (narrow32Word# (x# `timesWord#` y#))
513 negate (W32# x#) = W32# (narrow32Word# (int2Word# (negateInt# (word2Int# x#))))
517 fromInteger (S# i#) = W32# (narrow32Word# (int2Word# i#))
518 fromInteger (J# s# d#) = W32# (narrow32Word# (integer2Word# s# d#))
520 instance Enum Word32 where
522 | x /= maxBound = x + 1
523 | otherwise = succError "Word32"
525 | x /= minBound = x - 1
526 | otherwise = predError "Word32"
529 #if WORD_SIZE_IN_BITS > 32
530 && i <= fromIntegral (maxBound::Word32)
532 = W32# (int2Word# i#)
533 | otherwise = toEnumError "Word32" i (minBound::Word32, maxBound::Word32)
534 #if WORD_SIZE_IN_BITS == 32
536 | x <= fromIntegral (maxBound::Int)
538 | otherwise = fromEnumError "Word32" x
539 enumFrom = integralEnumFrom
540 enumFromThen = integralEnumFromThen
541 enumFromTo = integralEnumFromTo
542 enumFromThenTo = integralEnumFromThenTo
544 fromEnum (W32# x#) = I# (word2Int# x#)
545 enumFrom = boundedEnumFrom
546 enumFromThen = boundedEnumFromThen
549 instance Integral Word32 where
550 quot x@(W32# x#) y@(W32# y#)
551 | y /= 0 = W32# (x# `quotWord#` y#)
552 | otherwise = divZeroError
553 rem x@(W32# x#) y@(W32# y#)
554 | y /= 0 = W32# (x# `remWord#` y#)
555 | otherwise = divZeroError
556 div x@(W32# x#) y@(W32# y#)
557 | y /= 0 = W32# (x# `quotWord#` y#)
558 | otherwise = divZeroError
559 mod x@(W32# x#) y@(W32# y#)
560 | y /= 0 = W32# (x# `remWord#` y#)
561 | otherwise = divZeroError
562 quotRem x@(W32# x#) y@(W32# y#)
563 | y /= 0 = (W32# (x# `quotWord#` y#), W32# (x# `remWord#` y#))
564 | otherwise = divZeroError
565 divMod x@(W32# x#) y@(W32# y#)
566 | y /= 0 = (W32# (x# `quotWord#` y#), W32# (x# `remWord#` y#))
567 | otherwise = divZeroError
569 #if WORD_SIZE_IN_BITS == 32
571 | otherwise = case word2Integer# x# of (# s, d #) -> J# s d
578 instance Bits Word32 where
579 (W32# x#) .&. (W32# y#) = W32# (x# `and#` y#)
580 (W32# x#) .|. (W32# y#) = W32# (x# `or#` y#)
581 (W32# x#) `xor` (W32# y#) = W32# (x# `xor#` y#)
582 complement (W32# x#) = W32# (x# `xor#` mb#) where W32# mb# = maxBound
583 (W32# x#) `shift` (I# i#)
584 | i# >=# 0# = W32# (narrow32Word# (x# `shiftL#` i#))
585 | otherwise = W32# (x# `shiftRL#` negateInt# i#)
586 (W32# x#) `rotate` (I# i#)
587 | i'# ==# 0# = W32# x#
588 | otherwise = W32# (narrow32Word# ((x# `shiftL#` i'#) `or#`
589 (x# `shiftRL#` (32# -# i'#))))
591 i'# = word2Int# (int2Word# i# `and#` int2Word# 31#)
596 "fromIntegral/Word8->Word32" fromIntegral = \(W8# x#) -> W32# x#
597 "fromIntegral/Word16->Word32" fromIntegral = \(W16# x#) -> W32# x#
598 "fromIntegral/Word32->Word32" fromIntegral = id :: Word32 -> Word32
599 "fromIntegral/Word32->Integer" fromIntegral = toInteger :: Word32 -> Integer
600 "fromIntegral/a->Word32" fromIntegral = \x -> case fromIntegral x of W# x# -> W32# (narrow32Word# x#)
601 "fromIntegral/Word32->a" fromIntegral = \(W32# x#) -> fromIntegral (W# x#)
606 instance Show Word32 where
607 #if WORD_SIZE_IN_BITS < 33
608 showsPrec p x = showsPrec p (toInteger x)
610 showsPrec p x = showsPrec p (fromIntegral x :: Int)
614 instance Real Word32 where
615 toRational x = toInteger x % 1
617 instance Bounded Word32 where
619 maxBound = 0xFFFFFFFF
621 instance Ix Word32 where
623 unsafeIndex b@(m,_) i = fromIntegral (i - m)
624 inRange (m,n) i = m <= i && i <= n
626 instance Read Word32 where
627 #if WORD_SIZE_IN_BITS < 33
628 readsPrec p s = [(fromInteger x, r) | (x, r) <- readsPrec p s]
630 readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
633 ------------------------------------------------------------------------
635 ------------------------------------------------------------------------
637 #if WORD_SIZE_IN_BITS < 64
639 data Word64 = W64# Word64#
640 -- ^ 64-bit unsigned integer type
642 instance Eq Word64 where
643 (W64# x#) == (W64# y#) = x# `eqWord64#` y#
644 (W64# x#) /= (W64# y#) = x# `neWord64#` y#
646 instance Ord Word64 where
647 (W64# x#) < (W64# y#) = x# `ltWord64#` y#
648 (W64# x#) <= (W64# y#) = x# `leWord64#` y#
649 (W64# x#) > (W64# y#) = x# `gtWord64#` y#
650 (W64# x#) >= (W64# y#) = x# `geWord64#` y#
652 instance Num Word64 where
653 (W64# x#) + (W64# y#) = W64# (int64ToWord64# (word64ToInt64# x# `plusInt64#` word64ToInt64# y#))
654 (W64# x#) - (W64# y#) = W64# (int64ToWord64# (word64ToInt64# x# `minusInt64#` word64ToInt64# y#))
655 (W64# x#) * (W64# y#) = W64# (int64ToWord64# (word64ToInt64# x# `timesInt64#` word64ToInt64# y#))
656 negate (W64# x#) = W64# (int64ToWord64# (negateInt64# (word64ToInt64# x#)))
660 fromInteger (S# i#) = W64# (int64ToWord64# (intToInt64# i#))
661 fromInteger (J# s# d#) = W64# (integerToWord64# s# d#)
663 instance Enum Word64 where
665 | x /= maxBound = x + 1
666 | otherwise = succError "Word64"
668 | x /= minBound = x - 1
669 | otherwise = predError "Word64"
671 | i >= 0 = W64# (wordToWord64# (int2Word# i#))
672 | otherwise = toEnumError "Word64" i (minBound::Word64, maxBound::Word64)
674 | x <= fromIntegral (maxBound::Int)
675 = I# (word2Int# (word64ToWord# x#))
676 | otherwise = fromEnumError "Word64" x
677 enumFrom = integralEnumFrom
678 enumFromThen = integralEnumFromThen
679 enumFromTo = integralEnumFromTo
680 enumFromThenTo = integralEnumFromThenTo
682 instance Integral Word64 where
683 quot x@(W64# x#) y@(W64# y#)
684 | y /= 0 = W64# (x# `quotWord64#` y#)
685 | otherwise = divZeroError
686 rem x@(W64# x#) y@(W64# y#)
687 | y /= 0 = W64# (x# `remWord64#` y#)
688 | otherwise = divZeroError
689 div x@(W64# x#) y@(W64# y#)
690 | y /= 0 = W64# (x# `quotWord64#` y#)
691 | otherwise = divZeroError
692 mod x@(W64# x#) y@(W64# y#)
693 | y /= 0 = W64# (x# `remWord64#` y#)
694 | otherwise = divZeroError
695 quotRem x@(W64# x#) y@(W64# y#)
696 | y /= 0 = (W64# (x# `quotWord64#` y#), W64# (x# `remWord64#` y#))
697 | otherwise = divZeroError
698 divMod x@(W64# x#) y@(W64# y#)
699 | y /= 0 = (W64# (x# `quotWord64#` y#), W64# (x# `remWord64#` y#))
700 | otherwise = divZeroError
701 toInteger x@(W64# x#)
702 | x <= 0x7FFFFFFF = S# (word2Int# (word64ToWord# x#))
703 | otherwise = case word64ToInteger# x# of (# s, d #) -> J# s d
705 instance Bits Word64 where
706 (W64# x#) .&. (W64# y#) = W64# (x# `and64#` y#)
707 (W64# x#) .|. (W64# y#) = W64# (x# `or64#` y#)
708 (W64# x#) `xor` (W64# y#) = W64# (x# `xor64#` y#)
709 complement (W64# x#) = W64# (not64# x#)
710 (W64# x#) `shift` (I# i#)
711 | i# >=# 0# = W64# (x# `shiftL64#` i#)
712 | otherwise = W64# (x# `shiftRL64#` negateInt# i#)
713 (W64# x#) `rotate` (I# i#)
714 | i'# ==# 0# = W64# x#
715 | otherwise = W64# ((x# `uncheckedShiftL64#` i'#) `or64#`
716 (x# `uncheckedShiftRL64#` (64# -# i'#)))
718 i'# = word2Int# (int2Word# i# `and#` int2Word# 63#)
722 -- give the 64-bit shift operations the same treatment as the 32-bit
723 -- ones (see GHC.Base), namely we wrap them in tests to catch the
724 -- cases when we're shifting more than 64 bits to avoid unspecified
725 -- behaviour in the C shift operations.
727 shiftL64#, shiftRL64# :: Word64# -> Int# -> Word64#
729 a `shiftL64#` b | b >=# 64# = wordToWord64# (int2Word# 0#)
730 | otherwise = a `uncheckedShiftL64#` b
732 a `shiftRL64#` b | b >=# 64# = wordToWord64# (int2Word# 0#)
733 | otherwise = a `uncheckedShiftRL64#` b
736 foreign import ccall unsafe "stg_eqWord64" eqWord64# :: Word64# -> Word64# -> Bool
737 foreign import ccall unsafe "stg_neWord64" neWord64# :: Word64# -> Word64# -> Bool
738 foreign import ccall unsafe "stg_ltWord64" ltWord64# :: Word64# -> Word64# -> Bool
739 foreign import ccall unsafe "stg_leWord64" leWord64# :: Word64# -> Word64# -> Bool
740 foreign import ccall unsafe "stg_gtWord64" gtWord64# :: Word64# -> Word64# -> Bool
741 foreign import ccall unsafe "stg_geWord64" geWord64# :: Word64# -> Word64# -> Bool
742 foreign import ccall unsafe "stg_int64ToWord64" int64ToWord64# :: Int64# -> Word64#
743 foreign import ccall unsafe "stg_word64ToInt64" word64ToInt64# :: Word64# -> Int64#
744 foreign import ccall unsafe "stg_intToInt64" intToInt64# :: Int# -> Int64#
745 foreign import ccall unsafe "stg_wordToWord64" wordToWord64# :: Word# -> Word64#
746 foreign import ccall unsafe "stg_word64ToWord" word64ToWord# :: Word64# -> Word#
747 foreign import ccall unsafe "stg_plusInt64" plusInt64# :: Int64# -> Int64# -> Int64#
748 foreign import ccall unsafe "stg_minusInt64" minusInt64# :: Int64# -> Int64# -> Int64#
749 foreign import ccall unsafe "stg_timesInt64" timesInt64# :: Int64# -> Int64# -> Int64#
750 foreign import ccall unsafe "stg_negateInt64" negateInt64# :: Int64# -> Int64#
751 foreign import ccall unsafe "stg_quotWord64" quotWord64# :: Word64# -> Word64# -> Word64#
752 foreign import ccall unsafe "stg_remWord64" remWord64# :: Word64# -> Word64# -> Word64#
753 foreign import ccall unsafe "stg_and64" and64# :: Word64# -> Word64# -> Word64#
754 foreign import ccall unsafe "stg_or64" or64# :: Word64# -> Word64# -> Word64#
755 foreign import ccall unsafe "stg_xor64" xor64# :: Word64# -> Word64# -> Word64#
756 foreign import ccall unsafe "stg_not64" not64# :: Word64# -> Word64#
757 foreign import ccall unsafe "stg_uncheckedShiftL64" uncheckedShiftL64# :: Word64# -> Int# -> Word64#
758 foreign import ccall unsafe "stg_uncheckedShiftRL64" uncheckedShiftRL64# :: Word64# -> Int# -> Word64#
760 foreign import ccall unsafe "stg_integerToWord64" integerToWord64# :: Int# -> ByteArray# -> Word64#
764 "fromIntegral/Int->Word64" fromIntegral = \(I# x#) -> W64# (int64ToWord64# (intToInt64# x#))
765 "fromIntegral/Word->Word64" fromIntegral = \(W# x#) -> W64# (wordToWord64# x#)
766 "fromIntegral/Word64->Int" fromIntegral = \(W64# x#) -> I# (word2Int# (word64ToWord# x#))
767 "fromIntegral/Word64->Word" fromIntegral = \(W64# x#) -> W# (word64ToWord# x#)
768 "fromIntegral/Word64->Word64" fromIntegral = id :: Word64 -> Word64
773 -- Word64 is represented in the same way as Word.
774 -- Operations may assume and must ensure that it holds only values
775 -- from its logical range.
777 data Word64 = W64# Word# deriving (Eq, Ord)
778 -- ^ 64-bit unsigned integer type
780 instance Num Word64 where
781 (W64# x#) + (W64# y#) = W64# (x# `plusWord#` y#)
782 (W64# x#) - (W64# y#) = W64# (x# `minusWord#` y#)
783 (W64# x#) * (W64# y#) = W64# (x# `timesWord#` y#)
784 negate (W64# x#) = W64# (int2Word# (negateInt# (word2Int# x#)))
788 fromInteger (S# i#) = W64# (int2Word# i#)
789 fromInteger (J# s# d#) = W64# (integer2Word# s# d#)
791 instance Enum Word64 where
793 | x /= maxBound = x + 1
794 | otherwise = succError "Word64"
796 | x /= minBound = x - 1
797 | otherwise = predError "Word64"
799 | i >= 0 = W64# (int2Word# i#)
800 | otherwise = toEnumError "Word64" i (minBound::Word64, maxBound::Word64)
802 | x <= fromIntegral (maxBound::Int)
804 | otherwise = fromEnumError "Word64" x
805 enumFrom = integralEnumFrom
806 enumFromThen = integralEnumFromThen
807 enumFromTo = integralEnumFromTo
808 enumFromThenTo = integralEnumFromThenTo
810 instance Integral Word64 where
811 quot x@(W64# x#) y@(W64# y#)
812 | y /= 0 = W64# (x# `quotWord#` y#)
813 | otherwise = divZeroError
814 rem x@(W64# x#) y@(W64# y#)
815 | y /= 0 = W64# (x# `remWord#` y#)
816 | otherwise = divZeroError
817 div x@(W64# x#) y@(W64# y#)
818 | y /= 0 = W64# (x# `quotWord#` y#)
819 | otherwise = divZeroError
820 mod x@(W64# x#) y@(W64# y#)
821 | y /= 0 = W64# (x# `remWord#` y#)
822 | otherwise = divZeroError
823 quotRem x@(W64# x#) y@(W64# y#)
824 | y /= 0 = (W64# (x# `quotWord#` y#), W64# (x# `remWord#` y#))
825 | otherwise = divZeroError
826 divMod x@(W64# x#) y@(W64# y#)
827 | y /= 0 = (W64# (x# `quotWord#` y#), W64# (x# `remWord#` y#))
828 | otherwise = divZeroError
831 | otherwise = case word2Integer# x# of (# s, d #) -> J# s d
835 instance Bits Word64 where
836 (W64# x#) .&. (W64# y#) = W64# (x# `and#` y#)
837 (W64# x#) .|. (W64# y#) = W64# (x# `or#` y#)
838 (W64# x#) `xor` (W64# y#) = W64# (x# `xor#` y#)
839 complement (W64# x#) = W64# (x# `xor#` mb#) where W64# mb# = maxBound
840 (W64# x#) `shift` (I# i#)
841 | i# >=# 0# = W64# (x# `shiftL#` i#)
842 | otherwise = W64# (x# `shiftRL#` negateInt# i#)
843 (W64# x#) `rotate` (I# i#)
844 | i'# ==# 0# = W64# x#
845 | otherwise = W64# ((x# `shiftL#` i'#) `or#`
846 (x# `shiftRL#` (64# -# i'#)))
848 i'# = word2Int# (int2Word# i# `and#` int2Word# 63#)
853 "fromIntegral/a->Word64" fromIntegral = \x -> case fromIntegral x of W# x# -> W64# x#
854 "fromIntegral/Word64->a" fromIntegral = \(W64# x#) -> fromIntegral (W# x#)
859 instance Show Word64 where
860 showsPrec p x = showsPrec p (toInteger x)
862 instance Real Word64 where
863 toRational x = toInteger x % 1
865 instance Bounded Word64 where
867 maxBound = 0xFFFFFFFFFFFFFFFF
869 instance Ix Word64 where
871 unsafeIndex b@(m,_) i = fromIntegral (i - m)
872 inRange (m,n) i = m <= i && i <= n
874 instance Read Word64 where
875 readsPrec p s = [(fromInteger x, r) | (x, r) <- readsPrec p s]