[Git][ghc/ghc][wip/make-Wdata-kinds-tc-an-error] Remove -Wdata-kinds-tc warning, make DataKinds issues in typechecker become errors

Ryan Scott (@RyanGlScott) gitlab at gitlab.haskell.org
Thu Mar 6 12:22:03 UTC 2025



Ryan Scott pushed to branch wip/make-Wdata-kinds-tc-an-error at Glasgow Haskell Compiler / GHC


Commits:
6db8d605 by Ryan Scott at 2025-03-06T07:21:46-05:00
Remove -Wdata-kinds-tc warning, make DataKinds issues in typechecker become errors

!11314 introduced the `-Wdata-kinds-tc` warning as part of a fix for #22141.
This was a temporary stopgap measure to allow users who were accidentally
relying on code which needed the `DataKinds` extension in order to typecheck
without having to explicitly enable the extension.

Now that some amount of time has passed, this patch removes `-Wdata-kinds-tc`
and upgrades any `DataKinds`-related issues in the typechecker (which were
previously warnings) into errors.

- - - - -


29 changed files:

- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Tc/Validity.hs
- docs/users_guide/9.14.1-notes.rst
- docs/users_guide/using-warnings.rst
- − testsuite/tests/typecheck/should_compile/T22141a.stderr
- − testsuite/tests/typecheck/should_compile/T22141b.stderr
- − testsuite/tests/typecheck/should_compile/T22141c.stderr
- − testsuite/tests/typecheck/should_compile/T22141d.stderr
- − testsuite/tests/typecheck/should_compile/T22141e.stderr
- testsuite/tests/typecheck/should_compile/all.T
- testsuite/tests/typecheck/should_fail/T20873c.hs
- testsuite/tests/typecheck/should_fail/T20873c.stderr
- testsuite/tests/typecheck/should_compile/T22141a.hs → testsuite/tests/typecheck/should_fail/T22141a.hs
- testsuite/tests/typecheck/should_fail/T22141a.stderr
- testsuite/tests/typecheck/should_compile/T22141b.hs → testsuite/tests/typecheck/should_fail/T22141b.hs
- testsuite/tests/typecheck/should_fail/T22141b.stderr
- testsuite/tests/typecheck/should_compile/T22141c.hs → testsuite/tests/typecheck/should_fail/T22141c.hs
- testsuite/tests/typecheck/should_fail/T22141c.stderr
- testsuite/tests/typecheck/should_compile/T22141d.hs → testsuite/tests/typecheck/should_fail/T22141d.hs
- testsuite/tests/typecheck/should_fail/T22141d.stderr
- testsuite/tests/typecheck/should_compile/T22141e.hs → testsuite/tests/typecheck/should_fail/T22141e.hs
- testsuite/tests/typecheck/should_fail/T22141e.stderr
- testsuite/tests/typecheck/should_compile/T22141e_Aux.hs → testsuite/tests/typecheck/should_fail/T22141e_Aux.hs
- testsuite/tests/typecheck/should_fail/all.T
- testsuite/tests/vdq-rta/should_fail/T23739_fail_case.hs
- testsuite/tests/vdq-rta/should_fail/T23739_fail_case.stderr


Changes:

=====================================
compiler/GHC/Driver/Flags.hs
=====================================
@@ -1073,7 +1073,6 @@ data WarningFlag =
    | Opt_WarnIncompleteRecordSelectors               -- Since 9.10
    | Opt_WarnBadlyStagedTypes                        -- Since 9.10
    | Opt_WarnInconsistentFlags                       -- Since 9.8
-   | Opt_WarnDataKindsTC                             -- Since 9.10
    | Opt_WarnDefaultedExceptionContext               -- Since 9.10
    | Opt_WarnViewPatternSignatures                   -- Since 9.12
    deriving (Eq, Ord, Show, Enum, Bounded)
