[Git][ghc/ghc][wip/int-index/deprecated-type-abstractions] Add name for -Wdeprecated-type-abstractions (#24154)

Vladislav Zavialov (@int-index) gitlab at gitlab.haskell.org
Thu Nov 23 12:38:49 UTC 2023



Vladislav Zavialov pushed to branch wip/int-index/deprecated-type-abstractions at Glasgow Haskell Compiler / GHC


Commits:
8b934c7e by Vladislav Zavialov at 2023-11-23T15:38:32+03:00
Add name for -Wdeprecated-type-abstractions (#24154)

This warning had no name or flag and was triggered unconditionally.
Now it is part of -Wcompat.

- - - - -


8 changed files:

- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Rename/Pat.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- docs/users_guide/9.10.1-notes.rst
- docs/users_guide/using-warnings.rst
- testsuite/tests/typecheck/should_fail/T23776.stderr
- testsuite/tests/typecheck/should_fail/all.T


Changes:

=====================================
compiler/GHC/Driver/Flags.hs
=====================================
@@ -697,6 +697,7 @@ data WarningFlag =
    | Opt_WarnBadlyStagedTypes                        -- Since 9.10
    | Opt_WarnInconsistentFlags                       -- Since 9.8
    | Opt_WarnDataKindsTC                             -- Since 9.10
+   | Opt_WarnDeprecatedTypeAbstractions              -- Since 9.10
    deriving (Eq, Ord, Show, Enum, Bounded)
 
 -- | Return the names of a WarningFlag
@@ -811,6 +812,7 @@ warnFlagNames wflag = case wflag of
   Opt_WarnBadlyStagedTypes                        -> "badly-staged-types" :| []
   Opt_WarnInconsistentFlags                       -> "inconsistent-flags" :| []
   Opt_WarnDataKindsTC                             -> "data-kinds-tc" :| []
+  Opt_WarnDeprecatedTypeAbstractions              -> "deprecated-type-abstractions" :| []
 
 -- -----------------------------------------------------------------------------
 -- Standard sets of warning options
@@ -1007,6 +1009,7 @@ minusWcompatOpts
       , Opt_WarnCompatUnqualifiedImports
       , Opt_WarnTypeEqualityOutOfScope
       , Opt_WarnImplicitRhsQuantification
+      , Opt_WarnDeprecatedTypeAbstractions
       ]
 
 -- | Things you get with -Wunused-binds


=====================================
compiler/GHC/Driver/Session.hs
=====================================
@@ -2285,6 +2285,7 @@ wWarningFlagsDeps = [minBound..maxBound] >>= \x -> case x of
   Opt_WarnIncompleteExportWarnings -> warnSpec x
   Opt_WarnIncompleteRecordSelectors -> warnSpec x
   Opt_WarnDataKindsTC -> warnSpec x
+  Opt_WarnDeprecatedTypeAbstractions -> warnSpec x
 
 warningGroupsDeps :: [(Deprecation, FlagSpec WarningGroup)]
 warningGroupsDeps = map mk warningGroups


=====================================
compiler/GHC/Rename/Pat.hs
=====================================
@@ -663,21 +663,10 @@ rnConPatAndThen mk con (PrefixCon tyargs pats)
         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)
+           -- See Note [Deprecated type abstractions in constructor patterns]
+           ; if | type_abs -> return ()
+                | type_app && scoped_tvs -> addDiagnostic TcRnDeprecatedInvisTyArgInConPat
+                | otherwise -> addErrTc $ TcRnTypeApplicationsDisabled (TypeApplicationInPattern arg)
            }
 
     rnConPatTyArg (HsConPatTyArg at t) = do
@@ -701,6 +690,29 @@ rnConPatAndThen mk con (RecCon rpats)
             }
         }
 
+{- Note [Deprecated type abstractions in constructor patterns]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+Type abstractions in constructor patterns allow the user to bind
+existential type variables:
+
+    import Type.Reflection (Typeable, typeRep)
+    data Ex = forall e. (Typeable e, Show e) => MkEx e
+    showEx (MkEx @e a) = show a ++ " :: " ++ show (typeRep @e)
+
+Note the pattern `MkEx @e a`, and specifically the `@e` binder.
+
+For historical reasons, using this feature only required TypeApplications
+and ScopedTypeVariables to be enabled. As per GHC Proposal #448 (and especially
+its amendment #604) we are now transitioning towards guarding this feature
+behind TypeAbstractions instead.
+
+As a compatibility measure, we continue to support old programs that use
+TypeApplications with ScopedTypeVariables instead of TypeAbstractions,
+but emit the appropriate compatibility warning, -Wdeprecated-type-abstractions.
+This warning is scheduled to become an error in GHC 9.14, at which point
+we can simply require TypeAbstractions.
+-}
+
 checkUnusedRecordWildcardCps :: SrcSpan
                              -> Maybe [ImplicitFieldBinders]
                              -> CpsRn ()


