[Git][ghc/ghc][wip/mp-revert-exit-joins] Revert "Use fix-sized equality primops for fixed size boxed types"

Matthew Pickering (@mpickering) gitlab at gitlab.haskell.org
Mon Feb 6 16:07:20 UTC 2023



Matthew Pickering pushed to branch wip/mp-revert-exit-joins at Glasgow Haskell Compiler / GHC


Commits:
ce3b05d0 by Ben Gamari at 2023-02-06T15:24:49+00:00
Revert "Use fix-sized equality primops for fixed size boxed types"

This reverts commit 024020c38126f3ce326ff56906d53525bc71690c.

(cherry picked from commit b1d109ad542e4c37ae5af6ace71baf2cb509d865)

- - - - -


2 changed files:

- libraries/base/GHC/Int.hs
- libraries/base/GHC/Word.hs


Changes:

=====================================
libraries/base/GHC/Int.hs
=====================================
@@ -69,8 +69,8 @@ instance Eq Int8 where
     (/=) = neInt8
 
 eqInt8, neInt8 :: Int8 -> Int8 -> Bool
-eqInt8 (I8# x) (I8# y) = isTrue# (x `eqInt8#` y)
-neInt8 (I8# x) (I8# y) = isTrue# (x `neInt8#` y)
+eqInt8 (I8# x) (I8# y) = isTrue# ((int8ToInt# x) ==# (int8ToInt# y))
+neInt8 (I8# x) (I8# y) = isTrue# ((int8ToInt# x) /=# (int8ToInt# y))
 {-# INLINE [1] eqInt8 #-}
 {-# INLINE [1] neInt8 #-}
 
@@ -280,8 +280,8 @@ instance Eq Int16 where
     (/=) = neInt16
 
 eqInt16, neInt16 :: Int16 -> Int16 -> Bool
-eqInt16 (I16# x) (I16# y) = isTrue# (x `eqInt16#` y)
-neInt16 (I16# x) (I16# y) = isTrue# (x `neInt16#` y)
+eqInt16 (I16# x) (I16# y) = isTrue# ((int16ToInt# x) ==# (int16ToInt# y))
+neInt16 (I16# x) (I16# y) = isTrue# ((int16ToInt# x) /=# (int16ToInt# y))
 {-# INLINE [1] eqInt16 #-}
 {-# INLINE [1] neInt16 #-}
 
@@ -488,8 +488,8 @@ instance Eq Int32 where
     (/=) = neInt32
 
 eqInt32, neInt32 :: Int32 -> Int32 -> Bool
-eqInt32 (I32# x) (I32# y) = isTrue# (x `eqInt32#` y)
-neInt32 (I32# x) (I32# y) = isTrue# (x `neInt32#` y)
+eqInt32 (I32# x) (I32# y) = isTrue# ((int32ToInt# x) ==# (int32ToInt# y))
+neInt32 (I32# x) (I32# y) = isTrue# ((int32ToInt# x) /=# (int32ToInt# y))
 {-# INLINE [1] eqInt32 #-}
 {-# INLINE [1] neInt32 #-}
 


=====================================
libraries/base/GHC/Word.hs
=====================================
@@ -78,8 +78,8 @@ instance Eq Word8 where
     (/=) = neWord8
 
 eqWord8, neWord8 :: Word8 -> Word8 -> Bool
-eqWord8 (W8# x) (W8# y) = isTrue# (x `eqWord8#` y)
-neWord8 (W8# x) (W8# y) = isTrue# (x `neWord8#` y)
+eqWord8 (W8# x) (W8# y) = isTrue# ((word8ToWord# x) `eqWord#` (word8ToWord# y))
+neWord8 (W8# x) (W8# y) = isTrue# ((word8ToWord# x) `neWord#` (word8ToWord# y))
 {-# INLINE [1] eqWord8 #-}
 {-# INLINE [1] neWord8 #-}
 
@@ -268,8 +268,8 @@ instance Eq Word16 where
     (/=) = neWord16
 
 eqWord16, neWord16 :: Word16 -> Word16 -> Bool
-eqWord16 (W16# x) (W16# y) = isTrue# (x `eqWord16#` y)
-neWord16 (W16# x) (W16# y) = isTrue# (x `neWord16#` y)
+eqWord16 (W16# x) (W16# y) = isTrue# ((word16ToWord# x) `eqWord#` (word16ToWord# y))
+neWord16 (W16# x) (W16# y) = isTrue# ((word16ToWord# x) `neWord#` (word16ToWord# y))
 {-# INLINE [1] eqWord16 #-}
 {-# INLINE [1] neWord16 #-}
 
@@ -500,8 +500,8 @@ instance Eq Word32 where
     (/=) = neWord32
 
 eqWord32, neWord32 :: Word32 -> Word32 -> Bool
-eqWord32 (W32# x) (W32# y) = isTrue# (x `eqWord32#` y)
-neWord32 (W32# x) (W32# y) = isTrue# (x `neWord32#` y)
+eqWord32 (W32# x) (W32# y) = isTrue# ((word32ToWord# x) `eqWord#` (word32ToWord# y))
+neWord32 (W32# x) (W32# y) = isTrue# ((word32ToWord# x) `neWord#` (word32ToWord# y))
 {-# INLINE [1] eqWord32 #-}
 {-# INLINE [1] neWord32 #-}
 



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ce3b05d03f60fb66f4d0a0f312c790070aee5088

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ce3b05d03f60fb66f4d0a0f312c790070aee5088
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20230206/ffd81f14/attachment-0001.html>


More information about the ghc-commits mailing list