@@ -1189,7 +1188,6 @@ warnFlagNames wflag = case wflag of
   Opt_WarnIncompleteRecordSelectors               -> "incomplete-record-selectors" :| []
   Opt_WarnBadlyStagedTypes                        -> "badly-staged-types" :| []
   Opt_WarnInconsistentFlags                       -> "inconsistent-flags" :| []
-  Opt_WarnDataKindsTC                             -> "data-kinds-tc" :| []
   Opt_WarnDefaultedExceptionContext               -> "defaulted-exception-context" :| []
   Opt_WarnViewPatternSignatures                   -> "view-pattern-signatures" :| []
 
@@ -1331,7 +1329,6 @@ standardWarnings -- see Note [Documenting warning flags]
         Opt_WarnBadlyStagedTypes,
         Opt_WarnTypeEqualityRequiresOperators,
         Opt_WarnInconsistentFlags,
-        Opt_WarnDataKindsTC,
         Opt_WarnTypeEqualityOutOfScope,
         Opt_WarnViewPatternSignatures
       ]


=====================================
compiler/GHC/Driver/Session.hs
=====================================
@@ -2355,7 +2355,6 @@ wWarningFlagsDeps = [minBound..maxBound] >>= \x -> case x of
   Opt_WarnImplicitRhsQuantification -> warnSpec x
   Opt_WarnIncompleteExportWarnings -> warnSpec x
   Opt_WarnIncompleteRecordSelectors -> warnSpec x
-  Opt_WarnDataKindsTC -> warnSpec x
   Opt_WarnDefaultedExceptionContext -> warnSpec x
   Opt_WarnViewPatternSignatures -> warnSpec x
 


=====================================
compiler/GHC/Tc/Errors/Ppr.hs
=====================================
@@ -1715,21 +1715,15 @@ instance Diagnostic TcRnMessage where
                 , inHsDocContext doc ]
 
     TcRnDataKindsError typeOrKind thing
-      -- See Note [Checking for DataKinds] (Wrinkle: Migration story for
-      -- DataKinds typechecker errors) in GHC.Tc.Validity for why we give
-      -- different diagnostic messages below.
       -> case thing of
            Left renamer_thing ->
-             mkSimpleDecorated $
-               text "Illegal" <+> ppr_level <> colon <+> quotes (ppr renamer_thing)
+             mkSimpleDecorated $ msg renamer_thing
            Right typechecker_thing ->
-             mkSimpleDecorated $ vcat
-               [ text "An occurrence of" <+> quotes (ppr typechecker_thing) <+>
-                 text "in a" <+> ppr_level <+> text "requires DataKinds."
-               , text "Future versions of GHC will turn this warning into an error."
-               ]
+             mkSimpleDecorated $ msg typechecker_thing
       where
-        ppr_level = text $ levelString typeOrKind
+        msg :: Outputable a => a -> SDoc
+        msg thing = text "Illegal" <+> text (levelString typeOrKind) <>
+                    colon <+> quotes (ppr thing)
 
     TcRnTypeSynonymCycle decl_or_tcs
       -> mkSimpleDecorated $
@@ -2524,17 +2518,8 @@ instance Diagnostic TcRnMessage where
       -> ErrorWithoutFlag
     TcRnUnusedQuantifiedTypeVar{}
       -> WarningWithFlag Opt_WarnUnusedForalls
-    TcRnDataKindsError _ thing
-      -- DataKinds errors can arise from either the renamer (Left) or the
-      -- typechecker (Right). The latter category of DataKinds errors are a
-      -- fairly recent addition to GHC (introduced in GHC 9.10), and in order
-      -- to prevent these new errors from breaking users' code, we temporarily
-      -- downgrade these errors to warnings. See Note [Checking for DataKinds]
-      -- (Wrinkle: Migration story for DataKinds typechecker errors)
-      -- in GHC.Tc.Validity.
-      -> case thing of
-           Left  _ -> ErrorWithoutFlag
-           Right _ -> WarningWithFlag Opt_WarnDataKindsTC
+    TcRnDataKindsError{}
+      -> ErrorWithoutFlag
     TcRnTypeSynonymCycle{}
       -> ErrorWithoutFlag
     TcRnZonkerMessage msg


