[Git][ghc/ghc][wip/T22141] Accept new T20873c test output, add T20873d test

Ryan Scott (@RyanGlScott) gitlab at gitlab.haskell.org
Mon Sep 25 11:00:47 UTC 2023



Ryan Scott pushed to branch wip/T22141 at Glasgow Haskell Compiler / GHC


Commits:
b35c4b0d by Ryan Scott at 2023-09-25T06:58:22-04:00
Accept new T20873c test output, add T20873d test

Now that we also check for `DataKinds` violations pre–type synonym expansion
(as well as post–type synonym expansion), the use of `Int` in the kind `U Int`
(where `U` is a type synonym) in the `T20873c` test case triggers a `DataKinds`
violation. I've updated the expected test output to accept these changes.

To make sure that the spirit of the original `T20873c` test is preserved, I've
also added a `T20873d` test case that uses `U Type` instead of `U Int`, which
instead fails due to not enabling `KindSignatures` (rather than incidentally
failing due to not enabling `DataKinds`).

- - - - -


4 changed files:

- testsuite/tests/typecheck/should_fail/T20873c.stderr
- + testsuite/tests/typecheck/should_fail/T20873d.hs
- + testsuite/tests/typecheck/should_fail/T20873d.stderr
- testsuite/tests/typecheck/should_fail/all.T


Changes:

=====================================
testsuite/tests/typecheck/should_fail/T20873c.stderr
=====================================
@@ -1,5 +1,5 @@
 
-T20873c.hs:10:1: error: [GHC-49378]
-    • Illegal kind signature ‘Foo :: U Int’
-    • In the data declaration for ‘Foo’
-    Suggested fix: Perhaps you intended to use KindSignatures
+T20873c.hs:10:1: error: [GHC-68567]
+    • Illegal kind: ‘Int’
+    • In the data type declaration for ‘Foo’
+    Suggested fix: Perhaps you intended to use DataKinds


=====================================
testsuite/tests/typecheck/should_fail/T20873d.hs
=====================================
@@ -0,0 +1,11 @@
+
+{-# LANGUAGE GADTSyntax, NoKindSignatures, NoDataKinds #-}
+
+module T20873d where
+
+import Data.Kind ( Type )
+
+type U a = Type
+
+data Foo :: U Type where
+  MkFoo :: Foo


=====================================
testsuite/tests/typecheck/should_fail/T20873d.stderr
=====================================
@@ -0,0 +1,5 @@
+
+T20873d.hs:10:1: error: [GHC-49378]
+    • Illegal kind signature ‘Foo :: U Type’
+    • In the data declaration for ‘Foo’
+    Suggested fix: Perhaps you intended to use KindSignatures


=====================================
testsuite/tests/typecheck/should_fail/all.T
=====================================
@@ -647,6 +647,7 @@ test('T20588', [extra_files(['T20588.hs', 'T20588.hs-boot', 'T20588_aux.hs'])],
 test('T20588c', [extra_files(['T20588c.hs', 'T20588c.hs-boot', 'T20588c_aux.hs'])], multimod_compile_fail, ['T20588c_aux.hs', '-v0'])
 test('T20189', normal, compile_fail, [''])
 test('T20873c', normal, compile_fail, [''])
+test('T20873d', normal, compile_fail, [''])
 test('FunDepOrigin1b', normal, compile_fail, [''])
 test('FD1', normal, compile_fail, [''])
 test('FD2', normal, compile_fail, [''])



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b35c4b0de9680e893036c541d8ebb1f35500ea65
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/20230925/c115085f/attachment-0001.html>


More information about the ghc-commits mailing list