Zubin pushed to branch wip/9.12.3-backports at Glasgow Haskell Compiler / GHC
Commits:
91db1d51 by Zubin Duggal at 2025-09-16T08:52:56+00:00
QuickLook: do a shape test before unifying
This commit ensures we do a shape test before unifying. This ensures
we don't try to unify a TyVarTv with a non-tyvar, e.g.
alpha[tyv] := Int
Fixes #25950
(cherry picked from commit a4c0c8d32e8c29364062b199abe19b033e3d4381)
Co-authored-by: sheaf
- - - - -
4 changed files:
- compiler/GHC/Tc/Gen/App.hs
- + testsuite/tests/typecheck/should_fail/T25950.hs
- + testsuite/tests/typecheck/should_fail/T25950.stderr
- testsuite/tests/typecheck/should_fail/all.T
Changes:
=====================================
compiler/GHC/Tc/Gen/App.hs
=====================================
@@ -2040,6 +2040,10 @@ qlUnify ty1 ty2
go_flexi1 kappa ty2 -- ty2 is zonked
| -- See Note [QuickLook unification] (UQL1)
simpleUnifyCheck UC_QuickLook kappa ty2
+ , checkTopShape (metaTyVarInfo kappa) ty2
+ -- NB: don't forget to do a shape check, as we might be dealing
+ -- with an ordinary metavariable (and not a quick-look instantiation variable).
+ -- (Forgetting this led to #25950.)
= do { co <- unifyKind (Just (TypeThing ty2)) ty2_kind kappa_kind
-- unifyKind: see (UQL2) in Note [QuickLook unification]
-- and (MIV2) in Note [Monomorphise instantiation variables]
=====================================
testsuite/tests/typecheck/should_fail/T25950.hs
=====================================
@@ -0,0 +1,6 @@
+{-# LANGUAGE PartialTypeSignatures #-}
+
+module T25950 where
+
+fails :: _ => a
+fails = id $ ()
=====================================
testsuite/tests/typecheck/should_fail/T25950.stderr
=====================================
@@ -0,0 +1,9 @@
+T25950.hs:6:9: error: [GHC-25897]
+ • Couldn't match expected type ‘a’ with actual type ‘()’
+ ‘a’ is a rigid type variable bound by
+ the inferred type of fails :: a
+ at T25950.hs:5:1-15
+ • In the expression: id $ ()
+ In an equation for ‘fails’: fails = id $ ()
+ • Relevant bindings include fails :: a (bound at T25950.hs:6:1)
+
=====================================
testsuite/tests/typecheck/should_fail/all.T
=====================================
@@ -724,6 +724,7 @@ test('T17594c', normal, compile_fail, [''])
test('T17594d', normal, compile_fail, [''])
test('T17594g', normal, compile_fail, [''])
+test('T25950', normal, compile_fail, [''])
test('T24470a', normal, compile_fail, [''])
test('T24553', normal, compile_fail, [''])
test('T23739b', normal, compile_fail, [''])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/91db1d51d2d53346612fe843e863cd71...
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/91db1d51d2d53346612fe843e863cd71...
You're receiving this email because of your account on gitlab.haskell.org.