=====================================
compiler/GHC/Tc/Errors/Types.hs
=====================================
@@ -2519,11 +2519,11 @@ data TcRnMessage where
                   rename/should_fail/T22478e
                   th/TH_Promoted1Tuple
                   typecheck/should_compile/tcfail094
-                  typecheck/should_compile/T22141a
-                  typecheck/should_compile/T22141b
-                  typecheck/should_compile/T22141c
-                  typecheck/should_compile/T22141d
-                  typecheck/should_compile/T22141e
+                  typecheck/should_fail/T22141a
+                  typecheck/should_fail/T22141b
+                  typecheck/should_fail/T22141c
+                  typecheck/should_fail/T22141d
+                  typecheck/should_fail/T22141e
                   typecheck/should_compile/T22141f
                   typecheck/should_compile/T22141g
                   typecheck/should_fail/T20873c


=====================================
compiler/GHC/Tc/Validity.hs
=====================================
@@ -1000,18 +1000,11 @@ checkVdqOK ve tvbs ty = do
 
 -- | Check for a DataKinds violation in a kind context.
 -- See @Note [Checking for DataKinds]@.
---
--- Note that emitting DataKinds errors from the typechecker is a fairly recent
--- addition to GHC (introduced in GHC 9.10), and in order to prevent these new
--- errors from breaking users' code, we temporarily downgrade these errors to
--- warnings. (This is why we use 'diagnosticTcM' below.) See
--- @Note [Checking for DataKinds] (Wrinkle: Migration story for DataKinds
--- typechecker errors)@.
 checkDataKinds :: ValidityEnv -> Type -> TcM ()
 checkDataKinds (ValidityEnv{ ve_ctxt = ctxt, ve_tidy_env = env }) ty = do
   data_kinds <- xoptM LangExt.DataKinds
-  diagnosticTcM
-    (not (data_kinds || typeLevelUserTypeCtxt ctxt)) $
+  checkTcM
+    (data_kinds || typeLevelUserTypeCtxt ctxt) $
     (env, TcRnDataKindsError KindLevel (Right (tidyType env ty)))
 
 {- Note [No constraints in kinds]
@@ -1163,28 +1156,6 @@ different places in the code:
   synonym), so we also catch a subset of kind-level violations in the renamer
   to allow for earlier reporting of these errors.
 
------
--- Wrinkle: Migration story for DataKinds typechecker errors
------
-
-As mentioned above, DataKinds is checked in two different places: the renamer
-and the typechecker. The checks in the renamer have been around since DataKinds
-was introduced. The checks in the typechecker, on the other hand, are a fairly
-recent addition, having been introduced in GHC 9.10. As such, it is possible
-that there are some programs in the wild that (1) do not enable DataKinds, and
-(2) were accepted by a previous GHC version, but would now be rejected by the
-new DataKinds checks in the typechecker.
-
-To prevent the new DataKinds checks in the typechecker from breaking users'
-code, we temporarily allow programs to compile if they violate a DataKinds
-check in the typechecker, but GHC will emit a warning if such a violation
-occurs. Users can then silence the warning by enabling DataKinds in the module
-where the affected code lives. It is fairly straightforward to distinguish
-between DataKinds violations arising from the renamer versus the typechecker,
-as TcRnDataKindsError (the error message type classifying all DataKinds errors)
-stores an Either field that is Left when the error comes from the renamer and
-Right when the error comes from the typechecker.
-
 ************************************************************************
 *                                                                      *
 \subsection{Checking a theta or source type}


