[Git][ghc/ghc][master] Deprecate -Wdata-kinds-tc, make DataKinds issues in typechecker become errors

Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: d3e60e97 by Ryan Scott at 2025-06-18T22:29:21-04:00 Deprecate -Wdata-kinds-tc, 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 deprecates `-Wdata-kinds-tc` and upgrades any `DataKinds`-related issues in the typechecker (which were previously warnings) into errors. - - - - - 30 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/T20873c.hs - − 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 ===================================== @@ -1364,7 +1364,6 @@ standardWarnings -- see Note [Documenting warning flags] Opt_WarnBadlyLevelledTypes, Opt_WarnTypeEqualityRequiresOperators, Opt_WarnInconsistentFlags, - Opt_WarnDataKindsTC, Opt_WarnTypeEqualityOutOfScope, Opt_WarnImplicitRhsQuantification, -- was in -Wcompat since 9.8, enabled by default since 9.14, to turn into a hard error in 9.16 Opt_WarnViewPatternSignatures, ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -2382,7 +2382,8 @@ wWarningFlagsDeps = [minBound..maxBound] >>= \x -> case x of Opt_WarnImplicitRhsQuantification -> warnSpec x Opt_WarnIncompleteExportWarnings -> warnSpec x Opt_WarnIncompleteRecordSelectors -> warnSpec x - Opt_WarnDataKindsTC -> warnSpec x + Opt_WarnDataKindsTC + -> depWarnSpec x "DataKinds violations are now always an error" Opt_WarnDefaultedExceptionContext -> warnSpec x Opt_WarnViewPatternSignatures -> warnSpec x Opt_WarnUselessSpecialisations -> warnSpec x ===================================== compiler/GHC/Tc/Errors/Ppr.hs ===================================== @@ -1750,21 +1750,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 $ @@ -2567,17 +2561,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 ===================================== @@ -2553,11 +2553,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 ===================================== @@ -1001,18 +1001,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] @@ -1164,28 +1157,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 ===================================== @@ -70,6 +70,21 @@ Language * The :extension:`ExplicitNamespaces` extension now allows the ``data`` namespace specifier in import and export lists. +* The ``-Wdata-kinds-tc`` warning has been deprecated, 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`.) + * The :extension:`MonadComprehensions` extension now implies :extension:`ParallelListComp` as was originally intended (see `Monad Comprehensions https://ghc.gitlab.haskell.org/ghc/doc/users_guide/exts/monad_comprehensions...`_). 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:`-Wimplicit-rhs-quantification` * :ghc-flag:`-Wunusable-unpack-pragmas` @@ -2601,24 +2600,19 @@ of ``-W(no-)*``. 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 + :shortdesc: *(deprecated)* Does nothing :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). + This warning is deprecated. It no longer has any effect since GHC 9.14. + + In the past, GHC 9.10 and 9.12 was overly permissive about which types or + kinds could be used without enabling the :extension:`DataKinds` extension. + In GHC 9.14 or later, however, GHC now consistently requires + :extension:`DataKinds`, and all :extension:`DataKinds` violations are now + errors. :ghc-flag:`-Wdata-kinds-tc` was used in the migration period before + the breaking change took place. .. ghc-flag:: -Wdefaulted-exception-context :shortdesc: warn when an :base-ref:`Control.Exception.Context.ExceptionContext` ===================================== testsuite/tests/typecheck/should_compile/T20873c.hs ===================================== @@ -0,0 +1,14 @@ + +{-# LANGUAGE GADTSyntax, KindSignatures, NoDataKinds #-} + +module T20873c where + +import Data.Kind ( Type ) + +type U a = Type + +-- 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_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 ===================================== @@ -819,6 +819,7 @@ test('T20588d', [extra_files(['T20588d.hs', 'T20588d.hs-boot', 'T20588d_aux.hs'] test('T20661', [extra_files(['T20661.hs', 'T20661.hs-boot', 'T20661_aux.hs'])], multimod_compile, ['T20661_aux.hs', '-v0']) test('T20873', normal, compile, ['']) test('T20873b', [extra_files(['T20873b_aux.hs'])], multimod_compile, ['T20873b', '-v0']) +test('T20873c', normal, compile, ['']) test('StaticPtrTypeFamily', normal, compile, ['']) test('T20946', normal, compile, ['']) test('T20996', normal, compile, ['']) @@ -864,11 +865,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 deleted ===================================== @@ -1,11 +0,0 @@ - -{-# LANGUAGE GADTSyntax, NoKindSignatures, NoDataKinds #-} - -module T20873c where - -import Data.Kind ( Type ) - -type U a = Type - -data Foo :: U Int where - MkFoo :: Foo ===================================== testsuite/tests/typecheck/should_fail/T20873c.stderr deleted ===================================== @@ -1,6 +0,0 @@ -T20873c.hs:10:1: error: [GHC-49378] - • Illegal kind signature ‘Foo :: U Int’ - • 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 ===================================== @@ -646,7 +646,6 @@ test('T20542', normal, compile_fail, ['']) test('T20588', [extra_files(['T20588.hs', 'T20588.hs-boot', 'T20588_aux.hs'])], multimod_compile_fail, ['T20588_aux.hs', '-v0']) 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, ['']) @@ -667,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 @@ -6,4 +7,4 @@ bad :: forall (b :: Bool) -> String bad t = case t of False -> "False" - True -> "True" \ No newline at end of file + True -> "True" ===================================== 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/d3e60e97d0afa2ad3a1e4d2e9fa64542... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d3e60e97d0afa2ad3a1e4d2e9fa64542... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Marge Bot (@marge-bot)