From 21eeb926c8bf398e38919429d2375b78be45b14b Mon Sep 17 00:00:00 2001 From: "simonpj@microsoft.com" Date: Fri, 11 Dec 2009 17:39:20 +0000 Subject: [PATCH] Use full equality for CSE In CSE we were getting lots of apprarently-unequal expressions with the same hash code. In fact they were perfectly equal -- but we were using a cheap-and-cheerful equality tests for CoreExpr that said False for any lambda expression! This patch adds a proper equality test for Core, with alpha-renaming. It's easy to do, and will avoid silly cases of CSE failing to fire. We should get less of this: WARNING: file compiler/simplCore/CSE.lhs line 326 extendCSEnv: long list, length 18 from a compiler built with -DDEBUG --- compiler/coreSyn/CoreUtils.lhs | 50 +++++++++++++++++++++++++++++++++++++++- compiler/simplCore/CSE.lhs | 20 +++++++++------- compiler/types/Coercion.lhs | 6 ++++- compiler/types/Type.lhs | 10 +++++--- 4 files changed, 73 insertions(+), 13 deletions(-) diff --git a/compiler/coreSyn/CoreUtils.lhs b/compiler/coreSyn/CoreUtils.lhs index 1590978..a8439f8 100644 --- a/compiler/coreSyn/CoreUtils.lhs +++ b/compiler/coreSyn/CoreUtils.lhs @@ -36,7 +36,7 @@ module CoreUtils ( hashExpr, -- * Equality - cheapEqExpr, + cheapEqExpr, eqExpr, -- * Manipulating data constructors and types applyTypeToArgs, applyTypeToArg, @@ -913,7 +913,9 @@ cheapEqExpr (Cast e1 t1) (Cast e2 t2) = e1 `cheapEqExpr` e2 && t1 `coreEqCoercion` t2 cheapEqExpr _ _ = False +\end{code} +\begin{code} exprIsBig :: Expr b -> Bool -- ^ Returns @True@ of expressions that are too big to be compared by 'cheapEqExpr' exprIsBig (Lit _) = False @@ -925,7 +927,53 @@ exprIsBig (Cast e _) = exprIsBig e -- Hopefully coercions are not too big! exprIsBig _ = True \end{code} +\begin{code} +eqExpr :: InScopeSet -> CoreExpr -> CoreExpr -> Bool +-- Compares for equality, modulo alpha +eqExpr in_scope e1 e2 + = go (mkRnEnv2 in_scope) e1 e2 + where + go _ (Lit lit1) (Lit lit2) = lit1 == lit2 + go env (Type t1) (Type t2) = coreEqType2 env t1 t2 + go env (Var v1) (Var v2) = rnOccL env v1 == rnOccR env v2 + go env (Cast e1 t1) (Cast e2 t2) = go env e1 e2 && coreEqCoercion2 env t1 t2 + go env (App f1 a1) (App f2 a2) = go env f1 f2 && go env a1 a2 + + go env (Lam b1 e1) (Lam b2 e2) + = coreEqType2 env (varType b1) (varType b2) -- Will return False for Id/TyVar combination + && go (rnBndr2 env b1 b2) e1 e2 + + go env (Case e1 b1 _ a1) (Case e2 b2 _ a2) + = go env e1 e2 + && coreEqType2 env (idType b1) (idType b2) + && all2 (go_alt (rnBndr2 env b1 b2)) a1 a2 + + go env (Let (NonRec b1 r1) e1) (Let (NonRec b2 r2) e2) + = go env r1 r2 -- No need to check binder types, since RHSs match + && go (rnBndr2 env b1 b2) e1 e2 + + go env (Let (Rec p1) e1) (Let (Rec p2) e2) + | equalLength p1 p2 + = all2 (go env') rs1 rs2 && go env' e1 e2 + where + (bs1,rs1) = unzip p1 + (bs2,rs2) = unzip p2 + env' = rnBndrs2 env bs1 bs2 + go env (Note n1 e1) (Note n2 e2) = go_note n1 n2 && go env e1 e2 + + go _ _ _ = False + + ----------- + go_alt env (c1, bs1, e1) (c2, bs2, e2) + = c1 == c2 && go (rnBndrs2 env bs1 bs2) e1 e2 + + ----------- + go_note (SCC cc1) (SCC cc2) = cc1==cc2 + go_note (CoreNote s1) (CoreNote s2) = s1==s2 + go_note _ _ = False +\end{code} + %************************************************************************ %* * diff --git a/compiler/simplCore/CSE.lhs b/compiler/simplCore/CSE.lhs index 8c38661..523431f 100644 --- a/compiler/simplCore/CSE.lhs +++ b/compiler/simplCore/CSE.lhs @@ -11,7 +11,7 @@ module CSE ( #include "HsVersions.h" import Id ( Id, idType, idInlineActivation, zapIdOccInfo ) -import CoreUtils ( hashExpr, cheapEqExpr, exprIsBig, mkAltExpr, exprIsCheap ) +import CoreUtils ( hashExpr, eqExpr, exprIsBig, mkAltExpr, exprIsCheap ) import DataCon ( isUnboxedTupleCon ) import Type ( tyConAppArgs ) import CoreSyn @@ -301,15 +301,19 @@ emptyCSEnv :: CSEnv emptyCSEnv = CS emptyUFM emptyInScopeSet emptyVarEnv lookupCSEnv :: CSEnv -> CoreExpr -> Maybe CoreExpr -lookupCSEnv (CS cs _ _) expr +lookupCSEnv (CS cs in_scope _) expr = case lookupUFM cs (hashExpr expr) of Nothing -> Nothing - Just pairs -> lookup_list pairs expr - -lookup_list :: [(CoreExpr,CoreExpr)] -> CoreExpr -> Maybe CoreExpr -lookup_list [] _ = Nothing -lookup_list ((e,e'):es) expr | cheapEqExpr e expr = Just e' - | otherwise = lookup_list es expr + Just pairs -> lookup_list pairs + where + -- In this lookup we use full expression equality + -- Reason: when expressions differ we generally find out quickly + -- but I found that cheapEqExpr was saying (\x.x) /= (\y.y), + -- and this kind of thing happened in real programs + lookup_list :: [(CoreExpr,CoreExpr)] -> Maybe CoreExpr + lookup_list [] = Nothing + lookup_list ((e,e'):es) | eqExpr in_scope e expr = Just e' + | otherwise = lookup_list es addCSEnvItem :: CSEnv -> CoreExpr -> CoreExpr -> CSEnv addCSEnvItem env expr expr' | exprIsBig expr = env diff --git a/compiler/types/Coercion.lhs b/compiler/types/Coercion.lhs index 597b025..41ab164 100644 --- a/compiler/types/Coercion.lhs +++ b/compiler/types/Coercion.lhs @@ -50,7 +50,7 @@ module Coercion ( optCoercion, -- ** Comparison - coreEqCoercion, + coreEqCoercion, coreEqCoercion2, -- * CoercionI CoercionI(..), @@ -70,6 +70,7 @@ import Type import TyCon import Class import Var +import VarEnv import Name import PrelNames import Util @@ -576,6 +577,9 @@ splitNewTypeRepCo_maybe _ -- | Determines syntactic equality of coercions coreEqCoercion :: Coercion -> Coercion -> Bool coreEqCoercion = coreEqType + +coreEqCoercion2 :: RnEnv2 -> Coercion -> Coercion -> Bool +coreEqCoercion2 = coreEqType2 \end{code} diff --git a/compiler/types/Type.lhs b/compiler/types/Type.lhs index 6053721..fd275da 100644 --- a/compiler/types/Type.lhs +++ b/compiler/types/Type.lhs @@ -98,7 +98,8 @@ module Type ( tidyKind, -- * Type comparison - coreEqType, tcEqType, tcEqTypes, tcCmpType, tcCmpTypes, + coreEqType, coreEqType2, + tcEqType, tcEqTypes, tcCmpType, tcCmpTypes, tcEqPred, tcEqPredX, tcCmpPred, tcEqTypeX, tcPartOfType, tcPartOfPred, -- * Forcing evaluation of types @@ -1140,11 +1141,14 @@ See Note [Newtype eta] in TyCon.lhs \begin{code} -- | Type equality test for Core types (i.e. ignores predicate-types, synonyms etc.) coreEqType :: Type -> Type -> Bool -coreEqType t1 t2 - = eq rn_env t1 t2 +coreEqType t1 t2 = coreEqType2 rn_env t1 t2 where rn_env = mkRnEnv2 (mkInScopeSet (tyVarsOfType t1 `unionVarSet` tyVarsOfType t2)) +coreEqType2 :: RnEnv2 -> Type -> Type -> Bool +coreEqType2 rn_env t1 t2 + = eq rn_env t1 t2 + where eq env (TyVarTy tv1) (TyVarTy tv2) = rnOccL env tv1 == rnOccR env tv2 eq env (ForAllTy tv1 t1) (ForAllTy tv2 t2) = eq (rnBndr2 env tv1 tv2) t1 t2 eq env (AppTy s1 t1) (AppTy s2 t2) = eq env s1 s2 && eq env t1 t2 -- 1.7.10.4