=====================================
docs/users_guide/9.14.1-notes.rst
=====================================
@@ -40,6 +40,21 @@ Language
 
 * Multiline strings are now accepted in foreign imports. (#25157)
 
+* The ``-Wdata-kinds-tc`` warning has been removed, and the use of promoted
+  data types in kinds is now an error (rather than a warning) unless the
+  :extension:`DataKinds` extension is enabled. For example, the following code
+  will be rejected unless :extension:`DataKinds` is on:
+
+    import Data.Kind (Type)
+    import GHC.TypeNats (Nat)
+
+    -- Nat shouldn't be allowed here without DataKinds
+    data Vec :: Nat -> Type -> Type
+
+  (The ``-Wdata-kinds-tc`` warning was introduced in GHC 9.10 as part of a fix
+  for an accidental oversight in which programs like the one above were
+  mistakenly accepted without the use of :extension:`DataKinds`.)
+
 Compiler
 ~~~~~~~~
 


=====================================
docs/users_guide/using-warnings.rst
=====================================
@@ -82,7 +82,6 @@ as ``-Wno-...`` for every individual warning in the group.
         * :ghc-flag:`-Winconsistent-flags`
         * :ghc-flag:`-Wnoncanonical-monoid-instances`
         * :ghc-flag:`-Wnoncanonical-monad-instances`
-        * :ghc-flag:`-Wdata-kinds-tc`
 
 .. ghc-flag:: -W
     :shortdesc: enable normal warnings
@@ -2535,26 +2534,6 @@ of ``-W(no-)*``.
     issued. Another example is :ghc-flag:`-dynamic` is ignored when :ghc-flag:`-dynamic-too`
     is passed.
 
-.. ghc-flag:: -Wdata-kinds-tc
-    :shortdesc: warn when an illegal use of a type or kind without
-                :extension:`DataKinds` is caught by the typechecker
-    :type: dynamic
-    :reverse: -Wno-data-kinds-tc
-
-    :since: 9.10.1
-
-    Introduced in GHC 9.10.1, this warns when an illegal use of a type or kind
-    (without having enabled the :extension:`DataKinds` extension) is caught in
-    the typechecker (hence the ``-tc`` suffix). These warnings complement the
-    existing :extension:`DataKinds` checks (that have existed since
-    :extension:`DataKinds` was first introduced), which result in errors
-    instead of warnings.
-
-    This warning is scheduled to be changed to an error in a future GHC
-    version, at which point the :ghc-flag:`-Wdata-kinds-tc` flag will be
-    removed. Users can enable the :extension:`DataKinds` extension to avoid
-    issues (thus silencing the warning).
-
 .. ghc-flag:: -Wdefaulted-exception-context
     :shortdesc: warn when an :base-ref:`Control.Exception.Context.ExceptionContext`
                 implicit parameter is defaulted to


=====================================
testsuite/tests/typecheck/should_compile/T22141a.stderr deleted
=====================================
@@ -1,8 +0,0 @@
-T22141a.hs:8:1: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)]
-    • An occurrence of ‘GHC.Internal.Bignum.Natural.Natural’ in a kind requires DataKinds.
-      Future versions of GHC will turn this warning into an error.
-    • In the expansion of type synonym ‘Nat’
-      In the data type declaration for ‘Vector’
-    Suggested fix:
-      Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’)
-


=====================================
testsuite/tests/typecheck/should_compile/T22141b.stderr deleted
=====================================
@@ -1,9 +0,0 @@
-T22141b.hs:10:1: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)]
-    • An occurrence of ‘GHC.Internal.Bignum.Natural.Natural’ in a kind requires DataKinds.
-      Future versions of GHC will turn this warning into an error.
-    • In the expansion of type synonym ‘Nat’
-      In the expansion of type synonym ‘MyNat’
-      In the data type declaration for ‘Vector’
-    Suggested fix:
-      Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’)
-


