recursion-ninja pushed to branch wip/fix-26636 at Glasgow Haskell Compiler / GHC

Commits:

21 changed files:

Changes:

  • compiler/GHC/Builtin/Utils.hs
    ... ... @@ -79,6 +79,7 @@ import GHC.Utils.Panic
    79 79
     import GHC.Utils.Constants (debugIsOn)
    
    80 80
     import GHC.Parser.Annotation
    
    81 81
     import GHC.Hs.Doc
    
    82
    +import GHC.Hs.Extension (GhcPass)
    
    82 83
     import GHC.Unit.Module.ModIface (IfaceExport)
    
    83 84
     import GHC.Unit.Module.Warnings
    
    84 85
     
    
    ... ... @@ -263,7 +264,7 @@ ghcPrimNames
    263 264
         ]
    
    264 265
     
    
    265 266
     -- See Note [GHC.Prim Deprecations]
    
    266
    -ghcPrimWarns :: Warnings a
    
    267
    +ghcPrimWarns :: Warnings (GhcPass p)
    
    267 268
     ghcPrimWarns = WarnSome
    
    268 269
       -- declaration warnings
    
    269 270
       (map mk_decl_dep primOpDeprecations)
    

  • compiler/GHC/Hs/Decls.hs
    ... ... @@ -1391,7 +1391,6 @@ type instance XXWarnDecls (GhcPass _) = DataConCantHappen
    1391 1391
     type instance XWarning      (GhcPass _) = (NamespaceSpecifier, (EpToken "[", EpToken "]"))
    
    1392 1392
     type instance XXWarnDecl    (GhcPass _) = DataConCantHappen
    
    1393 1393
     
    
    1394
    -
    
    1395 1394
     instance OutputableBndrId p
    
    1396 1395
             => Outputable (WarnDecls (GhcPass p)) where
    
    1397 1396
         ppr (Warnings ext decls)
    
    ... ... @@ -1411,7 +1410,7 @@ instance OutputableBndrId p
    1411 1410
                   <+> ppr txt
    
    1412 1411
           where
    
    1413 1412
             ppr_category = case txt of
    
    1414
    -                         WarningTxt (Just cat) _ _ -> ppr cat
    
    1413
    +                         WarningTxt _ (Just cat) _ -> ppr cat
    
    1415 1414
                              _ -> empty
    
    1416 1415
     
    
    1417 1416
     {-
    

  • compiler/GHC/Hs/Instances.hs
    ... ... @@ -35,6 +35,7 @@ import GHC.Hs.ImpExp
    35 35
     import GHC.Parser.Annotation
    
    36 36
     import GHC.Types.Name.Reader (WithUserRdr(..))
    
    37 37
     import GHC.Data.BooleanFormula (BooleanFormula(..))
    
    38
    +import Language.Haskell.Syntax.Decls
    
    38 39
     import Language.Haskell.Syntax.Extension (Anno)
    
    39 40
     
    
    40 41
     -- ---------------------------------------------------------------------
    
    ... ... @@ -276,6 +277,14 @@ deriving instance Data (WarnDecl GhcPs)
    276 277
     deriving instance Data (WarnDecl GhcRn)
    
    277 278
     deriving instance Data (WarnDecl GhcTc)
    
    278 279
     
    
    280
    +deriving instance Data (WarningTxt GhcPs)
    
    281
    +deriving instance Data (WarningTxt GhcRn)
    
    282
    +deriving instance Data (WarningTxt GhcTc)
    
    283
    +
    
    284
    +deriving instance Data (InWarningCategory GhcPs)
    
    285
    +deriving instance Data (InWarningCategory GhcRn)
    
    286
    +deriving instance Data (InWarningCategory GhcTc)
    
    287
    +
    
    279 288
     -- deriving instance (DataIdLR p p) => Data (AnnDecl p)
    
    280 289
     deriving instance Data (AnnProvenance GhcPs)
    
    281 290
     deriving instance Data (AnnProvenance GhcRn)
    

  • compiler/GHC/Iface/Syntax.hs
    ... ... @@ -424,8 +424,8 @@ data IfaceWarnings
    424 424
                    [(IfExtName, IfaceWarningTxt)]
    
    425 425
     
    
    426 426
     data IfaceWarningTxt
    
    427
    -  = IfWarningTxt (Maybe WarningCategory) SourceText [(IfaceStringLiteral, [IfExtName])]
    
    428
    -  | IfDeprecatedTxt                      SourceText [(IfaceStringLiteral, [IfExtName])]
    
    427
    +  = IfWarningTxt    SourceText (Maybe WarningCategory) [(IfaceStringLiteral, [IfExtName])]
    
    428
    +  | IfDeprecatedTxt SourceText [(IfaceStringLiteral, [IfExtName])]
    
    429 429
     
    
    430 430
     data IfaceStringLiteral
    
    431 431
       = IfStringLiteral SourceText FastString
    
    ... ... @@ -664,7 +664,7 @@ fromIfaceWarnings = \case
    664 664
     
    
    665 665
     fromIfaceWarningTxt :: IfaceWarningTxt -> WarningTxt GhcRn
    
    666 666
     fromIfaceWarningTxt = \case
    
    667
    -    IfWarningTxt mb_cat src strs -> WarningTxt (noLocA . fromWarningCategory <$> mb_cat) src (noLocA <$> map fromIfaceStringLiteralWithNames strs)
    
    667
    +    IfWarningTxt src mb_cat strs -> WarningTxt src (noLocA . fromWarningCategory <$> mb_cat) (noLocA <$> map fromIfaceStringLiteralWithNames strs)
    
    668 668
         IfDeprecatedTxt src strs -> DeprecatedTxt src (noLocA <$> map fromIfaceStringLiteralWithNames strs)
    
    669 669
     
    
    670 670
     fromIfaceStringLiteralWithNames :: (IfaceStringLiteral, [IfExtName]) -> WithHsDocIdentifiers StringLiteral GhcRn
    

  • compiler/GHC/Iface/Warnings.hs
    ... ... @@ -23,7 +23,7 @@ toIfaceWarnings (WarnSome vs ds) = IfWarnSome vs' ds'
    23 23
         ds' = [(occ, toIfaceWarningTxt txt) | (occ, txt) <- ds]
    
    24 24
     
    
    25 25
     toIfaceWarningTxt :: WarningTxt GhcRn -> IfaceWarningTxt
    
    26
    -toIfaceWarningTxt (WarningTxt mb_cat src strs) = IfWarningTxt (unLoc . iwc_wc . unLoc <$> mb_cat) src (map (toIfaceStringLiteralWithNames . unLoc) strs)
    
    26
    +toIfaceWarningTxt (WarningTxt src mb_cat strs) = IfWarningTxt src (unLoc . iwc_wc . unLoc <$> mb_cat) (map (toIfaceStringLiteralWithNames . unLoc) strs)
    
    27 27
     toIfaceWarningTxt (DeprecatedTxt src strs) = IfDeprecatedTxt src (map (toIfaceStringLiteralWithNames . unLoc) strs)
    
    28 28
     
    
    29 29
     toIfaceStringLiteralWithNames :: WithHsDocIdentifiers StringLiteral GhcRn -> (IfaceStringLiteral, [IfExtName])
    

  • compiler/GHC/Parser.y
    ... ... @@ -2053,12 +2053,12 @@ maybe_warning_pragma :: { Maybe (LWarningTxt GhcPs) }
    2053 2053
                                 {% fmap Just $ amsr (sLL $1 $> $ DeprecatedTxt (getDEPRECATED_PRAGs $1) (map stringLiteralToHsDocWst $ snd $ unLoc $2))
    
    2054 2054
                                     (AnnPragma (glR $1) (epTok $3) (fst $ unLoc $2) noAnn noAnn noAnn noAnn) }
    
    2055 2055
             | '{-# WARNING' warning_category strings '#-}'
    
    2056
    -                            {% fmap Just $ amsr (sLL $1 $> $ WarningTxt $2 (getWARNING_PRAGs $1) (map stringLiteralToHsDocWst $ snd $ unLoc $3))
    
    2056
    +                            {% fmap Just $ amsr (sLL $1 $> $ WarningTxt (getWARNING_PRAGs $1) $2 (map stringLiteralToHsDocWst $ snd $ unLoc $3))
    
    2057 2057
                                     (AnnPragma (glR $1) (epTok $4) (fst $ unLoc $3) noAnn noAnn noAnn noAnn)}
    
    2058 2058
             |  {- empty -}      { Nothing }
    
    2059 2059
     
    
    2060
    -warning_category :: { Maybe (LocatedE InWarningCategory) }
    
    2061
    -        : 'in' STRING                  { Just (reLoc $ sLL $1 $> $ InWarningCategory (epTok $1) (getSTRINGs $2)
    
    2060
    +warning_category :: { Maybe (LocatedE (InWarningCategory GhcPs)) }
    
    2061
    +        : 'in' STRING                  { Just (reLoc $ sLL $1 $> $ InWarningCategory (epTok $1, getSTRINGs $2)
    
    2062 2062
                                                                         (reLoc $ sL1 $2 $ mkWarningCategory (getSTRING $2))) }
    
    2063 2063
             | {- empty -}                  { Nothing }
    
    2064 2064
     
    
    ... ... @@ -2083,7 +2083,7 @@ warning :: { OrdList (LWarnDecl GhcPs) }
    2083 2083
             : warning_category namespace_spec namelist strings
    
    2084 2084
                     {% fmap unitOL $ amsA' (L (comb4 $1 $2 $3 $4)
    
    2085 2085
                          (Warning (unLoc $2, fst $ unLoc $4) (unLoc $3)
    
    2086
    -                              (WarningTxt $1 NoSourceText $ map stringLiteralToHsDocWst $ snd $ unLoc $4))) }
    
    2086
    +                              (WarningTxt NoSourceText $1 (map stringLiteralToHsDocWst $ snd $ unLoc $4)))) }
    
    2087 2087
     
    
    2088 2088
     namespace_spec :: { Located NamespaceSpecifier }
    
    2089 2089
       : 'type'      { sL1 $1 $ TypeNamespaceSpecifier (epTok $1) }
    

  • compiler/GHC/Rename/Module.hs
    ... ... @@ -320,12 +320,16 @@ rnSrcWarnDecls bndr_set decls'
    320 320
                                   rdrNameOcc (unLoc x) == rdrNameOcc (unLoc y))
    
    321 321
     
    
    322 322
     rnWarningTxt :: WarningTxt GhcPs -> RnM (WarningTxt GhcRn)
    
    323
    -rnWarningTxt (WarningTxt mb_cat st wst) = do
    
    324
    -  forM_ mb_cat $ \(L _ (InWarningCategory _ _ (L loc cat))) ->
    
    325
    -    unless (validWarningCategory cat) $
    
    326
    -      addErrAt (locA loc) (TcRnInvalidWarningCategory cat)
    
    323
    +rnWarningTxt (WarningTxt st mb_cat wst) = do
    
    324
    +  mb_cat' <- case mb_cat of
    
    325
    +    Nothing -> pure Nothing
    
    326
    +    Just (L x (InWarningCategory y (L loc cat))) -> do
    
    327
    +      unless (validWarningCategory cat) $
    
    328
    +        addErrAt (locA loc) (TcRnInvalidWarningCategory cat)
    
    329
    +      pure . Just $ L x (InWarningCategory y (L loc cat))
    
    327 330
       wst' <- traverse (traverse rnHsDoc) wst
    
    328
    -  pure (WarningTxt mb_cat st wst')
    
    331
    +  pure (WarningTxt st mb_cat' wst')
    
    332
    +
    
    329 333
     rnWarningTxt (DeprecatedTxt st wst) = do
    
    330 334
       wst' <- traverse (traverse rnHsDoc) wst
    
    331 335
       pure (DeprecatedTxt st wst')
    

  • compiler/GHC/Rename/Utils.hs
    ... ... @@ -69,7 +69,6 @@ import GHC.Data.Bag ( mapBagM, headMaybe )
    69 69
     import Control.Monad
    
    70 70
     import GHC.Settings.Constants ( mAX_TUPLE_SIZE, mAX_CTUPLE_SIZE )
    
    71 71
     import GHC.Unit.Module
    
    72
    -import GHC.Unit.Module.Warnings  ( WarningTxt(..) )
    
    73 72
     import GHC.Iface.Load
    
    74 73
     import qualified GHC.LanguageExtensions as LangExt
    
    75 74
     
    

  • compiler/GHC/Tc/Deriv.hs
    ... ... @@ -57,7 +57,6 @@ import GHC.Types.Var.Env
    57 57
     import GHC.Types.Var.Set
    
    58 58
     import GHC.Types.SrcLoc
    
    59 59
     
    
    60
    -import GHC.Unit.Module.Warnings
    
    61 60
     import GHC.Builtin.Names
    
    62 61
     
    
    63 62
     import GHC.Utils.Error
    

  • compiler/GHC/Tc/Deriv/Utils.hs
    ... ... @@ -52,7 +52,6 @@ import GHC.Core.Type
    52 52
     import GHC.Hs
    
    53 53
     import GHC.Driver.Session
    
    54 54
     import GHC.Unit.Module (getModule)
    
    55
    -import GHC.Unit.Module.Warnings
    
    56 55
     import GHC.Unit.Module.ModIface (mi_fix)
    
    57 56
     
    
    58 57
     import GHC.Iface.Load   (loadInterfaceForName)
    

  • compiler/GHC/Tc/Errors/Ppr.hs
    ... ... @@ -1841,7 +1841,7 @@ instance Diagnostic TcRnMessage where
    1841 1841
                    nest 2 (vcat (map (ppr . hsDocString . unLoc) msg)) ]
    
    1842 1842
              where
    
    1843 1843
               (extra, msg) = case txt of
    
    1844
    -            WarningTxt _ _ msg -> ("", msg)
    
    1844
    +            WarningTxt  _ _ msg -> ("", msg)
    
    1845 1845
                 DeprecatedTxt _ msg -> (" is deprecated", msg)
    
    1846 1846
         TcRnRedundantSourceImport mod_name
    
    1847 1847
           -> mkSimpleDecorated $
    

  • compiler/GHC/Tc/Errors/Types.hs
    ... ... @@ -221,7 +221,6 @@ import GHC.Types.DefaultEnv (ClassDefaults)
    221 221
     
    
    222 222
     import GHC.Unit.Types (Module)
    
    223 223
     import GHC.Unit.State (UnitState)
    
    224
    -import GHC.Unit.Module.Warnings (WarningCategory, WarningTxt)
    
    225 224
     import GHC.Unit.Module.ModIface (ModIface)
    
    226 225
     
    
    227 226
     import GHC.Utils.Outputable
    

  • compiler/GHC/Tc/Types/Origin.hs
    ... ... @@ -67,7 +67,6 @@ import GHC.Core.PatSyn
    67 67
     import GHC.Core.Multiplicity ( scaledThing )
    
    68 68
     
    
    69 69
     import GHC.Unit.Module
    
    70
    -import GHC.Unit.Module.Warnings
    
    71 70
     import GHC.Types.Id
    
    72 71
     import GHC.Types.Name
    
    73 72
     import GHC.Types.Name.Reader
    

  • compiler/GHC/Tc/Utils/Instantiate.hs
    ... ... @@ -91,7 +91,6 @@ import GHC.Utils.Unique (sameUnique)
    91 91
     
    
    92 92
     import GHC.Unit.State
    
    93 93
     import GHC.Unit.External
    
    94
    -import GHC.Unit.Module.Warnings
    
    95 94
     
    
    96 95
     import Data.List ( mapAccumL )
    
    97 96
     import qualified Data.List.NonEmpty as NE
    

  • compiler/GHC/Types/DefaultEnv.hs
    ... ... @@ -21,13 +21,12 @@ where
    21 21
     
    
    22 22
     import GHC.Core.Class (Class (className))
    
    23 23
     import GHC.Prelude
    
    24
    -import GHC.Hs.Extension (GhcRn)
    
    24
    +import GHC.Hs
    
    25 25
     import GHC.Tc.Utils.TcType (Type)
    
    26 26
     import GHC.Types.Name (Name, nameUnique, stableNameCmp)
    
    27 27
     import GHC.Types.Name.Env
    
    28 28
     import GHC.Types.Unique.FM (lookupUFM_Directly)
    
    29 29
     import GHC.Types.SrcLoc (SrcSpan)
    
    30
    -import GHC.Unit.Module.Warnings (WarningTxt)
    
    31 30
     import GHC.Unit.Types (Module)
    
    32 31
     import GHC.Utils.Outputable
    
    33 32
     
    

  • compiler/GHC/Types/Error/Codes.hs
    ... ... @@ -768,6 +768,7 @@ type family GhcDiagnosticCode c = n | n -> c where
    768 768
       -- TcRnPragmaWarning
    
    769 769
       GhcDiagnosticCode "WarningTxt"                                    = 63394
    
    770 770
       GhcDiagnosticCode "DeprecatedTxt"                                 = 68441
    
    771
    +  GhcDiagnosticCode "XWarningTxt"                                   = 68077
    
    771 772
     
    
    772 773
       -- TcRnRunSliceFailure/ConversionFail
    
    773 774
       GhcDiagnosticCode "IllegalOccName"                                = 55017
    

  • compiler/GHC/Unit/Module/Warnings.hs
    ... ... @@ -11,6 +11,9 @@
    11 11
     {-# LANGUAGE LambdaCase #-}
    
    12 12
     {-# LANGUAGE TypeFamilies #-}
    
    13 13
     
    
    14
    +-- Eq instances for WarningTxt, InWarningCategory
    
    15
    +{-# OPTIONS_GHC -fno-warn-orphans #-}
    
    16
    +
    
    14 17
     -- | Warnings for a module
    
    15 18
     module GHC.Unit.Module.Warnings
    
    16 19
        ( WarningCategory(..)
    
    ... ... @@ -48,7 +51,7 @@ where
    48 51
     
    
    49 52
     import GHC.Prelude
    
    50 53
     
    
    51
    -import GHC.Data.FastString (FastString, mkFastString, unpackFS)
    
    54
    +import GHC.Data.FastString (mkFastString, unpackFS)
    
    52 55
     import GHC.Types.SourceText
    
    53 56
     import GHC.Types.Name.Occurrence
    
    54 57
     import GHC.Types.Name.Env
    
    ... ... @@ -65,77 +68,15 @@ import GHC.Utils.Binary
    65 68
     import GHC.Unicode
    
    66 69
     
    
    67 70
     import Language.Haskell.Syntax.Extension
    
    71
    +import Language.Haskell.Syntax.Decls
    
    68 72
     
    
    69
    -import Data.Data
    
    70 73
     import Data.List (isPrefixOf)
    
    71
    -import GHC.Generics ( Generic )
    
    72
    -import Control.DeepSeq
    
    73
    -
    
    74
    -
    
    75
    -{-
    
    76
    -Note [Warning categories]
    
    77
    -~~~~~~~~~~~~~~~~~~~~~~~~~
    
    78
    -See GHC Proposal 541 for the design of the warning categories feature:
    
    79
    -https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0541-warning-pragmas-with-categories.rst
    
    80
    -
    
    81
    -A WARNING pragma may be annotated with a category such as "x-partial" written
    
    82
    -after the 'in' keyword, like this:
    
    83
    -
    
    84
    -    {-# WARNING in "x-partial" head "This function is partial..." #-}
    
    85
    -
    
    86
    -This is represented by the 'Maybe (Located WarningCategory)' field in
    
    87
    -'WarningTxt'.  The parser will accept an arbitrary string as the category name,
    
    88
    -then the renamer (in 'rnWarningTxt') will check it contains only valid
    
    89
    -characters, so we can generate a nicer error message than a parse error.
    
    90
    -
    
    91
    -The corresponding warnings can then be controlled with the -Wx-partial,
    
    92
    --Wno-x-partial, -Werror=x-partial and -Wwarn=x-partial flags.  Such a flag is
    
    93
    -distinguished from an 'unrecognisedWarning' by the flag parser testing
    
    94
    -'validWarningCategory'.  The 'x-' prefix means we can still usually report an
    
    95
    -unrecognised warning where the user has made a mistake.
    
    96
    -
    
    97
    -A DEPRECATED pragma may not have a user-defined category, and is always treated
    
    98
    -as belonging to the special category 'deprecations'.  Similarly, a WARNING
    
    99
    -pragma without a category belongs to the 'deprecations' category.
    
    100
    -Thus the '-Wdeprecations' flag will enable all of the following:
    
    101
    -
    
    102
    -    {-# WARNING in "deprecations" foo "This function is deprecated..." #-}
    
    103
    -    {-# WARNING foo "This function is deprecated..." #-}
    
    104
    -    {-# DEPRECATED foo "This function is deprecated..." #-}
    
    105
    -
    
    106
    -The '-Wwarnings-deprecations' flag is supported for backwards compatibility
    
    107
    -purposes as being equivalent to '-Wdeprecations'.
    
    108
    -
    
    109
    -The '-Wextended-warnings' warning group collects together all warnings with
    
    110
    -user-defined categories, so they can be enabled or disabled
    
    111
    -collectively. Moreover they are treated as being part of other warning groups
    
    112
    -such as '-Wdefault' (see 'warningGroupIncludesExtendedWarnings').
    
    113
    -
    
    114
    -'DynFlags' and 'DiagOpts' each contain a set of enabled and a set of fatal
    
    115
    -warning categories, just as they do for the finite enumeration of 'WarningFlag's
    
    116
    -built in to GHC.  These are represented as 'WarningCategorySet's to allow for
    
    117
    -the possibility of them being infinite.
    
    118
    -
    
    119
    --}
    
    120 74
     
    
    121
    -data InWarningCategory
    
    122
    -  = InWarningCategory
    
    123
    -    { iwc_in :: !(EpToken "in"),
    
    124
    -      iwc_st :: !SourceText,
    
    125
    -      iwc_wc :: (LocatedE WarningCategory)
    
    126
    -    } deriving Data
    
    127 75
     
    
    128
    -fromWarningCategory :: WarningCategory -> InWarningCategory
    
    129
    -fromWarningCategory wc = InWarningCategory noAnn NoSourceText (noLocA wc)
    
    130
    -
    
    131
    -
    
    132
    --- See Note [Warning categories]
    
    133
    -newtype WarningCategory = WarningCategory FastString
    
    134
    -  deriving stock Data
    
    135
    -  deriving newtype (Binary, Eq, Outputable, Show, Uniquable, NFData)
    
    136
    -
    
    137
    -mkWarningCategory :: FastString -> WarningCategory
    
    138
    -mkWarningCategory = WarningCategory
    
    76
    +fromWarningCategory ::
    
    77
    +  HasAnnotation (Anno WarningCategory) =>
    
    78
    +  WarningCategory -> InWarningCategory (GhcPass p)
    
    79
    +fromWarningCategory wc = InWarningCategory (noAnn, NoSourceText) (noLocA wc)
    
    139 80
     
    
    140 81
     -- | The @deprecations@ category is used for all DEPRECATED pragmas and for
    
    141 82
     -- WARNING pragmas that do not specify a category.
    
    ... ... @@ -153,7 +94,6 @@ validWarningCategory cat@(WarningCategory c) =
    153 94
         s = unpackFS c
    
    154 95
         is_allowed c = isAlphaNum c || c == '\'' || c == '-'
    
    155 96
     
    
    156
    -
    
    157 97
     -- | A finite or infinite set of warning categories.
    
    158 98
     --
    
    159 99
     -- Unlike 'WarningFlag', there are (in principle) infinitely many warning
    
    ... ... @@ -198,66 +138,74 @@ deleteWarningCategorySet c (CofiniteWarningCategorySet s) = CofiniteWarningCateg
    198 138
     
    
    199 139
     type LWarningTxt pass = XRec pass (WarningTxt pass)
    
    200 140
     
    
    201
    --- | Warning Text
    
    202
    ---
    
    203
    --- reason/explanation from a WARNING or DEPRECATED pragma
    
    204
    -data WarningTxt pass
    
    205
    -   = WarningTxt
    
    206
    -      (Maybe (LocatedE InWarningCategory))
    
    207
    -        -- ^ Warning category attached to this WARNING pragma, if any;
    
    208
    -        -- see Note [Warning categories]
    
    209
    -      SourceText
    
    210
    -      [LocatedE (WithHsDocIdentifiers StringLiteral pass)]
    
    211
    -   | DeprecatedTxt
    
    212
    -      SourceText
    
    213
    -      [LocatedE (WithHsDocIdentifiers StringLiteral pass)]
    
    214
    -  deriving Generic
    
    215
    -
    
    216 141
     -- | To which warning category does this WARNING or DEPRECATED pragma belong?
    
    217 142
     -- See Note [Warning categories].
    
    218
    -warningTxtCategory :: WarningTxt pass -> WarningCategory
    
    219
    -warningTxtCategory (WarningTxt (Just (L _ (InWarningCategory _  _ (L _ cat)))) _ _) = cat
    
    143
    +warningTxtCategory :: WarningTxt (GhcPass p) -> WarningCategory
    
    144
    +warningTxtCategory (WarningTxt _ (Just (L _ (InWarningCategory _ (L _ cat)))) _) = cat
    
    220 145
     warningTxtCategory _ = defaultWarningCategory
    
    221 146
     
    
    147
    +
    
    222 148
     -- | The message that the WarningTxt was specified to output
    
    223
    -warningTxtMessage :: WarningTxt p -> [LocatedE (WithHsDocIdentifiers StringLiteral p)]
    
    224
    -warningTxtMessage (WarningTxt _ _ m) = m
    
    149
    +warningTxtMessage :: WarningTxt (GhcPass p) -> [LocatedE (WithHsDocIdentifiers StringLiteral (GhcPass p))]
    
    150
    +warningTxtMessage (WarningTxt  _ _ m) = m
    
    225 151
     warningTxtMessage (DeprecatedTxt _ m) = m
    
    226 152
     
    
    227 153
     -- | True if the 2 WarningTxts have the same category and messages
    
    228
    -warningTxtSame :: WarningTxt p1 -> WarningTxt p2 -> Bool
    
    154
    +warningTxtSame :: WarningTxt (GhcPass p) -> WarningTxt (GhcPass p) -> Bool
    
    229 155
     warningTxtSame w1 w2
    
    230 156
       = warningTxtCategory w1 == warningTxtCategory w2
    
    231 157
       && literal_message w1 == literal_message w2
    
    232 158
       && same_type
    
    233 159
       where
    
    234
    -    literal_message :: WarningTxt p -> [StringLiteral]
    
    160
    +    literal_message :: WarningTxt (GhcPass p) -> [StringLiteral]
    
    235 161
         literal_message = map (hsDocString . unLoc) . warningTxtMessage
    
    236 162
         same_type | DeprecatedTxt {} <- w1, DeprecatedTxt {} <- w2 = True
    
    237
    -              | WarningTxt {} <- w1, WarningTxt {} <- w2       = True
    
    163
    +              | WarningTxt    {} <- w1, WarningTxt {} <- w2    = True
    
    238 164
                   | otherwise                                      = False
    
    239 165
     
    
    240
    -deriving instance Eq InWarningCategory
    
    166
    +instance Outputable (InWarningCategory (GhcPass pass)) where
    
    167
    +  ppr (InWarningCategory _ wt) = text "in" <+> doubleQuotes (ppr wt)
    
    241 168
     
    
    242
    -deriving instance (Eq (IdP pass)) => Eq (WarningTxt pass)
    
    243
    -deriving instance (Data pass, Data (IdP pass)) => Data (WarningTxt pass)
    
    169
    +type instance XDeprecatedTxt       (GhcPass _) = SourceText
    
    170
    +type instance XWarningTxt          (GhcPass _) = SourceText
    
    171
    +type instance XXWarningTxt         (GhcPass _) = DataConCantHappen
    
    172
    +type instance XInWarningCategory   (GhcPass _) = (EpToken "in", SourceText)
    
    173
    +type instance XXInWarningCategory  (GhcPass _) = DataConCantHappen
    
    244 174
     
    
    175
    +type instance Anno (WithHsDocIdentifiers StringLiteral pass) = EpaLocation
    
    176
    +type instance Anno (InWarningCategory (GhcPass pass)) = EpaLocation
    
    177
    +type instance Anno (WarningCategory) = EpaLocation
    
    245 178
     type instance Anno (WarningTxt (GhcPass pass)) = SrcSpanAnnP
    
    246 179
     
    
    247
    -instance Outputable InWarningCategory where
    
    248
    -  ppr (InWarningCategory _ _ wt) = text "in" <+> doubleQuotes (ppr wt)
    
    180
    +deriving stock instance Eq (WarningTxt GhcPs)
    
    181
    +deriving stock instance Eq (WarningTxt GhcRn)
    
    182
    +deriving stock instance Eq (WarningTxt GhcTc)
    
    183
    +
    
    184
    +deriving stock instance Eq (InWarningCategory GhcPs)
    
    185
    +deriving stock instance Eq (InWarningCategory GhcRn)
    
    186
    +deriving stock instance Eq (InWarningCategory GhcTc)
    
    187
    +
    
    188
    +-- TODO: Move to respecitive type-class definition modules after removing
    
    189
    +-- the Language.Haskell.Syntax.Decls module's dependency on GHC.Hs.Doc.
    
    190
    +-- Subsequently, create a Language.Haskell.Syntax.Decls.Warnings sub-module
    
    191
    +-- with the "warning declaration" types and have Language.Haskell.Syntax.Decls
    
    192
    +-- re-export Language.Haskell.Syntax.Decls.Warnings. This will prevent cyclic
    
    193
    +-- import, but it will only work once GHC.Hs.Doc is no longer a GHC dependency.
    
    194
    +deriving instance Binary WarningCategory
    
    249 195
     
    
    196
    +deriving instance Outputable WarningCategory
    
    250 197
     
    
    251
    -instance Outputable (WarningTxt pass) where
    
    252
    -    ppr (WarningTxt mcat lsrc ws)
    
    198
    +deriving instance Uniquable WarningCategory
    
    199
    +
    
    200
    +instance Outputable (WarningTxt (GhcPass pass)) where
    
    201
    +    ppr (WarningTxt lsrc mcat ws)
    
    253 202
           = case lsrc of
    
    254 203
                 NoSourceText   -> pp_ws ws
    
    255 204
                 SourceText src -> ftext src <+> ctg_doc <+> pp_ws ws <+> text "#-}"
    
    256 205
             where
    
    257 206
               ctg_doc = maybe empty (\ctg -> ppr ctg) mcat
    
    258 207
     
    
    259
    -
    
    260
    -    ppr (DeprecatedTxt lsrc  ds)
    
    208
    +    ppr (DeprecatedTxt lsrc ds)
    
    261 209
           = case lsrc of
    
    262 210
               NoSourceText   -> pp_ws ds
    
    263 211
               SourceText src -> ftext src <+> pp_ws ds <+> text "#-}"
    
    ... ... @@ -270,7 +218,7 @@ pp_ws ws
    270 218
         <+> text "]"
    
    271 219
     
    
    272 220
     
    
    273
    -pprWarningTxtForMsg :: WarningTxt p -> SDoc
    
    221
    +pprWarningTxtForMsg :: WarningTxt (GhcPass pass) -> SDoc
    
    274 222
     pprWarningTxtForMsg (WarningTxt _ _ ws)
    
    275 223
                          = doubleQuotes (vcat (map (ftext . sl_fs . hsDocString . unLoc) ws))
    
    276 224
     pprWarningTxtForMsg (DeprecatedTxt _ ds)
    
    ... ... @@ -316,8 +264,6 @@ type DeclWarnOccNames pass = [(OccName, WarningTxt pass)]
    316 264
     -- | Names that are deprecated as exports
    
    317 265
     type ExportWarnNames pass = [(Name, WarningTxt pass)]
    
    318 266
     
    
    319
    -deriving instance Eq (IdP pass) => Eq (Warnings pass)
    
    320
    -
    
    321 267
     emptyWarn :: Warnings p
    
    322 268
     emptyWarn = WarnSome [] []
    
    323 269
     
    

  • compiler/Language/Haskell/Syntax/Decls.hs
    1
    -
    
    2 1
     {-# LANGUAGE ConstraintKinds #-}
    
    3 2
     {-# LANGUAGE DataKinds #-}
    
    4 3
     {-# LANGUAGE DeriveDataTypeable #-}
    
    5 4
     {-# LANGUAGE DeriveTraversable #-}
    
    5
    +{-# LANGUAGE DerivingStrategies #-}
    
    6 6
     {-# LANGUAGE FlexibleContexts #-}
    
    7 7
     {-# LANGUAGE FlexibleInstances #-}
    
    8
    +{-# LANGUAGE GeneralizedNewtypeDeriving #-}
    
    8 9
     {-# LANGUAGE LambdaCase #-}
    
    9 10
     {-# LANGUAGE ScopedTypeVariables #-}
    
    10 11
     {-# LANGUAGE TypeApplications #-}
    
    ... ... @@ -83,7 +84,18 @@ module Language.Haskell.Syntax.Decls (
    83 84
       FamilyResultSig(..), LFamilyResultSig, InjectivityAnn(..), LInjectivityAnn,
    
    84 85
     
    
    85 86
       -- * Grouping
    
    86
    -  HsGroup(..)
    
    87
    +  HsGroup(..),
    
    88
    +
    
    89
    +  -- * Warnings
    
    90
    +  WarningTxt(..),
    
    91
    +  WarningCategory(..),
    
    92
    +  mkWarningCategory,
    
    93
    +  InWarningCategory(..),
    
    94
    +  -- ** Extension
    
    95
    +  XDeprecatedTxt,
    
    96
    +  XWarningTxt,
    
    97
    +  XXWarningTxt,
    
    98
    +  XInWarningCategory,
    
    87 99
         ) where
    
    88 100
     
    
    89 101
     -- friends:
    
    ... ... @@ -101,12 +113,14 @@ import GHC.Types.Basic (TopLevelFlag, OverlapMode, RuleName, Activation
    101 113
                            ,TyConFlavour(..), TypeOrData(..), NewOrData(..))
    
    102 114
     import GHC.Types.ForeignCall (CType, CCallConv, Safety, Header, CLabelString, CCallTarget, CExportSpec)
    
    103 115
     
    
    104
    -import GHC.Unit.Module.Warnings (WarningTxt)
    
    105
    -
    
    116
    +import GHC.Data.FastString (FastString)
    
    106 117
     import GHC.Hs.Doc (LHsDoc) -- ROMES:TODO Discuss in #21592 whether this is parsed AST or base AST
    
    118
    +import GHC.Hs.Doc (WithHsDocIdentifiers)
    
    119
    +import GHC.Types.SourceText (StringLiteral)
    
    107 120
     
    
    108
    -import Control.Monad
    
    121
    +import Control.DeepSeq
    
    109 122
     import Control.Exception (assert)
    
    123
    +import Control.Monad
    
    110 124
     import Data.Data        hiding (TyCon, Fixity, Infix)
    
    111 125
     import Data.Maybe
    
    112 126
     import Data.String
    
    ... ... @@ -117,6 +131,8 @@ import Prelude (Show)
    117 131
     import Data.Foldable
    
    118 132
     import Data.Traversable
    
    119 133
     import Data.List.NonEmpty (NonEmpty (..))
    
    134
    +import GHC.Generics ( Generic )
    
    135
    +
    
    120 136
     
    
    121 137
     {-
    
    122 138
     ************************************************************************
    
    ... ... @@ -1589,3 +1605,85 @@ data RoleAnnotDecl pass
    1589 1605
                       (LIdP pass)              -- type constructor
    
    1590 1606
                       [XRec pass (Maybe Role)] -- optional annotations
    
    1591 1607
       | XRoleAnnotDecl !(XXRoleAnnotDecl pass)
    
    1608
    +
    
    1609
    +{-
    
    1610
    +************************************************************************
    
    1611
    +*                                                                      *
    
    1612
    +\subsection[WarnAnnot]{Warning annotations}
    
    1613
    +*                                                                      *
    
    1614
    +************************************************************************
    
    1615
    +-}
    
    1616
    +
    
    1617
    +-- | Warning Text
    
    1618
    +--
    
    1619
    +-- reason/explanation from a WARNING or DEPRECATED pragma
    
    1620
    +data WarningTxt pass
    
    1621
    +   = DeprecatedTxt
    
    1622
    +      (XDeprecatedTxt pass)
    
    1623
    +      [XRec pass (WithHsDocIdentifiers StringLiteral pass)]
    
    1624
    +   | WarningTxt
    
    1625
    +       (XWarningTxt pass)
    
    1626
    +       (Maybe (XRec pass (InWarningCategory pass)))
    
    1627
    +           -- ^ Warning category attached to this WARNING pragma, if any;
    
    1628
    +           -- see Note [Warning categories]
    
    1629
    +       [XRec pass (WithHsDocIdentifiers StringLiteral pass)]
    
    1630
    +   | XWarningTxt !(XXWarningTxt pass)
    
    1631
    +  deriving Generic
    
    1632
    +
    
    1633
    +{-
    
    1634
    +Note [Warning categories]
    
    1635
    +~~~~~~~~~~~~~~~~~~~~~~~~~
    
    1636
    +See GHC Proposal 541 for the design of the warning categories feature:
    
    1637
    +https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0541-warning-pragmas-with-categories.rst
    
    1638
    +
    
    1639
    +A WARNING pragma may be annotated with a category such as "x-partial" written
    
    1640
    +after the 'in' keyword, like this:
    
    1641
    +
    
    1642
    +    {-# WARNING in "x-partial" head "This function is partial..." #-}
    
    1643
    +
    
    1644
    +This is represented by the 'Maybe (Located WarningCategory)' field in
    
    1645
    +'WarningTxt'.  The parser will accept an arbitrary string as the category name,
    
    1646
    +then the renamer (in 'rnWarningTxt') will check it contains only valid
    
    1647
    +characters, so we can generate a nicer error message than a parse error.
    
    1648
    +
    
    1649
    +The corresponding warnings can then be controlled with the -Wx-partial,
    
    1650
    +-Wno-x-partial, -Werror=x-partial and -Wwarn=x-partial flags.  Such a flag is
    
    1651
    +distinguished from an 'unrecognisedWarning' by the flag parser testing
    
    1652
    +'validWarningCategory'.  The 'x-' prefix means we can still usually report an
    
    1653
    +unrecognised warning where the user has made a mistake.
    
    1654
    +
    
    1655
    +A DEPRECATED pragma may not have a user-defined category, and is always treated
    
    1656
    +as belonging to the special category 'deprecations'.  Similarly, a WARNING
    
    1657
    +pragma without a category belongs to the 'deprecations' category.
    
    1658
    +Thus the '-Wdeprecations' flag will enable all of the following:
    
    1659
    +
    
    1660
    +    {-# WARNING in "deprecations" foo "This function is deprecated..." #-}
    
    1661
    +    {-# WARNING foo "This function is deprecated..." #-}
    
    1662
    +    {-# DEPRECATED foo "This function is deprecated..." #-}
    
    1663
    +The '-Wwarnings-deprecations' flag is supported for backwards compatibility
    
    1664
    +purposes as being equivalent to '-Wdeprecations'.
    
    1665
    +
    
    1666
    +The '-Wextended-warnings' warning group collects together all warnings with
    
    1667
    +user-defined categories, so they can be enabled or disabled
    
    1668
    +collectively. Moreover they are treated as being part of other warning groups
    
    1669
    +such as '-Wdefault' (see 'warningGroupIncludesExtendedWarnings').
    
    1670
    +
    
    1671
    +'DynFlags' and 'DiagOpts' each contain a set of enabled and a set of fatal
    
    1672
    +warning categories, just as they do for the finite enumeration of 'WarningFlag's
    
    1673
    +built in to GHC.  These are represented as 'WarningCategorySet's to allow for
    
    1674
    +the possibility of them being infinite.
    
    1675
    +
    
    1676
    +-}
    
    1677
    +data InWarningCategory pass
    
    1678
    +  = InWarningCategory
    
    1679
    +    { iwc_st :: (XInWarningCategory pass),
    
    1680
    +      iwc_wc :: (XRec pass WarningCategory)
    
    1681
    +    }
    
    1682
    +  | XInWarningCategory !(XXInWarningCategory pass)
    
    1683
    +
    
    1684
    +newtype WarningCategory = WarningCategory FastString
    
    1685
    +  deriving stock (Data)
    
    1686
    +  deriving newtype (Eq, Show, NFData)
    
    1687
    +
    
    1688
    +mkWarningCategory :: FastString -> WarningCategory
    
    1689
    +mkWarningCategory = WarningCategory

  • compiler/Language/Haskell/Syntax/Extension.hs
    ... ... @@ -421,6 +421,17 @@ type family XXWarnDecls x
    421 421
     type family XWarning        x
    
    422 422
     type family XXWarnDecl      x
    
    423 423
     
    
    424
    +-- -------------------------------------
    
    425
    +-- WarningTxt type families
    
    426
    +type family XDeprecatedTxt x
    
    427
    +type family XWarningTxt    x
    
    428
    +type family XXWarningTxt   x
    
    429
    +
    
    430
    +-- -------------------------------------
    
    431
    +-- InWarningCategory type families
    
    432
    +type family XInWarningCategory  x
    
    433
    +type family XXInWarningCategory x
    
    434
    +
    
    424 435
     -- -------------------------------------
    
    425 436
     -- AnnDecl type families
    
    426 437
     type family XHsAnnotation  x
    

  • utils/check-exact/ExactPrint.hs
    ... ... @@ -53,7 +53,6 @@ import GHC.Types.PkgQual
    53 53
     import GHC.Types.SourceText
    
    54 54
     import GHC.Types.SrcLoc
    
    55 55
     import GHC.Types.Var
    
    56
    -import GHC.Unit.Module.Warnings
    
    57 56
     import GHC.Utils.Misc
    
    58 57
     import GHC.Utils.Outputable hiding ( (<>) )
    
    59 58
     import GHC.Utils.Panic
    
    ... ... @@ -1570,14 +1569,14 @@ instance ExactPrint (LocatedP (WarningTxt GhcPs)) where
    1570 1569
       getAnnotationEntry = entryFromLocatedA
    
    1571 1570
       setAnnotationAnchor = setAnchorAn
    
    1572 1571
     
    
    1573
    -  exact (L (EpAnn l (AnnPragma o c (os,cs) l1 l2 t m) css) (WarningTxt mb_cat src ws)) = do
    
    1572
    +  exact (L (EpAnn l (AnnPragma o c (os,cs) l1 l2 t m) css) (WarningTxt src mb_cat ws)) = do
    
    1574 1573
         o' <- markAnnOpen'' o src "{-# WARNING"
    
    1575 1574
         mb_cat' <- markAnnotated mb_cat
    
    1576 1575
         os' <- markEpToken os
    
    1577 1576
         ws' <- markAnnotated ws
    
    1578 1577
         cs' <- markEpToken cs
    
    1579 1578
         c' <- markEpToken c
    
    1580
    -    return (L (EpAnn l (AnnPragma o' c' (os',cs') l1 l2 t m) css) (WarningTxt mb_cat' src ws'))
    
    1579
    +    return (L (EpAnn l (AnnPragma o' c' (os',cs') l1 l2 t m) css) (WarningTxt src mb_cat' ws'))
    
    1581 1580
     
    
    1582 1581
       exact (L (EpAnn l (AnnPragma o c (os,cs) l1 l2 t m) css) (DeprecatedTxt src ws)) = do
    
    1583 1582
         o' <- markAnnOpen'' o src "{-# DEPRECATED"
    
    ... ... @@ -1587,14 +1586,14 @@ instance ExactPrint (LocatedP (WarningTxt GhcPs)) where
    1587 1586
         c' <- markEpToken c
    
    1588 1587
         return (L (EpAnn l (AnnPragma o' c' (os',cs') l1 l2 t m) css) (DeprecatedTxt src ws'))
    
    1589 1588
     
    
    1590
    -instance ExactPrint InWarningCategory where
    
    1589
    +instance Typeable p => ExactPrint (InWarningCategory (GhcPass p)) where
    
    1591 1590
       getAnnotationEntry _ = NoEntryVal
    
    1592 1591
       setAnnotationAnchor a _ _ _ = a
    
    1593 1592
     
    
    1594
    -  exact (InWarningCategory tkIn source (L l wc)) = do
    
    1593
    +  exact (InWarningCategory (tkIn, source) (L l wc)) = do
    
    1595 1594
           tkIn' <- markEpToken tkIn
    
    1596 1595
           L l' (_,wc') <- markAnnotated (L l (source, wc))
    
    1597
    -      return (InWarningCategory tkIn' source (L l' wc'))
    
    1596
    +      return (InWarningCategory (tkIn', source) (L l' wc'))
    
    1598 1597
     
    
    1599 1598
     instance ExactPrint (SourceText, WarningCategory) where
    
    1600 1599
       getAnnotationEntry _ = NoEntryVal
    
    ... ... @@ -1935,14 +1934,14 @@ instance ExactPrint (WarnDecl GhcPs) where
    1935 1934
       getAnnotationEntry _ = NoEntryVal
    
    1936 1935
       setAnnotationAnchor a _ _ _ = a
    
    1937 1936
     
    
    1938
    -  exact (Warning (ns_spec, (o,c)) lns  (WarningTxt mb_cat src ls )) = do
    
    1937
    +  exact (Warning (ns_spec, (o,c)) lns  (WarningTxt src mb_cat ls )) = do
    
    1939 1938
         mb_cat' <- markAnnotated mb_cat
    
    1940 1939
         ns_spec' <- exactNsSpec ns_spec
    
    1941 1940
         lns' <- markAnnotated lns
    
    1942 1941
         o' <- markEpToken o
    
    1943 1942
         ls' <- markAnnotated ls
    
    1944 1943
         c' <- markEpToken c
    
    1945
    -    return (Warning (ns_spec', (o',c')) lns'  (WarningTxt mb_cat' src ls'))
    
    1944
    +    return (Warning (ns_spec', (o',c')) lns'  (WarningTxt src mb_cat' ls'))
    
    1946 1945
     
    
    1947 1946
       exact (Warning (ns_spec, (o,c)) lns (DeprecatedTxt src ls)) = do
    
    1948 1947
         ns_spec' <- exactNsSpec ns_spec
    

  • utils/haddock/haddock-api/src/Haddock/Interface/Create.hs
    ... ... @@ -354,7 +354,7 @@ parseWarning
    354 354
       -> IfM m (Doc Name)
    
    355 355
     parseWarning parserOpts sDocContext w = case w of
    
    356 356
       IfDeprecatedTxt _ msg -> format "Deprecated: " (map dstToDoc msg)
    
    357
    -  IfWarningTxt _ _ msg -> format "Warning: " (map dstToDoc msg)
    
    357
    +  IfWarningTxt  _ _ msg -> format "Warning: " (map dstToDoc msg)
    
    358 358
       where
    
    359 359
         dstToDoc :: (IfaceStringLiteral, [Name]) -> HsDoc GhcRn
    
    360 360
         dstToDoc ((IfStringLiteral _ fs), ids) = WithHsDocIdentifiers (fsToDoc fs) (map noLoc ids)