diff --git a/libraries/base/GHC/Int.hs b/libraries/base/GHC/Int.hs index bde52848fd0071ac1cc5a048c2f84bb7fdaff68d..5afe9db6a54aea3403e71cdc3f80a2eb27340b34 100644 --- a/libraries/base/GHC/Int.hs +++ b/libraries/base/GHC/Int.hs @@ -194,29 +194,29 @@ instance Bits Int8 where {-# INLINE testBit #-} {-# INLINE popCount #-} - (I8# x#) .&. (I8# y#) = I8# (word8ToInt8# (int8ToWord8# x# `andWord8#` int8ToWord8# y#)) - (I8# x#) .|. (I8# y#) = I8# (word8ToInt8# (int8ToWord8# x# `orWord8#` int8ToWord8# y#)) - (I8# x#) `xor` (I8# y#) = I8# (word8ToInt8# (int8ToWord8# x# `xorWord8#` int8ToWord8# y#)) - complement (I8# x#) = I8# (word8ToInt8# (notWord8# (int8ToWord8# x#))) + (I8# x#) .&. (I8# y#) = I8# (intToInt8# ((int8ToInt# x#) `andI#` (int8ToInt# y#))) + (I8# x#) .|. (I8# y#) = I8# (intToInt8# ((int8ToInt# x#) `orI#` (int8ToInt# y#))) + (I8# x#) `xor` (I8# y#) = I8# (intToInt8# ((int8ToInt# x#) `xorI#` (int8ToInt# y#))) + complement (I8# x#) = I8# (intToInt8# (notI# (int8ToInt# x#))) (I8# x#) `shift` (I# i#) - | isTrue# (i# >=# 0#) = I8# (x# `shiftLInt8#` i#) - | otherwise = I8# (x# `shiftRAInt8#` negateInt# i#) + | isTrue# (i# >=# 0#) = I8# (intToInt8# ((int8ToInt# x#) `iShiftL#` i#)) + | otherwise = I8# (intToInt8# ((int8ToInt# x#) `iShiftRA#` negateInt# i#)) (I8# x#) `shiftL` (I# i#) - | isTrue# (i# >=# 0#) = I8# (x# `shiftLInt8#` i#) + | isTrue# (i# >=# 0#) = I8# (intToInt8# ((int8ToInt# x#) `iShiftL#` i#)) | otherwise = overflowError - (I8# x#) `unsafeShiftL` (I# i#) = I8# (x# `uncheckedShiftLInt8#` i#) + (I8# x#) `unsafeShiftL` (I# i#) = I8# (intToInt8# ((int8ToInt# x#) `uncheckedIShiftL#` i#)) (I8# x#) `shiftR` (I# i#) - | isTrue# (i# >=# 0#) = I8# (x# `shiftRAInt8#` i#) + | isTrue# (i# >=# 0#) = I8# (intToInt8# ((int8ToInt# x#) `iShiftRA#` i#)) | otherwise = overflowError - (I8# x#) `unsafeShiftR` (I# i#) = I8# (x# `uncheckedShiftRAInt8#` i#) + (I8# x#) `unsafeShiftR` (I# i#) = I8# (intToInt8# ((int8ToInt# x#) `uncheckedIShiftRA#` i#)) (I8# x#) `rotate` (I# i#) | isTrue# (i'# ==# 0#) = I8# x# | otherwise - = I8# (word8ToInt8# ((x'# `uncheckedShiftLWord8#` i'#) `orWord8#` - (x'# `uncheckedShiftRLWord8#` (8# -# i'#)))) + = I8# (intToInt8# (word2Int# ((x'# `uncheckedShiftL#` i'#) `or#` + (x'# `uncheckedShiftRL#` (8# -# i'#))))) where - !x'# = int8ToWord8# x# + !x'# = narrow8Word# (int2Word# (int8ToInt# x#)) !i'# = word2Int# (int2Word# i# `and#` 7##) bitSizeMaybe i = Just (finiteBitSize i) bitSize i = finiteBitSize i @@ -405,29 +405,29 @@ instance Bits Int16 where {-# INLINE testBit #-} {-# INLINE popCount #-} - (I16# x#) .&. (I16# y#) = I16# (word16ToInt16# (int16ToWord16# x# `andWord16#` int16ToWord16# y#)) - (I16# x#) .|. (I16# y#) = I16# (word16ToInt16# (int16ToWord16# x# `orWord16#` int16ToWord16# y#)) - (I16# x#) `xor` (I16# y#) = I16# (word16ToInt16# (int16ToWord16# x# `xorWord16#` int16ToWord16# y#)) - complement (I16# x#) = I16# (word16ToInt16# (notWord16# (int16ToWord16# x#))) + (I16# x#) .&. (I16# y#) = I16# (intToInt16# ((int16ToInt# x#) `andI#` (int16ToInt# y#))) + (I16# x#) .|. (I16# y#) = I16# (intToInt16# ((int16ToInt# x#) `orI#` (int16ToInt# y#))) + (I16# x#) `xor` (I16# y#) = I16# (intToInt16# ((int16ToInt# x#) `xorI#` (int16ToInt# y#))) + complement (I16# x#) = I16# (intToInt16# (notI# (int16ToInt# x#))) (I16# x#) `shift` (I# i#) - | isTrue# (i# >=# 0#) = I16# (x# `shiftLInt16#` i#) - | otherwise = I16# (x# `shiftRAInt16#` negateInt# i#) + | isTrue# (i# >=# 0#) = I16# (intToInt16# ((int16ToInt# x#) `iShiftL#` i#)) + | otherwise = I16# (intToInt16# ((int16ToInt# x#) `iShiftRA#` negateInt# i#)) (I16# x#) `shiftL` (I# i#) - | isTrue# (i# >=# 0#) = I16# (x# `shiftLInt16#` i#) + | isTrue# (i# >=# 0#) = I16# (intToInt16# ((int16ToInt# x#) `iShiftL#` i#)) | otherwise = overflowError - (I16# x#) `unsafeShiftL` (I# i#) = I16# (x# `uncheckedShiftLInt16#` i#) + (I16# x#) `unsafeShiftL` (I# i#) = I16# (intToInt16# ((int16ToInt# x#) `uncheckedIShiftL#` i#)) (I16# x#) `shiftR` (I# i#) - | isTrue# (i# >=# 0#) = I16# (x# `shiftRAInt16#` i#) + | isTrue# (i# >=# 0#) = I16# (intToInt16# ((int16ToInt# x#) `iShiftRA#` i#)) | otherwise = overflowError - (I16# x#) `unsafeShiftR` (I# i#) = I16# (x# `uncheckedShiftRAInt16#` i#) + (I16# x#) `unsafeShiftR` (I# i#) = I16# (intToInt16# ((int16ToInt# x#) `uncheckedIShiftRA#` i#)) (I16# x#) `rotate` (I# i#) | isTrue# (i'# ==# 0#) = I16# x# | otherwise - = I16# (word16ToInt16# ((x'# `uncheckedShiftLWord16#` i'#) `orWord16#` - (x'# `uncheckedShiftRLWord16#` (16# -# i'#)))) + = I16# (intToInt16# (word2Int# ((x'# `uncheckedShiftL#` i'#) `or#` + (x'# `uncheckedShiftRL#` (16# -# i'#))))) where - !x'# = int16ToWord16# x# + !x'# = narrow16Word# (int2Word# (int16ToInt# x#)) !i'# = word2Int# (int2Word# i# `and#` 15##) bitSizeMaybe i = Just (finiteBitSize i) bitSize i = finiteBitSize i @@ -607,25 +607,25 @@ instance Bits Int32 where (I32# x#) `xor` (I32# y#) = I32# (intToInt32# ((int32ToInt# x#) `xorI#` (int32ToInt# y#))) complement (I32# x#) = I32# (intToInt32# (notI# (int32ToInt# x#))) (I32# x#) `shift` (I# i#) - | isTrue# (i# >=# 0#) = I32# (x# `shiftLInt32#` i#) - | otherwise = I32# (x# `shiftRAInt32#` negateInt# i#) + | isTrue# (i# >=# 0#) = I32# (intToInt32# ((int32ToInt# x#) `iShiftL#` i#)) + | otherwise = I32# (intToInt32# ((int32ToInt# x#) `iShiftRA#` negateInt# i#)) (I32# x#) `shiftL` (I# i#) - | isTrue# (i# >=# 0#) = I32# (x# `shiftLInt32#` i#) + | isTrue# (i# >=# 0#) = I32# (intToInt32# ((int32ToInt# x#) `iShiftL#` i#)) | otherwise = overflowError (I32# x#) `unsafeShiftL` (I# i#) = - I32# (x# `uncheckedShiftLInt32#` i#) + I32# (intToInt32# ((int32ToInt# x#) `uncheckedIShiftL#` i#)) (I32# x#) `shiftR` (I# i#) - | isTrue# (i# >=# 0#) = I32# (x# `shiftRAInt32#` i#) + | isTrue# (i# >=# 0#) = I32# (intToInt32# ((int32ToInt# x#) `iShiftRA#` i#)) | otherwise = overflowError - (I32# x#) `unsafeShiftR` (I# i#) = I32# (x# `uncheckedShiftRAInt32#` i#) + (I32# x#) `unsafeShiftR` (I# i#) = I32# (intToInt32# ((int32ToInt# x#) `uncheckedIShiftRA#` i#)) (I32# x#) `rotate` (I# i#) | isTrue# (i'# ==# 0#) = I32# x# | otherwise - = I32# (word32ToInt32# ((x'# `uncheckedShiftLWord32#` i'#) `orWord32#` - (x'# `uncheckedShiftRLWord32#` (32# -# i'#)))) + = I32# (intToInt32# (word2Int# ((x'# `uncheckedShiftL#` i'#) `or#` + (x'# `uncheckedShiftRL#` (32# -# i'#))))) where - !x'# = int32ToWord32# x# + !x'# = narrow32Word# (int2Word# (int32ToInt# x#)) !i'# = word2Int# (int2Word# i# `and#` 31##) bitSizeMaybe i = Just (finiteBitSize i) bitSize i = finiteBitSize i @@ -1095,31 +1095,10 @@ a `shiftRLInt32#` b = uncheckedShiftRLInt32# a b `andInt32#` intToInt32# (shift_ -shiftLInt8# :: Int8# -> Int# -> Int8# -a `shiftLInt8#` b = uncheckedShiftLInt8# a b `andInt8#` intToInt8# (shift_mask 8# b) - -shiftLInt16# :: Int16# -> Int# -> Int16# -a `shiftLInt16#` b = uncheckedShiftLInt16# a b `andInt16#` intToInt16# (shift_mask 16# b) - -shiftLInt32# :: Int32# -> Int# -> Int32# -a `shiftLInt32#` b = uncheckedShiftLInt32# a b `andInt32#` intToInt32# (shift_mask 32# b) - shiftLInt64# :: Int64# -> Int# -> Int64# a `shiftLInt64#` b = uncheckedIShiftL64# a b `andInt64#` intToInt64# (shift_mask 64# b) -shiftRAInt8# :: Int8# -> Int# -> Int8# -a `shiftRAInt8#` b | isTrue# (b >=# 8#) = intToInt8# (negateInt# (a `ltInt8#` (intToInt8# 0#))) - | otherwise = a `uncheckedShiftRAInt8#` b - -shiftRAInt16# :: Int16# -> Int# -> Int16# -a `shiftRAInt16#` b | isTrue# (b >=# 16#) = intToInt16# (negateInt# (a `ltInt16#` (intToInt16# 0#))) - | otherwise = a `uncheckedShiftRAInt16#` b - -shiftRAInt32# :: Int32# -> Int# -> Int32# -a `shiftRAInt32#` b | isTrue# (b >=# 32#) = intToInt32# (negateInt# (a `ltInt32#` (intToInt32# 0#))) - | otherwise = a `uncheckedShiftRAInt32#` b - shiftRAInt64# :: Int64# -> Int# -> Int64# a `shiftRAInt64#` b | isTrue# (b >=# 64#) = intToInt64# (negateInt# (a `ltInt64#` (intToInt64# 0#))) | otherwise = a `uncheckedIShiftRA64#` b diff --git a/libraries/base/GHC/Word.hs b/libraries/base/GHC/Word.hs index c82657e058b26b07ce82f700a4d6e9a6415aa35b..67ad2ed1be9e6fdcb13a659f8afe51a1c4734719 100644 --- a/libraries/base/GHC/Word.hs +++ b/libraries/base/GHC/Word.hs @@ -184,26 +184,26 @@ instance Bits Word8 where {-# INLINE testBit #-} {-# INLINE popCount #-} - (W8# x#) .&. (W8# y#) = W8# (x# `andWord8#` y#) - (W8# x#) .|. (W8# y#) = W8# (x# `orWord8#` y#) - (W8# x#) `xor` (W8# y#) = W8# (x# `xorWord8#` y#) - complement (W8# x#) = W8# (notWord8# x#) + (W8# x#) .&. (W8# y#) = W8# (wordToWord8# ((word8ToWord# x#) `and#` (word8ToWord# y#))) + (W8# x#) .|. (W8# y#) = W8# (wordToWord8# ((word8ToWord# x#) `or#` (word8ToWord# y#))) + (W8# x#) `xor` (W8# y#) = W8# (wordToWord8# ((word8ToWord# x#) `xor#` (word8ToWord# y#))) + complement (W8# x#) = W8# (wordToWord8# (not# (word8ToWord# x#))) (W8# x#) `shift` (I# i#) - | isTrue# (i# >=# 0#) = W8# (x# `shiftLWord8#` i#) - | otherwise = W8# (x# `shiftRLWord8#` negateInt# i#) + | isTrue# (i# >=# 0#) = W8# (wordToWord8# ((word8ToWord# x#) `shiftL#` i#)) + | otherwise = W8# (wordToWord8# ((word8ToWord# x#) `shiftRL#` negateInt# i#)) (W8# x#) `shiftL` (I# i#) - | isTrue# (i# >=# 0#) = W8# (x# `shiftLWord8#` i#) + | isTrue# (i# >=# 0#) = W8# (wordToWord8# ((word8ToWord# x#) `shiftL#` i#)) | otherwise = overflowError (W8# x#) `unsafeShiftL` (I# i#) = - W8# (x# `uncheckedShiftLWord8#` i#) + W8# (wordToWord8# ((word8ToWord# x#) `uncheckedShiftL#` i#)) (W8# x#) `shiftR` (I# i#) - | isTrue# (i# >=# 0#) = W8# (x# `shiftRLWord8#` i#) + | isTrue# (i# >=# 0#) = W8# (wordToWord8# ((word8ToWord# x#) `shiftRL#` i#)) | otherwise = overflowError - (W8# x#) `unsafeShiftR` (I# i#) = W8# (x# `uncheckedShiftRLWord8#` i#) + (W8# x#) `unsafeShiftR` (I# i#) = W8# (wordToWord8# ((word8ToWord# x#) `uncheckedShiftRL#` i#)) (W8# x#) `rotate` (I# i#) | isTrue# (i'# ==# 0#) = W8# x# - | otherwise = W8# ((x# `uncheckedShiftLWord8#` i'#) `orWord8#` - (x# `uncheckedShiftRLWord8#` (8# -# i'#))) + | otherwise = W8# (wordToWord8# (((word8ToWord# x#) `uncheckedShiftL#` i'#) `or#` + ((word8ToWord# x#) `uncheckedShiftRL#` (8# -# i'#)))) where !i'# = word2Int# (int2Word# i# `and#` 7##) bitSizeMaybe i = Just (finiteBitSize i) @@ -374,26 +374,26 @@ instance Bits Word16 where {-# INLINE testBit #-} {-# INLINE popCount #-} - (W16# x#) .&. (W16# y#) = W16# (x# `andWord16#` y#) - (W16# x#) .|. (W16# y#) = W16# (x# `orWord16#` y#) - (W16# x#) `xor` (W16# y#) = W16# (x# `xorWord16#` y#) - complement (W16# x#) = W16# (notWord16# x#) + (W16# x#) .&. (W16# y#) = W16# (wordToWord16# ((word16ToWord# x#) `and#` (word16ToWord# y#))) + (W16# x#) .|. (W16# y#) = W16# (wordToWord16# ((word16ToWord# x#) `or#` (word16ToWord# y#))) + (W16# x#) `xor` (W16# y#) = W16# (wordToWord16# ((word16ToWord# x#) `xor#` (word16ToWord# y#))) + complement (W16# x#) = W16# (wordToWord16# (not# (word16ToWord# x#))) (W16# x#) `shift` (I# i#) - | isTrue# (i# >=# 0#) = W16# (x# `shiftLWord16#` i#) - | otherwise = W16# (x# `shiftRLWord16#` negateInt# i#) + | isTrue# (i# >=# 0#) = W16# (wordToWord16# ((word16ToWord# x#) `shiftL#` i#)) + | otherwise = W16# (wordToWord16# ((word16ToWord# x#) `shiftRL#` negateInt# i#)) (W16# x#) `shiftL` (I# i#) - | isTrue# (i# >=# 0#) = W16# (x# `shiftLWord16#` i#) + | isTrue# (i# >=# 0#) = W16# (wordToWord16# ((word16ToWord# x#) `shiftL#` i#)) | otherwise = overflowError (W16# x#) `unsafeShiftL` (I# i#) = - W16# (x# `uncheckedShiftLWord16#` i#) + W16# (wordToWord16# ((word16ToWord# x#) `uncheckedShiftL#` i#)) (W16# x#) `shiftR` (I# i#) - | isTrue# (i# >=# 0#) = W16# (x# `shiftRLWord16#` i#) + | isTrue# (i# >=# 0#) = W16# (wordToWord16# ((word16ToWord# x#) `shiftRL#` i#)) | otherwise = overflowError - (W16# x#) `unsafeShiftR` (I# i#) = W16# (x# `uncheckedShiftRLWord16#` i#) + (W16# x#) `unsafeShiftR` (I# i#) = W16# (wordToWord16# ((word16ToWord# x#) `uncheckedShiftRL#` i#)) (W16# x#) `rotate` (I# i#) | isTrue# (i'# ==# 0#) = W16# x# - | otherwise = W16# ((x# `uncheckedShiftLWord16#` i'#) `orWord16#` - (x# `uncheckedShiftRLWord16#` (16# -# i'#))) + | otherwise = W16# (wordToWord16# (((word16ToWord# x#) `uncheckedShiftL#` i'#) `or#` + ((word16ToWord# x#) `uncheckedShiftRL#` (16# -# i'#)))) where !i'# = word2Int# (int2Word# i# `and#` 15##) bitSizeMaybe i = Just (finiteBitSize i) @@ -601,26 +601,26 @@ instance Bits Word32 where {-# INLINE testBit #-} {-# INLINE popCount #-} - (W32# x#) .&. (W32# y#) = W32# (x# `andWord32#` y#) - (W32# x#) .|. (W32# y#) = W32# (x# `orWord32#` y#) - (W32# x#) `xor` (W32# y#) = W32# (x# `xorWord32#` y#) - complement (W32# x#) = W32# (notWord32# x#) + (W32# x#) .&. (W32# y#) = W32# (wordToWord32# ((word32ToWord# x#) `and#` (word32ToWord# y#))) + (W32# x#) .|. (W32# y#) = W32# (wordToWord32# ((word32ToWord# x#) `or#` (word32ToWord# y#))) + (W32# x#) `xor` (W32# y#) = W32# (wordToWord32# ((word32ToWord# x#) `xor#` (word32ToWord# y#))) + complement (W32# x#) = W32# (wordToWord32# (not# (word32ToWord# x#))) (W32# x#) `shift` (I# i#) - | isTrue# (i# >=# 0#) = W32# (x# `shiftLWord32#` i#) - | otherwise = W32# (x# `shiftRLWord32#` negateInt# i#) + | isTrue# (i# >=# 0#) = W32# (wordToWord32# ((word32ToWord# x#) `shiftL#` i#)) + | otherwise = W32# (wordToWord32# ((word32ToWord# x#) `shiftRL#` negateInt# i#)) (W32# x#) `shiftL` (I# i#) - | isTrue# (i# >=# 0#) = W32# (x# `shiftLWord32#` i#) + | isTrue# (i# >=# 0#) = W32# (wordToWord32# ((word32ToWord# x#) `shiftL#` i#)) | otherwise = overflowError (W32# x#) `unsafeShiftL` (I# i#) = - W32# (x# `uncheckedShiftLWord32#` i#) + W32# (wordToWord32# ((word32ToWord# x#) `uncheckedShiftL#` i#)) (W32# x#) `shiftR` (I# i#) - | isTrue# (i# >=# 0#) = W32# (x# `shiftRLWord32#` i#) + | isTrue# (i# >=# 0#) = W32# (wordToWord32# ((word32ToWord# x#) `shiftRL#` i#)) | otherwise = overflowError - (W32# x#) `unsafeShiftR` (I# i#) = W32# (x# `uncheckedShiftRLWord32#` i#) + (W32# x#) `unsafeShiftR` (I# i#) = W32# (wordToWord32# ((word32ToWord# x#) `uncheckedShiftRL#` i#)) (W32# x#) `rotate` (I# i#) | isTrue# (i'# ==# 0#) = W32# x# - | otherwise = W32# ((x# `uncheckedShiftLWord32#` i'#) `orWord32#` - (x# `uncheckedShiftRLWord32#` (32# -# i'#))) + | otherwise = W32# (wordToWord32# (((word32ToWord# x#) `uncheckedShiftL#` i'#) `or#` + ((word32ToWord# x#) `uncheckedShiftRL#` (32# -# i'#)))) where !i'# = word2Int# (int2Word# i# `and#` 31##) bitSizeMaybe i = Just (finiteBitSize i) @@ -894,34 +894,10 @@ bitReverse64 (W64# w#) = W64# (bitReverse64# w#) -- The following safe shift operations wrap unchecked primops to take this into -- account: 0 is consistently returned when the shift amount is too big. -shiftRLWord8# :: Word8# -> Int# -> Word8# -a `shiftRLWord8#` b = uncheckedShiftRLWord8# a b - `andWord8#` wordToWord8# (int2Word# (shift_mask 8# b)) - -shiftRLWord16# :: Word16# -> Int# -> Word16# -a `shiftRLWord16#` b = uncheckedShiftRLWord16# a b - `andWord16#` wordToWord16# (int2Word# (shift_mask 16# b)) - -shiftRLWord32# :: Word32# -> Int# -> Word32# -a `shiftRLWord32#` b = uncheckedShiftRLWord32# a b - `andWord32#` wordToWord32# (int2Word# (shift_mask 32# b)) - shiftRLWord64# :: Word64# -> Int# -> Word64# a `shiftRLWord64#` b = uncheckedShiftRL64# a b `and64#` int64ToWord64# (intToInt64# (shift_mask 64# b)) -shiftLWord8# :: Word8# -> Int# -> Word8# -a `shiftLWord8#` b = uncheckedShiftLWord8# a b - `andWord8#` wordToWord8# (int2Word# (shift_mask 8# b)) - -shiftLWord16# :: Word16# -> Int# -> Word16# -a `shiftLWord16#` b = uncheckedShiftLWord16# a b - `andWord16#` wordToWord16# (int2Word# (shift_mask 16# b)) - -shiftLWord32# :: Word32# -> Int# -> Word32# -a `shiftLWord32#` b = uncheckedShiftLWord32# a b - `andWord32#` wordToWord32# (int2Word# (shift_mask 32# b)) - shiftLWord64# :: Word64# -> Int# -> Word64# a `shiftLWord64#` b = uncheckedShiftL64# a b `and64#` int64ToWord64# (intToInt64# (shift_mask 64# b)) diff --git a/testsuite/tests/simplCore/should_run/T20203.stderr-ws-32 b/testsuite/tests/simplCore/should_run/T20203.stderr-ws-32 index 53717d52a2941b3950bef342a4446b1f8975a20c..baf346e8f3923d7c5bf96d19169ad7284579a831 100644 --- a/testsuite/tests/simplCore/should_run/T20203.stderr-ws-32 +++ b/testsuite/tests/simplCore/should_run/T20203.stderr-ws-32 @@ -1,7 +1,7 @@ ==================== Tidy Core ==================== Result size of Tidy Core - = {terms: 290, types: 141, coercions: 0, joins: 0/0} + = {terms: 340, types: 140, coercions: 0, joins: 0/0} bitOrTwoVarInt = \ x y -> @@ -24,33 +24,50 @@ bitOrTwoVarInt8 case x of { I8# x# -> case y of { I8# x#1 -> I8# - (word8ToInt8# - (orWord8# 17#Word8 (orWord8# (int8ToWord8# x#) (int8ToWord8# x#1)))) + (intToInt8# + (orI# + (int8ToInt# (intToInt8# (orI# (int8ToInt# x#) 1#))) + (int8ToInt# (intToInt8# (orI# (int8ToInt# x#1) 16#))))) } } -bitAndInt1 = I8# 0#Int8 - bitAndTwoVarInt8 = \ x y -> - case x of { I8# x# -> case y of { I8# x#1 -> bitAndInt1 } } + case x of { I8# x# -> + case y of { I8# x#1 -> + I8# + (intToInt8# + (andI# + (int8ToInt# (intToInt8# (andI# (int8ToInt# x#) 1#))) + (int8ToInt# (intToInt8# (andI# (int8ToInt# x#1) 16#))))) + } + } bitOrInt8 = \ x -> case x of { I8# x# -> - I8# (word8ToInt8# (orWord8# 17#Word8 (int8ToWord8# x#))) + I8# + (intToInt8# + (orI# (int8ToInt# (intToInt8# (orI# (int8ToInt# x#) 1#))) 16#)) } -bitAndInt8 = \ x -> case x of { I8# x# -> bitAndInt1 } +bitAndInt8 + = / x -> + case x of { I8# x# -> + I8# + (intToInt8# + (andI# (int8ToInt# (intToInt8# (andI# (int8ToInt# x#) 1#))) 16#)) + } bitOrTwoVarInt16 = \ x y -> case x of { I16# x# -> case y of { I16# x#1 -> I16# - (word16ToInt16# - (orWord16# - 255#Word16 (orWord16# (int16ToWord16# x#) (int16ToWord16# x#1)))) + (intToInt16# + (orI# + (int16ToInt# (intToInt16# (orI# (int16ToInt# x#) 250#))) + (int16ToInt# (intToInt16# (orI# (int16ToInt# x#1) 175#))))) } } @@ -59,22 +76,28 @@ bitAndTwoVarInt16 case x of { I16# x# -> case y of { I16# x#1 -> I16# - (word16ToInt16# - (andWord16# - 170#Word16 (andWord16# (int16ToWord16# x#) (int16ToWord16# x#1)))) - } + (intToInt16# + (andI# + (int16ToInt# (intToInt16# (andI# (int16ToInt# x#) 250#))) + (int16ToInt# (intToInt16# (andI# (int16ToInt# x#1) 175#))))) } } bitOrInt16 = \ x -> case x of { I16# x# -> - I16# (word16ToInt16# (orWord16# 255#Word16 (int16ToWord16# x#))) + I16# + (intToInt16# + (orI# + (int16ToInt# (intToInt16# (orI# (int16ToInt# x#) 250#))) 175#)) } bitAndInt16 = \ x -> case x of { I16# x# -> - I16# (word16ToInt16# (andWord16# 170#Word16 (int16ToWord16# x#))) + I16# + (intToInt16# + (andI# + (int16ToInt# (intToInt16# (andI# (int16ToInt# x#) 250#))) 175#)) } bitOrTwoVarInt32 @@ -125,7 +148,7 @@ bitOrTwoVarInt64 case y of { I64# x#1 -> I64# (word64ToInt64# - (or64# 255#Word64 (or64# (int64ToWord64# x#) (int64ToWord64# x#1)))) + (or64# 255#Word64 (or64# (int64ToWord64# x#) (int64ToWord64# x#1)))) } } @@ -135,7 +158,7 @@ bitAndTwoVarInt64 case y of { I64# x#1 -> I64# (word64ToInt64# - (and64# 170#Word64 (and64# (int64ToWord64# x#) (int64ToWord64# x#1)))) + (and64# 170#Word64 (and64# (int64ToWord64# x#) (int64ToWord64# x#1)))) } } @@ -144,7 +167,7 @@ bitOrInt64 case x of { I64# x# -> I64# (word64ToInt64# (or64# 255#Word64 (int64ToWord64# x#))) } - + bitAndInt64 = / x -> case x of { I64# x# -> diff --git a/testsuite/tests/simplCore/should_run/T20203.stderr-ws-64 b/testsuite/tests/simplCore/should_run/T20203.stderr-ws-64 index 6d45ef7edebd0b7701c84d273686461b2fcfbfc2..270c460e100a7c29b3ad8119fa33f2e529e1af94 100644 --- a/testsuite/tests/simplCore/should_run/T20203.stderr-ws-64 +++ b/testsuite/tests/simplCore/should_run/T20203.stderr-ws-64 @@ -1,7 +1,7 @@ ==================== Tidy Core ==================== Result size of Tidy Core - = {terms: 290, types: 141, coercions: 0, joins: 0/0} + = {terms: 340, types: 140, coercions: 0, joins: 0/0} bitOrTwoVarInt = \ x y -> @@ -24,34 +24,50 @@ bitOrTwoVarInt8 case x of { I8# x# -> case y of { I8# x#1 -> I8# - (word8ToInt8# - (orWord8# - 17#Word8 (orWord8# (int8ToWord8# x#) (int8ToWord8# x#1)))) + (intToInt8# + (orI# + (int8ToInt# (intToInt8# (orI# (int8ToInt# x#) 1#))) + (int8ToInt# (intToInt8# (orI# (int8ToInt# x#1) 16#))))) } } -bitAndInt1 = I8# 0#Int8 - bitAndTwoVarInt8 = \ x y -> - case x of { I8# x# -> case y of { I8# x#1 -> bitAndInt1 } } + case x of { I8# x# -> + case y of { I8# x#1 -> + I8# + (intToInt8# + (andI# + (int8ToInt# (intToInt8# (andI# (int8ToInt# x#) 1#))) + (int8ToInt# (intToInt8# (andI# (int8ToInt# x#1) 16#))))) + } + } bitOrInt8 = \ x -> case x of { I8# x# -> - I8# (word8ToInt8# (orWord8# 17#Word8 (int8ToWord8# x#))) + I8# + (intToInt8# + (orI# (int8ToInt# (intToInt8# (orI# (int8ToInt# x#) 1#))) 16#)) } -bitAndInt8 = \ x -> case x of { I8# x# -> bitAndInt1 } +bitAndInt8 + = \ x -> + case x of { I8# x# -> + I8# + (intToInt8# + (andI# (int8ToInt# (intToInt8# (andI# (int8ToInt# x#) 1#))) 16#)) + } bitOrTwoVarInt16 = \ x y -> case x of { I16# x# -> case y of { I16# x#1 -> I16# - (word16ToInt16# - (orWord16# - 255#Word16 (orWord16# (int16ToWord16# x#) (int16ToWord16# x#1)))) + (intToInt16# + (orI# + (int16ToInt# (intToInt16# (orI# (int16ToInt# x#) 250#))) + (int16ToInt# (intToInt16# (orI# (int16ToInt# x#1) 175#))))) } } @@ -60,22 +76,29 @@ bitAndTwoVarInt16 case x of { I16# x# -> case y of { I16# x#1 -> I16# - (word16ToInt16# - (andWord16# - 170#Word16 (andWord16# (int16ToWord16# x#) (int16ToWord16# x#1)))) + (intToInt16# + (andI# + (int16ToInt# (intToInt16# (andI# (int16ToInt# x#) 250#))) + (int16ToInt# (intToInt16# (andI# (int16ToInt# x#1) 175#))))) } } bitOrInt16 = \ x -> case x of { I16# x# -> - I16# (word16ToInt16# (orWord16# 255#Word16 (int16ToWord16# x#))) + I16# + (intToInt16# + (orI# + (int16ToInt# (intToInt16# (orI# (int16ToInt# x#) 250#))) 175#)) } bitAndInt16 = \ x -> case x of { I16# x# -> - I16# (word16ToInt16# (andWord16# 170#Word16 (int16ToWord16# x#))) + I16# + (intToInt16# + (andI# + (int16ToInt# (intToInt16# (andI# (int16ToInt# x#) 250#))) 175#)) } bitOrTwoVarInt32