=====================================
testsuite/tests/typecheck/should_compile/T22141c.stderr deleted
=====================================
@@ -1,37 +0,0 @@
-T22141c.hs:10:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)]
-    • An occurrence of ‘(# *, * #)’ in a kind requires DataKinds.
-      Future versions of GHC will turn this warning into an error.
-    • In the expansion of type synonym ‘T’
-      In a standalone kind signature for ‘D’: Proxy T -> Type
-    Suggested fix:
-      Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’)
-
-T22141c.hs:10:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)]
-    • An occurrence of ‘'[]’ in a kind requires DataKinds.
-      Future versions of GHC will turn this warning into an error.
-    • In a standalone kind signature for ‘D’: Proxy T -> Type
-    Suggested fix:
-      Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’)
-
-T22141c.hs:10:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)]
-    • An occurrence of ‘'[GHC.Internal.Types.LiftedRep]’ in a kind requires DataKinds.
-      Future versions of GHC will turn this warning into an error.
-    • In a standalone kind signature for ‘D’: Proxy T -> Type
-    Suggested fix:
-      Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’)
-
-T22141c.hs:10:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)]
-    • An occurrence of ‘[GHC.Internal.Types.LiftedRep,
-                         GHC.Internal.Types.LiftedRep]’ in a kind requires DataKinds.
-      Future versions of GHC will turn this warning into an error.
-    • In a standalone kind signature for ‘D’: Proxy T -> Type
-    Suggested fix:
-      Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’)
-
-T22141c.hs:10:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)]
-    • An occurrence of ‘Proxy T’ in a kind requires DataKinds.
-      Future versions of GHC will turn this warning into an error.
-    • In a standalone kind signature for ‘D’: Proxy T -> Type
-    Suggested fix:
-      Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’)
-


=====================================
testsuite/tests/typecheck/should_compile/T22141d.stderr deleted
=====================================
@@ -1,37 +0,0 @@
-T22141d.hs:10:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)]
-    • An occurrence of ‘(# * | * #)’ in a kind requires DataKinds.
-      Future versions of GHC will turn this warning into an error.
-    • In the expansion of type synonym ‘T’
-      In a standalone kind signature for ‘D’: Proxy T -> Type
-    Suggested fix:
-      Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’)
-
-T22141d.hs:10:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)]
-    • An occurrence of ‘'[]’ in a kind requires DataKinds.
-      Future versions of GHC will turn this warning into an error.
-    • In a standalone kind signature for ‘D’: Proxy T -> Type
-    Suggested fix:
-      Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’)
-
-T22141d.hs:10:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)]
-    • An occurrence of ‘'[GHC.Internal.Types.LiftedRep]’ in a kind requires DataKinds.
-      Future versions of GHC will turn this warning into an error.
-    • In a standalone kind signature for ‘D’: Proxy T -> Type
-    Suggested fix:
-      Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’)
-
-T22141d.hs:10:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)]
-    • An occurrence of ‘[GHC.Internal.Types.LiftedRep,
-                         GHC.Internal.Types.LiftedRep]’ in a kind requires DataKinds.
-      Future versions of GHC will turn this warning into an error.
-    • In a standalone kind signature for ‘D’: Proxy T -> Type
-    Suggested fix:
-      Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’)
-
-T22141d.hs:10:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)]
-    • An occurrence of ‘Proxy T’ in a kind requires DataKinds.
-      Future versions of GHC will turn this warning into an error.
-    • In a standalone kind signature for ‘D’: Proxy T -> Type
-    Suggested fix:
-      Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’)
-


=====================================
testsuite/tests/typecheck/should_compile/T22141e.stderr deleted
=====================================
@@ -1,22 +0,0 @@
-T22141e.hs:8:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)]
-    • An occurrence of ‘42’ in a kind requires DataKinds.
-      Future versions of GHC will turn this warning into an error.
-    • In the expansion of type synonym ‘T’
-      In a standalone kind signature for ‘D’: Proxy T -> Type
-    Suggested fix:
-      Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’)
-
-T22141e.hs:8:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)]
-    • An occurrence of ‘GHC.Internal.Bignum.Natural.Natural’ in a kind requires DataKinds.
-      Future versions of GHC will turn this warning into an error.
-    • In a standalone kind signature for ‘D’: Proxy T -> Type
-    Suggested fix:
-      Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’)
-
-T22141e.hs:8:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)]
-    • An occurrence of ‘Proxy T’ in a kind requires DataKinds.
-      Future versions of GHC will turn this warning into an error.
-    • In a standalone kind signature for ‘D’: Proxy T -> Type
-    Suggested fix:
-      Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’)
-