=====================================
compiler/GHC/Tc/Errors/Ppr.hs
=====================================
@@ -1877,7 +1877,7 @@ instance Diagnostic TcRnMessage where
     TcRnDeprecatedInvisTyArgInConPat ->
       mkSimpleDecorated $
         cat [ text "Type applications in constructor patterns will require"
-            , text "the TypeAbstractions extension starting from GHC 9.12." ]
+            , text "the TypeAbstractions extension starting from GHC 9.14." ]
 
     TcRnInvisBndrWithoutSig _ hs_bndr ->
       mkSimpleDecorated $
@@ -2516,7 +2516,7 @@ instance Diagnostic TcRnMessage where
     TcRnIllegalInvisTyVarBndr{}
       -> ErrorWithoutFlag
     TcRnDeprecatedInvisTyArgInConPat {}
-      -> WarningWithoutFlag
+      -> WarningWithFlag Opt_WarnDeprecatedTypeAbstractions
     TcRnInvalidInvisTyVarBndr{}
       -> ErrorWithoutFlag
     TcRnInvisBndrWithoutSig{}


=====================================
docs/users_guide/9.10.1-notes.rst
=====================================
@@ -73,6 +73,10 @@ Compiler
 - Defaulting plugins can now propose solutions to entangled sets of type variables. This allows defaulting
   of multi-parameter type classes. See :ghc-ticket:`23832`.
 
+- Type abstractions in constructor patterns that were previously admitted without enabling the :extension:`TypeAbstractions`
+  extension now trigger a warning, :ghc-flag:`-Wdeprecated-type-abstractions`.
+  This new warning is part of the :ghc-flag:`-Wcompat` warning group and will become an error in a future GHC release.
+
 GHCi
 ~~~~
 


=====================================
docs/users_guide/using-warnings.rst
=====================================
@@ -171,6 +171,7 @@ as ``-Wno-...`` for every individual warning in the group.
         * :ghc-flag:`-Wcompat-unqualified-imports`
         * :ghc-flag:`-Wtype-equality-out-of-scope`
         * :ghc-flag:`-Wimplicit-rhs-quantification`
+        * :ghc-flag:`-Wdeprecated-type-abstractions`
 
 .. ghc-flag:: -w
     :shortdesc: disable all warnings
@@ -2504,6 +2505,36 @@ of ``-W(no-)*``.
 
     This warning detects code that will be affected by this breaking change.
 
+.. ghc-flag:: -Wdeprecated-type-abstractions
+    :shortdesc: warn when type abstractions in constructor patterns are used without enabling :extension:`TypeApplications`
+    :type: dynamic
+    :reverse: -Wno-deprecated-type-abstractions
+    :category:
+
+    :since: 9.10.1
+    :default: off
+
+    Type abstractions in constructor patterns allow binding existential type variables: ::
+
+      import Type.Reflection (Typeable, typeRep)
+      data Ex = forall e. (Typeable e, Show e) => MkEx e
+      showEx (MkEx @e a) = show a ++ " :: " ++ show (typeRep @e)
+
+    Note the pattern ``MkEx @e a``, and specifically the ``@e`` binder.
+
+    Support for this feature was added to GHC in version 9.2, but instead of getting
+    its own language extension the feature was enabled by a combination of
+    :extension:`TypeApplications` and :extension:`ScopedTypeVariables`.
+    As per `GHC Proposal #448
+    <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0448-type-variable-scoping.rst>`__
+    and its amendment `#604 <https://github.com/ghc-proposals/ghc-proposals/pull/604>`__
+    we are now transitioning towards guarding this feature behind :extension:`TypeAbstractions` instead.
+
+    As a compatibility measure, GHC continues to support old programs that use type abstractions
+    in constructor patterns without enabling the appropriate extension :extension:`TypeAbstractions`,
+    but it will stop doing so in a future release.
+
+    This warning detects code that will be affected by this breaking change.
 
 .. ghc-flag:: -Wincomplete-export-warnings
     :shortdesc: warn when some but not all of exports for a name are warned about


=====================================
testsuite/tests/typecheck/should_fail/T23776.stderr
=====================================
@@ -1,5 +1,5 @@
 
-T23776.hs:8:6: warning: [GHC-69797]
+T23776.hs:8:6: error: [GHC-69797] [-Wdeprecated-type-abstractions (in -Wcompat), Werror=deprecated-type-abstractions]
     Type applications in constructor patterns will require
-    the TypeAbstractions extension starting from GHC 9.12.
+    the TypeAbstractions extension starting from GHC 9.14.
     Suggested fix: Perhaps you intended to use TypeAbstractions


=====================================
testsuite/tests/typecheck/should_fail/all.T
=====================================
@@ -703,7 +703,7 @@ 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
+test('T23776', normal, compile_fail, ['']) # error due to -Werror=compat, scheduled to become an actual error in GHC 9.14
 test('T17940', normal, compile_fail, [''])
 test('ErrorIndexLinks', normal, compile_fail, ['-fprint-error-index-links=always'])
 test('T24064', normal, compile_fail, [''])



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8b934c7eff9b5e4dbd7abbb42e7a5d89ab21f721
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/20231123/8a0cb016/attachment-0001.html>


More information about the ghc-commits mailing list