diff --git a/compiler/GHC/Driver/DynFlags.hs b/compiler/GHC/Driver/DynFlags.hs index 7bf3341b404e831facbad4f6d35efde540b287fc..a9e89ffac835debbd3f7834e96b728f87cfa1b8e 100644 --- a/compiler/GHC/Driver/DynFlags.hs +++ b/compiler/GHC/Driver/DynFlags.hs @@ -1413,7 +1413,6 @@ languageExtensions (Just GHC2021) LangExt.PostfixOperators, LangExt.RankNTypes, LangExt.ScopedTypeVariables, - LangExt.TypeAbstractions, -- implied by ScopedTypeVariables according to GHC Proposal #448 "Modern Scoped Type Variables" LangExt.StandaloneDeriving, LangExt.StandaloneKindSignatures, LangExt.TupleSections, diff --git a/compiler/GHC/Driver/Session.hs b/compiler/GHC/Driver/Session.hs index 0ed06940087ff8f5aa92acb4239c917b5911c5b0..8cc82e9fc5d5fa090205607b83f5695e69b70164 100644 --- a/compiler/GHC/Driver/Session.hs +++ b/compiler/GHC/Driver/Session.hs @@ -2797,9 +2797,6 @@ impliedXFlags , (LangExt.MultiParamTypeClasses, turnOn, LangExt.ConstrainedClassMethods) -- c.f. #7854 , (LangExt.TypeFamilyDependencies, turnOn, LangExt.TypeFamilies) - -- In accordance with GHC Proposal #448 "Modern Scoped Type Variables" - , (LangExt.ScopedTypeVariables, turnOn, LangExt.TypeAbstractions) - , (LangExt.RebindableSyntax, turnOff, LangExt.ImplicitPrelude) -- NB: turn off! , (LangExt.DerivingVia, turnOn, LangExt.DerivingStrategies) diff --git a/compiler/GHC/Rename/HsType.hs b/compiler/GHC/Rename/HsType.hs index f88bc1e7afd893a1d312878197c72a7702d8bf7e..83d7de121f889d394936633d65bb57821e2fc786 100644 --- a/compiler/GHC/Rename/HsType.hs +++ b/compiler/GHC/Rename/HsType.hs @@ -38,6 +38,7 @@ module GHC.Rename.HsType ( extractConDeclGADTDetailsTyVars, extractDataDefnKindVars, extractHsOuterTvBndrs, extractHsTyArgRdrKiTyVars, nubL, nubN, + -- Error helpers badKindSigErr ) where diff --git a/compiler/GHC/Rename/Pat.hs b/compiler/GHC/Rename/Pat.hs index 79900c349bc9e202346b310ca4ddebd107526dc9..331cfdd99789a84137560428424f431725f427d2 100644 --- a/compiler/GHC/Rename/Pat.hs +++ b/compiler/GHC/Rename/Pat.hs @@ -7,6 +7,7 @@ {-# LANGUAGE ViewPatterns #-} {-# LANGUAGE DisambiguateRecordFields #-} {-# LANGUAGE NamedFieldPuns #-} +{-# LANGUAGE MultiWayIf #-} {-# LANGUAGE DerivingStrategies #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} @@ -657,9 +658,26 @@ rnConPatAndThen mk con (PrefixCon tyargs pats) where check_lang_exts :: RnM () check_lang_exts = - unlessXOptM LangExt.TypeAbstractions $ - for_ (listToMaybe tyargs) $ \ arg -> - addErrTc $ TcRnTypeApplicationsDisabled (TypeApplicationInPattern arg) + for_ (listToMaybe tyargs) $ \ arg -> + do { type_abs <- xoptM LangExt.TypeAbstractions + ; type_app <- xoptM LangExt.TypeApplications + ; scoped_tvs <- xoptM LangExt.ScopedTypeVariables + ; if | type_abs + -> return () + + -- As per [GHC Proposal 604](https://github.com/ghc-proposals/ghc-proposals/pull/604/), + -- we allow type applications in constructor patterns when -XTypeApplications and + -- -XScopedTypeVariables are both enabled, but we emit a warning when doing so. + -- + -- This warning is scheduled to become an error in GHC 9.12, in + -- which case we will get the usual error (below), + -- which suggests enabling -XTypeAbstractions. + | type_app && scoped_tvs + -> addDiagnostic TcRnDeprecatedInvisTyArgInConPat + + | otherwise + -> addErrTc $ TcRnTypeApplicationsDisabled (TypeApplicationInPattern arg) + } rnConPatTyArg (HsConPatTyArg at t) = do t' <- rnHsTyPat HsTypePatCtx t diff --git a/compiler/GHC/Tc/Errors/Ppr.hs b/compiler/GHC/Tc/Errors/Ppr.hs index 5080f4675ef177f207436d6ac404cc42aff0cf3d..fd36158ba4d5cdd085ae926a8bfaec6e0a431d9d 100644 --- a/compiler/GHC/Tc/Errors/Ppr.hs +++ b/compiler/GHC/Tc/Errors/Ppr.hs @@ -1845,6 +1845,11 @@ instance Diagnostic TcRnMessage where text "whereas" <+> quotes (text "forall {a}.") <+> text "and" <+> quotes (text "forall a ->") <+> text "do not." ]] + TcRnDeprecatedInvisTyArgInConPat -> + mkSimpleDecorated $ + cat [ text "Type applications in constructor patterns will require" + , text "the TypeAbstractions extension starting from GHC 9.12." ] + TcRnInvisBndrWithoutSig _ hs_bndr -> mkSimpleDecorated $ vcat [ hang (text "Invalid invisible type variable binder:") @@ -2446,6 +2451,8 @@ instance Diagnostic TcRnMessage where -> WarningWithFlag Opt_WarnMissingRoleAnnotations TcRnIllegalInvisTyVarBndr{} -> ErrorWithoutFlag + TcRnDeprecatedInvisTyArgInConPat {} + -> WarningWithoutFlag TcRnInvalidInvisTyVarBndr{} -> ErrorWithoutFlag TcRnInvisBndrWithoutSig{} @@ -3100,6 +3107,8 @@ instance Diagnostic TcRnMessage where -> noHints TcRnIllegalInvisTyVarBndr{} -> [suggestExtension LangExt.TypeAbstractions] + TcRnDeprecatedInvisTyArgInConPat{} + -> [suggestExtension LangExt.TypeAbstractions] TcRnInvalidInvisTyVarBndr{} -> noHints TcRnInvisBndrWithoutSig name _ diff --git a/compiler/GHC/Tc/Errors/Types.hs b/compiler/GHC/Tc/Errors/Types.hs index 588dca81e8c611677a22fabd4c0ad896e5244e7e..e19cab0834349b92c764bfea7f121da178e07038 100644 --- a/compiler/GHC/Tc/Errors/Types.hs +++ b/compiler/GHC/Tc/Errors/Types.hs @@ -3067,6 +3067,15 @@ data TcRnMessage where -> !(LHsTyVarBndr (HsBndrVis GhcRn) GhcRn) -> TcRnMessage + {-| TcRnDeprecatedInvisTyArgInConPat is a warning that triggers on type applications + in constructor patterns when the user has not enabled '-XTypeAbstractions' + but instead has enabled both '-XScopedTypeVariables' and '-XTypeApplications'. + + This warning is a deprecation mechanism that is scheduled until GHC 9.12. + -} + TcRnDeprecatedInvisTyArgInConPat + :: TcRnMessage + {-| TcRnLoopySuperclassSolve is a warning, controlled by @-Wloopy-superclass-solve@, that is triggered when GHC solves a constraint in a possibly-loopy way, violating the class instance termination rules described in the section diff --git a/compiler/GHC/Types/Error/Codes.hs b/compiler/GHC/Types/Error/Codes.hs index c71d69e9f26f616e9ea7bdfb3f36a390470ac24d..9ea1a158dc3bb68c846605db97d91d55f351a871 100644 --- a/compiler/GHC/Types/Error/Codes.hs +++ b/compiler/GHC/Types/Error/Codes.hs @@ -594,6 +594,7 @@ type family GhcDiagnosticCode c = n | n -> c where GhcDiagnosticCode "TcRnImplicitRhsQuantification" = 16382 GhcDiagnosticCode "TcRnBadTyConTelescope" = 87279 GhcDiagnosticCode "TcRnPatersonCondFailure" = 22979 + GhcDiagnosticCode "TcRnDeprecatedInvisTyArgInConPat" = 69797 -- TcRnTypeApplicationsDisabled GhcDiagnosticCode "TypeApplication" = 23482 diff --git a/testsuite/tests/typecheck/should_fail/T23776.hs b/testsuite/tests/typecheck/should_fail/T23776.hs new file mode 100644 index 0000000000000000000000000000000000000000..29d02ff43a10392730e8946a39d4f44695cffc00 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T23776.hs @@ -0,0 +1,9 @@ +{-# LANGUAGE GHC2021 #-} + +module T23776 where + +import Data.Kind + +foo :: Maybe a -> Maybe a +foo (Just @b x) = Just @b x +foo _ = Nothing diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index 406fffb6ab3311febf875aca15150fc7300fe6b7..5cef546ad5d4b3a77ef162ce94f7ae5214964851 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -699,3 +699,4 @@ test('VisFlag5', normal, compile_fail, ['']) test('T22684', normal, compile_fail, ['']) test('T23514a', normal, compile_fail, ['']) test('T22478c', normal, compile_fail, ['']) +test('T23776', normal, compile, ['']) # to become an error in GHC 9.12