[Git][ghc/ghc][master] Hide WARNING/DEPRECATED namespacing under -XExplicitNamespaces (#24396)

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Mon Feb 5 22:59:47 UTC 2024



Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
ce90f12f by Andrei Borzenkov at 2024-02-05T17:59:09-05:00
Hide WARNING/DEPRECATED namespacing under -XExplicitNamespaces (#24396)

- - - - -


12 changed files:

- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Rename/Module.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Types/Error/Codes.hs
- docs/users_guide/9.10.1-notes.rst
- docs/users_guide/exts/pragmas.rst
- libraries/ghc-prim/GHC/Tuple.hs
- testsuite/tests/warnings/should_compile/T24396a.hs
- + testsuite/tests/warnings/should_fail/T24396c.hs
- + testsuite/tests/warnings/should_fail/T24396c.stderr
- testsuite/tests/warnings/should_fail/all.T


Changes:

=====================================
compiler/GHC/Hs/Decls.hs
=====================================
@@ -1288,7 +1288,7 @@ data NamespaceSpecifier
   = NoNamespaceSpecifier
   | TypeNamespaceSpecifier (EpToken "type")
   | DataNamespaceSpecifier (EpToken "data")
-  deriving (Data)
+  deriving (Eq, Data)
 
 overlappingNamespaceSpecifiers :: NamespaceSpecifier -> NamespaceSpecifier -> Bool
 overlappingNamespaceSpecifiers NoNamespaceSpecifier _ = True


=====================================
compiler/GHC/Rename/Module.hs
=====================================
@@ -283,10 +283,13 @@ rnSrcWarnDecls bndr_set decls'
 
    sig_ctxt = TopSigCtxt bndr_set
 
-   rn_deprec (Warning (ns_spec, _) rdr_names txt)
+   rn_deprec w@(Warning (ns_spec, _) rdr_names txt)
        -- ensures that the names are defined locally
      = do { names <- concatMapM (lookupLocalTcNames sig_ctxt what ns_spec . unLoc)
                                 rdr_names
+          ; unlessXOptM LangExt.ExplicitNamespaces $
+            when (ns_spec /= NoNamespaceSpecifier) $
+            addErr (TcRnNamespacedWarningPragmaWithoutFlag w)
           ; txt' <- rnWarningTxt txt
           ; return [(nameOccName nm, txt') | (_, nm) <- names] }
   -- Use the OccName from the Name we looked up, rather than from the RdrName,


=====================================
compiler/GHC/Tc/Errors/Ppr.hs
=====================================
@@ -1889,6 +1889,17 @@ instance Diagnostic TcRnMessage where
             | otherwise
             = text "they are not unfilled metavariables"
 
+    TcRnNamespacedWarningPragmaWithoutFlag warning@(Warning (kw, _) _ txt) -> mkSimpleDecorated $
+      vcat [ text "Illegal use of the" <+> quotes (ppr kw) <+> text "keyword:"
+           , nest 2 (ppr warning)
+           , text "in a" <+> pragma_type <+> text "pragma"
+           ]
+      where
+        pragma_type = case txt of
+          WarningTxt{} -> text "WARNING"
+          DeprecatedTxt{} -> text "DEPRECATED"
+
+  diagnosticReason :: TcRnMessage -> DiagnosticReason
   diagnosticReason = \case
     TcRnUnknownMessage m
       -> diagnosticReason m
@@ -2512,6 +2523,8 @@ instance Diagnostic TcRnMessage where
       -> ErrorWithoutFlag
     TcRnInvalidDefaultedTyVar{}
       -> ErrorWithoutFlag
+    TcRnNamespacedWarningPragmaWithoutFlag{}
+      -> ErrorWithoutFlag
 
   diagnosticHints = \case
     TcRnUnknownMessage m
@@ -3170,6 +3183,8 @@ instance Diagnostic TcRnMessage where
       -> noHints
     TcRnInvalidDefaultedTyVar{}
       -> noHints
+    TcRnNamespacedWarningPragmaWithoutFlag{}
+      -> [suggestExtension LangExt.ExplicitNamespaces]
 
   diagnosticCode = constructorCode
 


=====================================
compiler/GHC/Tc/Errors/Types.hs
=====================================
@@ -4205,6 +4205,13 @@ data TcRnMessage where
       -> NE.NonEmpty TcTyVar  -- ^ The invalid type variables of the proposal
       -> TcRnMessage
 
+  {-| TcRnNamespacedWarningPragmaWithoutFlag is an error that occurs when
+      a namespace specifier is used in {-# WARNING ... #-} or {-# DEPRECATED ... #-}
+      pragmas without the -XExplicitNamespaces extension enabled
+
+  -}
+  TcRnNamespacedWarningPragmaWithoutFlag :: WarnDecl GhcPs -> TcRnMessage
+
   deriving Generic
 
 


=====================================
compiler/GHC/Types/Error/Codes.hs
=====================================
@@ -600,6 +600,7 @@ type family GhcDiagnosticCode c = n | n -> c where
   GhcDiagnosticCode "TcRnDeprecatedInvisTyArgInConPat"              = 69797
   GhcDiagnosticCode "TcRnInvalidDefaultedTyVar"                     = 45625
   GhcDiagnosticCode "TcRnIllegalTermLevelUse"                       = 01928
+  GhcDiagnosticCode "TcRnNamespacedWarningPragmaWithoutFlag"        = 14995
 
   -- TcRnTypeApplicationsDisabled
   GhcDiagnosticCode "TypeApplication"                               = 23482


=====================================
docs/users_guide/9.10.1-notes.rst
=====================================
@@ -75,9 +75,10 @@ Language
 
 - GHC Proposal `#65 <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0065-type-infix.rst>`_
   "Require namespacing fixity declarations for type names and WARNING/DEPRECATED pragmas" has been partially implemented.
-  Now you can specify namespace of a name that you want to warn about or deprecate: ::
+  Now, with :extension:`ExplicitNamespaces` enabled, you can specify the
+  namespace of a name that you want to warn about or deprecate: ::
 
-    {-# DEPRACATED type D "Use `()` instead" #-} -- this will deprecate type D, but will not touch pattern synonym
+    {-# DEPRECATED type D "Use `()` instead" #-} -- this will deprecate type D, but will not touch pattern synonym
     data D = MkD
 
     {-# DEPRECATED data D "Use `MkD` instead" #-} -- this will deprecate pattern synonym only


=====================================
docs/users_guide/exts/pragmas.rst
=====================================
@@ -251,7 +251,8 @@ When a deprecated name appears in both value and type namespaces (i.e. punning o
     {-# DEPRECATED D "This will deprecate both the type D and the pattern synonym D" #-}
 
 It is possible to specify the namespace of the name to be warned about
-or deprecated using ``type`` and ``data`` specifiers: ::
+or deprecated using ``type`` and ``data`` specifiers, but this feature
+requires enabling :extension:`ExplicitNamespaces`: ::
 
     {-# LANGUAGE PatternSynonyms #-}
 


=====================================
libraries/ghc-prim/GHC/Tuple.hs
=====================================
@@ -1,5 +1,5 @@
 {-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE NoImplicitPrelude, PatternSynonyms #-}
+{-# LANGUAGE NoImplicitPrelude, PatternSynonyms, ExplicitNamespaces #-}
 -----------------------------------------------------------------------------
 -- |
 -- Module      :  GHC.Tuple


=====================================
testsuite/tests/warnings/should_compile/T24396a.hs
=====================================
@@ -1,3 +1,5 @@
+{-# LANGUAGE ExplicitNamespaces #-}
+
 module T24396a where
 
 class C1


=====================================
testsuite/tests/warnings/should_fail/T24396c.hs
=====================================
@@ -0,0 +1,20 @@
+
+module T24396c where
+
+
+f = id
+
+{-# WARNING data f "warning on data level" #-}
+
+data F
+
+{-# WARNING type F "warning on type level" #-}
+
+
+g = id
+
+{-# DEPRECATED data g "deprecation on data level" #-}
+
+data G
+
+{-# DEPRECATED type G "deprecation on type level" #-}


=====================================
testsuite/tests/warnings/should_fail/T24396c.stderr
=====================================
@@ -0,0 +1,24 @@
+
+T24396c.hs:7:13: error: [GHC-14995]
+    Illegal use of the ‘data’ keyword:
+      data f "warning on data level"
+    in a WARNING pragma
+    Suggested fix: Perhaps you intended to use ExplicitNamespaces
+
+T24396c.hs:11:13: error: [GHC-14995]
+    Illegal use of the ‘type’ keyword:
+      type F "warning on type level"
+    in a WARNING pragma
+    Suggested fix: Perhaps you intended to use ExplicitNamespaces
+
+T24396c.hs:16:16: error: [GHC-14995]
+    Illegal use of the ‘data’ keyword:
+      data g "deprecation on data level"
+    in a DEPRECATED pragma
+    Suggested fix: Perhaps you intended to use ExplicitNamespaces
+
+T24396c.hs:20:16: error: [GHC-14995]
+    Illegal use of the ‘type’ keyword:
+      type G "deprecation on type level"
+    in a DEPRECATED pragma
+    Suggested fix: Perhaps you intended to use ExplicitNamespaces


=====================================
testsuite/tests/warnings/should_fail/all.T
=====================================
@@ -26,3 +26,4 @@ test('WarningCategory5', [extra_files(['WarningCategory1.hs', 'WarningCategory1_
 test('WarningCategory6', [extra_files(['WarningCategory1.hs', 'WarningCategory1_B.hs', 'WarningCategoryModule.hs'])], multimod_compile_fail, ['WarningCategory1', '-v0 -Wno-extended-warnings -Wdeprecations -Werror=warnings-deprecations'])
 test('WarningCategory7', [extra_files(['WarningCategory1.hs', 'WarningCategory1_B.hs', 'WarningCategoryModule.hs'])], multimod_compile_fail, ['WarningCategory1', '-v0 -Werror -w -Wall'])
 test('WarningCategoryInvalid', normal, compile_fail, [''])
+test('T24396c', normal, compile_fail, [''])



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ce90f12f53dca5c55e87158d60529340a75851d2
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/20240205/12e95601/attachment-0001.html>


More information about the ghc-commits mailing list