=====================================
testsuite/tests/typecheck/should_compile/all.T
=====================================
@@ -862,11 +862,6 @@ test('T21951a', normal, compile, ['-Wredundant-strictness-flags'])
 test('T21951b', normal, compile, ['-Wredundant-strictness-flags'])
 test('DataToTagSolving', normal, compile, [''])
 test('T21550', normal, compile, [''])
-test('T22141a', normal, compile, [''])
-test('T22141b', normal, compile, [''])
-test('T22141c', normal, compile, [''])
-test('T22141d', normal, compile, [''])
-test('T22141e', [extra_files(['T22141e_Aux.hs'])], multimod_compile, ['T22141e.hs', '-v0'])
 test('T22141f', normal, compile, [''])
 test('T22141g', normal, compile, [''])
 test('T22310', normal, compile, [''])


=====================================
testsuite/tests/typecheck/should_fail/T20873c.hs
=====================================
@@ -7,5 +7,8 @@ import Data.Kind ( Type )
 
 type U a = Type
 
-data Foo :: U Int where
+-- This should be allowed without enabling DataKinds, This is because the return
+-- kind only mentions Type, which is always permitted in kinds, and U, which is
+-- simply a type synonym that expands to Type.
+data Foo :: U Type where
   MkFoo :: Foo


=====================================
testsuite/tests/typecheck/should_fail/T20873c.stderr
=====================================
@@ -1,5 +1,5 @@
-T20873c.hs:10:1: error: [GHC-49378]
-    • Illegal kind signature ‘Foo :: U Int’
+T20873c.hs:13:1: error: [GHC-49378]
+    • Illegal kind signature ‘Foo :: U Type’
     • In the data type declaration for ‘Foo’
     Suggested fix:
       Perhaps you intended to use the ‘KindSignatures’ extension (implied by ‘TypeFamilies’ and ‘PolyKinds’)


=====================================
testsuite/tests/typecheck/should_compile/T22141a.hs → testsuite/tests/typecheck/should_fail/T22141a.hs
=====================================


=====================================
testsuite/tests/typecheck/should_fail/T22141a.stderr
=====================================
@@ -1,6 +1,7 @@
-
 T22141a.hs:8:1: error: [GHC-68567]
-    • Illegal kind: ‘GHC.Num.Natural.Natural’
+    • Illegal kind: ‘GHC.Internal.Bignum.Natural.Natural’
     • In the expansion of type synonym ‘Nat’
       In the data type declaration for ‘Vector’
-    Suggested fix: Perhaps you intended to use DataKinds
+    Suggested fix:
+      Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’)
+


=====================================
testsuite/tests/typecheck/should_compile/T22141b.hs → testsuite/tests/typecheck/should_fail/T22141b.hs
=====================================


=====================================
testsuite/tests/typecheck/should_fail/T22141b.stderr
=====================================
@@ -1,7 +1,8 @@
-
 T22141b.hs:10:1: error: [GHC-68567]
-    • Illegal kind: ‘GHC.Num.Natural.Natural’
+    • Illegal kind: ‘GHC.Internal.Bignum.Natural.Natural’
     • In the expansion of type synonym ‘Nat’
       In the expansion of type synonym ‘MyNat’
       In the data type declaration for ‘Vector’
-    Suggested fix: Perhaps you intended to use DataKinds
+    Suggested fix:
+      Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’)
+


=====================================
testsuite/tests/typecheck/should_compile/T22141c.hs → testsuite/tests/typecheck/should_fail/T22141c.hs
=====================================


