[Git][ghc/ghc][wip/T22948] Treat type data declarations as empty when checking pattern-matching coverage
Ryan Scott (@RyanGlScott)
gitlab at gitlab.haskell.org
Sat Feb 11 23:37:13 UTC 2023
Ryan Scott pushed to branch wip/T22948 at Glasgow Haskell Compiler / GHC
Commits:
78dc538f by Ryan Scott at 2023-02-11T18:35:05-05:00
Treat type data declarations as empty when checking pattern-matching coverage
The data constructors for a `type data` declaration don't exist at the value
level, so we don't want GHC to warn users to match on them.
Fixes #22964.
- - - - -
4 changed files:
- compiler/GHC/HsToCore/Pmc/Solver.hs
- compiler/GHC/Rename/Module.hs
- + testsuite/tests/pmcheck/should_compile/T22964.hs
- testsuite/tests/pmcheck/should_compile/all.T
Changes:
=====================================
compiler/GHC/HsToCore/Pmc/Solver.hs
=====================================
@@ -146,11 +146,16 @@ updRcm f (RCM vanilla pragmas)
-- Ex.: @vanillaCompleteMatchTC 'Maybe' ==> Just ("Maybe", {'Just','Nothing'})@
vanillaCompleteMatchTC :: TyCon -> Maybe CompleteMatch
vanillaCompleteMatchTC tc =
- let -- TYPE acts like an empty data type on the term-level (#14086), but
- -- it is a PrimTyCon, so tyConDataCons_maybe returns Nothing. Hence a
- -- special case.
- mb_dcs | tc == tYPETyCon = Just []
- | otherwise = tyConDataCons_maybe tc
+ let mb_dcs | -- TYPE acts like an empty data type on the term level (#14086),
+ -- but it is a PrimTyCon, so tyConDataCons_maybe returns Nothing.
+ -- Hence a special case.
+ tc == tYPETyCon = Just []
+ | -- Similarly, treat `type data` declarations as empty data types on
+ -- the term level, as `type data` data constructors only exist at
+ -- the type level (#22964).
+ -- See Note [Type data declarations] in GHC.Rename.Module.
+ isTypeDataTyCon tc = Just []
+ | otherwise = tyConDataCons_maybe tc
in vanillaCompleteMatch . mkUniqDSet . map RealDataCon <$> mb_dcs
-- | Initialise from 'dsGetCompleteMatches' (containing all COMPLETE pragmas)
=====================================
compiler/GHC/Rename/Module.hs
=====================================
@@ -2146,6 +2146,21 @@ The main parts of the implementation are:
declared as a `type data` declaration, however, the wrapper is omitted.
See `wrapped_reqd` in GHC.Types.Id.Make.mkDataConRep` for the place where
this check is implemented.
+
+* Although `type data` data constructors do not exist at the value level,
+ it is still possible to match on a value whose type is headed by a `type data`
+ type constructor, such as this example from #22964:
+
+ type data T a where
+ A :: T Int
+ B :: T a
+
+ f :: T a -> ()
+ f x = case x of {}
+
+ During checking the coverage of `f`'s pattern matches, we treat `T` as if it
+ were an empty data type so that GHC does not warn the user to match against
+ `A` or `B`.
-}
warnNoDerivStrat :: Maybe (LDerivStrategy GhcRn)
=====================================
testsuite/tests/pmcheck/should_compile/T22964.hs
=====================================
@@ -0,0 +1,15 @@
+{-# LANGUAGE TypeData #-}
+module X where
+
+type data T1 a where
+ A1 :: T1 Int
+ B1 :: T1 a
+
+f1 :: T1 a -> ()
+f1 x = case x of {}
+
+type data T2 a where
+ A2 :: T2 Int
+
+f2 :: T2 a -> ()
+f2 x = case x of {}
=====================================
testsuite/tests/pmcheck/should_compile/all.T
=====================================
@@ -158,3 +158,4 @@ test('EmptyCase009', [], compile, [overlapping_incomplete])
test('EmptyCase010', [], compile, [overlapping_incomplete])
test('T19271', [], compile, [overlapping_incomplete])
test('T21761', [], compile, [overlapping_incomplete])
+test('T22964', [], compile, [overlapping_incomplete])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/78dc538f31dd54f47f956e1ca66b75ce8251dc1c
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/78dc538f31dd54f47f956e1ca66b75ce8251dc1c
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/20230211/016881a2/attachment-0001.html>
More information about the ghc-commits
mailing list