[commit: ghc] ghc-8.0: base: Fix GHC.Word and GHC.Int on 32-bit platforms (bf6e208)

git at git.haskell.org git at git.haskell.org
Fri Mar 25 10:25:41 UTC 2016


Repository : ssh://git@git.haskell.org/ghc

On branch  : ghc-8.0
Link       : http://ghc.haskell.org/trac/ghc/changeset/bf6e2085ce7e9de0c56b4b2ef8db24df65cd8d68/ghc

>---------------------------------------------------------------

commit bf6e2085ce7e9de0c56b4b2ef8db24df65cd8d68
Author: Ben Gamari <ben at smart-cactus.org>
Date:   Fri Mar 25 00:48:22 2016 +0100

    base: Fix GHC.Word and GHC.Int on 32-bit platforms
    
    Due to a cut-and-paste error D1980 (#11688) broke 32-bit platforms. This
    should fix it.
    
    See #11750.
    
    (cherry picked from commit 26f86f3d397159f9c0db0b59766138f553ba5a86)


>---------------------------------------------------------------

bf6e2085ce7e9de0c56b4b2ef8db24df65cd8d68
 libraries/base/GHC/Int.hs  | 4 ++--
 libraries/base/GHC/Word.hs | 4 ++--
 2 files changed, 4 insertions(+), 4 deletions(-)

diff --git a/libraries/base/GHC/Int.hs b/libraries/base/GHC/Int.hs
index 558d30d..62a5a68 100644
--- a/libraries/base/GHC/Int.hs
+++ b/libraries/base/GHC/Int.hs
@@ -600,8 +600,8 @@ instance Eq Int64 where
     (/=) = neInt64
 
 eqInt64, neInt64 :: Int64 -> Int64 -> Bool
-eqInt64 (I64# x) (I64# y) = isTrue# (x ==# y)
-neInt64 (I64# x) (I64# y) = isTrue# (x /=# y)
+eqInt64 (I64# x) (I64# y) = isTrue# (x `eqInt64#` y)
+neInt64 (I64# x) (I64# y) = isTrue# (x `neInt64#` y)
 {-# INLINE [1] eqInt64 #-}
 {-# INLINE [1] neInt64 #-}
 
diff --git a/libraries/base/GHC/Word.hs b/libraries/base/GHC/Word.hs
index 5022ffd..384cf38 100644
--- a/libraries/base/GHC/Word.hs
+++ b/libraries/base/GHC/Word.hs
@@ -602,8 +602,8 @@ instance Eq Word64 where
     (/=) = neWord64
 
 eqWord64, neWord64 :: Word64 -> Word64 -> Bool
-eqWord64 (W64# x) (W64# y) = isTrue# (x `eqWord#` y)
-neWord64 (W64# x) (W64# y) = isTrue# (x `neWord#` y)
+eqWord64 (W64# x) (W64# y) = isTrue# (x `eqWord64#` y)
+neWord64 (W64# x) (W64# y) = isTrue# (x `neWord64#` y)
 {-# INLINE [1] eqWord64 #-}
 {-# INLINE [1] neWord64 #-}
 



More information about the ghc-commits mailing list