[Git][ghc/ghc][wip/T24326] Pmc: COMPLETE pragmas associated with Family TyCons should apply to...

Sebastian Graf (@sgraf812) gitlab at gitlab.haskell.org
Thu Jan 11 12:37:37 UTC 2024



Sebastian Graf pushed to branch wip/T24326 at Glasgow Haskell Compiler / GHC


Commits:
0690a28c by Sebastian Graf at 2024-01-11T13:37:07+01:00
Pmc: COMPLETE pragmas associated with Family TyCons should apply to representation TyCons as well (#24326)

Fixes #24326.

- - - - -


3 changed files:

- compiler/GHC/Types/CompleteMatch.hs
- + testsuite/tests/pmcheck/complete_sigs/T24326.hs
- testsuite/tests/pmcheck/complete_sigs/all.T


Changes:

=====================================
compiler/GHC/Types/CompleteMatch.hs
=====================================
@@ -35,6 +35,11 @@ completeMatchAppliesAtType ty cm = all @Maybe ty_matches (cmResultTyCon cm)
     ty_matches sig_tc
       | Just (tc, _arg_tys) <- splitTyConApp_maybe ty
       , tc == sig_tc
+      || sig_tc `is_family_ty_con_of` tc
+         -- #24326: sig_tc might be the data Family TyCon of the representation
+         --         TyCon tc -- this CompleteMatch still applies
       = True
       | otherwise
       = False
+    fam_tc `is_family_ty_con_of` repr_tc =
+      (fst <$> tyConFamInst_maybe repr_tc) == Just fam_tc


=====================================
testsuite/tests/pmcheck/complete_sigs/T24326.hs
=====================================
@@ -0,0 +1,9 @@
+{-# LANGUAGE TypeFamilies #-}
+
+module T24326 where
+
+data family Foo
+data instance Foo = A | B
+{-# COMPLETE A :: Foo #-}
+f :: Foo -> Int
+f A = 0


=====================================
testsuite/tests/pmcheck/complete_sigs/all.T
=====================================
@@ -29,3 +29,4 @@ test('T18277', normal, compile, [''])
 test('T18960', normal, compile, [''])
 test('T18960b', normal, compile, [''])
 test('T19475', normal, compile, [''])
+test('T24326', normal, compile, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0690a28c1bb895d8b35d3bb6b6a53d2da5266076

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0690a28c1bb895d8b35d3bb6b6a53d2da5266076
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/20240111/99752811/attachment-0001.html>


More information about the ghc-commits mailing list