[Git][ghc/ghc][wip/T23070-dicts] Avoid an assertion failure in abstractFloats

Simon Peyton Jones (@simonpj) gitlab at gitlab.haskell.org
Sun May 21 20:52:11 UTC 2023



Simon Peyton Jones pushed to branch wip/T23070-dicts at Glasgow Haskell Compiler / GHC


Commits:
432b0361 by Simon Peyton Jones at 2023-05-21T21:51:15+01:00
Avoid an assertion failure in abstractFloats

The function GHC.Core.Opt.Simplify.Utils.abstractFloats
was carelessly calling lookupIdSubst_maybe on a CoVar;
but a precondition of the latter is being given an Id.

In fact it's harmless to call it on a CoVar, but still, the
precondition on lookupIdSubst_maybe makes sense, so I added
a test for CoVars.

This avoids a crash in a DEBUG compiler, but otherwise has
no effect. Fixes #23426.

- - - - -


3 changed files:

- compiler/GHC/Core/Opt/Simplify/Utils.hs
- + testsuite/tests/simplCore/should_compile/T23426.hs
- testsuite/tests/simplCore/should_compile/all.T


Changes:

=====================================
compiler/GHC/Core/Opt/Simplify/Utils.hs
=====================================
@@ -2143,6 +2143,9 @@ abstractFloats uf_opts top_lvl main_tvs floats body
         get_tvs var free_tvs
            | isTyVar var      -- CoVars have been substituted away
            = extendVarSet free_tvs var
+           | isCoVar var  -- CoVars can be free in the RHS, but they are never let-bound;
+           = free_tvs     -- Do not call lookupIdSubst_maybe, though (#23426)
+                          --    because it has a non-CoVar precondition
            | Just poly_app <- GHC.Core.Subst.lookupIdSubst_maybe subst var
            = -- 'var' is like 'x' in (AB4)
              exprSomeFreeVars isTyVar poly_app `unionVarSet` free_tvs


=====================================
testsuite/tests/simplCore/should_compile/T23426.hs
=====================================
@@ -0,0 +1,8 @@
+module T23426 where
+
+class (Char ~ a) => ListLike a where
+    mnull :: a -> b
+
+indent :: forall a. (ListLike a) => a -> Bool
+indent x = let doText y = const (mnull y) doText
+           in const (doText x) doText


=====================================
testsuite/tests/simplCore/should_compile/all.T
=====================================
@@ -483,4 +483,4 @@ test('T23307', normal, compile, ['-O -ddump-simpl -dno-typeable-binds -dsuppress
 test('T23307a', normal, compile, ['-O -ddump-simpl -dno-typeable-binds -dsuppress-uniques'])
 test('T23307b', normal, compile, ['-O'])
 test('T23307c', normal, compile, ['-O'])
-
+test('T23426', normal, compile, ['-O'])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/432b03612ea005a0925f3b33164893eeb1e891f0

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/432b03612ea005a0925f3b33164893eeb1e891f0
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/20230521/2ed30297/attachment-0001.html>


More information about the ghc-commits mailing list