#include "MachDeps.h"
module GHC.Word (
Word(..), Word8(..), Word16(..), Word32(..), Word64(..),
uncheckedShiftL64#,
uncheckedShiftRL64#,
byteSwap16,
byteSwap32,
byteSwap64,
eqWord, neWord, gtWord, geWord, ltWord, leWord,
eqWord8, neWord8, gtWord8, geWord8, ltWord8, leWord8,
eqWord16, neWord16, gtWord16, geWord16, ltWord16, leWord16,
eqWord32, neWord32, gtWord32, geWord32, ltWord32, leWord32,
eqWord64, neWord64, gtWord64, geWord64, ltWord64, leWord64
) where
import Data.Bits
import Data.Maybe
#if WORD_SIZE_IN_BITS < 64
import GHC.IntWord64
#endif
import GHC.Base
import GHC.Enum
import GHC.Num
import GHC.Real
import GHC.Read
import GHC.Arr
import GHC.Show
data Word8 = W8# Word#
instance Eq Word8 where
(==) = eqWord8
(/=) = neWord8
eqWord8, neWord8 :: Word8 -> Word8 -> Bool
eqWord8 (W8# x) (W8# y) = isTrue# (x `eqWord#` y)
neWord8 (W8# x) (W8# y) = isTrue# (x `neWord#` y)
instance Ord Word8 where
(<) = ltWord8
(<=) = leWord8
(>=) = geWord8
(>) = gtWord8
gtWord8, geWord8, ltWord8, leWord8 :: Word8 -> Word8 -> Bool
(W8# x) `gtWord8` (W8# y) = isTrue# (x `gtWord#` y)
(W8# x) `geWord8` (W8# y) = isTrue# (x `geWord#` y)
(W8# x) `ltWord8` (W8# y) = isTrue# (x `ltWord#` y)
(W8# x) `leWord8` (W8# y) = isTrue# (x `leWord#` y)
instance Show Word8 where
showsPrec p x = showsPrec p (fromIntegral x :: Int)
instance Num Word8 where
(W8# x#) + (W8# y#) = W8# (narrow8Word# (x# `plusWord#` y#))
(W8# x#) (W8# y#) = W8# (narrow8Word# (x# `minusWord#` y#))
(W8# x#) * (W8# y#) = W8# (narrow8Word# (x# `timesWord#` y#))
negate (W8# x#) = W8# (narrow8Word# (int2Word# (negateInt# (word2Int# x#))))
abs x = x
signum 0 = 0
signum _ = 1
fromInteger i = W8# (narrow8Word# (integerToWord i))
instance Real Word8 where
toRational x = toInteger x % 1
instance Enum Word8 where
succ x
| x /= maxBound = x + 1
| otherwise = succError "Word8"
pred x
| x /= minBound = x 1
| otherwise = predError "Word8"
toEnum i@(I# i#)
| i >= 0 && i <= fromIntegral (maxBound::Word8)
= W8# (int2Word# i#)
| otherwise = toEnumError "Word8" i (minBound::Word8, maxBound::Word8)
fromEnum (W8# x#) = I# (word2Int# x#)
enumFrom = boundedEnumFrom
enumFromThen = boundedEnumFromThen
instance Integral Word8 where
quot (W8# x#) y@(W8# y#)
| y /= 0 = W8# (x# `quotWord#` y#)
| otherwise = divZeroError
rem (W8# x#) y@(W8# y#)
| y /= 0 = W8# (x# `remWord#` y#)
| otherwise = divZeroError
div (W8# x#) y@(W8# y#)
| y /= 0 = W8# (x# `quotWord#` y#)
| otherwise = divZeroError
mod (W8# x#) y@(W8# y#)
| y /= 0 = W8# (x# `remWord#` y#)
| otherwise = divZeroError
quotRem (W8# x#) y@(W8# y#)
| y /= 0 = case x# `quotRemWord#` y# of
(# q, r #) ->
(W8# q, W8# r)
| otherwise = divZeroError
divMod (W8# x#) y@(W8# y#)
| y /= 0 = (W8# (x# `quotWord#` y#), W8# (x# `remWord#` y#))
| otherwise = divZeroError
toInteger (W8# x#) = smallInteger (word2Int# x#)
instance Bounded Word8 where
minBound = 0
maxBound = 0xFF
instance Ix Word8 where
range (m,n) = [m..n]
unsafeIndex (m,_) i = fromIntegral (i m)
inRange (m,n) i = m <= i && i <= n
instance Read Word8 where
readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
instance Bits Word8 where
(W8# x#) .&. (W8# y#) = W8# (x# `and#` y#)
(W8# x#) .|. (W8# y#) = W8# (x# `or#` y#)
(W8# x#) `xor` (W8# y#) = W8# (x# `xor#` y#)
complement (W8# x#) = W8# (x# `xor#` mb#)
where !(W8# mb#) = maxBound
(W8# x#) `shift` (I# i#)
| isTrue# (i# >=# 0#) = W8# (narrow8Word# (x# `shiftL#` i#))
| otherwise = W8# (x# `shiftRL#` negateInt# i#)
(W8# x#) `shiftL` (I# i#) = W8# (narrow8Word# (x# `shiftL#` i#))
(W8# x#) `unsafeShiftL` (I# i#) =
W8# (narrow8Word# (x# `uncheckedShiftL#` i#))
(W8# x#) `shiftR` (I# i#) = W8# (x# `shiftRL#` i#)
(W8# x#) `unsafeShiftR` (I# i#) = W8# (x# `uncheckedShiftRL#` i#)
(W8# x#) `rotate` (I# i#)
| isTrue# (i'# ==# 0#) = W8# x#
| otherwise = W8# (narrow8Word# ((x# `uncheckedShiftL#` i'#) `or#`
(x# `uncheckedShiftRL#` (8# -# i'#))))
where
!i'# = word2Int# (int2Word# i# `and#` 7##)
bitSizeMaybe i = Just (finiteBitSize i)
bitSize i = finiteBitSize i
isSigned _ = False
popCount (W8# x#) = I# (word2Int# (popCnt8# x#))
bit = bitDefault
testBit = testBitDefault
instance FiniteBits Word8 where
finiteBitSize _ = 8
countLeadingZeros (W8# x#) = I# (word2Int# (clz8# x#))
countTrailingZeros (W8# x#) = I# (word2Int# (ctz8# x#))
data Word16 = W16# Word#
instance Eq Word16 where
(==) = eqWord16
(/=) = neWord16
eqWord16, neWord16 :: Word16 -> Word16 -> Bool
eqWord16 (W16# x) (W16# y) = isTrue# (x `eqWord#` y)
neWord16 (W16# x) (W16# y) = isTrue# (x `neWord#` y)
instance Ord Word16 where
(<) = ltWord16
(<=) = leWord16
(>=) = geWord16
(>) = gtWord16
gtWord16, geWord16, ltWord16, leWord16 :: Word16 -> Word16 -> Bool
(W16# x) `gtWord16` (W16# y) = isTrue# (x `gtWord#` y)
(W16# x) `geWord16` (W16# y) = isTrue# (x `geWord#` y)
(W16# x) `ltWord16` (W16# y) = isTrue# (x `ltWord#` y)
(W16# x) `leWord16` (W16# y) = isTrue# (x `leWord#` y)
instance Show Word16 where
showsPrec p x = showsPrec p (fromIntegral x :: Int)
instance Num Word16 where
(W16# x#) + (W16# y#) = W16# (narrow16Word# (x# `plusWord#` y#))
(W16# x#) (W16# y#) = W16# (narrow16Word# (x# `minusWord#` y#))
(W16# x#) * (W16# y#) = W16# (narrow16Word# (x# `timesWord#` y#))
negate (W16# x#) = W16# (narrow16Word# (int2Word# (negateInt# (word2Int# x#))))
abs x = x
signum 0 = 0
signum _ = 1
fromInteger i = W16# (narrow16Word# (integerToWord i))
instance Real Word16 where
toRational x = toInteger x % 1
instance Enum Word16 where
succ x
| x /= maxBound = x + 1
| otherwise = succError "Word16"
pred x
| x /= minBound = x 1
| otherwise = predError "Word16"
toEnum i@(I# i#)
| i >= 0 && i <= fromIntegral (maxBound::Word16)
= W16# (int2Word# i#)
| otherwise = toEnumError "Word16" i (minBound::Word16, maxBound::Word16)
fromEnum (W16# x#) = I# (word2Int# x#)
enumFrom = boundedEnumFrom
enumFromThen = boundedEnumFromThen
instance Integral Word16 where
quot (W16# x#) y@(W16# y#)
| y /= 0 = W16# (x# `quotWord#` y#)
| otherwise = divZeroError
rem (W16# x#) y@(W16# y#)
| y /= 0 = W16# (x# `remWord#` y#)
| otherwise = divZeroError
div (W16# x#) y@(W16# y#)
| y /= 0 = W16# (x# `quotWord#` y#)
| otherwise = divZeroError
mod (W16# x#) y@(W16# y#)
| y /= 0 = W16# (x# `remWord#` y#)
| otherwise = divZeroError
quotRem (W16# x#) y@(W16# y#)
| y /= 0 = case x# `quotRemWord#` y# of
(# q, r #) ->
(W16# q, W16# r)
| otherwise = divZeroError
divMod (W16# x#) y@(W16# y#)
| y /= 0 = (W16# (x# `quotWord#` y#), W16# (x# `remWord#` y#))
| otherwise = divZeroError
toInteger (W16# x#) = smallInteger (word2Int# x#)
instance Bounded Word16 where
minBound = 0
maxBound = 0xFFFF
instance Ix Word16 where
range (m,n) = [m..n]
unsafeIndex (m,_) i = fromIntegral (i m)
inRange (m,n) i = m <= i && i <= n
instance Read Word16 where
readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
instance Bits Word16 where
(W16# x#) .&. (W16# y#) = W16# (x# `and#` y#)
(W16# x#) .|. (W16# y#) = W16# (x# `or#` y#)
(W16# x#) `xor` (W16# y#) = W16# (x# `xor#` y#)
complement (W16# x#) = W16# (x# `xor#` mb#)
where !(W16# mb#) = maxBound
(W16# x#) `shift` (I# i#)
| isTrue# (i# >=# 0#) = W16# (narrow16Word# (x# `shiftL#` i#))
| otherwise = W16# (x# `shiftRL#` negateInt# i#)
(W16# x#) `shiftL` (I# i#) = W16# (narrow16Word# (x# `shiftL#` i#))
(W16# x#) `unsafeShiftL` (I# i#) =
W16# (narrow16Word# (x# `uncheckedShiftL#` i#))
(W16# x#) `shiftR` (I# i#) = W16# (x# `shiftRL#` i#)
(W16# x#) `unsafeShiftR` (I# i#) = W16# (x# `uncheckedShiftRL#` i#)
(W16# x#) `rotate` (I# i#)
| isTrue# (i'# ==# 0#) = W16# x#
| otherwise = W16# (narrow16Word# ((x# `uncheckedShiftL#` i'#) `or#`
(x# `uncheckedShiftRL#` (16# -# i'#))))
where
!i'# = word2Int# (int2Word# i# `and#` 15##)
bitSizeMaybe i = Just (finiteBitSize i)
bitSize i = finiteBitSize i
isSigned _ = False
popCount (W16# x#) = I# (word2Int# (popCnt16# x#))
bit = bitDefault
testBit = testBitDefault
instance FiniteBits Word16 where
finiteBitSize _ = 16
countLeadingZeros (W16# x#) = I# (word2Int# (clz16# x#))
countTrailingZeros (W16# x#) = I# (word2Int# (ctz16# x#))
byteSwap16 :: Word16 -> Word16
byteSwap16 (W16# w#) = W16# (narrow16Word# (byteSwap16# w#))
#if WORD_SIZE_IN_BITS > 32
#endif
data Word32 = W32# Word#
instance Eq Word32 where
(==) = eqWord32
(/=) = neWord32
eqWord32, neWord32 :: Word32 -> Word32 -> Bool
eqWord32 (W32# x) (W32# y) = isTrue# (x `eqWord#` y)
neWord32 (W32# x) (W32# y) = isTrue# (x `neWord#` y)
instance Ord Word32 where
(<) = ltWord32
(<=) = leWord32
(>=) = geWord32
(>) = gtWord32
gtWord32, geWord32, ltWord32, leWord32 :: Word32 -> Word32 -> Bool
(W32# x) `gtWord32` (W32# y) = isTrue# (x `gtWord#` y)
(W32# x) `geWord32` (W32# y) = isTrue# (x `geWord#` y)
(W32# x) `ltWord32` (W32# y) = isTrue# (x `ltWord#` y)
(W32# x) `leWord32` (W32# y) = isTrue# (x `leWord#` y)
instance Num Word32 where
(W32# x#) + (W32# y#) = W32# (narrow32Word# (x# `plusWord#` y#))
(W32# x#) (W32# y#) = W32# (narrow32Word# (x# `minusWord#` y#))
(W32# x#) * (W32# y#) = W32# (narrow32Word# (x# `timesWord#` y#))
negate (W32# x#) = W32# (narrow32Word# (int2Word# (negateInt# (word2Int# x#))))
abs x = x
signum 0 = 0
signum _ = 1
fromInteger i = W32# (narrow32Word# (integerToWord i))
instance Enum Word32 where
succ x
| x /= maxBound = x + 1
| otherwise = succError "Word32"
pred x
| x /= minBound = x 1
| otherwise = predError "Word32"
toEnum i@(I# i#)
| i >= 0
#if WORD_SIZE_IN_BITS > 32
&& i <= fromIntegral (maxBound::Word32)
#endif
= W32# (int2Word# i#)
| otherwise = toEnumError "Word32" i (minBound::Word32, maxBound::Word32)
#if WORD_SIZE_IN_BITS == 32
fromEnum x@(W32# x#)
| x <= fromIntegral (maxBound::Int)
= I# (word2Int# x#)
| otherwise = fromEnumError "Word32" x
enumFrom = integralEnumFrom
enumFromThen = integralEnumFromThen
enumFromTo = integralEnumFromTo
enumFromThenTo = integralEnumFromThenTo
#else
fromEnum (W32# x#) = I# (word2Int# x#)
enumFrom = boundedEnumFrom
enumFromThen = boundedEnumFromThen
#endif
instance Integral Word32 where
quot (W32# x#) y@(W32# y#)
| y /= 0 = W32# (x# `quotWord#` y#)
| otherwise = divZeroError
rem (W32# x#) y@(W32# y#)
| y /= 0 = W32# (x# `remWord#` y#)
| otherwise = divZeroError
div (W32# x#) y@(W32# y#)
| y /= 0 = W32# (x# `quotWord#` y#)
| otherwise = divZeroError
mod (W32# x#) y@(W32# y#)
| y /= 0 = W32# (x# `remWord#` y#)
| otherwise = divZeroError
quotRem (W32# x#) y@(W32# y#)
| y /= 0 = case x# `quotRemWord#` y# of
(# q, r #) ->
(W32# q, W32# r)
| otherwise = divZeroError
divMod (W32# x#) y@(W32# y#)
| y /= 0 = (W32# (x# `quotWord#` y#), W32# (x# `remWord#` y#))
| otherwise = divZeroError
toInteger (W32# x#)
#if WORD_SIZE_IN_BITS == 32
| isTrue# (i# >=# 0#) = smallInteger i#
| otherwise = wordToInteger x#
where
!i# = word2Int# x#
#else
= smallInteger (word2Int# x#)
#endif
instance Bits Word32 where
(W32# x#) .&. (W32# y#) = W32# (x# `and#` y#)
(W32# x#) .|. (W32# y#) = W32# (x# `or#` y#)
(W32# x#) `xor` (W32# y#) = W32# (x# `xor#` y#)
complement (W32# x#) = W32# (x# `xor#` mb#)
where !(W32# mb#) = maxBound
(W32# x#) `shift` (I# i#)
| isTrue# (i# >=# 0#) = W32# (narrow32Word# (x# `shiftL#` i#))
| otherwise = W32# (x# `shiftRL#` negateInt# i#)
(W32# x#) `shiftL` (I# i#) = W32# (narrow32Word# (x# `shiftL#` i#))
(W32# x#) `unsafeShiftL` (I# i#) =
W32# (narrow32Word# (x# `uncheckedShiftL#` i#))
(W32# x#) `shiftR` (I# i#) = W32# (x# `shiftRL#` i#)
(W32# x#) `unsafeShiftR` (I# i#) = W32# (x# `uncheckedShiftRL#` i#)
(W32# x#) `rotate` (I# i#)
| isTrue# (i'# ==# 0#) = W32# x#
| otherwise = W32# (narrow32Word# ((x# `uncheckedShiftL#` i'#) `or#`
(x# `uncheckedShiftRL#` (32# -# i'#))))
where
!i'# = word2Int# (int2Word# i# `and#` 31##)
bitSizeMaybe i = Just (finiteBitSize i)
bitSize i = finiteBitSize i
isSigned _ = False
popCount (W32# x#) = I# (word2Int# (popCnt32# x#))
bit = bitDefault
testBit = testBitDefault
instance FiniteBits Word32 where
finiteBitSize _ = 32
countLeadingZeros (W32# x#) = I# (word2Int# (clz32# x#))
countTrailingZeros (W32# x#) = I# (word2Int# (ctz32# x#))
instance Show Word32 where
#if WORD_SIZE_IN_BITS < 33
showsPrec p x = showsPrec p (toInteger x)
#else
showsPrec p x = showsPrec p (fromIntegral x :: Int)
#endif
instance Real Word32 where
toRational x = toInteger x % 1
instance Bounded Word32 where
minBound = 0
maxBound = 0xFFFFFFFF
instance Ix Word32 where
range (m,n) = [m..n]
unsafeIndex (m,_) i = fromIntegral (i m)
inRange (m,n) i = m <= i && i <= n
instance Read Word32 where
#if WORD_SIZE_IN_BITS < 33
readsPrec p s = [(fromInteger x, r) | (x, r) <- readsPrec p s]
#else
readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
#endif
byteSwap32 :: Word32 -> Word32
byteSwap32 (W32# w#) = W32# (narrow32Word# (byteSwap32# w#))
#if WORD_SIZE_IN_BITS < 64
data Word64 = W64# Word64#
instance Eq Word64 where
(==) = eqWord64
(/=) = neWord64
eqWord64, neWord64 :: Word64 -> Word64 -> Bool
eqWord64 (W64# x) (W64# y) = isTrue# (x `eqWord64#` y)
neWord64 (W64# x) (W64# y) = isTrue# (x `neWord64#` y)
instance Ord Word64 where
(<) = ltWord64
(<=) = leWord64
(>=) = geWord64
(>) = gtWord64
gtWord64, geWord64, ltWord64, leWord64 :: Word64 -> Word64 -> Bool
(W64# x) `gtWord64` (W64# y) = isTrue# (x `gtWord64#` y)
(W64# x) `geWord64` (W64# y) = isTrue# (x `geWord64#` y)
(W64# x) `ltWord64` (W64# y) = isTrue# (x `ltWord64#` y)
(W64# x) `leWord64` (W64# y) = isTrue# (x `leWord64#` y)
instance Num Word64 where
(W64# x#) + (W64# y#) = W64# (int64ToWord64# (word64ToInt64# x# `plusInt64#` word64ToInt64# y#))
(W64# x#) (W64# y#) = W64# (int64ToWord64# (word64ToInt64# x# `minusInt64#` word64ToInt64# y#))
(W64# x#) * (W64# y#) = W64# (int64ToWord64# (word64ToInt64# x# `timesInt64#` word64ToInt64# y#))
negate (W64# x#) = W64# (int64ToWord64# (negateInt64# (word64ToInt64# x#)))
abs x = x
signum 0 = 0
signum _ = 1
fromInteger i = W64# (integerToWord64 i)
instance Enum Word64 where
succ x
| x /= maxBound = x + 1
| otherwise = succError "Word64"
pred x
| x /= minBound = x 1
| otherwise = predError "Word64"
toEnum i@(I# i#)
| i >= 0 = W64# (wordToWord64# (int2Word# i#))
| otherwise = toEnumError "Word64" i (minBound::Word64, maxBound::Word64)
fromEnum x@(W64# x#)
| x <= fromIntegral (maxBound::Int)
= I# (word2Int# (word64ToWord# x#))
| otherwise = fromEnumError "Word64" x
enumFrom = integralEnumFrom
enumFromThen = integralEnumFromThen
enumFromTo = integralEnumFromTo
enumFromThenTo = integralEnumFromThenTo
instance Integral Word64 where
quot (W64# x#) y@(W64# y#)
| y /= 0 = W64# (x# `quotWord64#` y#)
| otherwise = divZeroError
rem (W64# x#) y@(W64# y#)
| y /= 0 = W64# (x# `remWord64#` y#)
| otherwise = divZeroError
div (W64# x#) y@(W64# y#)
| y /= 0 = W64# (x# `quotWord64#` y#)
| otherwise = divZeroError
mod (W64# x#) y@(W64# y#)
| y /= 0 = W64# (x# `remWord64#` y#)
| otherwise = divZeroError
quotRem (W64# x#) y@(W64# y#)
| y /= 0 = (W64# (x# `quotWord64#` y#), W64# (x# `remWord64#` y#))
| otherwise = divZeroError
divMod (W64# x#) y@(W64# y#)
| y /= 0 = (W64# (x# `quotWord64#` y#), W64# (x# `remWord64#` y#))
| otherwise = divZeroError
toInteger (W64# x#) = word64ToInteger x#
instance Bits Word64 where
(W64# x#) .&. (W64# y#) = W64# (x# `and64#` y#)
(W64# x#) .|. (W64# y#) = W64# (x# `or64#` y#)
(W64# x#) `xor` (W64# y#) = W64# (x# `xor64#` y#)
complement (W64# x#) = W64# (not64# x#)
(W64# x#) `shift` (I# i#)
| isTrue# (i# >=# 0#) = W64# (x# `shiftL64#` i#)
| otherwise = W64# (x# `shiftRL64#` negateInt# i#)
(W64# x#) `shiftL` (I# i#) = W64# (x# `shiftL64#` i#)
(W64# x#) `unsafeShiftL` (I# i#) = W64# (x# `uncheckedShiftL64#` i#)
(W64# x#) `shiftR` (I# i#) = W64# (x# `shiftRL64#` i#)
(W64# x#) `unsafeShiftR` (I# i#) = W64# (x# `uncheckedShiftRL64#` i#)
(W64# x#) `rotate` (I# i#)
| isTrue# (i'# ==# 0#) = W64# x#
| otherwise = W64# ((x# `uncheckedShiftL64#` i'#) `or64#`
(x# `uncheckedShiftRL64#` (64# -# i'#)))
where
!i'# = word2Int# (int2Word# i# `and#` 63##)
bitSizeMaybe i = Just (finiteBitSize i)
bitSize i = finiteBitSize i
isSigned _ = False
popCount (W64# x#) = I# (word2Int# (popCnt64# x#))
bit = bitDefault
testBit = testBitDefault
shiftL64#, shiftRL64# :: Word64# -> Int# -> Word64#
a `shiftL64#` b | isTrue# (b >=# 64#) = wordToWord64# 0##
| otherwise = a `uncheckedShiftL64#` b
a `shiftRL64#` b | isTrue# (b >=# 64#) = wordToWord64# 0##
| otherwise = a `uncheckedShiftRL64#` b
#else
data Word64 = W64# Word#
instance Eq Word64 where
(==) = eqWord64
(/=) = neWord64
eqWord64, neWord64 :: Word64 -> Word64 -> Bool
eqWord64 (W64# x) (W64# y) = isTrue# (x `eqWord#` y)
neWord64 (W64# x) (W64# y) = isTrue# (x `neWord#` y)
instance Ord Word64 where
(<) = ltWord64
(<=) = leWord64
(>=) = geWord64
(>) = gtWord64
gtWord64, geWord64, ltWord64, leWord64 :: Word64 -> Word64 -> Bool
(W64# x) `gtWord64` (W64# y) = isTrue# (x `gtWord#` y)
(W64# x) `geWord64` (W64# y) = isTrue# (x `geWord#` y)
(W64# x) `ltWord64` (W64# y) = isTrue# (x `ltWord#` y)
(W64# x) `leWord64` (W64# y) = isTrue# (x `leWord#` y)
instance Num Word64 where
(W64# x#) + (W64# y#) = W64# (x# `plusWord#` y#)
(W64# x#) (W64# y#) = W64# (x# `minusWord#` y#)
(W64# x#) * (W64# y#) = W64# (x# `timesWord#` y#)
negate (W64# x#) = W64# (int2Word# (negateInt# (word2Int# x#)))
abs x = x
signum 0 = 0
signum _ = 1
fromInteger i = W64# (integerToWord i)
instance Enum Word64 where
succ x
| x /= maxBound = x + 1
| otherwise = succError "Word64"
pred x
| x /= minBound = x 1
| otherwise = predError "Word64"
toEnum i@(I# i#)
| i >= 0 = W64# (int2Word# i#)
| otherwise = toEnumError "Word64" i (minBound::Word64, maxBound::Word64)
fromEnum x@(W64# x#)
| x <= fromIntegral (maxBound::Int)
= I# (word2Int# x#)
| otherwise = fromEnumError "Word64" x
enumFrom = integralEnumFrom
enumFromThen = integralEnumFromThen
enumFromTo = integralEnumFromTo
enumFromThenTo = integralEnumFromThenTo
instance Integral Word64 where
quot (W64# x#) y@(W64# y#)
| y /= 0 = W64# (x# `quotWord#` y#)
| otherwise = divZeroError
rem (W64# x#) y@(W64# y#)
| y /= 0 = W64# (x# `remWord#` y#)
| otherwise = divZeroError
div (W64# x#) y@(W64# y#)
| y /= 0 = W64# (x# `quotWord#` y#)
| otherwise = divZeroError
mod (W64# x#) y@(W64# y#)
| y /= 0 = W64# (x# `remWord#` y#)
| otherwise = divZeroError
quotRem (W64# x#) y@(W64# y#)
| y /= 0 = case x# `quotRemWord#` y# of
(# q, r #) ->
(W64# q, W64# r)
| otherwise = divZeroError
divMod (W64# x#) y@(W64# y#)
| y /= 0 = (W64# (x# `quotWord#` y#), W64# (x# `remWord#` y#))
| otherwise = divZeroError
toInteger (W64# x#)
| isTrue# (i# >=# 0#) = smallInteger i#
| otherwise = wordToInteger x#
where
!i# = word2Int# x#
instance Bits Word64 where
(W64# x#) .&. (W64# y#) = W64# (x# `and#` y#)
(W64# x#) .|. (W64# y#) = W64# (x# `or#` y#)
(W64# x#) `xor` (W64# y#) = W64# (x# `xor#` y#)
complement (W64# x#) = W64# (x# `xor#` mb#)
where !(W64# mb#) = maxBound
(W64# x#) `shift` (I# i#)
| isTrue# (i# >=# 0#) = W64# (x# `shiftL#` i#)
| otherwise = W64# (x# `shiftRL#` negateInt# i#)
(W64# x#) `shiftL` (I# i#) = W64# (x# `shiftL#` i#)
(W64# x#) `unsafeShiftL` (I# i#) = W64# (x# `uncheckedShiftL#` i#)
(W64# x#) `shiftR` (I# i#) = W64# (x# `shiftRL#` i#)
(W64# x#) `unsafeShiftR` (I# i#) = W64# (x# `uncheckedShiftRL#` i#)
(W64# x#) `rotate` (I# i#)
| isTrue# (i'# ==# 0#) = W64# x#
| otherwise = W64# ((x# `uncheckedShiftL#` i'#) `or#`
(x# `uncheckedShiftRL#` (64# -# i'#)))
where
!i'# = word2Int# (int2Word# i# `and#` 63##)
bitSizeMaybe i = Just (finiteBitSize i)
bitSize i = finiteBitSize i
isSigned _ = False
popCount (W64# x#) = I# (word2Int# (popCnt64# x#))
bit = bitDefault
testBit = testBitDefault
uncheckedShiftL64# :: Word# -> Int# -> Word#
uncheckedShiftL64# = uncheckedShiftL#
uncheckedShiftRL64# :: Word# -> Int# -> Word#
uncheckedShiftRL64# = uncheckedShiftRL#
#endif
instance FiniteBits Word64 where
finiteBitSize _ = 64
countLeadingZeros (W64# x#) = I# (word2Int# (clz64# x#))
countTrailingZeros (W64# x#) = I# (word2Int# (ctz64# x#))
instance Show Word64 where
showsPrec p x = showsPrec p (toInteger x)
instance Real Word64 where
toRational x = toInteger x % 1
instance Bounded Word64 where
minBound = 0
maxBound = 0xFFFFFFFFFFFFFFFF
instance Ix Word64 where
range (m,n) = [m..n]
unsafeIndex (m,_) i = fromIntegral (i m)
inRange (m,n) i = m <= i && i <= n
instance Read Word64 where
readsPrec p s = [(fromInteger x, r) | (x, r) <- readsPrec p s]
#if WORD_SIZE_IN_BITS < 64
byteSwap64 :: Word64 -> Word64
byteSwap64 (W64# w#) = W64# (byteSwap64# w#)
#else
byteSwap64 :: Word64 -> Word64
byteSwap64 (W64# w#) = W64# (byteSwap# w#)
#endif