[Git][ghc/ghc][wip/haddocks-for-ghc-warnings] Improve haddock-visible documentation for GHC.Driver.Flags

Bodigrim (@Bodigrim) gitlab at gitlab.haskell.org
Wed Mar 12 23:44:08 UTC 2025



Bodigrim pushed to branch wip/haddocks-for-ghc-warnings at Glasgow Haskell Compiler / GHC


Commits:
60bafd21 by Andrew Lelechenko at 2025-03-12T23:43:55+00:00
Improve haddock-visible documentation for GHC.Driver.Flags

- - - - -


1 changed file:

- compiler/GHC/Driver/Flags.hs


Changes:

=====================================
compiler/GHC/Driver/Flags.hs
=====================================
@@ -360,7 +360,7 @@ validHoleFitsImpliedGFlags
     , (Opt_ShowTypeAppVarsOfHoleFits, turnOff, Opt_ShowTypeAppOfHoleFits)
     , (Opt_UnclutterValidHoleFits, turnOff, Opt_ShowProvOfHoleFits) ]
 
--- General flags that are switched on/off when other general flags are switched
+-- | General flags that are switched on/off when other general flags are switched
 -- on
 impliedGFlags :: [(GeneralFlag, TurnOnFlag, GeneralFlag)]
 impliedGFlags = [(Opt_DeferTypeErrors, turnOn, Opt_DeferTypedHoles)
@@ -373,12 +373,12 @@ impliedGFlags = [(Opt_DeferTypeErrors, turnOn, Opt_DeferTypedHoles)
                 ,(Opt_InfoTableMap, turnOn, Opt_InfoTableMapWithFallback)
                 ] ++ validHoleFitsImpliedGFlags
 
--- General flags that are switched on/off when other general flags are switched
+-- | General flags that are switched on/off when other general flags are switched
 -- off
 impliedOffGFlags :: [(GeneralFlag, TurnOnFlag, GeneralFlag)]
 impliedOffGFlags = [(Opt_Strictness, turnOff, Opt_WorkerWrapper)]
 
--- Please keep what_glasgow_exts_does.rst up to date with this list
+-- | Please keep @docs/users_guide/what_glasgow_exts_does.rst@ up to date with this list.
 glasgowExtsFlags :: [LangExt.Extension]
 glasgowExtsFlags = [
              LangExt.ConstrainedClassMethods
@@ -426,7 +426,7 @@ data DumpFlag
    -- enabled if you run -ddump-cmm-verbose-by-proc
    -- Each flag corresponds to exact stage of Cmm pipeline.
    | Opt_D_dump_cmm_verbose
-   -- same as -ddump-cmm-verbose-by-proc but writes each stage
+   -- ^ same as -ddump-cmm-verbose-by-proc but writes each stage
    -- to a separate file (if used with -ddump-to-file)
    | Opt_D_dump_cmm_cfg
    | Opt_D_dump_cmm_cbe
@@ -500,9 +500,9 @@ data DumpFlag
    | Opt_D_dump_rn_stats
    | Opt_D_dump_opt_cmm
    | Opt_D_dump_simpl_stats
-   | Opt_D_dump_cs_trace -- Constraint solver in type checker
+   | Opt_D_dump_cs_trace -- ^ Constraint solver in type checker
    | Opt_D_dump_tc_trace
-   | Opt_D_dump_ec_trace -- Pattern match exhaustiveness checker
+   | Opt_D_dump_ec_trace -- ^ Pattern match exhaustiveness checker
    | Opt_D_dump_if_trace
    | Opt_D_dump_splices
    | Opt_D_th_dec_file
@@ -591,9 +591,13 @@ data GeneralFlag
    | Opt_InfoTableMapWithFallback
    | Opt_InfoTableMapWithStack
 
-   | Opt_WarnIsError                    -- -Werror; makes warnings fatal
-   | Opt_ShowWarnGroups                 -- Show the group a warning belongs to
-   | Opt_HideSourcePaths                -- Hide module source/object paths
+   | Opt_WarnIsError
+   -- ^ @-Werror@; makes all warnings fatal.
+   -- See 'wopt_set_fatal' for making individual warnings fatal as in @-Werror=foo at .
+   | Opt_ShowWarnGroups
+   -- ^ Show the group a warning belongs to.
+   | Opt_HideSourcePaths
+   -- ^ @-fhide-source-paths@; hide module source/object paths.
 
    | Opt_PrintExplicitForalls
    | Opt_PrintExplicitKinds
@@ -641,15 +645,15 @@ data GeneralFlag
    | Opt_IgnoreAsserts
    | Opt_DoEtaReduction
    | Opt_CaseMerge
-   | Opt_CaseFolding                    -- Constant folding through case-expressions
+   | Opt_CaseFolding                    -- ^ Constant folding through case-expressions
    | Opt_UnboxStrictFields
    | Opt_UnboxSmallStrictFields
    | Opt_DictsCheap
-   | Opt_EnableRewriteRules             -- Apply rewrite rules during simplification
-   | Opt_EnableThSpliceWarnings         -- Enable warnings for TH splices
-   | Opt_RegsGraph                      -- do graph coloring register allocation
-   | Opt_RegsIterative                  -- do iterative coalescing graph coloring register allocation
-   | Opt_PedanticBottoms                -- Be picky about how we treat bottom
+   | Opt_EnableRewriteRules             -- ^ Apply rewrite rules during simplification
+   | Opt_EnableThSpliceWarnings         -- ^ Enable warnings for TH splices
+   | Opt_RegsGraph                      -- ^ Do graph coloring register allocation
+   | Opt_RegsIterative                  -- ^ Do iterative coalescing graph coloring register allocation
+   | Opt_PedanticBottoms                -- ^ Be picky about how we treat bottom
    | Opt_LlvmFillUndefWithGarbage       -- Testing for undef bugs (hidden flag)
    | Opt_IrrefutableTuples
    | Opt_CmmSink
@@ -658,13 +662,13 @@ data GeneralFlag
    | Opt_CmmControlFlow
    | Opt_AsmShortcutting
    | Opt_OmitYields
-   | Opt_FunToThunk               -- deprecated
-   | Opt_DictsStrict                     -- be strict in argument dictionaries
+   | Opt_FunToThunk                -- deprecated
+   | Opt_DictsStrict               -- ^ Be strict in argument dictionaries
    | Opt_DmdTxDictSel              -- ^ deprecated, no effect and behaviour is now default.
                                    -- Allowed switching of a special demand transformer for dictionary selectors
-   | Opt_Loopification                  -- See Note [Self-recursive tail calls]
-   | Opt_CfgBlocklayout             -- ^ Use the cfg based block layout algorithm.
-   | Opt_WeightlessBlocklayout         -- ^ Layout based on last instruction per block.
+   | Opt_Loopification             -- See Note [Self-recursive tail calls]
+   | Opt_CfgBlocklayout            -- ^ Use the cfg based block layout algorithm.
+   | Opt_WeightlessBlocklayout     -- ^ Layout based on last instruction per block.
    | Opt_CprAnal
    | Opt_WorkerWrapper
    | Opt_WorkerWrapperUnlift  -- ^ Do W/W split for unlifting even if we won't unbox anything.
@@ -681,7 +685,7 @@ data GeneralFlag
    -- Inference flags
    | Opt_DoTagInferenceChecks
 
-   -- PreInlining is on by default. The option is there just to see how
+   -- | PreInlining is on by default. The option is there just to see how
    -- bad things get if you turn it off!
    | Opt_SimplPreInlining
 
@@ -690,15 +694,15 @@ data GeneralFlag
    | Opt_OmitInterfacePragmas
    | Opt_ExposeAllUnfoldings
    | Opt_ExposeOverloadedUnfoldings
-   | Opt_KeepAutoRules -- ^Keep auto-generated rules even if they seem to have become useless
-   | Opt_WriteInterface -- forces .hi files to be written even with -fno-code
+   | Opt_KeepAutoRules -- ^ Keep auto-generated rules even if they seem to have become useless
+   | Opt_WriteInterface -- ^ Forces .hi files to be written even with -fno-code
    | Opt_WriteSelfRecompInfo
    | Opt_WriteSelfRecompFlags -- ^ Include detailed flag information for self-recompilation debugging
-   | Opt_WriteHie -- generate .hie files
+   | Opt_WriteHie -- ^ Generate .hie files
 
    -- JavaScript opts
-   | Opt_DisableJsMinifier -- ^ render JavaScript pretty-printed instead of minified (compacted)
-   | Opt_DisableJsCsources -- ^ don't link C sources (compiled to JS) with Haskell code (compiled to JS)
+   | Opt_DisableJsMinifier -- ^ Render JavaScript pretty-printed instead of minified (compacted)
+   | Opt_DisableJsCsources -- ^ Don't link C sources (compiled to JS) with Haskell code (compiled to JS)
 
    -- profiling opts
    | Opt_AutoSccsOnIndividualCafs
@@ -781,11 +785,11 @@ data GeneralFlag
    | Opt_LinkRts
 
    -- output style opts
-   | Opt_ErrorSpans -- Include full span info in error messages,
+   | Opt_ErrorSpans -- ^ Include full span info in error messages,
                     -- instead of just the start position.
    | Opt_DeferDiagnostics
    | Opt_DiagnosticsAsJSON  -- ^ Dump diagnostics as JSON
-   | Opt_DiagnosticsShowCaret -- Show snippets of offending code
+   | Opt_DiagnosticsShowCaret -- ^ Show snippets of offending code
    | Opt_PprCaseAsLet
    | Opt_PprShowTicks
    | Opt_ShowHoleConstraints
@@ -808,29 +812,29 @@ data GeneralFlag
    | Opt_ShowLoadedModules
    | Opt_HexWordLiterals -- See Note [Print Hexadecimal Literals]
 
-   -- Suppress a coercions inner structure, replacing it with '...'
+   -- | Suppress a coercions inner structure, replacing it with '...'
    | Opt_SuppressCoercions
-   -- Suppress the type of a coercion as well
+   -- | Suppress the type of a coercion as well
    | Opt_SuppressCoercionTypes
    | Opt_SuppressVarKinds
-   -- Suppress module id prefixes on variables.
+   -- | Suppress module id prefixes on variables.
    | Opt_SuppressModulePrefixes
-   -- Suppress type applications.
+   -- | Suppress type applications.
    | Opt_SuppressTypeApplications
-   -- Suppress info such as arity and unfoldings on identifiers.
+   -- | Suppress info such as arity and unfoldings on identifiers.
    | Opt_SuppressIdInfo
-   -- Suppress separate type signatures in core, but leave types on
+   -- | Suppress separate type signatures in core, but leave types on
    -- lambda bound vars
    | Opt_SuppressUnfoldings
-   -- Suppress the details of even stable unfoldings
+   -- | Suppress the details of even stable unfoldings
    | Opt_SuppressTypeSignatures
-   -- Suppress unique ids on variables.
+   -- | Suppress unique ids on variables.
    -- Except for uniques, as some simplifier phases introduce new
    -- variables that have otherwise identical names.
    | Opt_SuppressUniques
    | Opt_SuppressStgExts
    | Opt_SuppressStgReps
-   | Opt_SuppressTicks     -- Replaces Opt_PprShowTicks
+   | Opt_SuppressTicks      -- ^ Replaces Opt_PprShowTicks
    | Opt_SuppressTimestamps -- ^ Suppress timestamps in dumps
    | Opt_SuppressCoreSizes  -- ^ Suppress per binding Core size stats in dumps
 
@@ -1030,54 +1034,54 @@ data WarningFlag =
    | Opt_WarnDerivingTypeable
    | Opt_WarnDeferredTypeErrors
    | Opt_WarnDeferredOutOfScopeVariables
-   | Opt_WarnNonCanonicalMonadInstances              -- since 8.0
-   | Opt_WarnNonCanonicalMonadFailInstances          -- since 8.0, removed 8.8
-   | Opt_WarnNonCanonicalMonoidInstances             -- since 8.0
-   | Opt_WarnMissingPatternSynonymSignatures         -- since 8.0
-   | Opt_WarnUnrecognisedWarningFlags                -- since 8.0
-   | Opt_WarnSimplifiableClassConstraints            -- Since 8.2
-   | Opt_WarnCPPUndef                                -- Since 8.2
-   | Opt_WarnUnbangedStrictPatterns                  -- Since 8.2
-   | Opt_WarnMissingHomeModules                      -- Since 8.2
-   | Opt_WarnPartialFields                           -- Since 8.4
+   | Opt_WarnNonCanonicalMonadInstances              -- ^ @since 8.0
+   | Opt_WarnNonCanonicalMonadFailInstances          -- ^ @since 8.0, has no effect since 8.8
+   | Opt_WarnNonCanonicalMonoidInstances             -- ^ @since 8.0
+   | Opt_WarnMissingPatternSynonymSignatures         -- ^ @since 8.0
+   | Opt_WarnUnrecognisedWarningFlags                -- ^ @since 8.0
+   | Opt_WarnSimplifiableClassConstraints            -- ^ @since 8.2
+   | Opt_WarnCPPUndef                                -- ^ @since 8.2
+   | Opt_WarnUnbangedStrictPatterns                  -- ^ @since 8.2
+   | Opt_WarnMissingHomeModules                      -- ^ @since 8.2
+   | Opt_WarnPartialFields                           -- ^ @since 8.4
    | Opt_WarnMissingExportList
    | Opt_WarnInaccessibleCode
-   | Opt_WarnStarIsType                              -- Since 8.6
-   | Opt_WarnStarBinder                              -- Since 8.6
-   | Opt_WarnImplicitKindVars                        -- Since 8.6
+   | Opt_WarnStarIsType                              -- ^ @since 8.6
+   | Opt_WarnStarBinder                              -- ^ @since 8.6
+   | Opt_WarnImplicitKindVars                        -- ^ @since 8.6
    | Opt_WarnSpaceAfterBang
-   | Opt_WarnMissingDerivingStrategies               -- Since 8.8
-   | Opt_WarnPrepositiveQualifiedModule              -- Since 8.10
-   | Opt_WarnUnusedPackages                          -- Since 8.10
-   | Opt_WarnInferredSafeImports                     -- Since 8.10
-   | Opt_WarnMissingSafeHaskellMode                  -- Since 8.10
-   | Opt_WarnCompatUnqualifiedImports                -- Since 8.10
+   | Opt_WarnMissingDerivingStrategies               -- ^ @since 8.8
+   | Opt_WarnPrepositiveQualifiedModule              -- ^ @since 8.10
+   | Opt_WarnUnusedPackages                          -- ^ @since 8.10
+   | Opt_WarnInferredSafeImports                     -- ^ @since 8.10
+   | Opt_WarnMissingSafeHaskellMode                  -- ^ @since 8.10
+   | Opt_WarnCompatUnqualifiedImports                -- ^ @since 8.10
    | Opt_WarnDerivingDefaults
-   | Opt_WarnInvalidHaddock                          -- Since 9.0
-   | Opt_WarnOperatorWhitespaceExtConflict           -- Since 9.2
-   | Opt_WarnOperatorWhitespace                      -- Since 9.2
-   | Opt_WarnAmbiguousFields                         -- Since 9.2
-   | Opt_WarnImplicitLift                            -- Since 9.2
-   | Opt_WarnMissingKindSignatures                   -- Since 9.2
-   | Opt_WarnMissingPolyKindSignatures               -- Since 9.8
-   | Opt_WarnMissingExportedPatternSynonymSignatures -- since 9.2
-   | Opt_WarnRedundantStrictnessFlags                -- Since 9.4
-   | Opt_WarnForallIdentifier                        -- Since 9.4
-   | Opt_WarnUnicodeBidirectionalFormatCharacters    -- Since 9.0.2
-   | Opt_WarnGADTMonoLocalBinds                      -- Since 9.4
-   | Opt_WarnTypeEqualityOutOfScope                  -- Since 9.4
-   | Opt_WarnTypeEqualityRequiresOperators           -- Since 9.4
-   | Opt_WarnLoopySuperclassSolve                    -- Since 9.6, has no effect since 9.10
-   | Opt_WarnTermVariableCapture                     -- Since 9.8
-   | Opt_WarnMissingRoleAnnotations                  -- Since 9.8
-   | Opt_WarnImplicitRhsQuantification               -- Since 9.8
-   | Opt_WarnIncompleteExportWarnings                -- Since 9.8
-   | Opt_WarnIncompleteRecordSelectors               -- Since 9.10
-   | Opt_WarnBadlyStagedTypes                        -- Since 9.10
-   | Opt_WarnInconsistentFlags                       -- Since 9.8
-   | Opt_WarnDataKindsTC                             -- Since 9.10
-   | Opt_WarnDefaultedExceptionContext               -- Since 9.10
-   | Opt_WarnViewPatternSignatures                   -- Since 9.12
+   | Opt_WarnInvalidHaddock                          -- ^ @since 9.0
+   | Opt_WarnOperatorWhitespaceExtConflict           -- ^ @since 9.2
+   | Opt_WarnOperatorWhitespace                      -- ^ @since 9.2
+   | Opt_WarnAmbiguousFields                         -- ^ @since 9.2
+   | Opt_WarnImplicitLift                            -- ^ @since 9.2
+   | Opt_WarnMissingKindSignatures                   -- ^ @since 9.2
+   | Opt_WarnMissingPolyKindSignatures               -- ^ @since 9.8
+   | Opt_WarnMissingExportedPatternSynonymSignatures -- ^ @since 9.2
+   | Opt_WarnRedundantStrictnessFlags                -- ^ @since 9.4
+   | Opt_WarnForallIdentifier                        -- ^ @since 9.4
+   | Opt_WarnUnicodeBidirectionalFormatCharacters    -- ^ @since 9.0.2
+   | Opt_WarnGADTMonoLocalBinds                      -- ^ @since 9.4
+   | Opt_WarnTypeEqualityOutOfScope                  -- ^ @since 9.4
+   | Opt_WarnTypeEqualityRequiresOperators           -- ^ @since 9.4
+   | Opt_WarnLoopySuperclassSolve                    -- ^ @since 9.6, has no effect since 9.10
+   | Opt_WarnTermVariableCapture                     -- ^ @since 9.8
+   | Opt_WarnMissingRoleAnnotations                  -- ^ @since 9.8
+   | Opt_WarnImplicitRhsQuantification               -- ^ @since 9.8
+   | Opt_WarnIncompleteExportWarnings                -- ^ @since 9.8
+   | Opt_WarnIncompleteRecordSelectors               -- ^ @since 9.10
+   | Opt_WarnBadlyStagedTypes                        -- ^ @since 9.10
+   | Opt_WarnInconsistentFlags                       -- ^ @since 9.8
+   | Opt_WarnDataKindsTC                             -- ^ @since 9.10
+   | Opt_WarnDefaultedExceptionContext               -- ^ @since 9.10
+   | Opt_WarnViewPatternSignatures                   -- ^ @since 9.12
    deriving (Eq, Ord, Show, Enum, Bounded)
 
 -- | Return the names of a WarningFlag
@@ -1253,7 +1257,7 @@ warningGroupIncludesExtendedWarnings W_everything        = True
 
 -- | Warning groups.
 --
--- As all warnings are in the Weverything set, it is ignored when
+-- As all warnings are in the 'W_everything' set, it is ignored when
 -- displaying to the user which group a warning is in.
 warningGroups :: [WarningGroup]
 warningGroups = [minBound..maxBound]
@@ -1268,7 +1272,7 @@ warningGroups = [minBound..maxBound]
 -- Separating this from 'warningGroups' allows for multiple
 -- hierarchies with no inherent relation to be defined.
 --
--- The special-case Weverything group is not included.
+-- The special-case 'W_everything' group is not included.
 warningHierarchies :: [[WarningGroup]]
 warningHierarchies = hierarchies ++ map (:[]) rest
   where
@@ -1338,7 +1342,7 @@ standardWarnings -- see Note [Documenting warning flags]
         Opt_WarnViewPatternSignatures
       ]
 
--- | Things you get with -W
+-- | Things you get with @-W at .
 minusWOpts :: [WarningFlag]
 minusWOpts
     = standardWarnings ++
@@ -1354,7 +1358,7 @@ minusWOpts
         Opt_WarnUnbangedStrictPatterns
       ]
 
