[commit: ghc] wip/ttypeable: Fix up obviously incorrect comparisons (dfd90e2)
git at git.haskell.org
git at git.haskell.org
Sun Jan 29 20:22:04 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/ttypeable
Link : http://ghc.haskell.org/trac/ghc/changeset/dfd90e24ba3757128860890f09e4a6eb25320dcb/ghc
>---------------------------------------------------------------
commit dfd90e24ba3757128860890f09e4a6eb25320dcb
Author: Ben Gamari <ben at smart-cactus.org>
Date: Sat Jan 28 10:52:31 2017 -0500
Fix up obviously incorrect comparisons
Up too late late night.
>---------------------------------------------------------------
dfd90e24ba3757128860890f09e4a6eb25320dcb
libraries/base/Data/Typeable/Internal.hs | 10 ++++++----
1 file changed, 6 insertions(+), 4 deletions(-)
diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs
index 93eb2d3..aa04030 100644
--- a/libraries/base/Data/Typeable/Internal.hs
+++ b/libraries/base/Data/Typeable/Internal.hs
@@ -186,13 +186,15 @@ on f g = \ x y -> g x `f` g y
-- | @since 2.01
instance Eq (TypeRep a) where
- TrTyCon a _ _ _ _ == TrTyCon b _ _ _ _ = a == b
+ _ == _ = True
{-# INLINABLE (==) #-}
instance TestEquality TypeRep where
- testEquality (TrTyCon a _ _ _ _) (TrTyCon b _ _ _ _)
- | a == b = Just (unsafeCoerce# Refl)
- | otherwise = Nothing
+ a `testEquality` b
+ | Just HRefl <- eqTypeRep a b
+ = Just Refl
+ | otherwise
+ = Nothing
{-# INLINEABLE testEquality #-}
-- | @since 4.4.0.0
More information about the ghc-commits
mailing list