summaryrefslogtreecommitdiff
path: root/libraries/base/GHC/Word.hs
diff options
context:
space:
mode:
Diffstat (limited to 'libraries/base/GHC/Word.hs')
-rw-r--r--libraries/base/GHC/Word.hs268
1 files changed, 135 insertions, 133 deletions
diff --git a/libraries/base/GHC/Word.hs b/libraries/base/GHC/Word.hs
index 75ed7d1f73..4ff2cc4837 100644
--- a/libraries/base/GHC/Word.hs
+++ b/libraries/base/GHC/Word.hs
@@ -67,7 +67,10 @@ import GHC.Show
-- Word8 is represented in the same way as Word. Operations may assume
-- and must ensure that it holds only values from its logical range.
-data {-# CTYPE "HsWord8" #-} Word8 = W8# Word#
+data {-# CTYPE "HsWord8" #-} Word8
+ = W8# Word8#
+
+
-- ^ 8-bit unsigned integer type
-- See GHC.Classes#matching_overloaded_methods_in_rules
@@ -77,8 +80,8 @@ instance Eq Word8 where
(/=) = neWord8
eqWord8, neWord8 :: Word8 -> Word8 -> Bool
-eqWord8 (W8# x) (W8# y) = isTrue# (x `eqWord#` y)
-neWord8 (W8# x) (W8# y) = isTrue# (x `neWord#` y)
+eqWord8 (W8# x) (W8# y) = isTrue# ((extendWord8# x) `eqWord#` (extendWord8# y))
+neWord8 (W8# x) (W8# y) = isTrue# ((extendWord8# x) `neWord#` (extendWord8# y))
{-# INLINE [1] eqWord8 #-}
{-# INLINE [1] neWord8 #-}
@@ -94,10 +97,10 @@ instance Ord Word8 where
{-# INLINE [1] ltWord8 #-}
{-# INLINE [1] leWord8 #-}
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)
+(W8# x) `gtWord8` (W8# y) = isTrue# ((extendWord8# x) `gtWord#` (extendWord8# y))
+(W8# x) `geWord8` (W8# y) = isTrue# ((extendWord8# x) `geWord#` (extendWord8# y))
+(W8# x) `ltWord8` (W8# y) = isTrue# ((extendWord8# x) `ltWord#` (extendWord8# y))
+(W8# x) `leWord8` (W8# y) = isTrue# ((extendWord8# x) `leWord#` (extendWord8# y))
-- | @since 2.01
instance Show Word8 where
@@ -105,14 +108,14 @@ instance Show Word8 where
-- | @since 2.01
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#))))
+ (W8# x#) + (W8# y#) = W8# (narrowWord8# ((extendWord8# x#) `plusWord#` (extendWord8# y#)))
+ (W8# x#) - (W8# y#) = W8# (narrowWord8# ((extendWord8# x#) `minusWord#` (extendWord8# y#)))
+ (W8# x#) * (W8# y#) = W8# (narrowWord8# ((extendWord8# x#) `timesWord#` (extendWord8# y#)))
+ negate (W8# x#) = W8# (narrowWord8# (int2Word# (negateInt# (word2Int# ((extendWord8# x#))))))
abs x = x
signum 0 = 0
signum _ = 1
- fromInteger i = W8# (narrow8Word# (integerToWord# i))
+ fromInteger i = W8# (narrowWord8# (integerToWord# i))
-- | @since 2.01
instance Real Word8 where
@@ -128,35 +131,36 @@ instance Enum Word8 where
| otherwise = predError "Word8"
toEnum i@(I# i#)
| i >= 0 && i <= fromIntegral (maxBound::Word8)
- = W8# (int2Word# i#)
+ = W8# (narrowWord8# (int2Word# i#))
| otherwise = toEnumError "Word8" i (minBound::Word8, maxBound::Word8)
- fromEnum (W8# x#) = I# (word2Int# x#)
+ fromEnum (W8# x#) = I# (word2Int# (extendWord8# x#))
enumFrom = boundedEnumFrom
enumFromThen = boundedEnumFromThen
-- | @since 2.01
instance Integral Word8 where
quot (W8# x#) y@(W8# y#)
- | y /= 0 = W8# (x# `quotWord#` y#)
+ | y /= 0 = W8# (narrowWord8# ((extendWord8# x#) `quotWord#` (extendWord8# y#)))
| otherwise = divZeroError
rem (W8# x#) y@(W8# y#)
- | y /= 0 = W8# (x# `remWord#` y#)
+ | y /= 0 = W8# (narrowWord8# ((extendWord8# x#) `remWord#` (extendWord8# y#)))
| otherwise = divZeroError
div (W8# x#) y@(W8# y#)
- | y /= 0 = W8# (x# `quotWord#` y#)
+ | y /= 0 = W8# (narrowWord8# ((extendWord8# x#) `quotWord#` (extendWord8# y#)))
| otherwise = divZeroError
mod (W8# x#) y@(W8# y#)
- | y /= 0 = W8# (x# `remWord#` y#)
+ | y /= 0 = W8# (narrowWord8# ((extendWord8# x#) `remWord#` (extendWord8# y#)))
| otherwise = divZeroError
quotRem (W8# x#) y@(W8# y#)
- | y /= 0 = case x# `quotRemWord#` y# of
+ | y /= 0 = case (extendWord8# x#) `quotRemWord#` (extendWord8# y#) of
(# q, r #) ->
- (W8# q, W8# r)
+ (W8# (narrowWord8# q), W8# (narrowWord8# r))
| otherwise = divZeroError
divMod (W8# x#) y@(W8# y#)
- | y /= 0 = (W8# (x# `quotWord#` y#), W8# (x# `remWord#` y#))
+ | y /= 0 = (W8# (narrowWord8# ((extendWord8# x#) `quotWord#` (extendWord8# y#)))
+ ,W8# (narrowWord8# ((extendWord8# x#) `remWord#` (extendWord8# y#))))
| otherwise = divZeroError
- toInteger (W8# x#) = IS (word2Int# x#)
+ toInteger (W8# x#) = IS (word2Int# (extendWord8# x#))
-- | @since 2.01
instance Bounded Word8 where
@@ -176,33 +180,32 @@ instance Bits Word8 where
{-# INLINE testBit #-}
{-# INLINE popCount #-}
- (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#) .&. (W8# y#) = W8# (narrowWord8# ((extendWord8# x#) `and#` (extendWord8# y#)))
+ (W8# x#) .|. (W8# y#) = W8# (narrowWord8# ((extendWord8# x#) `or#` (extendWord8# y#)))
+ (W8# x#) `xor` (W8# y#) = W8# (narrowWord8# ((extendWord8# x#) `xor#` (extendWord8# y#)))
+ complement (W8# x#) = W8# (narrowWord8# (not# (extendWord8# x#)))
(W8# x#) `shift` (I# i#)
- | isTrue# (i# >=# 0#) = W8# (narrow8Word# (x# `shiftL#` i#))
- | otherwise = W8# (x# `shiftRL#` negateInt# i#)
+ | isTrue# (i# >=# 0#) = W8# (narrowWord8# ((extendWord8# x#) `shiftL#` i#))
+ | otherwise = W8# (narrowWord8# ((extendWord8# x#) `shiftRL#` negateInt# i#))
(W8# x#) `shiftL` (I# i#)
- | isTrue# (i# >=# 0#) = W8# (narrow8Word# (x# `shiftL#` i#))
+ | isTrue# (i# >=# 0#) = W8# (narrowWord8# ((extendWord8# x#) `shiftL#` i#))
| otherwise = overflowError
(W8# x#) `unsafeShiftL` (I# i#) =
- W8# (narrow8Word# (x# `uncheckedShiftL#` i#))
+ W8# (narrowWord8# ((extendWord8# x#) `uncheckedShiftL#` i#))
(W8# x#) `shiftR` (I# i#)
- | isTrue# (i# >=# 0#) = W8# (x# `shiftRL#` i#)
+ | isTrue# (i# >=# 0#) = W8# (narrowWord8# ((extendWord8# x#) `shiftRL#` i#))
| otherwise = overflowError
- (W8# x#) `unsafeShiftR` (I# i#) = W8# (x# `uncheckedShiftRL#` i#)
+ (W8# x#) `unsafeShiftR` (I# i#) = W8# (narrowWord8# ((extendWord8# x#) `uncheckedShiftRL#` i#))
(W8# x#) `rotate` (I# i#)
| isTrue# (i'# ==# 0#) = W8# x#
- | otherwise = W8# (narrow8Word# ((x# `uncheckedShiftL#` i'#) `or#`
- (x# `uncheckedShiftRL#` (8# -# i'#))))
+ | otherwise = W8# (narrowWord8# (((extendWord8# x#) `uncheckedShiftL#` i'#) `or#`
+ ((extendWord8# 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#))
+ popCount (W8# x#) = I# (word2Int# (popCnt8# (extendWord8# x#)))
bit = bitDefault
testBit = testBitDefault
@@ -211,14 +214,14 @@ instance FiniteBits Word8 where
{-# INLINE countLeadingZeros #-}
{-# INLINE countTrailingZeros #-}
finiteBitSize _ = 8
- countLeadingZeros (W8# x#) = I# (word2Int# (clz8# x#))
- countTrailingZeros (W8# x#) = I# (word2Int# (ctz8# x#))
+ countLeadingZeros (W8# x#) = I# (word2Int# (clz8# (extendWord8# x#)))
+ countTrailingZeros (W8# x#) = I# (word2Int# (ctz8# (extendWord8# x#)))
{-# RULES
"fromIntegral/Word8->Word8" fromIntegral = id :: Word8 -> Word8
"fromIntegral/Word8->Integer" fromIntegral = toInteger :: Word8 -> Integer
-"fromIntegral/a->Word8" fromIntegral = \x -> case fromIntegral x of W# x# -> W8# (narrow8Word# x#)
-"fromIntegral/Word8->a" fromIntegral = \(W8# x#) -> fromIntegral (W# x#)
+"fromIntegral/a->Word8" fromIntegral = \x -> case fromIntegral x of W# x# -> W8# (narrowWord8# x#)
+"fromIntegral/Word8->a" fromIntegral = \(W8# x#) -> fromIntegral (W# (extendWord8# x#))
#-}
{-# RULES
@@ -258,7 +261,7 @@ instance FiniteBits Word8 where
-- Word16 is represented in the same way as Word. Operations may assume
-- and must ensure that it holds only values from its logical range.
-data {-# CTYPE "HsWord16" #-} Word16 = W16# Word#
+data {-# CTYPE "HsWord16" #-} Word16 = W16# Word16#
-- ^ 16-bit unsigned integer type
-- See GHC.Classes#matching_overloaded_methods_in_rules
@@ -268,8 +271,8 @@ instance Eq Word16 where
(/=) = neWord16
eqWord16, neWord16 :: Word16 -> Word16 -> Bool
-eqWord16 (W16# x) (W16# y) = isTrue# (x `eqWord#` y)
-neWord16 (W16# x) (W16# y) = isTrue# (x `neWord#` y)
+eqWord16 (W16# x) (W16# y) = isTrue# ((extendWord16# x) `eqWord#` (extendWord16# y))
+neWord16 (W16# x) (W16# y) = isTrue# ((extendWord16# x) `neWord#` (extendWord16# y))
{-# INLINE [1] eqWord16 #-}
{-# INLINE [1] neWord16 #-}
@@ -285,10 +288,10 @@ instance Ord Word16 where
{-# INLINE [1] ltWord16 #-}
{-# INLINE [1] leWord16 #-}
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)
+(W16# x) `gtWord16` (W16# y) = isTrue# ((extendWord16# x) `gtWord#` (extendWord16# y))
+(W16# x) `geWord16` (W16# y) = isTrue# ((extendWord16# x) `geWord#` (extendWord16# y))
+(W16# x) `ltWord16` (W16# y) = isTrue# ((extendWord16# x) `ltWord#` (extendWord16# y))
+(W16# x) `leWord16` (W16# y) = isTrue# ((extendWord16# x) `leWord#` (extendWord16# y))
-- | @since 2.01
instance Show Word16 where
@@ -296,14 +299,14 @@ instance Show Word16 where
-- | @since 2.01
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#))))
+ (W16# x#) + (W16# y#) = W16# (narrowWord16# ((extendWord16# x#) `plusWord#` (extendWord16# y#)))
+ (W16# x#) - (W16# y#) = W16# (narrowWord16# ((extendWord16# x#) `minusWord#` (extendWord16# y#)))
+ (W16# x#) * (W16# y#) = W16# (narrowWord16# ((extendWord16# x#) `timesWord#` (extendWord16# y#)))
+ negate (W16# x#) = W16# (narrowWord16# (int2Word# (negateInt# (word2Int# (extendWord16# x#)))))
abs x = x
signum 0 = 0
signum _ = 1
- fromInteger i = W16# (narrow16Word# (integerToWord# i))
+ fromInteger i = W16# (narrowWord16# (integerToWord# i))
-- | @since 2.01
instance Real Word16 where
@@ -319,35 +322,36 @@ instance Enum Word16 where
| otherwise = predError "Word16"
toEnum i@(I# i#)
| i >= 0 && i <= fromIntegral (maxBound::Word16)
- = W16# (int2Word# i#)
+ = W16# (narrowWord16# (int2Word# i#))
| otherwise = toEnumError "Word16" i (minBound::Word16, maxBound::Word16)
- fromEnum (W16# x#) = I# (word2Int# x#)
+ fromEnum (W16# x#) = I# (word2Int# (extendWord16# x#))
enumFrom = boundedEnumFrom
enumFromThen = boundedEnumFromThen
-- | @since 2.01
instance Integral Word16 where
quot (W16# x#) y@(W16# y#)
- | y /= 0 = W16# (x# `quotWord#` y#)
+ | y /= 0 = W16# (narrowWord16# ((extendWord16# x#) `quotWord#` (extendWord16# y#)))
| otherwise = divZeroError
rem (W16# x#) y@(W16# y#)
- | y /= 0 = W16# (x# `remWord#` y#)
+ | y /= 0 = W16# (narrowWord16# ((extendWord16# x#) `remWord#` (extendWord16# y#)))
| otherwise = divZeroError
div (W16# x#) y@(W16# y#)
- | y /= 0 = W16# (x# `quotWord#` y#)
+ | y /= 0 = W16# (narrowWord16# ((extendWord16# x#) `quotWord#` (extendWord16# y#)))
| otherwise = divZeroError
mod (W16# x#) y@(W16# y#)
- | y /= 0 = W16# (x# `remWord#` y#)
+ | y /= 0 = W16# (narrowWord16# ((extendWord16# x#) `remWord#` (extendWord16# y#)))
| otherwise = divZeroError
quotRem (W16# x#) y@(W16# y#)
- | y /= 0 = case x# `quotRemWord#` y# of
+ | y /= 0 = case (extendWord16# x#) `quotRemWord#` (extendWord16# y#) of
(# q, r #) ->
- (W16# q, W16# r)
+ (W16# (narrowWord16# q), W16# (narrowWord16# r))
| otherwise = divZeroError
divMod (W16# x#) y@(W16# y#)
- | y /= 0 = (W16# (x# `quotWord#` y#), W16# (x# `remWord#` y#))
+ | y /= 0 = (W16# (narrowWord16# ((extendWord16# x#) `quotWord#` (extendWord16# y#)))
+ ,W16# (narrowWord16# ((extendWord16# x#) `remWord#` (extendWord16# y#))))
| otherwise = divZeroError
- toInteger (W16# x#) = IS (word2Int# x#)
+ toInteger (W16# x#) = IS (word2Int# (extendWord16# x#))
-- | @since 2.01
instance Bounded Word16 where
@@ -367,33 +371,32 @@ instance Bits Word16 where
{-# INLINE testBit #-}
{-# INLINE popCount #-}
- (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#) .&. (W16# y#) = W16# (narrowWord16# ((extendWord16# x#) `and#` (extendWord16# y#)))
+ (W16# x#) .|. (W16# y#) = W16# (narrowWord16# ((extendWord16# x#) `or#` (extendWord16# y#)))
+ (W16# x#) `xor` (W16# y#) = W16# (narrowWord16# ((extendWord16# x#) `xor#` (extendWord16# y#)))
+ complement (W16# x#) = W16# (narrowWord16# (not# (extendWord16# x#)))
(W16# x#) `shift` (I# i#)
- | isTrue# (i# >=# 0#) = W16# (narrow16Word# (x# `shiftL#` i#))
- | otherwise = W16# (x# `shiftRL#` negateInt# i#)
+ | isTrue# (i# >=# 0#) = W16# (narrowWord16# ((extendWord16# x#) `shiftL#` i#))
+ | otherwise = W16# (narrowWord16# ((extendWord16# x#) `shiftRL#` negateInt# i#))
(W16# x#) `shiftL` (I# i#)
- | isTrue# (i# >=# 0#) = W16# (narrow16Word# (x# `shiftL#` i#))
+ | isTrue# (i# >=# 0#) = W16# (narrowWord16# ((extendWord16# x#) `shiftL#` i#))
| otherwise = overflowError
(W16# x#) `unsafeShiftL` (I# i#) =
- W16# (narrow16Word# (x# `uncheckedShiftL#` i#))
+ W16# (narrowWord16# ((extendWord16# x#) `uncheckedShiftL#` i#))
(W16# x#) `shiftR` (I# i#)
- | isTrue# (i# >=# 0#) = W16# (x# `shiftRL#` i#)
+ | isTrue# (i# >=# 0#) = W16# (narrowWord16# ((extendWord16# x#) `shiftRL#` i#))
| otherwise = overflowError
- (W16# x#) `unsafeShiftR` (I# i#) = W16# (x# `uncheckedShiftRL#` i#)
+ (W16# x#) `unsafeShiftR` (I# i#) = W16# (narrowWord16# ((extendWord16# x#) `uncheckedShiftRL#` i#))
(W16# x#) `rotate` (I# i#)
| isTrue# (i'# ==# 0#) = W16# x#
- | otherwise = W16# (narrow16Word# ((x# `uncheckedShiftL#` i'#) `or#`
- (x# `uncheckedShiftRL#` (16# -# i'#))))
+ | otherwise = W16# (narrowWord16# (((extendWord16# x#) `uncheckedShiftL#` i'#) `or#`
+ ((extendWord16# 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#))
+ popCount (W16# x#) = I# (word2Int# (popCnt16# (extendWord16# x#)))
bit = bitDefault
testBit = testBitDefault
@@ -402,21 +405,21 @@ instance FiniteBits Word16 where
{-# INLINE countLeadingZeros #-}
{-# INLINE countTrailingZeros #-}
finiteBitSize _ = 16
- countLeadingZeros (W16# x#) = I# (word2Int# (clz16# x#))
- countTrailingZeros (W16# x#) = I# (word2Int# (ctz16# x#))
+ countLeadingZeros (W16# x#) = I# (word2Int# (clz16# (extendWord16# x#)))
+ countTrailingZeros (W16# x#) = I# (word2Int# (ctz16# (extendWord16# x#)))
-- | Reverse order of bytes in 'Word16'.
--
-- @since 4.7.0.0
byteSwap16 :: Word16 -> Word16
-byteSwap16 (W16# w#) = W16# (narrow16Word# (byteSwap16# w#))
+byteSwap16 (W16# w#) = W16# (narrowWord16# (byteSwap16# (extendWord16# w#)))
{-# RULES
-"fromIntegral/Word8->Word16" fromIntegral = \(W8# x#) -> W16# x#
+"fromIntegral/Word8->Word16" fromIntegral = \(W8# x#) -> W16# (narrowWord16# (extendWord8# x#))
"fromIntegral/Word16->Word16" fromIntegral = id :: Word16 -> Word16
"fromIntegral/Word16->Integer" fromIntegral = toInteger :: Word16 -> Integer
-"fromIntegral/a->Word16" fromIntegral = \x -> case fromIntegral x of W# x# -> W16# (narrow16Word# x#)
-"fromIntegral/Word16->a" fromIntegral = \(W16# x#) -> fromIntegral (W# x#)
+"fromIntegral/a->Word16" fromIntegral = \x -> case fromIntegral x of W# x# -> W16# (narrowWord16# x#)
+"fromIntegral/Word16->a" fromIntegral = \(W16# x#) -> fromIntegral (W# (extendWord16# x#))
#-}
{-# RULES
@@ -492,7 +495,7 @@ byteSwap16 (W16# w#) = W16# (narrow16Word# (byteSwap16# w#))
#endif
-data {-# CTYPE "HsWord32" #-} Word32 = W32# Word#
+data {-# CTYPE "HsWord32" #-} Word32 = W32# Word32#
-- ^ 32-bit unsigned integer type
-- See GHC.Classes#matching_overloaded_methods_in_rules
@@ -502,8 +505,8 @@ instance Eq Word32 where
(/=) = neWord32
eqWord32, neWord32 :: Word32 -> Word32 -> Bool
-eqWord32 (W32# x) (W32# y) = isTrue# (x `eqWord#` y)
-neWord32 (W32# x) (W32# y) = isTrue# (x `neWord#` y)
+eqWord32 (W32# x) (W32# y) = isTrue# ((extendWord32# x) `eqWord#` (extendWord32# y))
+neWord32 (W32# x) (W32# y) = isTrue# ((extendWord32# x) `neWord#` (extendWord32# y))
{-# INLINE [1] eqWord32 #-}
{-# INLINE [1] neWord32 #-}
@@ -519,21 +522,21 @@ instance Ord Word32 where
{-# INLINE [1] ltWord32 #-}
{-# INLINE [1] leWord32 #-}
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)
+(W32# x) `gtWord32` (W32# y) = isTrue# ((extendWord32# x) `gtWord#` (extendWord32# y))
+(W32# x) `geWord32` (W32# y) = isTrue# ((extendWord32# x) `geWord#` (extendWord32# y))
+(W32# x) `ltWord32` (W32# y) = isTrue# ((extendWord32# x) `ltWord#` (extendWord32# y))
+(W32# x) `leWord32` (W32# y) = isTrue# ((extendWord32# x) `leWord#` (extendWord32# y))
-- | @since 2.01
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#))))
+ (W32# x#) + (W32# y#) = W32# (narrowWord32# ((extendWord32# x#) `plusWord#` (extendWord32# y#)))
+ (W32# x#) - (W32# y#) = W32# (narrowWord32# ((extendWord32# x#) `minusWord#` (extendWord32# y#)))
+ (W32# x#) * (W32# y#) = W32# (narrowWord32# ((extendWord32# x#) `timesWord#` (extendWord32# y#)))
+ negate (W32# x#) = W32# (narrowWord32# (int2Word# (negateInt# (word2Int# (extendWord32# x#)))))
abs x = x
signum 0 = 0
signum _ = 1
- fromInteger i = W32# (narrow32Word# (integerToWord# i))
+ fromInteger i = W32# (narrowWord32# (integerToWord# i))
-- | @since 2.01
instance Enum Word32 where
@@ -548,19 +551,19 @@ instance Enum Word32 where
#if WORD_SIZE_IN_BITS > 32
&& i <= fromIntegral (maxBound::Word32)
#endif
- = W32# (int2Word# i#)
+ = W32# (narrowWord32# (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#)
+ = I# (word2Int# (extendWord32# x#))
| otherwise = fromEnumError "Word32" x
enumFrom = integralEnumFrom
enumFromThen = integralEnumFromThen
enumFromTo = integralEnumFromTo
enumFromThenTo = integralEnumFromThenTo
#else
- fromEnum (W32# x#) = I# (word2Int# x#)
+ fromEnum (W32# x#) = I# (word2Int# (extendWord32# x#))
enumFrom = boundedEnumFrom
enumFromThen = boundedEnumFromThen
#endif
@@ -568,33 +571,34 @@ instance Enum Word32 where
-- | @since 2.01
instance Integral Word32 where
quot (W32# x#) y@(W32# y#)
- | y /= 0 = W32# (x# `quotWord#` y#)
+ | y /= 0 = W32# (narrowWord32# ((extendWord32# x#) `quotWord#` (extendWord32# y#)))
| otherwise = divZeroError
rem (W32# x#) y@(W32# y#)
- | y /= 0 = W32# (x# `remWord#` y#)
+ | y /= 0 = W32# (narrowWord32# ((extendWord32# x#) `remWord#` (extendWord32# y#)))
| otherwise = divZeroError
div (W32# x#) y@(W32# y#)
- | y /= 0 = W32# (x# `quotWord#` y#)
+ | y /= 0 = W32# (narrowWord32# ((extendWord32# x#) `quotWord#` (extendWord32# y#)))
| otherwise = divZeroError
mod (W32# x#) y@(W32# y#)
- | y /= 0 = W32# (x# `remWord#` y#)
+ | y /= 0 = W32# (narrowWord32# ((extendWord32# x#) `remWord#` (extendWord32# y#)))
| otherwise = divZeroError
quotRem (W32# x#) y@(W32# y#)
- | y /= 0 = case x# `quotRemWord#` y# of
+ | y /= 0 = case (extendWord32# x#) `quotRemWord#` (extendWord32# y#) of
(# q, r #) ->
- (W32# q, W32# r)
+ (W32# (narrowWord32# q), W32# (narrowWord32# r))
| otherwise = divZeroError
divMod (W32# x#) y@(W32# y#)
- | y /= 0 = (W32# (x# `quotWord#` y#), W32# (x# `remWord#` y#))
+ | y /= 0 = (W32# (narrowWord32# ((extendWord32# x#) `quotWord#` (extendWord32# y#)))
+ ,W32# (narrowWord32# ((extendWord32# x#) `remWord#` (extendWord32# y#))))
| otherwise = divZeroError
toInteger (W32# x#)
#if WORD_SIZE_IN_BITS == 32
| isTrue# (i# >=# 0#) = IS i#
- | otherwise = integerFromWord# x#
+ | otherwise = integerFromWord# (extendWord32# x#)
where
- !i# = word2Int# x#
+ !i# = word2Int# (extendWord32# x#)
#else
- = IS (word2Int# x#)
+ = IS (word2Int# (extendWord32# x#))
#endif
-- | @since 2.01
@@ -604,33 +608,32 @@ instance Bits Word32 where
{-# INLINE testBit #-}
{-# INLINE popCount #-}
- (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#) .&. (W32# y#) = W32# (narrowWord32# ((extendWord32# x#) `and#` (extendWord32# y#)))
+ (W32# x#) .|. (W32# y#) = W32# (narrowWord32# ((extendWord32# x#) `or#` (extendWord32# y#)))
+ (W32# x#) `xor` (W32# y#) = W32# (narrowWord32# ((extendWord32# x#) `xor#` (extendWord32# y#)))
+ complement (W32# x#) = W32# (narrowWord32# (not# (extendWord32# x#)))
(W32# x#) `shift` (I# i#)
- | isTrue# (i# >=# 0#) = W32# (narrow32Word# (x# `shiftL#` i#))
- | otherwise = W32# (x# `shiftRL#` negateInt# i#)
+ | isTrue# (i# >=# 0#) = W32# (narrowWord32# ((extendWord32# x#) `shiftL#` i#))
+ | otherwise = W32# (narrowWord32# ((extendWord32# x#) `shiftRL#` negateInt# i#))
(W32# x#) `shiftL` (I# i#)
- | isTrue# (i# >=# 0#) = W32# (narrow32Word# (x# `shiftL#` i#))
+ | isTrue# (i# >=# 0#) = W32# (narrowWord32# ((extendWord32# x#) `shiftL#` i#))
| otherwise = overflowError
(W32# x#) `unsafeShiftL` (I# i#) =
- W32# (narrow32Word# (x# `uncheckedShiftL#` i#))
+ W32# (narrowWord32# ((extendWord32# x#) `uncheckedShiftL#` i#))
(W32# x#) `shiftR` (I# i#)
- | isTrue# (i# >=# 0#) = W32# (x# `shiftRL#` i#)
+ | isTrue# (i# >=# 0#) = W32# (narrowWord32# ((extendWord32# x#) `shiftRL#` i#))
| otherwise = overflowError
- (W32# x#) `unsafeShiftR` (I# i#) = W32# (x# `uncheckedShiftRL#` i#)
+ (W32# x#) `unsafeShiftR` (I# i#) = W32# (narrowWord32# ((extendWord32# x#) `uncheckedShiftRL#` i#))
(W32# x#) `rotate` (I# i#)
| isTrue# (i'# ==# 0#) = W32# x#
- | otherwise = W32# (narrow32Word# ((x# `uncheckedShiftL#` i'#) `or#`
- (x# `uncheckedShiftRL#` (32# -# i'#))))
+ | otherwise = W32# (narrowWord32# (((extendWord32# x#) `uncheckedShiftL#` i'#) `or#`
+ ((extendWord32# 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#))
+ popCount (W32# x#) = I# (word2Int# (popCnt32# (extendWord32# x#)))
bit = bitDefault
testBit = testBitDefault
@@ -639,16 +642,16 @@ instance FiniteBits Word32 where
{-# INLINE countLeadingZeros #-}
{-# INLINE countTrailingZeros #-}
finiteBitSize _ = 32
- countLeadingZeros (W32# x#) = I# (word2Int# (clz32# x#))
- countTrailingZeros (W32# x#) = I# (word2Int# (ctz32# x#))
+ countLeadingZeros (W32# x#) = I# (word2Int# (clz32# (extendWord32# x#)))
+ countTrailingZeros (W32# x#) = I# (word2Int# (ctz32# (extendWord32# x#)))
{-# RULES
-"fromIntegral/Word8->Word32" fromIntegral = \(W8# x#) -> W32# x#
-"fromIntegral/Word16->Word32" fromIntegral = \(W16# x#) -> W32# x#
+"fromIntegral/Word8->Word32" fromIntegral = \(W8# x#) -> W32# (narrowWord32# (extendWord8# x#))
+"fromIntegral/Word16->Word32" fromIntegral = \(W16# x#) -> W32# (narrowWord32# (extendWord16# x#))
"fromIntegral/Word32->Word32" fromIntegral = id :: Word32 -> Word32
"fromIntegral/Word32->Integer" fromIntegral = toInteger :: Word32 -> Integer
-"fromIntegral/a->Word32" fromIntegral = \x -> case fromIntegral x of W# x# -> W32# (narrow32Word# x#)
-"fromIntegral/Word32->a" fromIntegral = \(W32# x#) -> fromIntegral (W# x#)
+"fromIntegral/a->Word32" fromIntegral = \x -> case fromIntegral x of W# x# -> W32# (narrowWord32# x#)
+"fromIntegral/Word32->a" fromIntegral = \(W32# x#) -> fromIntegral (W# (extendWord32# x#))
#-}
-- | @since 2.01
@@ -679,7 +682,7 @@ instance Ix Word32 where
--
-- @since 4.7.0.0
byteSwap32 :: Word32 -> Word32
-byteSwap32 (W32# w#) = W32# (narrow32Word# (byteSwap32# w#))
+byteSwap32 (W32# w#) = W32# (narrowWord32# (byteSwap32# (extendWord32# w#)))
------------------------------------------------------------------------
-- type Word64
@@ -969,8 +972,7 @@ 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
+ complement (W64# x#) = W64# (not# x#)
(W64# x#) `shift` (I# i#)
| isTrue# (i# >=# 0#) = W64# (x# `shiftL#` i#)
| otherwise = W64# (x# `shiftRL#` negateInt# i#)
@@ -1050,19 +1052,19 @@ byteSwap64 (W64# w#) = W64# (byteSwap# w#)
--
-- @since 4.12.0.0
bitReverse8 :: Word8 -> Word8
-bitReverse8 (W8# w#) = W8# (narrow8Word# (bitReverse8# w#))
+bitReverse8 (W8# w#) = W8# (narrowWord8# (bitReverse8# (extendWord8# w#)))
-- | Reverse the order of the bits in a 'Word16'.
--
-- @since 4.12.0.0
bitReverse16 :: Word16 -> Word16
-bitReverse16 (W16# w#) = W16# (narrow16Word# (bitReverse16# w#))
+bitReverse16 (W16# w#) = W16# (narrowWord16# (bitReverse16# (extendWord16# w#)))
-- | Reverse the order of the bits in a 'Word32'.
--
-- @since 4.12.0.0
bitReverse32 :: Word32 -> Word32
-bitReverse32 (W32# w#) = W32# (narrow32Word# (bitReverse32# w#))
+bitReverse32 (W32# w#) = W32# (narrowWord32# (bitReverse32# (extendWord32# w#)))
-- | Reverse the order of the bits in a 'Word64'.
--