[Git][ghc/ghc][master] Expand synonyms in RoughMap

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Fri Feb 17 01:32:47 UTC 2023



Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
8988eeef by sheaf at 2023-02-16T20:32:27-05:00
Expand synonyms in RoughMap

We were failing to expand type synonyms in the function
GHC.Core.RoughMap.typeToRoughMatchLookupTc, even though the
RoughMap infrastructure crucially relies on type synonym expansion
to work.

This patch adds the missing type-synonym expansion.

Fixes #22985

- - - - -


4 changed files:

- compiler/GHC/Core/RoughMap.hs
- + testsuite/tests/typecheck/should_compile/T22985a.hs
- + testsuite/tests/typecheck/should_compile/T22985b.hs
- testsuite/tests/typecheck/should_compile/all.T


Changes:

=====================================
compiler/GHC/Core/RoughMap.hs
=====================================
@@ -320,7 +320,11 @@ roughMatchTcsLookup tys = map typeToRoughMatchLookupTc tys
 
 typeToRoughMatchLookupTc :: Type -> RoughMatchLookupTc
 typeToRoughMatchLookupTc ty
-  | Just (ty', _) <- splitCastTy_maybe ty
+  -- Expand synonyms first, as explained in Note [Rough matching in class and family instances].
+  -- Failing to do so led to #22985.
+  | Just ty' <- coreView ty
+  = typeToRoughMatchLookupTc ty'
+  | CastTy ty' _ <- ty
   = typeToRoughMatchLookupTc ty'
   | otherwise
   = case splitAppTys ty of


=====================================
testsuite/tests/typecheck/should_compile/T22985a.hs
=====================================
@@ -0,0 +1,6 @@
+module T22985a where
+
+type Phase n = n
+
+addExpr :: Eq a => Phase a -> ()
+addExpr _ = ()


=====================================
testsuite/tests/typecheck/should_compile/T22985b.hs
=====================================
@@ -0,0 +1,6 @@
+module T22985b where
+
+type Phase n = n
+
+addExpr :: Num a => Phase a -> a
+addExpr x = let t = asTypeOf x 0 in t


=====================================
testsuite/tests/typecheck/should_compile/all.T
=====================================
@@ -861,4 +861,5 @@ test('T20666b', normal, compile, [''])
 test('T22891', normal, compile, [''])
 test('T22912', normal, compile, [''])
 test('T22924', normal, compile, [''])
-
+test('T22985a', normal, compile, ['-O'])
+test('T22985b', normal, compile, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8988eeef193f055d7b67de5aaa00590c63491fb5

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8988eeef193f055d7b67de5aaa00590c63491fb5
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/20230216/6e3aac71/attachment-0001.html>


More information about the ghc-commits mailing list