--- | Things you get with -Wall
+-- | Things you get with @-Wall at .
 minusWallOpts :: [WarningFlag]
 minusWallOpts
     = minusWOpts ++
@@ -1375,11 +1379,11 @@ minusWallOpts
         Opt_WarnDerivingTypeable
       ]
 
--- | Things you get with -Weverything, i.e. *all* known warnings flags
+-- | Things you get with @-Weverything@, i.e. *all* known warnings flags.
 minusWeverythingOpts :: [WarningFlag]
 minusWeverythingOpts = [ toEnum 0 .. ]
 
--- | Things you get with -Wcompat.
+-- | Things you get with @-Wcompat at .
 --
 -- This is intended to group together warnings that will be enabled by default
 -- at some point in the future, so that library authors eager to make their
@@ -1389,7 +1393,7 @@ minusWcompatOpts
     = [ Opt_WarnImplicitRhsQuantification
       ]
 
--- | Things you get with -Wunused-binds
+-- | Things you get with @-Wunused-binds at .
 unusedBindsFlags :: [WarningFlag]
 unusedBindsFlags = [ Opt_WarnUnusedTopBinds
                    , Opt_WarnUnusedLocalBinds



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/60bafd219638de2dec49c1342d50672542af8d62
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/20250312/f09624d7/attachment-0001.html>


More information about the ghc-commits mailing list