[Git][ghc/ghc][master] Stop if type constructors have kind errors
Marge Bot (@marge-bot)
gitlab at gitlab.haskell.org
Fri Apr 14 08:19:20 UTC 2023
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
d48fbfea by Simon Peyton Jones at 2023-04-14T04:19:05-04:00
Stop if type constructors have kind errors
Otherwise we get knock-on errors, such as #23252.
This makes GHC fail a bit sooner, and I have not attempted to add
recovery code, to add a fake TyCon place of the erroneous one,
in an attempt to get more type errors in one pass. We could
do that (perhaps) if there was a call for it.
- - - - -
6 changed files:
- compiler/GHC/Tc/TyCl.hs
- testsuite/tests/dependent/should_fail/T15743c.hs
- testsuite/tests/dependent/should_fail/T15743c.stderr
- + testsuite/tests/roles/should_fail/T23252.hs
- + testsuite/tests/roles/should_fail/T23252.stderr
- testsuite/tests/roles/should_fail/all.T
Changes:
=====================================
compiler/GHC/Tc/TyCl.hs
=====================================
@@ -248,7 +248,13 @@ tcTyClDecls tyclds kisig_env role_annots
= do { -- Step 1: kind-check this group and returns the final
-- (possibly-polymorphic) kind of each TyCon and Class
-- See Note [Kind checking for type and class decls]
- (tc_tycons, kindless) <- kcTyClGroup kisig_env tyclds
+ (tc_tycons, kindless) <- checkNoErrs $
+ kcTyClGroup kisig_env tyclds
+ -- checkNoErrs: If the TyCons are ill-kinded, stop now. Else we
+ -- can get follow-on errors. Example: #23252, where the TyCon
+ -- had an ill-scoped kind forall (d::k) k (a::k). blah
+ -- and that ill-scoped kind made role inference fall over.
+
; traceTc "tcTyAndCl generalized kinds" (vcat (map ppr_tc_tycon tc_tycons))
-- Step 2: type-check all groups together, returning
=====================================
testsuite/tests/dependent/should_fail/T15743c.hs
=====================================
@@ -8,4 +8,4 @@ import Data.Proxy
data SimilarKind :: forall (c :: k) (d :: k). Proxy c -> Proxy d -> Type
data T k (c :: k) (a :: Proxy c) b (x :: SimilarKind a b)
-data T2 k (c :: k) (a :: Proxy c) (b :: Proxy d) (x :: SimilarKind a b)
+
=====================================
testsuite/tests/dependent/should_fail/T15743c.stderr
=====================================
@@ -13,18 +13,3 @@ T15743c.hs:10:1: error:
(b :: Proxy d)
(x :: SimilarKind a b)
• In the data type declaration for ‘T’
-
-T15743c.hs:11:1: error:
- • The kind of ‘T2’ is ill-scoped
- Inferred kind: T2 :: forall (d :: k).
- forall k (c :: k) (a :: Proxy c) (b :: Proxy d) ->
- SimilarKind a b -> *
- NB: Specified variables (namely: (d :: k)) always come first
- Perhaps try this order instead:
- k
- (d :: k)
- (c :: k)
- (a :: Proxy c)
- (b :: Proxy d)
- (x :: SimilarKind a b)
- • In the data type declaration for ‘T2’
=====================================
testsuite/tests/roles/should_fail/T23252.hs
=====================================
@@ -0,0 +1,12 @@
+{-# LANGUAGE PolyKinds, DataKinds, ExplicitForAll #-}
+{-# LANGUAGE RoleAnnotations #-}
+
+module T15743 where
+
+import Data.Kind
+import Data.Proxy
+
+data SimilarKind :: forall (c :: k) (d :: k). Proxy c -> Proxy d -> Type
+
+data T2 k (c :: k) (a :: Proxy c) (b :: Proxy d) (x :: SimilarKind a b)
+type role T2 nominal nominal nominal nominal -- Too few!
=====================================
testsuite/tests/roles/should_fail/T23252.stderr
=====================================
@@ -0,0 +1,14 @@
+T23252.hs:11:1: error:
+ • The kind of ‘T2’ is ill-scoped
+ Inferred kind: T2 :: forall (d :: k).
+ forall k (c :: k) (a :: Proxy c) (b :: Proxy d) ->
+ SimilarKind a b -> *
+ NB: Specified variables (namely: (d :: k)) always come first
+ Perhaps try this order instead:
+ k
+ (d :: k)
+ (c :: k)
+ (a :: Proxy c)
+ (b :: Proxy d)
+ (x :: SimilarKind a b)
+ • In the data type declaration for ‘T2’
=====================================
testsuite/tests/roles/should_fail/all.T
=====================================
@@ -8,3 +8,4 @@ test('Roles12', [], makefile_test, [])
test('T8773', normal, compile_fail, [''])
test('T9204', [], makefile_test, [])
test('RolesIArray', normal, compile_fail, [''])
+test('T23252', normal, compile_fail, [''])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d48fbfea5f7b760ec3d13dd2947257986c095b75
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d48fbfea5f7b760ec3d13dd2947257986c095b75
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/20230414/94703bf2/attachment-0001.html>
More information about the ghc-commits
mailing list