[commit: ghc] master: Kill unnecessary cmpType in lhs_cmp_type (4ac0e81)

git at git.haskell.org git at git.haskell.org
Tue May 10 12:26:49 UTC 2016


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/4ac0e815739f6362c2815dd3ae531055a095d6a9/ghc

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

commit 4ac0e815739f6362c2815dd3ae531055a095d6a9
Author: Bartosz Nitka <niteria at gmail.com>
Date:   Tue May 10 05:26:06 2016 -0700

    Kill unnecessary cmpType in lhs_cmp_type
    
    This is the only call site of `lhs_cmp_type` and we only
    care about equality.
    `cmpType` is nondeterministic (because `TyCon`s are compared
    with Uniques in `cmpTc`), so if we don't have to use it, it's
    better not to.
    
    Test Plan: ./validate
    
    Reviewers: simonmar, goldfire, bgamari, austin, simonpj
    
    Reviewed By: simonpj
    
    Subscribers: thomie
    
    Differential Revision: https://phabricator.haskell.org/D2172
    
    GHC Trac Issues: #4012


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

4ac0e815739f6362c2815dd3ae531055a095d6a9
 compiler/typecheck/TcErrors.hs | 12 ++++++------
 1 file changed, 6 insertions(+), 6 deletions(-)

diff --git a/compiler/typecheck/TcErrors.hs b/compiler/typecheck/TcErrors.hs
index 78320c4..d9ba069 100644
--- a/compiler/typecheck/TcErrors.hs
+++ b/compiler/typecheck/TcErrors.hs
@@ -529,9 +529,9 @@ mkSkolReporter ctxt cts
           (yeses, noes) = partition (group_with ct) cts
 
      group_with ct1 ct2
-       | EQ <- cmp_loc      ct1 ct2 = True
-       | EQ <- cmp_lhs_type ct1 ct2 = True
-       | otherwise                  = False
+       | EQ <- cmp_loc ct1 ct2 = True
+       | eq_lhs_type   ct1 ct2 = True
+       | otherwise             = False
 
 mkHoleReporter :: Reporter
 -- Reports errors one at a time
@@ -563,11 +563,11 @@ mkGroupReporter mk_err ctxt cts
   = mapM_ (reportGroup mk_err ctxt) (equivClasses cmp_loc cts)
   where
 
-cmp_lhs_type :: Ct -> Ct -> Ordering
-cmp_lhs_type ct1 ct2
+eq_lhs_type :: Ct -> Ct -> Bool
+eq_lhs_type ct1 ct2
   = case (classifyPredType (ctPred ct1), classifyPredType (ctPred ct2)) of
        (EqPred eq_rel1 ty1 _, EqPred eq_rel2 ty2 _) ->
-         (eq_rel1 `compare` eq_rel2) `thenCmp` (ty1 `cmpType` ty2)
+         (eq_rel1 == eq_rel2) && (ty1 `eqType` ty2)
        _ -> pprPanic "mkSkolReporter" (ppr ct1 $$ ppr ct2)
 
 cmp_loc :: Ct -> Ct -> Ordering



More information about the ghc-commits mailing list