[Git][ghc/ghc][wip/marge_bot_batch_merge_job] Fix a bug in anyInRnEnvR

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Mon Aug 29 05:08:28 UTC 2022



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
23c0677d by Simon Peyton Jones at 2022-08-29T01:08:15-04:00
Fix a bug in anyInRnEnvR

This bug was a subtle error in anyInRnEnvR, introduced by

    commit d4d3fe6e02c0eb2117dbbc9df72ae394edf50f06
    Author: Andreas Klebinger <klebinger.andreas at gmx.at>
    Date:   Sat Jul 9 01:19:52 2022 +0200

    Rule matching: Don't compute the FVs if we don't look at them.

The net result was #22028, where a rewrite rule would wrongly
match on a lambda.

The fix to that function is easy.

- - - - -


4 changed files:

- compiler/GHC/Types/Var/Env.hs
- + testsuite/tests/simplCore/should_compile/T22028.hs
- + testsuite/tests/simplCore/should_compile/T22028.stderr
- testsuite/tests/simplCore/should_compile/all.T


Changes:

=====================================
compiler/GHC/Types/Var/Env.hs
=====================================
@@ -9,7 +9,7 @@ module GHC.Types.Var.Env (
 
         -- ** Manipulating these environments
         emptyVarEnv, unitVarEnv, mkVarEnv, mkVarEnv_Directly,
-        elemVarEnv, disjointVarEnv,
+        elemVarEnv, disjointVarEnv, anyVarEnv,
         extendVarEnv, extendVarEnv_C, extendVarEnv_Acc,
         extendVarEnvList,
         plusVarEnv, plusVarEnv_C, plusVarEnv_CD, plusMaybeVarEnv_C,
@@ -62,7 +62,8 @@ module GHC.Types.Var.Env (
 
         -- ** Operations on RnEnv2s
         mkRnEnv2, rnBndr2, rnBndrs2, rnBndr2_var,
-        rnOccL, rnOccR, inRnEnvL, inRnEnvR, rnOccL_maybe, rnOccR_maybe,
+        rnOccL, rnOccR, inRnEnvL, inRnEnvR,  anyInRnEnvR,
+        rnOccL_maybe, rnOccR_maybe,
         rnBndrL, rnBndrR, nukeRnEnvL, nukeRnEnvR, rnSwap,
         delBndrL, delBndrR, delBndrsL, delBndrsR,
         extendRnInScopeSetList,
@@ -72,7 +73,7 @@ module GHC.Types.Var.Env (
 
         -- * TidyEnv and its operation
         TidyEnv,
-        emptyTidyEnv, mkEmptyTidyEnv, delTidyEnvList, anyInRnEnvR
+        emptyTidyEnv, mkEmptyTidyEnv, delTidyEnvList
     ) where
 
 import GHC.Prelude
@@ -409,7 +410,7 @@ anyInRnEnvR :: RnEnv2 -> VarSet -> Bool
 anyInRnEnvR (RV2 { envR = env }) vs
   -- Avoid allocating the predicate if we deal with an empty env.
   | isEmptyVarEnv env = False
-  | otherwise = anyVarEnv (`elemVarSet` vs) env
+  | otherwise         = anyVarSet (`elemVarEnv` env) vs
 
 lookupRnInScope :: RnEnv2 -> Var -> Var
 lookupRnInScope env v = lookupInScope (in_scope env) v `orElse` v


=====================================
testsuite/tests/simplCore/should_compile/T22028.hs
=====================================
@@ -0,0 +1,19 @@
+
+-- This one triggers the bug reported in #22028, which
+-- was in a test for #1092
+-- The problem is that the rule
+--      forall w. f (\v->w) = w
+-- erroneously matches the call
+--      f id
+-- And that caused an assertion error.
+
+module Foo where
+
+f :: (Int -> Int) -> Int
+{-# NOINLINE f #-}
+f g = g 4
+{-# RULES "f" forall w. f (\v->w) = w  #-}
+
+h1 = f (\v -> v)   -- Rule should not fire
+h2 = f id          -- Rule should not fire
+h3 = f (\v -> 3)   -- Rule should fire


=====================================
testsuite/tests/simplCore/should_compile/T22028.stderr
=====================================
@@ -0,0 +1 @@
+Rule fired: f (Foo)


=====================================
testsuite/tests/simplCore/should_compile/all.T
=====================================
@@ -427,3 +427,4 @@ test('T21960', [grep_errmsg(r'^ Arity=5') ], compile, ['-O2 -ddump-simpl'])
 test('T21948', [grep_errmsg(r'^ Arity=5') ], compile, ['-O -ddump-simpl'])
 test('T21763', only_ways(['optasm']), compile, ['-O2 -ddump-rules'])
 test('T21763a', only_ways(['optasm']), compile, ['-O2 -ddump-rules'])
+test('T22028', normal, compile, ['-O -ddump-rule-firings'])



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/23c0677d55d4c095c3ad6cf6b2aae5125a53d4f2
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/20220829/02de2918/attachment-0001.html>


More information about the ghc-commits mailing list