=====================================
testsuite/tests/typecheck/should_fail/T22141c.stderr
=====================================
@@ -1,4 +1,6 @@
+T22141c.hs:10:11: error: [GHC-68567]
+    • Illegal kind: ‘Proxy T’
+    • In a standalone kind signature for ‘D’: Proxy T -> Type
+    Suggested fix:
+      Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’)
 
-T22141c.hs:8:17: error: [GHC-68567]
-    Illegal kind: ‘(# Type, Type #)’
-    Suggested fix: Perhaps you intended to use DataKinds


=====================================
testsuite/tests/typecheck/should_compile/T22141d.hs → testsuite/tests/typecheck/should_fail/T22141d.hs
=====================================


=====================================
testsuite/tests/typecheck/should_fail/T22141d.stderr
=====================================
@@ -1,4 +1,6 @@
+T22141d.hs:10:11: error: [GHC-68567]
+    • Illegal kind: ‘Proxy T’
+    • In a standalone kind signature for ‘D’: Proxy T -> Type
+    Suggested fix:
+      Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’)
 
-T22141d.hs:8:17: error: [GHC-68567]
-    Illegal kind: ‘(# Type | Type #)’
-    Suggested fix: Perhaps you intended to use DataKinds


=====================================
testsuite/tests/typecheck/should_compile/T22141e.hs → testsuite/tests/typecheck/should_fail/T22141e.hs
=====================================


=====================================
testsuite/tests/typecheck/should_fail/T22141e.stderr
=====================================
@@ -1,4 +1,6 @@
+T22141e.hs:8:11: error: [GHC-68567]
+    • Illegal kind: ‘Proxy T’
+    • In a standalone kind signature for ‘D’: Proxy T -> Type
+    Suggested fix:
+      Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’)
 
-T22141e.hs:7:17: error: [GHC-68567]
-    Illegal kind: ‘42’
-    Suggested fix: Perhaps you intended to use DataKinds


=====================================
testsuite/tests/typecheck/should_compile/T22141e_Aux.hs → testsuite/tests/typecheck/should_fail/T22141e_Aux.hs
=====================================


=====================================
testsuite/tests/typecheck/should_fail/all.T
=====================================
@@ -666,6 +666,11 @@ test('T21447', normal, compile_fail, [''])
 test('T21530a', normal, compile_fail, [''])
 test('T21530b', normal, compile_fail, [''])
 test('Or4', normal, compile_fail, [''])
+test('T22141a', normal, compile_fail, [''])
+test('T22141b', normal, compile_fail, [''])
+test('T22141c', normal, compile_fail, [''])
+test('T22141d', normal, compile_fail, [''])
+test('T22141e', [extra_files(['T22141e_Aux.hs'])], multimod_compile_fail, ['T22141e.hs', '-v0'])
 test('T22570', normal, compile_fail, [''])
 test('T22645', normal, compile_fail, [''])
 test('T20666', normal, compile_fail, [''])


=====================================
testsuite/tests/vdq-rta/should_fail/T23739_fail_case.hs
=====================================
@@ -1,3 +1,4 @@
+{-# LANGUAGE DataKinds #-}
 {-# LANGUAGE RequiredTypeArguments #-}
 
 module T23739_fail_case where


=====================================
testsuite/tests/vdq-rta/should_fail/T23739_fail_case.stderr
=====================================
@@ -1,7 +1,6 @@
-
-T23739_fail_case.hs:7:8: error: [GHC-01928]
+T23739_fail_case.hs:8:8: error: [GHC-01928]
     • Illegal term-level use of the type variable ‘t’
-    • bound at T23739_fail_case.hs:6:5
+    • bound at T23739_fail_case.hs:7:5
     • In the expression: t
       In the expression:
         case t of
@@ -12,3 +11,4 @@ T23739_fail_case.hs:7:8: error: [GHC-01928]
             = case t of
                 False -> "False"
                 True -> "True"
+



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6db8d60540aa68807cf82e7237e425de97ef143f
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/20250306/95f09859/attachment-0001.html>


More information about the ghc-commits mailing list