[Git][ghc/ghc][master] Better error for data deriving of type synonym/family. Closes #23522
Marge Bot (@marge-bot)
gitlab at gitlab.haskell.org
Mon Jul 3 07:34:37 UTC 2023
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
924a2362 by Gregory Gerasev at 2023-07-03T03:34:10-04:00
Better error for data deriving of type synonym/family. Closes #23522
- - - - -
5 changed files:
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Tc/Gen/HsType.hs
- + testsuite/tests/deriving/should_fail/T23522.hs
- + testsuite/tests/deriving/should_fail/T23522.stderr
- testsuite/tests/deriving/should_fail/all.T
Changes:
=====================================
compiler/GHC/Tc/Errors/Types.hs
=====================================
@@ -1201,11 +1201,15 @@ data TcRnMessage where
{-| TcRnIllegalClassInst is an error that occurs whenever a class instance is specified
for a non-class.
+ This also includes derived instances. See the T23522 test case.
+
Examples(s):
type C1 a = (Show (a -> Bool))
instance C1 Int where
- Test cases: polykinds/T13267
+ Test cases:
+ polykinds/T13267
+ deriving/should_fail/T23522
-}
TcRnIllegalClassInst :: !(TyConFlavour TyCon) -> TcRnMessage
=====================================
compiler/GHC/Tc/Gen/HsType.hs
=====================================
@@ -99,7 +99,6 @@ import GHC.Tc.Utils.Instantiate ( tcInstInvisibleTyBinders, tcInstInvisibleTyBin
import GHC.Tc.Zonk.TcType
import GHC.Core.Type
-import GHC.Core.Predicate
import GHC.Core.TyCo.Rep
import GHC.Core.TyCo.Ppr
@@ -639,9 +638,15 @@ tcHsDeriv hs_ty
= do { ty <- tcTopLHsType DerivClauseCtxt hs_ty
; let (tvs, pred) = splitForAllTyCoVars ty
(kind_args, _) = splitFunTys (typeKind pred)
- ; case getClassPredTys_maybe pred of
- Just (cls, tys) -> return (tvs, cls, tys, map scaledThing kind_args)
- Nothing -> failWithTc $ TcRnIllegalDerivingItem hs_ty }
+ -- Checking that `pred` a is type class application
+ ; case splitTyConApp_maybe pred of
+ Just (tyCon, tyConArgs) ->
+ case tyConClass_maybe tyCon of
+ Just clas ->
+ return (tvs, clas, tyConArgs, map scaledThing kind_args)
+ Nothing -> failWithTc $ TcRnIllegalClassInst (tyConFlavour tyCon)
+ Nothing -> failWithTc $ TcRnIllegalDerivingItem hs_ty
+ }
-- | Typecheck a deriving strategy. For most deriving strategies, this is a
-- no-op, but for the @via@ strategy, this requires typechecking the @via@ type.
=====================================
testsuite/tests/deriving/should_fail/T23522.hs
=====================================
@@ -0,0 +1,5 @@
+module T23522 where
+
+type F x = Show x
+
+data Proposition = Proposition deriving (F)
=====================================
testsuite/tests/deriving/should_fail/T23522.stderr
=====================================
@@ -0,0 +1,5 @@
+
+T23522.hs:5:42: [GHC-53946]
+ Illegal instance for a type synonym
+ A class instance must be for a class
+ In the data declaration for ‘Proposition’
=====================================
testsuite/tests/deriving/should_fail/all.T
=====================================
@@ -87,3 +87,4 @@ test('T21087b', [extra_files(['T21087b_aux.hs','T21087b_aux.hs-boot'])], multimo
test('T21302', normal, compile_fail, [''])
test('T21871', normal, compile_fail, [''])
test('T22696b', normal, compile_fail, [''])
+test('T23522', normal, compile_fail, [''])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/924a2362810d9fa27c5da212cb35fd3e357ab9d1
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/924a2362810d9fa27c5da212cb35fd3e357ab9d1
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/20230703/87ccab7e/attachment-0001.html>
More information about the ghc-commits
mailing list