From c561de8f2caad53d93fb272c6fcb4593eb5a15c8 Mon Sep 17 00:00:00 2001
From: Jade <Nils.Jadefalke@gmail.com>
Date: Thu, 28 Mar 2024 00:28:45 +0100
Subject: [PATCH] Improve suggestions for language extensions

- When suggesting Language extensions, also suggest Extensions which imply them
- Suggest ExplicitForAll and GADTSyntax instead of more specific
  extensions
- Rephrase suggestion to include the term 'Extension'
- Also moves some flag specific definitions out of Session.hs into
Flags.hs (#24478)

Fixes: #24477
Fixes: #24448
Fixes: #10893
---
 compiler/GHC/Driver/DynFlags.hs               |   4 -
 compiler/GHC/Driver/Flags.hs                  | 345 ++++++++++++++++++
 compiler/GHC/Driver/Session.hs                | 340 ++---------------
 compiler/GHC/Parser/Errors/Ppr.hs             |  11 +-
 compiler/GHC/Tc/Errors/Ppr.hs                 |   2 +-
 compiler/GHC/Types/Hint/Ppr.hs                |  34 +-
 compiler/GHC/Utils/Outputable.hs              |  12 +-
 .../tests/dependent/should_fail/T15215.stderr |   3 +-
 .../tests/dependent/should_fail/T15859.stderr |   3 +-
 .../dependent/should_fail/T16326_Fail1.stderr |   6 +-
 .../should_fail/T16326_Fail10.stderr          |   3 +-
 .../should_fail/T16326_Fail11.stderr          |   3 +-
 .../dependent/should_fail/T16326_Fail2.stderr |   3 +-
 .../dependent/should_fail/T16326_Fail3.stderr |   3 +-
 .../dependent/should_fail/T16326_Fail4.stderr |   3 +-
 .../dependent/should_fail/T16326_Fail5.stderr |   3 +-
 .../dependent/should_fail/T16326_Fail7.stderr |   6 +-
 .../dependent/should_fail/T16326_Fail9.stderr |   3 +-
 .../tests/dependent/should_fail/T17687.stderr |   3 +-
 .../deriving/should_compile/T16179.stderr     |   2 +-
 .../deriving/should_fail/T10598_fail2.stderr  |   5 +-
 .../deriving/should_fail/T10598_fail4.stderr  |   3 +-
 .../deriving/should_fail/T10598_fail5.stderr  |   3 +-
 .../tests/deriving/should_fail/T1133A.stderr  |   2 +-
 .../tests/deriving/should_fail/T12512.stderr  |   6 +-
 .../tests/deriving/should_fail/T19692.stderr  |  39 +-
 .../tests/deriving/should_fail/T3833.stderr   |   2 +-
 .../tests/deriving/should_fail/T3834.stderr   |   2 +-
 .../deriving/should_fail/T7401_fail.stderr    |   2 +-
 .../tests/deriving/should_fail/T7959.stderr   |   3 +-
 .../deriving/should_fail/T8165_fail2.stderr   |   3 +-
 .../tests/deriving/should_fail/T9600.stderr   |   2 +-
 .../should_fail/deriving-via-fail3.stderr     |   3 +-
 .../deriving/should_fail/drvfail008.stderr    |   2 +-
 .../deriving/should_fail/drvfail015.stderr    |   3 +-
 testsuite/tests/driver/T11381.stderr          |   9 +-
 testsuite/tests/driver/json.stderr            |   2 +-
 testsuite/tests/ffi/should_fail/T10461.stderr |   3 +-
 testsuite/tests/ffi/should_fail/T20116.stderr |   3 +-
 .../tests/ffi/should_fail/ccfail001.stderr    |   5 +-
 testsuite/tests/gadt/T20485.stderr            |   6 +-
 testsuite/tests/gadt/gadtSyntaxFail001.stderr |   2 +-
 testsuite/tests/gadt/gadtSyntaxFail002.stderr |   2 +-
 testsuite/tests/gadt/gadtSyntaxFail003.stderr |   2 +-
 .../T10604/T10604_no_PolyKinds.stderr         |   3 +-
 testsuite/tests/generics/T5462No1.stderr      |   5 +-
 testsuite/tests/ghci/prog006/prog006.stderr   |   2 +-
 testsuite/tests/ghci/prog011/prog011.stderr   |   2 +-
 testsuite/tests/ghci/scripts/T13202a.stderr   |   2 +-
 testsuite/tests/ghci/scripts/T14969.stderr    |   2 +-
 testsuite/tests/ghci/scripts/T23686.stderr    |   7 +-
 testsuite/tests/ghci/scripts/T9293.stderr     |   8 +-
 testsuite/tests/ghci/scripts/ghci057.stderr   |   8 +-
 .../tests/ghci/should_run/T10857a.stdout      |   2 +-
 testsuite/tests/ghci/should_run/T15806.stderr |   2 +-
 .../should_fail/BadFamInstDecl.stderr         |   9 +-
 .../should_fail/NotRelaxedExamples.stderr     |   9 +-
 .../should_fail/SimpleFail15.stderr           |   3 +-
 .../indexed-types/should_fail/T10817.stderr   |   3 +-
 .../indexed-types/should_fail/T13571.stderr   |   3 +-
 .../indexed-types/should_fail/T13571a.stderr  |   3 +-
 .../indexed-types/should_fail/T15172.stderr   |   3 +-
 .../should_fail/TyFamUndec.stderr             |   9 +-
 .../linear/should_fail/LinearNoExt.stderr     |   3 +-
 .../linear/should_fail/LinearNoExtU.stderr    |   3 +-
 .../tests/linear/should_fail/T18888.stderr    |   7 +-
 .../tests/mdo/should_fail/mdofail005.stderr   |   3 +-
 testsuite/tests/module/T20007.stderr          |   6 +-
 testsuite/tests/module/mod182.stderr          |   3 +-
 testsuite/tests/module/mod184.stderr          |   2 +-
 testsuite/tests/module/mod39.stderr           |   3 +-
 testsuite/tests/module/mod40.stderr           |   6 +-
 testsuite/tests/module/mod41.stderr           |   3 +-
 testsuite/tests/module/mod42.stderr           |   3 +-
 testsuite/tests/module/mod43.stderr           |   3 +-
 testsuite/tests/module/mod45.stderr           |   3 +-
 testsuite/tests/module/mod53.stderr           |   3 +-
 .../tests/numeric/should_compile/T8542.stderr |   2 +-
 .../should_fail/NoFieldSelectorsFail.stderr   |   9 +-
 .../T18999_NoDisambiguateRecordFields.stderr  |   3 +-
 .../overloadedrecfldsfail10.stderr            |   6 +-
 .../should_fail/ListTuplePunsFail1.stderr     |  27 +-
 .../should_fail/NoBlockArgumentsFail.stderr   |   2 +-
 .../should_fail/NoBlockArgumentsFail2.stderr  |   2 +-
 .../should_fail/NoBlockArgumentsFail3.stderr  |   2 +-
 .../NoBlockArgumentsFailArrowCmds.stderr      |   2 +-
 .../should_fail/NoDoAndIfThenElse.stderr      |   3 +-
 .../should_fail/NoNumericUnderscores0.stderr  |   3 +-
 .../should_fail/NoNumericUnderscores1.stderr  |   3 +-
 .../should_fail/NoPatternSynonyms.stderr      |   3 +-
 .../NondecreasingIndentationFail.stderr       |  10 +-
 .../should_fail/ParserNoForallUnicode.stderr  |   6 +-
 .../should_fail/ParserNoLambdaCase.stderr     |   3 +-
 .../should_fail/ParserNoMultiWayIf.stderr     |   3 +-
 .../parser/should_fail/ParserNoTH1.stderr     |   3 +-
 .../parser/should_fail/ParserNoTH2.stderr     |   3 +-
 .../should_fail/RecordDotSyntaxFail12.stderr  |   9 +-
 .../should_fail/RecordDotSyntaxFail2.stderr   |   3 +-
 .../should_fail/RecordWildCardsFail.stderr    |   3 +-
 .../tests/parser/should_fail/T12429.stderr    |   3 +-
 .../tests/parser/should_fail/T12446.stderr    |   3 +-
 .../tests/parser/should_fail/T12811.stderr    |   3 +-
 .../tests/parser/should_fail/T14588.stderr    |   3 +-
 .../tests/parser/should_fail/T16270.stderr    |  41 ++-
 .../tests/parser/should_fail/T16270h.stderr   |   3 +-
 .../tests/parser/should_fail/T17162.stderr    |   3 +-
 .../tests/parser/should_fail/T18251c.stderr   |   3 +-
 .../tests/parser/should_fail/T18251e.stderr   |   2 +-
 .../tests/parser/should_fail/T20385A.stderr   |   2 +-
 .../tests/parser/should_fail/T20385B.stderr   |   2 +-
 .../tests/parser/should_fail/T3095.stderr     |   6 +-
 .../tests/parser/should_fail/T3811e.stderr    |   3 +-
 .../parser/should_fail/T8258NoGADTs.stderr    |   4 +-
 .../tests/parser/should_fail/T8501a.stderr    |   2 +-
 .../tests/parser/should_fail/T8501b.stderr    |   3 +-
 .../tests/parser/should_fail/T8501c.stderr    |   2 +-
 .../should_fail/ViewPatternsFail.stderr       |   3 +-
 .../parser/should_fail/proposal-229c.stderr   |   3 +-
 .../parser/should_fail/readFail001.stderr     |   4 +-
 .../parser/should_fail/readFail035.stderr     |   9 +-
 .../parser/should_fail/readFail036.stderr     |   7 +-
 .../parser/should_fail/readFail037.stderr     |   3 +-
 .../parser/should_fail/readFail038.stderr     |   5 +-
 .../parser/should_fail/readFail039.stderr     |   2 +-
 .../parser/should_fail/readFail040.stderr     |   3 +-
 .../parser/should_fail/readFail041.stderr     |   3 +-
 .../parser/should_fail/readFail042.stderr     |  10 +-
 .../parser/should_fail/readFail043.stderr     |  15 +-
 .../readFailTraditionalRecords1.stderr        |   3 +-
 .../readFailTraditionalRecords2.stderr        |   3 +-
 .../readFailTraditionalRecords3.stderr        |   3 +-
 .../should_compile/T13324_compile2.stderr     |   2 +-
 .../patsyn/should_fail/export-syntax.stderr   |   3 +-
 testsuite/tests/polykinds/BadKindVar.stderr   |   7 +-
 testsuite/tests/polykinds/T12055a.stderr      |   3 +-
 testsuite/tests/polykinds/T14710.stderr       |  42 ++-
 testsuite/tests/polykinds/T16762b.stderr      |   4 +-
 testsuite/tests/polykinds/T7151.stderr        |   5 +-
 testsuite/tests/polykinds/T7433.stderr        |   3 +-
 .../tests/polykinds/TidyClassKinds.stderr     |   3 +-
 .../qualifieddo/should_fail/qdofail002.stderr |   6 +-
 .../quantified-constraints/T15231.stderr      |   3 +-
 .../quantified-constraints/T15316.stderr      |   3 +-
 .../tests/quotes/TH_double_splice.stderr      |   3 +-
 testsuite/tests/quotes/TH_top_splice.stderr   |   3 +-
 testsuite/tests/quotes/TTH_top_splice.stderr  |   3 +-
 .../rename/should_compile/T15798b.stderr      |   3 +-
 .../rename/should_compile/T15798c.stderr      |   3 +-
 .../tests/rename/should_compile/rn049.stderr  |   3 +-
 .../should_fail/PackageImportsDisabled.stderr |   6 +-
 .../should_fail/RnDefaultSigFail.stderr       |   3 +-
 .../rename/should_fail/RnEmptyCaseFail.stderr |  12 +-
 .../should_fail/RnEmptyStatementGroup1.stderr |   3 +-
 .../should_fail/RnPatternSynonymFail.stderr   |   3 +-
 .../RnUnexpectedStandaloneDeriving.stderr     |   3 +-
 .../tests/rename/should_fail/T11663.stderr    |  12 +-
 .../tests/rename/should_fail/T13568.stderr    |   2 +-
 .../tests/rename/should_fail/T14032c.stderr   |   6 +-
 .../tests/rename/should_fail/T17594b.stderr   |  63 ++--
 .../tests/rename/should_fail/T20147.stderr    |   3 +-
 .../tests/rename/should_fail/T22478e.stderr   |  48 ++-
 .../tests/rename/should_fail/T3265.stderr     |   6 +-
 .../tests/rename/should_fail/rnfail052.stderr |  18 +-
 .../tests/rename/should_fail/rnfail053.stderr |   2 +-
 .../tests/rename/should_fail/rnfail056.stderr |  10 +-
 .../tests/roles/should_fail/Roles5.stderr     |  29 +-
 .../tests/roles/should_fail/T8773.stderr      |   9 +-
 testsuite/tests/safeHaskell/ghci/p16.stderr   |   2 +-
 .../safeLanguage/SafeLang12.stderr            |   3 +-
 .../tests/saks/should_fail/T16722.stderr      |   7 +-
 .../saks/should_fail/saks_fail001.stderr      |   3 +-
 testsuite/tests/th/T12411.stderr              |   3 +-
 testsuite/tests/th/T14204.stderr              |   5 +-
 testsuite/tests/th/T16133.stderr              |   6 +-
 testsuite/tests/th/TH_Promoted1Tuple.stderr   |   3 +-
 testsuite/tests/th/TH_Roles1.stderr           |   3 +-
 .../type-data/should_fail/TDNoPragma.stderr   |   4 +-
 .../typecheck/should_compile/T15473.stderr    |   3 +-
 .../typecheck/should_compile/T15839a.stderr   |   2 +-
 .../typecheck/should_compile/T22141a.stderr   |   3 +-
 .../typecheck/should_compile/T22141b.stderr   |   3 +-
 .../typecheck/should_compile/T22141c.stderr   |  15 +-
 .../typecheck/should_compile/T22141d.stderr   |  15 +-
 .../typecheck/should_compile/T22141e.stderr   |   9 +-
 .../should_fail/LazyFieldsDisabled.stderr     |  10 +-
 .../tests/typecheck/should_fail/T10351.stderr |   3 +-
 .../tests/typecheck/should_fail/T11355.stderr |   3 +-
 .../typecheck/should_fail/T12083a.stderr      |   5 +-
 .../typecheck/should_fail/T12083b.stderr      |   3 +-
 .../tests/typecheck/should_fail/T12729.stderr |   3 +-
 .../tests/typecheck/should_fail/T15527.stderr |   3 +-
 .../typecheck/should_fail/T15552a.stderr      |   9 +-
 .../tests/typecheck/should_fail/T15883.stderr |   3 +-
 .../typecheck/should_fail/T16059c.stderr      |   3 +-
 .../typecheck/should_fail/T16059d.stderr      |   3 +-
 .../typecheck/should_fail/T16059e.stderr      |   3 +-
 .../typecheck/should_fail/T16512b.stderr      |   3 +-
 .../typecheck/should_fail/T16829a.stderr      |   3 +-
 .../typecheck/should_fail/T16829b.stderr      |   3 +-
 .../tests/typecheck/should_fail/T17213.stderr |   3 +-
 .../tests/typecheck/should_fail/T17563.stderr |   3 +-
 .../typecheck/should_fail/T18939_Fail.stderr  |   3 +-
 .../tests/typecheck/should_fail/T19109.stderr |   3 +-
 .../tests/typecheck/should_fail/T19187.stderr |   3 +-
 .../typecheck/should_fail/T19187a.stderr      |   3 +-
 .../typecheck/should_fail/T20873c.stderr      |   3 +-
 .../typecheck/should_fail/T20873d.stderr      |   3 +-
 .../should_fail/T22560_fail_ext.stderr        |   6 +-
 .../tests/typecheck/should_fail/T23776.stderr |   3 +-
 .../tests/typecheck/should_fail/T2538.stderr  |   9 +-
 .../tests/typecheck/should_fail/T3155.stderr  |   6 +-
 .../tests/typecheck/should_fail/T5957.stderr  |   3 +-
 .../tests/typecheck/should_fail/T6022.stderr  |   3 +-
 .../tests/typecheck/should_fail/T7019.stderr  |   3 +-
 .../tests/typecheck/should_fail/T7019a.stderr |   3 +-
 .../tests/typecheck/should_fail/T7809.stderr  |   3 +-
 .../tests/typecheck/should_fail/T8883.stderr  |   3 +-
 .../tests/typecheck/should_fail/T9196.stderr  |   6 +-
 .../tests/typecheck/should_fail/T9415.stderr  |   6 +-
 .../tests/typecheck/should_fail/T9739.stderr  |   6 +-
 .../should_fail/TcNoNullaryTC.stderr          |   3 +-
 .../should_fail/TyfamsDisabled.stderr         |  10 +-
 .../UnliftedNewtypesNotEnabled.stderr         |   3 +-
 .../typecheck/should_fail/fd-loop.stderr      |   3 +-
 .../typecheck/should_fail/tcfail027.stderr    |   6 +-
 .../typecheck/should_fail/tcfail044.stderr    |   6 +-
 .../typecheck/should_fail/tcfail047.stderr    |   3 +-
 .../typecheck/should_fail/tcfail079.stderr    |   3 +-
 .../typecheck/should_fail/tcfail094.stderr    |   5 +-
 .../typecheck/should_fail/tcfail108.stderr    |   3 +-
 .../typecheck/should_fail/tcfail117.stderr    |   2 +-
 .../typecheck/should_fail/tcfail127.stderr    |   3 +-
 .../typecheck/should_fail/tcfail139.stderr    |   3 +-
 .../typecheck/should_fail/tcfail150.stderr    |   3 +-
 .../typecheck/should_fail/tcfail154.stderr    |   3 +-
 .../typecheck/should_fail/tcfail157.stderr    |   3 +-
 .../typecheck/should_fail/tcfail166.stderr    |   6 +-
 .../typecheck/should_fail/tcfail173.stderr    |   3 +-
 .../typecheck/should_fail/tcfail183.stderr    |   6 +-
 .../typecheck/should_fail/tcfail184.stderr    |   3 +-
 .../typecheck/should_fail/tcfail196.stderr    |   3 +-
 .../typecheck/should_fail/tcfail197.stderr    |   3 +-
 .../typecheck/should_fail/tcfail209.stderr    |   3 +-
 .../typecheck/should_fail/tcfail209a.stderr   |   3 +-
 .../typecheck/should_fail/tcfail213.stderr    |   3 +-
 .../typecheck/should_fail/tcfail214.stderr    |   3 +-
 .../typecheck/should_fail/tcfail216.stderr    |   3 +-
 .../typecheck/should_fail/tcfail217.stderr    |   3 +-
 .../should_fail/T22326_fail_ext1.stderr       |   3 +-
 .../should_fail/T22326_fail_ext2.stderr       |   3 +-
 .../warnings/should_compile/T18862a.stderr    |   3 +-
 .../tests/warnings/should_fail/T24396c.stderr |  12 +-
 .../wcompat-warnings/WCompatWarningsOn.stderr |   3 +-
 253 files changed, 1218 insertions(+), 799 deletions(-)

diff --git a/compiler/GHC/Driver/DynFlags.hs b/compiler/GHC/Driver/DynFlags.hs
index 85fb5c99dcb0..418237be7c6e 100644
--- a/compiler/GHC/Driver/DynFlags.hs
+++ b/compiler/GHC/Driver/DynFlags.hs
@@ -1304,10 +1304,6 @@ optLevelFlags -- see Note [Documenting optimisation flags]
 --   Static Argument Transformation needs investigation. See #9374
     ]
 
-type TurnOnFlag = Bool   -- True  <=> we are turning the flag on
-                         -- False <=> we are turning the flag off
-turnOn  :: TurnOnFlag; turnOn  = True
-turnOff :: TurnOnFlag; turnOff = False
 
 default_PIC :: Platform -> [GeneralFlag]
 default_PIC platform =
diff --git a/compiler/GHC/Driver/Flags.hs b/compiler/GHC/Driver/Flags.hs
index d2117779e677..c14acdb60c62 100644
--- a/compiler/GHC/Driver/Flags.hs
+++ b/compiler/GHC/Driver/Flags.hs
@@ -1,3 +1,5 @@
+{-# LANGUAGE LambdaCase #-}
+
 module GHC.Driver.Flags
    ( DumpFlag(..)
    , getDumpFlagFrom
@@ -26,6 +28,22 @@ module GHC.Driver.Flags
    , minusWeverythingOpts
    , minusWcompatOpts
    , unusedBindsFlags
+
+   , TurnOnFlag
+   , turnOn
+   , turnOff
+   , impliedXFlags
+   , validHoleFitsImpliedGFlags
+   , impliedGFlags
+   , impliedOffGFlags
+   , glasgowExtsFlags
+
+   , ExtensionDeprecation(..)
+   , Deprecation(..)
+   , extensionDeprecation
+   , deprecation
+   , extensionNames
+   , extensionName
    )
 where
 
@@ -39,6 +57,8 @@ import Control.Monad (guard)
 import Data.List.NonEmpty (NonEmpty(..))
 import Data.Maybe (fromMaybe,mapMaybe)
 
+import qualified GHC.LanguageExtensions as LangExt
+
 data Language = Haskell98 | Haskell2010 | GHC2021 | GHC2024
    deriving (Eq, Enum, Show, Bounded)
 
@@ -57,6 +77,331 @@ instance Binary Language where
 instance NFData Language where
   rnf x = x `seq` ()
 
+type TurnOnFlag = Bool   -- True  <=> we are turning the flag on
+                         -- False <=> we are turning the flag off
+turnOn  :: TurnOnFlag; turnOn  = True
+turnOff :: TurnOnFlag; turnOff = False
+
+data Deprecation = NotDeprecated | Deprecated deriving (Eq, Ord)
+
+data ExtensionDeprecation
+  = ExtensionNotDeprecated
+  | ExtensionDeprecatedFor [LangExt.Extension]
+  | ExtensionFlagDeprecatedCond TurnOnFlag String
+  | ExtensionFlagDeprecated String
+  deriving Eq
+
+-- | Always returns 'Deprecated' even when the flag is
+-- only conditionally deprecated.
+deprecation :: ExtensionDeprecation -> Deprecation
+deprecation ExtensionNotDeprecated = NotDeprecated
+deprecation _ = Deprecated
+
+extensionDeprecation :: LangExt.Extension -> ExtensionDeprecation
+extensionDeprecation = \case
+  LangExt.TypeInType           -> ExtensionDeprecatedFor [LangExt.DataKinds, LangExt.PolyKinds]
+  LangExt.NullaryTypeClasses   -> ExtensionDeprecatedFor [LangExt.MultiParamTypeClasses]
+  LangExt.RelaxedPolyRec       -> ExtensionFlagDeprecatedCond turnOff
+                                    "You can't turn off RelaxedPolyRec any more"
+  LangExt.DatatypeContexts     -> ExtensionFlagDeprecatedCond turnOn
+                                    "It was widely considered a misfeature, and has been removed from the Haskell language."
+  LangExt.AutoDeriveTypeable   -> ExtensionFlagDeprecatedCond turnOn
+                                    "Typeable instances are created automatically for all types since GHC 8.2."
+  LangExt.OverlappingInstances -> ExtensionFlagDeprecated
+                                    "instead use per-instance pragmas OVERLAPPING/OVERLAPPABLE/OVERLAPS"
+  _                            -> ExtensionNotDeprecated
+
+
+extensionName :: LangExt.Extension -> String
+extensionName = \case
+  LangExt.Cpp -> "CPP"
+  LangExt.OverlappingInstances -> "OverlappingInstances"
+  LangExt.UndecidableInstances -> "UndecidableInstances"
+  LangExt.IncoherentInstances -> "IncoherentInstances"
+  LangExt.UndecidableSuperClasses -> "UndecidableSuperClasses"
+  LangExt.MonomorphismRestriction -> "MonomorphismRestriction"
+  LangExt.MonoLocalBinds -> "MonoLocalBinds"
+  LangExt.DeepSubsumption -> "DeepSubsumption"
+  LangExt.RelaxedPolyRec -> "RelaxedPolyRec"           -- Deprecated
+  LangExt.ExtendedDefaultRules -> "ExtendedDefaultRules"     -- Use GHC's extended rules for defaulting
+  LangExt.ForeignFunctionInterface -> "ForeignFunctionInterface"
+  LangExt.UnliftedFFITypes -> "UnliftedFFITypes"
+  LangExt.InterruptibleFFI -> "InterruptibleFFI"
+  LangExt.CApiFFI -> "CApiFFI"
+  LangExt.GHCForeignImportPrim -> "GHCForeignImportPrim"
+  LangExt.JavaScriptFFI -> "JavaScriptFFI"
+  LangExt.ParallelArrays -> "ParallelArrays"           -- Syntactic support for parallel arrays
+  LangExt.Arrows -> "Arrows"                   -- Arrow-notation syntax
+  LangExt.TemplateHaskell -> "TemplateHaskell"
+  LangExt.TemplateHaskellQuotes -> "TemplateHaskellQuotes"    -- subset of TH supported by stage1, no splice
+  LangExt.QualifiedDo -> "QualifiedDo"
+  LangExt.QuasiQuotes -> "QuasiQuotes"
+  LangExt.ImplicitParams -> "ImplicitParams"
+  LangExt.ImplicitPrelude -> "ImplicitPrelude"
+  LangExt.ScopedTypeVariables -> "ScopedTypeVariables"
+  LangExt.AllowAmbiguousTypes -> "AllowAmbiguousTypes"
+  LangExt.UnboxedTuples -> "UnboxedTuples"
+  LangExt.UnboxedSums -> "UnboxedSums"
+  LangExt.UnliftedNewtypes -> "UnliftedNewtypes"
+  LangExt.UnliftedDatatypes -> "UnliftedDatatypes"
+  LangExt.BangPatterns -> "BangPatterns"
+  LangExt.TypeFamilies -> "TypeFamilies"
+  LangExt.TypeFamilyDependencies -> "TypeFamilyDependencies"
+  LangExt.TypeInType -> "TypeInType"               -- Deprecated
+  LangExt.OverloadedStrings -> "OverloadedStrings"
+  LangExt.OverloadedLists -> "OverloadedLists"
+  LangExt.NumDecimals -> "NumDecimals"
+  LangExt.DisambiguateRecordFields -> "DisambiguateRecordFields"
+  LangExt.RecordWildCards -> "RecordWildCards"
+  LangExt.NamedFieldPuns -> "NamedFieldPuns"
+  LangExt.ViewPatterns -> "ViewPatterns"
+  LangExt.GADTs -> "GADTs"
+  LangExt.GADTSyntax -> "GADTSyntax"
+  LangExt.NPlusKPatterns -> "NPlusKPatterns"
+  LangExt.DoAndIfThenElse -> "DoAndIfThenElse"
+  LangExt.BlockArguments -> "BlockArguments"
+  LangExt.RebindableSyntax -> "RebindableSyntax"
+  LangExt.ConstraintKinds -> "ConstraintKinds"
+  LangExt.PolyKinds -> "PolyKinds"                -- Kind polymorphism
+  LangExt.DataKinds -> "DataKinds"                -- Datatype promotion
+  LangExt.TypeData -> "TypeData"                 -- allow @type data@ definitions
+  LangExt.InstanceSigs -> "InstanceSigs"
+  LangExt.ApplicativeDo -> "ApplicativeDo"
+  LangExt.LinearTypes -> "LinearTypes"
+  LangExt.RequiredTypeArguments -> "RequiredTypeArguments"    -- Visible forall (VDQ) in types of terms
+  LangExt.StandaloneDeriving -> "StandaloneDeriving"
+  LangExt.DeriveDataTypeable -> "DeriveDataTypeable"
+  LangExt.AutoDeriveTypeable -> "AutoDeriveTypeable"       -- Automatic derivation of Typeable
+  LangExt.DeriveFunctor -> "DeriveFunctor"
+  LangExt.DeriveTraversable -> "DeriveTraversable"
+  LangExt.DeriveFoldable -> "DeriveFoldable"
+  LangExt.DeriveGeneric -> "DeriveGeneric"            -- Allow deriving Generic/1
+  LangExt.DefaultSignatures -> "DefaultSignatures"        -- Allow extra signatures for defmeths
+  LangExt.DeriveAnyClass -> "DeriveAnyClass"           -- Allow deriving any class
+  LangExt.DeriveLift -> "DeriveLift"               -- Allow deriving Lift
+  LangExt.DerivingStrategies -> "DerivingStrategies"
+  LangExt.DerivingVia -> "DerivingVia"              -- Derive through equal representation
+  LangExt.TypeSynonymInstances -> "TypeSynonymInstances"
+  LangExt.FlexibleContexts -> "FlexibleContexts"
+  LangExt.FlexibleInstances -> "FlexibleInstances"
+  LangExt.ConstrainedClassMethods -> "ConstrainedClassMethods"
+  LangExt.MultiParamTypeClasses -> "MultiParamTypeClasses"
+  LangExt.NullaryTypeClasses -> "NullaryTypeClasses"
+  LangExt.FunctionalDependencies -> "FunctionalDependencies"
+  LangExt.UnicodeSyntax -> "UnicodeSyntax"
+  LangExt.ExistentialQuantification -> "ExistentialQuantification"
+  LangExt.MagicHash -> "MagicHash"
+  LangExt.EmptyDataDecls -> "EmptyDataDecls"
+  LangExt.KindSignatures -> "KindSignatures"
+  LangExt.RoleAnnotations -> "RoleAnnotations"
+  LangExt.ParallelListComp -> "ParallelListComp"
+  LangExt.TransformListComp -> "TransformListComp"
+  LangExt.MonadComprehensions -> "MonadComprehensions"
+  LangExt.GeneralizedNewtypeDeriving -> "GeneralizedNewtypeDeriving"
+  LangExt.RecursiveDo -> "RecursiveDo"
+  LangExt.PostfixOperators -> "PostfixOperators"
+  LangExt.TupleSections -> "TupleSections"
+  LangExt.PatternGuards -> "PatternGuards"
+  LangExt.LiberalTypeSynonyms -> "LiberalTypeSynonyms"
+  LangExt.RankNTypes -> "RankNTypes"
+  LangExt.ImpredicativeTypes -> "ImpredicativeTypes"
+  LangExt.TypeOperators -> "TypeOperators"
+  LangExt.ExplicitNamespaces -> "ExplicitNamespaces"
+  LangExt.PackageImports -> "PackageImports"
+  LangExt.ExplicitForAll -> "ExplicitForAll"
+  LangExt.AlternativeLayoutRule -> "AlternativeLayoutRule"
+  LangExt.AlternativeLayoutRuleTransitional -> "AlternativeLayoutRuleTransitional"
+  LangExt.DatatypeContexts -> "DatatypeContexts"
+  LangExt.NondecreasingIndentation -> "NondecreasingIndentation"
+  LangExt.RelaxedLayout -> "RelaxedLayout"
+  LangExt.TraditionalRecordSyntax -> "TraditionalRecordSyntax"
+  LangExt.LambdaCase -> "LambdaCase"
+  LangExt.MultiWayIf -> "MultiWayIf"
+  LangExt.BinaryLiterals -> "BinaryLiterals"
+  LangExt.NegativeLiterals -> "NegativeLiterals"
+  LangExt.HexFloatLiterals -> "HexFloatLiterals"
+  LangExt.DuplicateRecordFields -> "DuplicateRecordFields"
+  LangExt.OverloadedLabels -> "OverloadedLabels"
+  LangExt.EmptyCase -> "EmptyCase"
+  LangExt.PatternSynonyms -> "PatternSynonyms"
+  LangExt.PartialTypeSignatures -> "PartialTypeSignatures"
+  LangExt.NamedWildCards -> "NamedWildCards"
+  LangExt.StaticPointers -> "StaticPointers"
+  LangExt.TypeApplications -> "TypeApplications"
+  LangExt.Strict -> "Strict"
+  LangExt.StrictData -> "StrictData"
+  LangExt.EmptyDataDeriving -> "EmptyDataDeriving"
+  LangExt.NumericUnderscores -> "NumericUnderscores"
+  LangExt.QuantifiedConstraints -> "QuantifiedConstraints"
+  LangExt.StarIsType -> "StarIsType"
+  LangExt.ImportQualifiedPost -> "ImportQualifiedPost"
+  LangExt.CUSKs -> "CUSKs"
+  LangExt.StandaloneKindSignatures -> "StandaloneKindSignatures"
+  LangExt.LexicalNegation -> "LexicalNegation"
+  LangExt.FieldSelectors -> "FieldSelectors"
+  LangExt.OverloadedRecordDot -> "OverloadedRecordDot"
+  LangExt.OverloadedRecordUpdate -> "OverloadedRecordUpdate"
+  LangExt.TypeAbstractions -> "TypeAbstractions"
+  LangExt.ExtendedLiterals -> "ExtendedLiterals"
+  LangExt.ListTuplePuns -> "ListTuplePuns"
+
+-- | Is this extension known by any other names? For example
+-- -XGeneralizedNewtypeDeriving is accepted
+extensionAlternateNames :: LangExt.Extension -> [String]
+extensionAlternateNames = \case
+  LangExt.GeneralizedNewtypeDeriving -> ["GeneralisedNewtypeDeriving"]
+  LangExt.RankNTypes                 -> ["Rank2Types", "PolymorphicComponents"]
+  _ -> []
+
+extensionDeprecatedNames :: LangExt.Extension -> [String]
+extensionDeprecatedNames = \case
+  LangExt.RecursiveDo         -> ["DoRec"]
+  LangExt.NamedFieldPuns      -> ["RecordPuns"]
+  LangExt.ScopedTypeVariables -> ["PatternSignatures"]
+  _ -> []
+
+-- | All the names by which an extension is known.
+extensionNames :: LangExt.Extension -> [ (ExtensionDeprecation, String) ]
+extensionNames ext = mk (extensionDeprecation ext)     (extensionName ext : extensionAlternateNames ext)
+                  ++ mk (ExtensionDeprecatedFor [ext]) (extensionDeprecatedNames ext)
+  where mk depr = map (\name -> (depr, name))
+
+
+impliedXFlags :: [(LangExt.Extension, TurnOnFlag, LangExt.Extension)]
+impliedXFlags
+-- See Note [Updating flag description in the User's Guide]
+  = [ (LangExt.RankNTypes,                turnOn, LangExt.ExplicitForAll)
+    , (LangExt.QuantifiedConstraints,     turnOn, LangExt.ExplicitForAll)
+    , (LangExt.ScopedTypeVariables,       turnOn, LangExt.ExplicitForAll)
+    , (LangExt.LiberalTypeSynonyms,       turnOn, LangExt.ExplicitForAll)
+    , (LangExt.ExistentialQuantification, turnOn, LangExt.ExplicitForAll)
+    , (LangExt.FlexibleInstances,         turnOn, LangExt.TypeSynonymInstances)
+    , (LangExt.FunctionalDependencies,    turnOn, LangExt.MultiParamTypeClasses)
+    , (LangExt.MultiParamTypeClasses,     turnOn, LangExt.ConstrainedClassMethods)  -- c.f. #7854
+    , (LangExt.TypeFamilyDependencies,    turnOn, LangExt.TypeFamilies)
+
+    , (LangExt.RebindableSyntax, turnOff, LangExt.ImplicitPrelude)      -- NB: turn off!
+
+    , (LangExt.DerivingVia, turnOn, LangExt.DerivingStrategies)
+
+    , (LangExt.GADTs,            turnOn, LangExt.GADTSyntax)
+    , (LangExt.GADTs,            turnOn, LangExt.MonoLocalBinds)
+    , (LangExt.TypeFamilies,     turnOn, LangExt.MonoLocalBinds)
+
+    , (LangExt.TypeFamilies,     turnOn, LangExt.KindSignatures)  -- Type families use kind signatures
+    , (LangExt.PolyKinds,        turnOn, LangExt.KindSignatures)  -- Ditto polymorphic kinds
+
+    -- TypeInType is now just a synonym for a couple of other extensions.
+    , (LangExt.TypeInType,       turnOn, LangExt.DataKinds)
+    , (LangExt.TypeInType,       turnOn, LangExt.PolyKinds)
+    , (LangExt.TypeInType,       turnOn, LangExt.KindSignatures)
+
+    -- Standalone kind signatures are a replacement for CUSKs.
+    , (LangExt.StandaloneKindSignatures, turnOff, LangExt.CUSKs)
+
+    -- AutoDeriveTypeable is not very useful without DeriveDataTypeable
+    , (LangExt.AutoDeriveTypeable, turnOn, LangExt.DeriveDataTypeable)
+
+    -- We turn this on so that we can export associated type
+    -- type synonyms in subordinates (e.g. MyClass(type AssocType))
+    , (LangExt.TypeFamilies,     turnOn, LangExt.ExplicitNamespaces)
+    , (LangExt.TypeOperators, turnOn, LangExt.ExplicitNamespaces)
+
+    , (LangExt.ImpredicativeTypes,  turnOn, LangExt.RankNTypes)
+
+        -- Record wild-cards implies field disambiguation
+        -- Otherwise if you write (C {..}) you may well get
+        -- stuff like " 'a' not in scope ", which is a bit silly
+        -- if the compiler has just filled in field 'a' of constructor 'C'
+    , (LangExt.RecordWildCards,     turnOn, LangExt.DisambiguateRecordFields)
+
+    , (LangExt.ParallelArrays, turnOn, LangExt.ParallelListComp)
+
+    , (LangExt.JavaScriptFFI, turnOn, LangExt.InterruptibleFFI)
+
+    , (LangExt.DeriveTraversable, turnOn, LangExt.DeriveFunctor)
+    , (LangExt.DeriveTraversable, turnOn, LangExt.DeriveFoldable)
+
+    -- Duplicate record fields require field disambiguation
+    , (LangExt.DuplicateRecordFields, turnOn, LangExt.DisambiguateRecordFields)
+
+    , (LangExt.TemplateHaskell, turnOn, LangExt.TemplateHaskellQuotes)
+    , (LangExt.Strict, turnOn, LangExt.StrictData)
+
+    -- Historically only UnboxedTuples was required for unboxed sums to work.
+    -- To avoid breaking code, we make UnboxedTuples imply UnboxedSums.
+    , (LangExt.UnboxedTuples, turnOn, LangExt.UnboxedSums)
+
+    -- The extensions needed to declare an H98 unlifted data type
+    , (LangExt.UnliftedDatatypes, turnOn, LangExt.DataKinds)
+    , (LangExt.UnliftedDatatypes, turnOn, LangExt.StandaloneKindSignatures)
+
+    -- See Note [Non-variable pattern bindings aren't linear] in GHC.Tc.Gen.Bind
+    , (LangExt.LinearTypes, turnOn, LangExt.MonoLocalBinds)
+  ]
+
+
+validHoleFitsImpliedGFlags :: [(GeneralFlag, TurnOnFlag, GeneralFlag)]
+validHoleFitsImpliedGFlags
+  = [ (Opt_UnclutterValidHoleFits, turnOff, Opt_ShowTypeAppOfHoleFits)
+    , (Opt_UnclutterValidHoleFits, turnOff, Opt_ShowTypeAppVarsOfHoleFits)
+    , (Opt_UnclutterValidHoleFits, turnOff, Opt_ShowDocsOfHoleFits)
+    , (Opt_ShowTypeAppVarsOfHoleFits, turnOff, Opt_ShowTypeAppOfHoleFits)
+    , (Opt_UnclutterValidHoleFits, turnOff, Opt_ShowProvOfHoleFits) ]
+
+-- General flags that are switched on/off when other general flags are switched
+-- on
+impliedGFlags :: [(GeneralFlag, TurnOnFlag, GeneralFlag)]
+impliedGFlags = [(Opt_DeferTypeErrors, turnOn, Opt_DeferTypedHoles)
+                ,(Opt_DeferTypeErrors, turnOn, Opt_DeferOutOfScopeVariables)
+                ,(Opt_DoLinearCoreLinting, turnOn, Opt_DoCoreLinting)
+                ,(Opt_Strictness, turnOn, Opt_WorkerWrapper)
+                ,(Opt_WriteIfSimplifiedCore, turnOn, Opt_WriteInterface)
+                ,(Opt_ByteCodeAndObjectCode, turnOn, Opt_WriteIfSimplifiedCore)
+                ,(Opt_InfoTableMap, turnOn, Opt_InfoTableMapWithStack)
+                ,(Opt_InfoTableMap, turnOn, Opt_InfoTableMapWithFallback)
+                ] ++ validHoleFitsImpliedGFlags
+
+-- 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
+glasgowExtsFlags :: [LangExt.Extension]
+glasgowExtsFlags = [
+             LangExt.ConstrainedClassMethods
+           , LangExt.DeriveDataTypeable
+           , LangExt.DeriveFoldable
+           , LangExt.DeriveFunctor
+           , LangExt.DeriveGeneric
+           , LangExt.DeriveTraversable
+           , LangExt.EmptyDataDecls
+           , LangExt.ExistentialQuantification
+           , LangExt.ExplicitNamespaces
+           , LangExt.FlexibleContexts
+           , LangExt.FlexibleInstances
+           , LangExt.ForeignFunctionInterface
+           , LangExt.FunctionalDependencies
+           , LangExt.GeneralizedNewtypeDeriving
+           , LangExt.ImplicitParams
+           , LangExt.KindSignatures
+           , LangExt.LiberalTypeSynonyms
+           , LangExt.MagicHash
+           , LangExt.MultiParamTypeClasses
+           , LangExt.ParallelListComp
+           , LangExt.PatternGuards
+           , LangExt.PostfixOperators
+           , LangExt.RankNTypes
+           , LangExt.RecursiveDo
+           , LangExt.ScopedTypeVariables
+           , LangExt.StandaloneDeriving
+           , LangExt.TypeOperators
+           , LangExt.TypeSynonymInstances
+           , LangExt.UnboxedTuples
+           , LangExt.UnicodeSyntax
+           , LangExt.UnliftedFFITypes ]
+
 -- | Debugging flags
 data DumpFlag
 -- See Note [Updating flag description in the User's Guide] in GHC.Driver.Session
diff --git a/compiler/GHC/Driver/Session.hs b/compiler/GHC/Driver/Session.hs
index 5ee4dadbec22..d60fd824adf6 100644
--- a/compiler/GHC/Driver/Session.hs
+++ b/compiler/GHC/Driver/Session.hs
@@ -992,7 +992,6 @@ flagsPackage = map snd package_flags_deps
 
 type FlagMaker m = String -> OptKind m -> Flag m
 type DynFlagMaker = FlagMaker (CmdLineP DynFlags)
-data Deprecation = NotDeprecated | Deprecated deriving (Eq, Ord)
 
 -- Make a non-deprecated flag
 make_ord_flag :: DynFlagMaker -> String -> OptKind (CmdLineP DynFlags)
@@ -2143,18 +2142,6 @@ depFlagSpec' :: String
              -> (Deprecation, FlagSpec flag)
 depFlagSpec' name flag dep = depFlagSpecOp' name flag nop dep
 
-
--- | Define a new deprecated flag where the deprecation message
--- is shown depending on the flag value
-depFlagSpecCond :: String
-                -> flag
-                -> (TurnOnFlag -> Bool)
-                -> String
-                -> (Deprecation, FlagSpec flag)
-depFlagSpecCond name flag cond dep =
-    (Deprecated, FlagSpec name flag (\f -> when (cond f) $ deprecate dep)
-                                                                       AllModes)
-
 -- | Define a new flag for GHCi.
 flagGhciSpec :: String -> flag -> (Deprecation, FlagSpec flag)
 flagGhciSpec name flag = flagGhciSpec' name flag nop
@@ -2679,269 +2666,38 @@ safeHaskellFlagsDeps = [mkF Sf_Unsafe, mkF Sf_Trustworthy, mkF Sf_Safe]
 xFlags :: [FlagSpec LangExt.Extension]
 xFlags = map snd xFlagsDeps
 
-xFlagsDeps :: [(Deprecation, FlagSpec LangExt.Extension)]
-xFlagsDeps = [
--- See Note [Updating flag description in the User's Guide]
--- See Note [Supporting CLI completion]
--- See Note [Adding a language extension]
--- Please keep the list of flags below sorted alphabetically
-  flagSpec "AllowAmbiguousTypes"              LangExt.AllowAmbiguousTypes,
-  flagSpec "AlternativeLayoutRule"            LangExt.AlternativeLayoutRule,
-  flagSpec "AlternativeLayoutRuleTransitional"
-                                              LangExt.AlternativeLayoutRuleTransitional,
-  flagSpec "Arrows"                           LangExt.Arrows,
-  depFlagSpecCond "AutoDeriveTypeable"        LangExt.AutoDeriveTypeable
-    id
-         ("Typeable instances are created automatically " ++
-                     "for all types since GHC 8.2."),
-  flagSpec "BangPatterns"                     LangExt.BangPatterns,
-  flagSpec "BinaryLiterals"                   LangExt.BinaryLiterals,
-  flagSpec "CApiFFI"                          LangExt.CApiFFI,
-  flagSpec "CPP"                              LangExt.Cpp,
-  flagSpec "CUSKs"                            LangExt.CUSKs,
-  flagSpec "ConstrainedClassMethods"          LangExt.ConstrainedClassMethods,
-  flagSpec "ConstraintKinds"                  LangExt.ConstraintKinds,
-  flagSpec "DataKinds"                        LangExt.DataKinds,
-  depFlagSpecCond "DatatypeContexts"          LangExt.DatatypeContexts
-    id
-         ("It was widely considered a misfeature, " ++
-                     "and has been removed from the Haskell language."),
-  flagSpec "DefaultSignatures"                LangExt.DefaultSignatures,
-  flagSpec "DeriveAnyClass"                   LangExt.DeriveAnyClass,
-  flagSpec "DeriveDataTypeable"               LangExt.DeriveDataTypeable,
-  flagSpec "DeriveFoldable"                   LangExt.DeriveFoldable,
-  flagSpec "DeriveFunctor"                    LangExt.DeriveFunctor,
-  flagSpec "DeriveGeneric"                    LangExt.DeriveGeneric,
-  flagSpec "DeriveLift"                       LangExt.DeriveLift,
-  flagSpec "DeriveTraversable"                LangExt.DeriveTraversable,
-  flagSpec "DerivingStrategies"               LangExt.DerivingStrategies,
-  flagSpec' "DerivingVia"                     LangExt.DerivingVia
-                                              setDeriveVia,
-  flagSpec "DisambiguateRecordFields"         LangExt.DisambiguateRecordFields,
-  flagSpec "DoAndIfThenElse"                  LangExt.DoAndIfThenElse,
-  flagSpec "BlockArguments"                   LangExt.BlockArguments,
-  depFlagSpec' "DoRec"                        LangExt.RecursiveDo
-    (deprecatedForExtension "RecursiveDo"),
-  flagSpec "DuplicateRecordFields"            LangExt.DuplicateRecordFields,
-  flagSpec "FieldSelectors"                   LangExt.FieldSelectors,
-  flagSpec "EmptyCase"                        LangExt.EmptyCase,
-  flagSpec "EmptyDataDecls"                   LangExt.EmptyDataDecls,
-  flagSpec "EmptyDataDeriving"                LangExt.EmptyDataDeriving,
-  flagSpec "ExistentialQuantification"        LangExt.ExistentialQuantification,
-  flagSpec "ExplicitForAll"                   LangExt.ExplicitForAll,
-  flagSpec "ExplicitNamespaces"               LangExt.ExplicitNamespaces,
-  flagSpec "ExtendedDefaultRules"             LangExt.ExtendedDefaultRules,
-  flagSpec "ExtendedLiterals"                 LangExt.ExtendedLiterals,
-  flagSpec "FlexibleContexts"                 LangExt.FlexibleContexts,
-  flagSpec "FlexibleInstances"                LangExt.FlexibleInstances,
-  flagSpec "ForeignFunctionInterface"         LangExt.ForeignFunctionInterface,
-  flagSpec "FunctionalDependencies"           LangExt.FunctionalDependencies,
-  flagSpec "GADTSyntax"                       LangExt.GADTSyntax,
-  flagSpec "GADTs"                            LangExt.GADTs,
-  flagSpec "GHCForeignImportPrim"             LangExt.GHCForeignImportPrim,
-  flagSpec' "GeneralizedNewtypeDeriving"      LangExt.GeneralizedNewtypeDeriving
-                                              setGenDeriving,
-  flagSpec' "GeneralisedNewtypeDeriving"      LangExt.GeneralizedNewtypeDeriving
-                                              setGenDeriving,
-  flagSpec "ImplicitParams"                   LangExt.ImplicitParams,
-  flagSpec "ImplicitPrelude"                  LangExt.ImplicitPrelude,
-  flagSpec "ImportQualifiedPost"              LangExt.ImportQualifiedPost,
-  flagSpec "ImpredicativeTypes"               LangExt.ImpredicativeTypes,
-  flagSpec' "IncoherentInstances"             LangExt.IncoherentInstances
-                                              setIncoherentInsts,
-  flagSpec "TypeFamilyDependencies"           LangExt.TypeFamilyDependencies,
-  flagSpec "InstanceSigs"                     LangExt.InstanceSigs,
-  flagSpec "ApplicativeDo"                    LangExt.ApplicativeDo,
-  flagSpec "InterruptibleFFI"                 LangExt.InterruptibleFFI,
-  flagSpec "JavaScriptFFI"                    LangExt.JavaScriptFFI,
-  flagSpec "KindSignatures"                   LangExt.KindSignatures,
-  flagSpec "LambdaCase"                       LangExt.LambdaCase,
-  flagSpec "LexicalNegation"                  LangExt.LexicalNegation,
-  flagSpec "LiberalTypeSynonyms"              LangExt.LiberalTypeSynonyms,
-  flagSpec "LinearTypes"                      LangExt.LinearTypes,
-  flagSpec "ListTuplePuns"                    LangExt.ListTuplePuns,
-  flagSpec "MagicHash"                        LangExt.MagicHash,
-  flagSpec "MonadComprehensions"              LangExt.MonadComprehensions,
-  flagSpec "MonoLocalBinds"                   LangExt.MonoLocalBinds,
-  flagSpec "DeepSubsumption"                  LangExt.DeepSubsumption,
-  flagSpec "MonomorphismRestriction"          LangExt.MonomorphismRestriction,
-  flagSpec "MultiParamTypeClasses"            LangExt.MultiParamTypeClasses,
-  flagSpec "MultiWayIf"                       LangExt.MultiWayIf,
-  flagSpec "NumericUnderscores"               LangExt.NumericUnderscores,
-  flagSpec "NPlusKPatterns"                   LangExt.NPlusKPatterns,
-  flagSpec "NamedFieldPuns"                   LangExt.NamedFieldPuns,
-  flagSpec "NamedWildCards"                   LangExt.NamedWildCards,
-  flagSpec "NegativeLiterals"                 LangExt.NegativeLiterals,
-  flagSpec "HexFloatLiterals"                 LangExt.HexFloatLiterals,
-  flagSpec "NondecreasingIndentation"         LangExt.NondecreasingIndentation,
-  depFlagSpec' "NullaryTypeClasses"           LangExt.NullaryTypeClasses
-    (deprecatedForExtension "MultiParamTypeClasses"),
-  flagSpec "NumDecimals"                      LangExt.NumDecimals,
-  depFlagSpecOp "OverlappingInstances"        LangExt.OverlappingInstances
-    setOverlappingInsts
-    "instead use per-instance pragmas OVERLAPPING/OVERLAPPABLE/OVERLAPS",
-  flagSpec "OverloadedLabels"                 LangExt.OverloadedLabels,
-  flagSpec "OverloadedLists"                  LangExt.OverloadedLists,
-  flagSpec "OverloadedStrings"                LangExt.OverloadedStrings,
-  flagSpec "PackageImports"                   LangExt.PackageImports,
-  flagSpec "ParallelArrays"                   LangExt.ParallelArrays,
-  flagSpec "ParallelListComp"                 LangExt.ParallelListComp,
-  flagSpec "PartialTypeSignatures"            LangExt.PartialTypeSignatures,
-  flagSpec "PatternGuards"                    LangExt.PatternGuards,
-  depFlagSpec' "PatternSignatures"            LangExt.ScopedTypeVariables
-    (deprecatedForExtension "ScopedTypeVariables"),
-  flagSpec "PatternSynonyms"                  LangExt.PatternSynonyms,
-  flagSpec "PolyKinds"                        LangExt.PolyKinds,
-  flagSpec "PolymorphicComponents"            LangExt.RankNTypes,
-  flagSpec "QuantifiedConstraints"            LangExt.QuantifiedConstraints,
-  flagSpec "PostfixOperators"                 LangExt.PostfixOperators,
-  flagSpec "QuasiQuotes"                      LangExt.QuasiQuotes,
-  flagSpec "QualifiedDo"                      LangExt.QualifiedDo,
-  flagSpec "Rank2Types"                       LangExt.RankNTypes,
-  flagSpec "RankNTypes"                       LangExt.RankNTypes,
-  flagSpec "RebindableSyntax"                 LangExt.RebindableSyntax,
-  flagSpec "OverloadedRecordDot"              LangExt.OverloadedRecordDot,
-  flagSpec "OverloadedRecordUpdate"           LangExt.OverloadedRecordUpdate,
-  depFlagSpec' "RecordPuns"                   LangExt.NamedFieldPuns
-    (deprecatedForExtension "NamedFieldPuns"),
-  flagSpec "RecordWildCards"                  LangExt.RecordWildCards,
-  flagSpec "RecursiveDo"                      LangExt.RecursiveDo,
-  flagSpec "RelaxedLayout"                    LangExt.RelaxedLayout,
-  depFlagSpecCond "RelaxedPolyRec"            LangExt.RelaxedPolyRec
-    not
-         "You can't turn off RelaxedPolyRec any more",
-  flagSpec "RequiredTypeArguments"            LangExt.RequiredTypeArguments,
-  flagSpec "RoleAnnotations"                  LangExt.RoleAnnotations,
-  flagSpec "ScopedTypeVariables"              LangExt.ScopedTypeVariables,
-  flagSpec "StandaloneDeriving"               LangExt.StandaloneDeriving,
-  flagSpec "StarIsType"                       LangExt.StarIsType,
-  flagSpec "StaticPointers"                   LangExt.StaticPointers,
-  flagSpec "Strict"                           LangExt.Strict,
-  flagSpec "StrictData"                       LangExt.StrictData,
-  flagSpec' "TemplateHaskell"                 LangExt.TemplateHaskell
-                                              checkTemplateHaskellOk,
-  flagSpec "TemplateHaskellQuotes"            LangExt.TemplateHaskellQuotes,
-  flagSpec "StandaloneKindSignatures"         LangExt.StandaloneKindSignatures,
-  flagSpec "TraditionalRecordSyntax"          LangExt.TraditionalRecordSyntax,
-  flagSpec "TransformListComp"                LangExt.TransformListComp,
-  flagSpec "TupleSections"                    LangExt.TupleSections,
-  flagSpec "TypeAbstractions"                 LangExt.TypeAbstractions,
-  flagSpec "TypeApplications"                 LangExt.TypeApplications,
-  flagSpec "TypeData"                         LangExt.TypeData,
-  depFlagSpec' "TypeInType"                   LangExt.TypeInType
-    (deprecatedForExtensions ["DataKinds", "PolyKinds"]),
-  flagSpec "TypeFamilies"                     LangExt.TypeFamilies,
-  flagSpec "TypeOperators"                    LangExt.TypeOperators,
-  flagSpec "TypeSynonymInstances"             LangExt.TypeSynonymInstances,
-  flagSpec "UnboxedTuples"                    LangExt.UnboxedTuples,
-  flagSpec "UnboxedSums"                      LangExt.UnboxedSums,
-  flagSpec "UndecidableInstances"             LangExt.UndecidableInstances,
-  flagSpec "UndecidableSuperClasses"          LangExt.UndecidableSuperClasses,
-  flagSpec "UnicodeSyntax"                    LangExt.UnicodeSyntax,
-  flagSpec "UnliftedDatatypes"                LangExt.UnliftedDatatypes,
-  flagSpec "UnliftedFFITypes"                 LangExt.UnliftedFFITypes,
-  flagSpec "UnliftedNewtypes"                 LangExt.UnliftedNewtypes,
-  flagSpec "ViewPatterns"                     LangExt.ViewPatterns
-  ]
-
-validHoleFitsImpliedGFlags :: [(GeneralFlag, TurnOnFlag, GeneralFlag)]
-validHoleFitsImpliedGFlags
-  = [ (Opt_UnclutterValidHoleFits, turnOff, Opt_ShowTypeAppOfHoleFits)
-    , (Opt_UnclutterValidHoleFits, turnOff, Opt_ShowTypeAppVarsOfHoleFits)
-    , (Opt_UnclutterValidHoleFits, turnOff, Opt_ShowDocsOfHoleFits)
-    , (Opt_ShowTypeAppVarsOfHoleFits, turnOff, Opt_ShowTypeAppOfHoleFits)
-    , (Opt_UnclutterValidHoleFits, turnOff, Opt_ShowProvOfHoleFits) ]
-
--- General flags that are switched on/off when other general flags are switched
--- on
-impliedGFlags :: [(GeneralFlag, TurnOnFlag, GeneralFlag)]
-impliedGFlags = [(Opt_DeferTypeErrors, turnOn, Opt_DeferTypedHoles)
-                ,(Opt_DeferTypeErrors, turnOn, Opt_DeferOutOfScopeVariables)
-                ,(Opt_DoLinearCoreLinting, turnOn, Opt_DoCoreLinting)
-                ,(Opt_Strictness, turnOn, Opt_WorkerWrapper)
-                ,(Opt_WriteIfSimplifiedCore, turnOn, Opt_WriteInterface)
-                ,(Opt_ByteCodeAndObjectCode, turnOn, Opt_WriteIfSimplifiedCore)
-                ,(Opt_InfoTableMap, turnOn, Opt_InfoTableMapWithStack)
-                ,(Opt_InfoTableMap, turnOn, Opt_InfoTableMapWithFallback)
-                ] ++ validHoleFitsImpliedGFlags
-
--- General flags that are switched on/off when other general flags are switched
--- off
-impliedOffGFlags :: [(GeneralFlag, TurnOnFlag, GeneralFlag)]
-impliedOffGFlags = [(Opt_Strictness, turnOff, Opt_WorkerWrapper)]
-
-impliedXFlags :: [(LangExt.Extension, TurnOnFlag, LangExt.Extension)]
-impliedXFlags
--- See Note [Updating flag description in the User's Guide]
-  = [ (LangExt.RankNTypes,                turnOn, LangExt.ExplicitForAll)
-    , (LangExt.QuantifiedConstraints,     turnOn, LangExt.ExplicitForAll)
-    , (LangExt.ScopedTypeVariables,       turnOn, LangExt.ExplicitForAll)
-    , (LangExt.LiberalTypeSynonyms,       turnOn, LangExt.ExplicitForAll)
-    , (LangExt.ExistentialQuantification, turnOn, LangExt.ExplicitForAll)
-    , (LangExt.FlexibleInstances,         turnOn, LangExt.TypeSynonymInstances)
-    , (LangExt.FunctionalDependencies,    turnOn, LangExt.MultiParamTypeClasses)
-    , (LangExt.MultiParamTypeClasses,     turnOn, LangExt.ConstrainedClassMethods)  -- c.f. #7854
-    , (LangExt.TypeFamilyDependencies,    turnOn, LangExt.TypeFamilies)
-
-    , (LangExt.RebindableSyntax, turnOff, LangExt.ImplicitPrelude)      -- NB: turn off!
-
-    , (LangExt.DerivingVia, turnOn, LangExt.DerivingStrategies)
-
-    , (LangExt.GADTs,            turnOn, LangExt.GADTSyntax)
-    , (LangExt.GADTs,            turnOn, LangExt.MonoLocalBinds)
-    , (LangExt.TypeFamilies,     turnOn, LangExt.MonoLocalBinds)
+makeExtensionFlags :: LangExt.Extension -> [(Deprecation, FlagSpec LangExt.Extension)]
+makeExtensionFlags ext = [ makeExtensionFlag name depr ext | (depr, name) <- extensionNames ext ]
 
-    , (LangExt.TypeFamilies,     turnOn, LangExt.KindSignatures)  -- Type families use kind signatures
-    , (LangExt.PolyKinds,        turnOn, LangExt.KindSignatures)  -- Ditto polymorphic kinds
-
-    -- TypeInType is now just a synonym for a couple of other extensions.
-    , (LangExt.TypeInType,       turnOn, LangExt.DataKinds)
-    , (LangExt.TypeInType,       turnOn, LangExt.PolyKinds)
-    , (LangExt.TypeInType,       turnOn, LangExt.KindSignatures)
-
-    -- Standalone kind signatures are a replacement for CUSKs.
-    , (LangExt.StandaloneKindSignatures, turnOff, LangExt.CUSKs)
-
-    -- AutoDeriveTypeable is not very useful without DeriveDataTypeable
-    , (LangExt.AutoDeriveTypeable, turnOn, LangExt.DeriveDataTypeable)
-
-    -- We turn this on so that we can export associated type
-    -- type synonyms in subordinates (e.g. MyClass(type AssocType))
-    , (LangExt.TypeFamilies,     turnOn, LangExt.ExplicitNamespaces)
-    , (LangExt.TypeOperators, turnOn, LangExt.ExplicitNamespaces)
-
-    , (LangExt.ImpredicativeTypes,  turnOn, LangExt.RankNTypes)
-
-        -- Record wild-cards implies field disambiguation
-        -- Otherwise if you write (C {..}) you may well get
-        -- stuff like " 'a' not in scope ", which is a bit silly
-        -- if the compiler has just filled in field 'a' of constructor 'C'
-    , (LangExt.RecordWildCards,     turnOn, LangExt.DisambiguateRecordFields)
-
-    , (LangExt.ParallelArrays, turnOn, LangExt.ParallelListComp)
-
-    , (LangExt.JavaScriptFFI, turnOn, LangExt.InterruptibleFFI)
-
-    , (LangExt.DeriveTraversable, turnOn, LangExt.DeriveFunctor)
-    , (LangExt.DeriveTraversable, turnOn, LangExt.DeriveFoldable)
-
-    -- Duplicate record fields require field disambiguation
-    , (LangExt.DuplicateRecordFields, turnOn, LangExt.DisambiguateRecordFields)
-
-    , (LangExt.TemplateHaskell, turnOn, LangExt.TemplateHaskellQuotes)
-    , (LangExt.Strict, turnOn, LangExt.StrictData)
-
-    -- Historically only UnboxedTuples was required for unboxed sums to work.
-    -- To avoid breaking code, we make UnboxedTuples imply UnboxedSums.
-    , (LangExt.UnboxedTuples, turnOn, LangExt.UnboxedSums)
-
-    -- The extensions needed to declare an H98 unlifted data type
-    , (LangExt.UnliftedDatatypes, turnOn, LangExt.DataKinds)
-    , (LangExt.UnliftedDatatypes, turnOn, LangExt.StandaloneKindSignatures)
-
-    -- See Note [Non-variable pattern bindings aren't linear] in GHC.Tc.Gen.Bind
-    , (LangExt.LinearTypes, turnOn, LangExt.MonoLocalBinds)
-  ]
+xFlagsDeps :: [(Deprecation, FlagSpec LangExt.Extension)]
+xFlagsDeps = concatMap makeExtensionFlags [minBound .. maxBound]
+
+makeExtensionFlag :: String -> ExtensionDeprecation -> LangExt.Extension -> (Deprecation, FlagSpec LangExt.Extension)
+makeExtensionFlag name depr ext = (deprecation depr, spec)
+  where effect = extensionEffect ext
+        spec = FlagSpec name ext (\f -> effect f >> act f) AllModes
+        act = case depr of
+                ExtensionNotDeprecated -> nop
+                ExtensionDeprecatedFor xs
+                  -> deprecate . deprecatedForExtensions (map extensionName xs)
+                ExtensionFlagDeprecatedCond cond str
+                  -> \f -> when (f == cond) (deprecate str)
+                ExtensionFlagDeprecated str
+                  -> const (deprecate str)
+
+extensionEffect :: LangExt.Extension -> (TurnOnFlag -> DynP ())
+extensionEffect = \case
+  LangExt.TemplateHaskell
+    -> checkTemplateHaskellOk
+  LangExt.OverlappingInstances
+    -> setOverlappingInsts
+  LangExt.GeneralizedNewtypeDeriving
+    -> setGenDeriving
+  LangExt.IncoherentInstances
+    -> setIncoherentInsts
+  LangExt.DerivingVia
+    -> setDeriveVia
+  _ -> nop
 
 -- | Things you get with `-dlint`.
 enableDLint :: DynP ()
@@ -2967,40 +2723,6 @@ disableGlasgowExts :: DynP ()
 disableGlasgowExts = do unSetGeneralFlag Opt_PrintExplicitForalls
                         mapM_ unSetExtensionFlag glasgowExtsFlags
 
--- Please keep what_glasgow_exts_does.rst up to date with this list
-glasgowExtsFlags :: [LangExt.Extension]
-glasgowExtsFlags = [
-             LangExt.ConstrainedClassMethods
-           , LangExt.DeriveDataTypeable
-           , LangExt.DeriveFoldable
-           , LangExt.DeriveFunctor
-           , LangExt.DeriveGeneric
-           , LangExt.DeriveTraversable
-           , LangExt.EmptyDataDecls
-           , LangExt.ExistentialQuantification
-           , LangExt.ExplicitNamespaces
-           , LangExt.FlexibleContexts
-           , LangExt.FlexibleInstances
-           , LangExt.ForeignFunctionInterface
-           , LangExt.FunctionalDependencies
-           , LangExt.GeneralizedNewtypeDeriving
-           , LangExt.ImplicitParams
-           , LangExt.KindSignatures
-           , LangExt.LiberalTypeSynonyms
-           , LangExt.MagicHash
-           , LangExt.MultiParamTypeClasses
-           , LangExt.ParallelListComp
-           , LangExt.PatternGuards
-           , LangExt.PostfixOperators
-           , LangExt.RankNTypes
-           , LangExt.RecursiveDo
-           , LangExt.ScopedTypeVariables
-           , LangExt.StandaloneDeriving
-           , LangExt.TypeOperators
-           , LangExt.TypeSynonymInstances
-           , LangExt.UnboxedTuples
-           , LangExt.UnicodeSyntax
-           , LangExt.UnliftedFFITypes ]
 
 setWarnSafe :: Bool -> DynP ()
 setWarnSafe True  = getCurLoc >>= \l -> upd (\d -> d { warnSafeOnLoc = l })
diff --git a/compiler/GHC/Parser/Errors/Ppr.hs b/compiler/GHC/Parser/Errors/Ppr.hs
index 35d96ee83585..419ef897cd30 100644
--- a/compiler/GHC/Parser/Errors/Ppr.hs
+++ b/compiler/GHC/Parser/Errors/Ppr.hs
@@ -7,6 +7,7 @@
 {-# LANGUAGE PolyKinds #-}
 {-# LANGUAGE TypeApplications #-}
 {-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE OverloadedStrings #-}
 
 {-# OPTIONS_GHC -fno-warn-orphans #-} -- instance Diagnostic PsMessage
 
@@ -699,10 +700,8 @@ instance Diagnostic PsMessage where
     PsErrOverloadedRecordDotInvalid{}             -> noHints
     PsErrIllegalPatSynExport                      -> [suggestExtension LangExt.PatternSynonyms]
     PsErrOverloadedRecordUpdateNoQualifiedFields  -> noHints
-    PsErrExplicitForall is_unicode                ->
-      let info = text "or a similar language extension to enable explicit-forall syntax:" <+>
-                 forallSym is_unicode <+> text "<tvs>. <type>"
-      in [ suggestExtensionWithInfo info LangExt.RankNTypes ]
+    PsErrExplicitForall is_unicode                -> [useExtensionInOrderTo info LangExt.ExplicitForAll]
+      where info = "to enable syntax:" <+> forallSym is_unicode <+> angleBrackets "tvs" <> dot <+> angleBrackets "type"
     PsErrIllegalQualifiedDo{}                     -> [suggestExtension LangExt.QualifiedDo]
     PsErrQualifiedDoInCmd{}                       -> noHints
     PsErrRecordSyntaxInPatSynDecl{}               -> noHints
@@ -757,9 +756,7 @@ instance Diagnostic PsMessage where
     PsErrIfInFunAppExpr{}                         -> suggestParensAndBlockArgs
     PsErrProcInFunAppExpr{}                       -> suggestParensAndBlockArgs
     PsErrMalformedTyOrClDecl{}                    -> noHints
-    PsErrIllegalWhereInDataDecl                   ->
-      [ suggestExtensionWithInfo (text "or a similar language extension to enable syntax: data T where")
-                                 LangExt.GADTs ]
+    PsErrIllegalWhereInDataDecl                   -> [useExtensionInOrderTo "to enable syntax: data T where" LangExt.GADTSyntax]
     PsErrIllegalDataTypeContext{}                 -> [suggestExtension LangExt.DatatypeContexts]
     PsErrPrimStringInvalidChar                    -> noHints
     PsErrSuffixAT                                 -> noHints
diff --git a/compiler/GHC/Tc/Errors/Ppr.hs b/compiler/GHC/Tc/Errors/Ppr.hs
index 0d3230eeb623..a7703c8b6c64 100644
--- a/compiler/GHC/Tc/Errors/Ppr.hs
+++ b/compiler/GHC/Tc/Errors/Ppr.hs
@@ -6791,7 +6791,7 @@ thErrorHints = \case
 thSyntaxErrorHints :: THSyntaxError -> [GhcHint]
 thSyntaxErrorHints = \case
   IllegalTHQuotes{}
-    -> [suggestAnyExtension [LangExt.TemplateHaskell, LangExt.TemplateHaskellQuotes]]
+    -> [suggestExtension LangExt.TemplateHaskellQuotes]
   BadImplicitSplice {}
     -> noHints -- NB: don't suggest TemplateHaskell
                -- see comments on BadImplicitSplice in pprTHSyntaxError
diff --git a/compiler/GHC/Types/Hint/Ppr.hs b/compiler/GHC/Types/Hint/Ppr.hs
index e214619271dd..50e956ed2606 100644
--- a/compiler/GHC/Types/Hint/Ppr.hs
+++ b/compiler/GHC/Types/Hint/Ppr.hs
@@ -1,4 +1,5 @@
 {-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE OverloadedStrings #-}
 
 {-# OPTIONS_GHC -Wno-orphans #-}   -- instance Outputable GhcHint
 
@@ -24,9 +25,13 @@ import GHC.Unit.Module.Imported (ImportedModsVal(..))
 import GHC.Unit.Types
 import GHC.Utils.Outputable
 
-import Data.List (intersperse)
+import GHC.Driver.Flags
+
 import qualified Data.List.NonEmpty as NE
 
+import qualified GHC.LanguageExtensions as LangExt
+
+
 instance Outputable GhcHint where
   ppr = \case
     UnknownHint m
@@ -34,15 +39,20 @@ instance Outputable GhcHint where
     SuggestExtension extHint
       -> case extHint of
           SuggestSingleExtension extraUserInfo ext ->
-            (text "Perhaps you intended to use" <+> ppr ext) $$ extraUserInfo
+            ("Perhaps you intended to use" <+> extension_with_implied ext)
+            $$ extraUserInfo
           SuggestAnyExtension extraUserInfo exts ->
-            let header = text "Enable any of the following extensions:"
-            in  header <+> hcat (intersperse (text ", ") (map ppr exts)) $$ extraUserInfo
+            (enable "any" <+> unquotedListWith "or" (map implied exts))
+            $$ extraUserInfo
           SuggestExtensions extraUserInfo exts ->
-            let header = text "Enable all of the following extensions:"
-            in  header <+> hcat (intersperse (text ", ") (map ppr exts)) $$ extraUserInfo
+            (enable "all" <+> unquotedListWith "and" (map implied exts))
+            $$ extraUserInfo
           SuggestExtensionInOrderTo extraUserInfo ext ->
-            (text "Use" <+> ppr ext) $$ extraUserInfo
+            ("Use" <+> extension_with_implied ext)
+            $$ extraUserInfo
+      where extension_with_implied ext = "the" <+> quotes (ppr ext) <+> "extension" <+> pprImpliedExtensions ext
+            implied ext = quotes (ppr ext) <+> pprImpliedExtensions ext
+            enable any_or_all = "Enable" <+> any_or_all <+> "of the following extensions" <> colon
     SuggestCorrectPragmaName suggestions
       -> text "Perhaps you meant" <+> quotedListWithOr (map text suggestions)
     SuggestMissingDo
@@ -369,6 +379,16 @@ pprSimilarName tried_ns (SimilarRdrName rdr_name how_in_scope)
               | otherwise      = empty
       where ns = rdrNameSpace rdr
 
+pprImpliedExtensions :: LangExt.Extension -> SDoc
+pprImpliedExtensions extension = case implied of
+    [] -> empty
+    xs -> parens $ "implied by" <+> unquotedListWith "and" xs
+  where implied = map (quotes . ppr)
+                . filter (\ext -> extensionDeprecation ext == ExtensionNotDeprecated)
+                . map (\(impl, _, _) -> impl)
+                . filter (\(_, t, orig) -> orig == extension && t == turnOn)
+                $ impliedXFlags
+
 pprPrefixUnqual :: Name -> SDoc
 pprPrefixUnqual name =
   pprPrefixOcc (getOccName name)
diff --git a/compiler/GHC/Utils/Outputable.hs b/compiler/GHC/Utils/Outputable.hs
index ce7d606d4806..e18ea1002df7 100644
--- a/compiler/GHC/Utils/Outputable.hs
+++ b/compiler/GHC/Utils/Outputable.hs
@@ -33,6 +33,7 @@ module GHC.Utils.Outputable (
         docToSDoc,
         interppSP, interpp'SP, interpp'SP',
         pprQuotedList, pprWithCommas,
+        unquotedListWith,
         quotedListWithOr, quotedListWithNor, quotedListWithAnd,
         pprWithBars,
         spaceIfSingleQuote,
@@ -131,7 +132,7 @@ import GHC.Utils.Panic.Plain (assert)
 import GHC.Serialized
 import GHC.LanguageExtensions (Extension)
 import GHC.Utils.GlobalVars( unsafeHasPprDebug )
-import GHC.Utils.Misc (lastMaybe)
+import GHC.Utils.Misc (lastMaybe, snocView)
 
 import Data.ByteString (ByteString)
 import qualified Data.ByteString as BS
@@ -1440,6 +1441,15 @@ quotedListWithAnd :: [SDoc] -> SDoc
 quotedListWithAnd xs@(_:_:_) = quotedList (init xs) <+> text "and" <+> quotes (last xs)
 quotedListWithAnd xs = quotedList xs
 
+
+unquotedListWith :: SDoc -> [SDoc] -> SDoc
+-- "whatever" [x,y,z] ==> x, y whatever z
+unquotedListWith d xs
+  | Just (fs@(_:_), l) <- snocView xs = unquotedList fs <+> d <+> l
+  | otherwise                         = unquotedList xs
+  where
+    unquotedList = fsep . punctuate comma
+
 {-
 ************************************************************************
 *                                                                      *
diff --git a/testsuite/tests/dependent/should_fail/T15215.stderr b/testsuite/tests/dependent/should_fail/T15215.stderr
index 8ad50c4d4011..45ddef377101 100644
--- a/testsuite/tests/dependent/should_fail/T15215.stderr
+++ b/testsuite/tests/dependent/should_fail/T15215.stderr
@@ -3,7 +3,8 @@ T15215.hs:11:3: error: [GHC-80003]
     • Non type-variable argument in the constraint: Show (Maybe a)
     • In the definition of data constructor ‘MkA’
       In the data type declaration for ‘A’
-    Suggested fix: Perhaps you intended to use FlexibleContexts
+    Suggested fix:
+      Perhaps you intended to use the ‘FlexibleContexts’ extension
 
 T15215.hs:18:14: error: [GHC-28374]
     • Data constructor ‘MkB’ cannot be used here
diff --git a/testsuite/tests/dependent/should_fail/T15859.stderr b/testsuite/tests/dependent/should_fail/T15859.stderr
index 6562200e3920..ff421af0b0ea 100644
--- a/testsuite/tests/dependent/should_fail/T15859.stderr
+++ b/testsuite/tests/dependent/should_fail/T15859.stderr
@@ -6,4 +6,5 @@ T15859.hs:9:19: error: [GHC-51580]
       In the expression: (undefined :: forall k -> k -> Type) @Int
       In an equation for ‘a’:
           a = (undefined :: forall k -> k -> Type) @Int
-    Suggested fix: Perhaps you intended to use RequiredTypeArguments
+    Suggested fix:
+      Perhaps you intended to use the ‘RequiredTypeArguments’ extension
diff --git a/testsuite/tests/dependent/should_fail/T16326_Fail1.stderr b/testsuite/tests/dependent/should_fail/T16326_Fail1.stderr
index 993f19468071..b65cb68916f0 100644
--- a/testsuite/tests/dependent/should_fail/T16326_Fail1.stderr
+++ b/testsuite/tests/dependent/should_fail/T16326_Fail1.stderr
@@ -3,11 +3,13 @@ T16326_Fail1.hs:5:8: error: [GHC-51580]
     • Illegal visible, dependent quantification in the type of a term:
         forall a -> a -> a
     • In the type signature: id1 :: forall a -> a -> a
-    Suggested fix: Perhaps you intended to use RequiredTypeArguments
+    Suggested fix:
+      Perhaps you intended to use the ‘RequiredTypeArguments’ extension
 
 T16326_Fail1.hs:9:8: error: [GHC-51580]
     • Illegal visible, dependent quantification in the type of a term:
         forall a -> a -> a
     • In the expansion of type synonym ‘Foo’
       In the type signature: id2 :: Foo
-    Suggested fix: Perhaps you intended to use RequiredTypeArguments
+    Suggested fix:
+      Perhaps you intended to use the ‘RequiredTypeArguments’ extension
diff --git a/testsuite/tests/dependent/should_fail/T16326_Fail10.stderr b/testsuite/tests/dependent/should_fail/T16326_Fail10.stderr
index bdb7eb9af098..58ef1dab7528 100644
--- a/testsuite/tests/dependent/should_fail/T16326_Fail10.stderr
+++ b/testsuite/tests/dependent/should_fail/T16326_Fail10.stderr
@@ -4,4 +4,5 @@ T16326_Fail10.hs:12:18: error: [GHC-51580]
         forall a -> a -> a
     • In the type signature for ‘x’: forall a -> a -> a
       When checking the rewrite rule "flurmp"
-    Suggested fix: Perhaps you intended to use RequiredTypeArguments
+    Suggested fix:
+      Perhaps you intended to use the ‘RequiredTypeArguments’ extension
diff --git a/testsuite/tests/dependent/should_fail/T16326_Fail11.stderr b/testsuite/tests/dependent/should_fail/T16326_Fail11.stderr
index 741598d1016f..b0cad61639bc 100644
--- a/testsuite/tests/dependent/should_fail/T16326_Fail11.stderr
+++ b/testsuite/tests/dependent/should_fail/T16326_Fail11.stderr
@@ -4,4 +4,5 @@ T16326_Fail11.hs:9:11: error: [GHC-51580]
         forall x -> x
     • When checking the class method: m :: forall a b. C a => b -> a
       In the class declaration for ‘C’
-    Suggested fix: Perhaps you intended to use RequiredTypeArguments
+    Suggested fix:
+      Perhaps you intended to use the ‘RequiredTypeArguments’ extension
diff --git a/testsuite/tests/dependent/should_fail/T16326_Fail2.stderr b/testsuite/tests/dependent/should_fail/T16326_Fail2.stderr
index 2446580ad3b3..7204c9a38562 100644
--- a/testsuite/tests/dependent/should_fail/T16326_Fail2.stderr
+++ b/testsuite/tests/dependent/should_fail/T16326_Fail2.stderr
@@ -5,4 +5,5 @@ T16326_Fail2.hs:6:37: error: [GHC-51580]
     • In the type signature: blah :: forall a -> a -> IO ()
       When checking declaration:
         foreign import ccall safe "blah" blah :: forall a -> a -> IO ()
-    Suggested fix: Perhaps you intended to use RequiredTypeArguments
+    Suggested fix:
+      Perhaps you intended to use the ‘RequiredTypeArguments’ extension
diff --git a/testsuite/tests/dependent/should_fail/T16326_Fail3.stderr b/testsuite/tests/dependent/should_fail/T16326_Fail3.stderr
index 4b2321d93bce..87de11f9c384 100644
--- a/testsuite/tests/dependent/should_fail/T16326_Fail3.stderr
+++ b/testsuite/tests/dependent/should_fail/T16326_Fail3.stderr
@@ -2,4 +2,5 @@
 T16326_Fail3.hs:6:1: error: [GHC-51580]
     Illegal visible, dependent quantification in the type of a term:
       forall a -> [a]
-    Suggested fix: Perhaps you intended to use RequiredTypeArguments
+    Suggested fix:
+      Perhaps you intended to use the ‘RequiredTypeArguments’ extension
diff --git a/testsuite/tests/dependent/should_fail/T16326_Fail4.stderr b/testsuite/tests/dependent/should_fail/T16326_Fail4.stderr
index d881bd6476dc..c904a286644b 100644
--- a/testsuite/tests/dependent/should_fail/T16326_Fail4.stderr
+++ b/testsuite/tests/dependent/should_fail/T16326_Fail4.stderr
@@ -8,4 +8,5 @@ T16326_Fail4.hs:6:30: error: [GHC-51580]
         ‘((<>) :: forall a -> Maybe a -> Maybe a -> Maybe a)’
       In the expression:
         zipWith ((<>) :: forall a -> Maybe a -> Maybe a -> Maybe a) xs ys
-    Suggested fix: Perhaps you intended to use RequiredTypeArguments
+    Suggested fix:
+      Perhaps you intended to use the ‘RequiredTypeArguments’ extension
diff --git a/testsuite/tests/dependent/should_fail/T16326_Fail5.stderr b/testsuite/tests/dependent/should_fail/T16326_Fail5.stderr
index afa5830013ab..225ca46dd2af 100644
--- a/testsuite/tests/dependent/should_fail/T16326_Fail5.stderr
+++ b/testsuite/tests/dependent/should_fail/T16326_Fail5.stderr
@@ -6,4 +6,5 @@ T16326_Fail5.hs:7:20: error: [GHC-51580]
       In the pattern: Nothing :: forall a -> Maybe a
       In an equation for ‘isJust’:
           isJust (Nothing :: forall a -> Maybe a) = False
-    Suggested fix: Perhaps you intended to use RequiredTypeArguments
+    Suggested fix:
+      Perhaps you intended to use the ‘RequiredTypeArguments’ extension
diff --git a/testsuite/tests/dependent/should_fail/T16326_Fail7.stderr b/testsuite/tests/dependent/should_fail/T16326_Fail7.stderr
index 0380d29e72ce..5cbe11f93d02 100644
--- a/testsuite/tests/dependent/should_fail/T16326_Fail7.stderr
+++ b/testsuite/tests/dependent/should_fail/T16326_Fail7.stderr
@@ -2,5 +2,7 @@
 T16326_Fail7.hs:9:13: error: [GHC-25955]
     Illegal symbol ‘forall’ in type
     Suggested fix:
-      Perhaps you intended to use RankNTypes
-      or a similar language extension to enable explicit-forall syntax: forall <tvs>. <type>
+      Use the ‘ExplicitForAll’ extension (implied by ‘RankNTypes’,
+                                                     ‘QuantifiedConstraints’, ‘ScopedTypeVariables’,
+                                                     ‘LiberalTypeSynonyms’ and ‘ExistentialQuantification’)
+      to enable syntax: forall <tvs>. <type>
diff --git a/testsuite/tests/dependent/should_fail/T16326_Fail9.stderr b/testsuite/tests/dependent/should_fail/T16326_Fail9.stderr
index 2fcfe69e2876..e8f36cd6d01a 100644
--- a/testsuite/tests/dependent/should_fail/T16326_Fail9.stderr
+++ b/testsuite/tests/dependent/should_fail/T16326_Fail9.stderr
@@ -5,4 +5,5 @@ T16326_Fail9.hs:11:5: error: [GHC-51580]
     • In the expression: lol @(forall a -> a -> a) undefined True
       In an equation for ‘t’:
           t = lol @(forall a -> a -> a) undefined True
-    Suggested fix: Perhaps you intended to use RequiredTypeArguments
+    Suggested fix:
+      Perhaps you intended to use the ‘RequiredTypeArguments’ extension
diff --git a/testsuite/tests/dependent/should_fail/T17687.stderr b/testsuite/tests/dependent/should_fail/T17687.stderr
index 4983421a6ca5..be5732df9a53 100644
--- a/testsuite/tests/dependent/should_fail/T17687.stderr
+++ b/testsuite/tests/dependent/should_fail/T17687.stderr
@@ -3,4 +3,5 @@ T17687.hs:5:6: error: [GHC-51580]
     • Illegal visible, dependent quantification in the type of a term:
         forall a -> a -> a
     • In the type signature: x :: forall a -> a -> a
-    Suggested fix: Perhaps you intended to use RequiredTypeArguments
+    Suggested fix:
+      Perhaps you intended to use the ‘RequiredTypeArguments’ extension
diff --git a/testsuite/tests/deriving/should_compile/T16179.stderr b/testsuite/tests/deriving/should_compile/T16179.stderr
index 88493495b137..e742abafd3de 100644
--- a/testsuite/tests/deriving/should_compile/T16179.stderr
+++ b/testsuite/tests/deriving/should_compile/T16179.stderr
@@ -4,5 +4,5 @@ T16179.hs:7:30: warning: [GHC-20042] [-Wderiving-defaults (in -Wdefault)]
       Defaulting to the DeriveAnyClass strategy for instantiating C
     • In the newtype declaration for ‘T’
     Suggested fix:
-      Use DerivingStrategies
+      Use the ‘DerivingStrategies’ extension (implied by ‘DerivingVia’)
       to pick a different strategy
diff --git a/testsuite/tests/deriving/should_fail/T10598_fail2.stderr b/testsuite/tests/deriving/should_fail/T10598_fail2.stderr
index 4f9b5d833909..5257676e31c6 100644
--- a/testsuite/tests/deriving/should_fail/T10598_fail2.stderr
+++ b/testsuite/tests/deriving/should_fail/T10598_fail2.stderr
@@ -3,12 +3,13 @@ T10598_fail2.hs:5:37: error: [GHC-38178]
     • Can't make a derived instance of
         ‘Eq A’ with the anyclass strategy:
     • In the data declaration for ‘A’
-    Suggested fix: Perhaps you intended to use DeriveAnyClass
+    Suggested fix:
+      Perhaps you intended to use the ‘DeriveAnyClass’ extension
 
 T10598_fail2.hs:6:37: error: [GHC-26557]
     • Can't make a derived instance of
         ‘Eq B’ with the newtype strategy:
     • In the newtype declaration for ‘B’
     Suggested fix:
-      Perhaps you intended to use GeneralizedNewtypeDeriving
+      Perhaps you intended to use the ‘GeneralizedNewtypeDeriving’ extension
       for GHC's newtype-deriving extension
diff --git a/testsuite/tests/deriving/should_fail/T10598_fail4.stderr b/testsuite/tests/deriving/should_fail/T10598_fail4.stderr
index ce6a1cd4d868..4891b4fe1a64 100644
--- a/testsuite/tests/deriving/should_fail/T10598_fail4.stderr
+++ b/testsuite/tests/deriving/should_fail/T10598_fail4.stderr
@@ -1,4 +1,5 @@
 
 T10598_fail4.hs:4:12: error: [GHC-87139]
     Illegal deriving strategy: stock
-    Suggested fix: Perhaps you intended to use DerivingStrategies
+    Suggested fix:
+      Perhaps you intended to use the ‘DerivingStrategies’ extension (implied by ‘DerivingVia’)
diff --git a/testsuite/tests/deriving/should_fail/T10598_fail5.stderr b/testsuite/tests/deriving/should_fail/T10598_fail5.stderr
index b6b3877d32d3..595dd1e4d17f 100644
--- a/testsuite/tests/deriving/should_fail/T10598_fail5.stderr
+++ b/testsuite/tests/deriving/should_fail/T10598_fail5.stderr
@@ -1,4 +1,5 @@
 
 T10598_fail5.hs:3:1: error: [GHC-30281]
     Illegal use of multiple, consecutive deriving clauses
-    Suggested fix: Perhaps you intended to use DerivingStrategies
+    Suggested fix:
+      Perhaps you intended to use the ‘DerivingStrategies’ extension (implied by ‘DerivingVia’)
diff --git a/testsuite/tests/deriving/should_fail/T1133A.stderr b/testsuite/tests/deriving/should_fail/T1133A.stderr
index c05b28510e0b..311848ce003f 100644
--- a/testsuite/tests/deriving/should_fail/T1133A.stderr
+++ b/testsuite/tests/deriving/should_fail/T1133A.stderr
@@ -5,5 +5,5 @@ T1133A.hs:7:28: error: [GHC-30750]
         (an enumeration consists of one or more nullary, non-GADT constructors)
     • In the newtype declaration for ‘X’
     Suggested fix:
-      Perhaps you intended to use GeneralizedNewtypeDeriving
+      Perhaps you intended to use the ‘GeneralizedNewtypeDeriving’ extension
       for GHC's newtype-deriving extension
diff --git a/testsuite/tests/deriving/should_fail/T12512.stderr b/testsuite/tests/deriving/should_fail/T12512.stderr
index f335e6cbccd0..521b209521e3 100644
--- a/testsuite/tests/deriving/should_fail/T12512.stderr
+++ b/testsuite/tests/deriving/should_fail/T12512.stderr
@@ -3,10 +3,12 @@ T12512.hs:10:1: error: [GHC-00158]
     • Can't make a derived instance of ‘Wat1 (# a, b #)’:
         ‘Wat1’ is not a stock derivable class (Eq, Show, etc.)
     • In the stand-alone deriving instance for ‘Wat1 (# a, b #)’
-    Suggested fix: Perhaps you intended to use DeriveAnyClass
+    Suggested fix:
+      Perhaps you intended to use the ‘DeriveAnyClass’ extension
 
 T12512.hs:13:1: error: [GHC-00158]
     • Can't make a derived instance of ‘Wat2 (# a | b #)’:
         ‘Wat2’ is not a stock derivable class (Eq, Show, etc.)
     • In the stand-alone deriving instance for ‘Wat2 (# a | b #)’
-    Suggested fix: Perhaps you intended to use DeriveAnyClass
+    Suggested fix:
+      Perhaps you intended to use the ‘DeriveAnyClass’ extension
diff --git a/testsuite/tests/deriving/should_fail/T19692.stderr b/testsuite/tests/deriving/should_fail/T19692.stderr
index fc599703ba64..b21e919910cb 100644
--- a/testsuite/tests/deriving/should_fail/T19692.stderr
+++ b/testsuite/tests/deriving/should_fail/T19692.stderr
@@ -13,64 +13,75 @@ T19692.hs:14:23: error: [GHC-00158]
     • Can't make a derived instance of ‘C2 G2’:
         ‘C2’ is not a stock derivable class (Eq, Show, etc.)
     • In the data declaration for ‘G2’
-    Suggested fix: Perhaps you intended to use DeriveAnyClass
+    Suggested fix:
+      Perhaps you intended to use the ‘DeriveAnyClass’ extension
 
 T19692.hs:16:1: error: [GHC-00158]
     • Can't make a derived instance of ‘C2 G2'’:
         ‘C2’ is not a stock derivable class (Eq, Show, etc.)
     • In the stand-alone deriving instance for ‘C2 G2'’
-    Suggested fix: Perhaps you intended to use DeriveAnyClass
+    Suggested fix:
+      Perhaps you intended to use the ‘DeriveAnyClass’ extension
 
 T19692.hs:21:23: error: [GHC-00158]
     • Can't make a derived instance of ‘C3 G3’:
         ‘C3’ is not a stock derivable class (Eq, Show, etc.)
     • In the data declaration for ‘G3’
-    Suggested fix: Perhaps you intended to use DeriveAnyClass
+    Suggested fix:
+      Perhaps you intended to use the ‘DeriveAnyClass’ extension
 
 T19692.hs:23:1: error: [GHC-00158]
     • Can't make a derived instance of ‘C3 G3'’:
         ‘C3’ is not a stock derivable class (Eq, Show, etc.)
     • In the stand-alone deriving instance for ‘C3 G3'’
-    Suggested fix: Perhaps you intended to use DeriveAnyClass
+    Suggested fix:
+      Perhaps you intended to use the ‘DeriveAnyClass’ extension
 
 T19692.hs:29:23: error: [GHC-00158]
     • Can't make a derived instance of ‘C4 G4’:
         ‘C4’ is not a stock derivable class (Eq, Show, etc.)
     • In the data declaration for ‘G4’
-    Suggested fix: Perhaps you intended to use DeriveAnyClass
+    Suggested fix:
+      Perhaps you intended to use the ‘DeriveAnyClass’ extension
 
 T19692.hs:31:1: error: [GHC-00158]
     • Can't make a derived instance of ‘C4 G4'’:
         ‘C4’ is not a stock derivable class (Eq, Show, etc.)
     • In the stand-alone deriving instance for ‘C4 G4'’
-    Suggested fix: Perhaps you intended to use DeriveAnyClass
+    Suggested fix:
+      Perhaps you intended to use the ‘DeriveAnyClass’ extension
 
 T19692.hs:35:1: error: [GHC-38178]
     • Can't make a derived instance of ‘C5’:
     • In the stand-alone deriving instance for ‘C5’
-    Suggested fix: Perhaps you intended to use DeriveAnyClass
+    Suggested fix:
+      Perhaps you intended to use the ‘DeriveAnyClass’ extension
 
 T19692.hs:38:1: error: [GHC-38178]
     • Can't make a derived instance of ‘C6 a’:
     • In the stand-alone deriving instance for ‘C6 a’
-    Suggested fix: Perhaps you intended to use DeriveAnyClass
+    Suggested fix:
+      Perhaps you intended to use the ‘DeriveAnyClass’ extension
 
 T19692.hs:43:1: error: [GHC-38178]
     • Can't make a derived instance of ‘C7 a’:
     • In the stand-alone deriving instance for ‘C7 a’
-    Suggested fix: Perhaps you intended to use DeriveAnyClass
+    Suggested fix:
+      Perhaps you intended to use the ‘DeriveAnyClass’ extension
 
 T19692.hs:47:1: error: [GHC-38178]
     • Can't make a derived instance of ‘C8’:
     • In the stand-alone deriving instance for ‘C8’
-    Suggested fix: Perhaps you intended to use DeriveAnyClass
+    Suggested fix:
+      Perhaps you intended to use the ‘DeriveAnyClass’ extension
 
 T19692.hs:52:1: error: [GHC-23244]
     • Can't make a derived instance of ‘C9 Eq’:
         ‘Eq’ is a type class, and can only have a derived instance
         if DeriveAnyClass is enabled
     • In the stand-alone deriving instance for ‘C9 Eq’
-    Suggested fix: Perhaps you intended to use DeriveAnyClass
+    Suggested fix:
+      Perhaps you intended to use the ‘DeriveAnyClass’ extension
 
 T19692.hs:57:1: error: [GHC-23244]
     • Can't make a derived instance of ‘C10 Eq’:
@@ -82,10 +93,12 @@ T19692.hs:61:38: error: [GHC-38178]
     • Can't make a derived instance of
         ‘Eq G11’ with the anyclass strategy:
     • In the data declaration for ‘G11’
-    Suggested fix: Perhaps you intended to use DeriveAnyClass
+    Suggested fix:
+      Perhaps you intended to use the ‘DeriveAnyClass’ extension
 
 T19692.hs:63:1: error: [GHC-38178]
     • Can't make a derived instance of
         ‘Eq G11'’ with the anyclass strategy:
     • In the stand-alone deriving instance for ‘Eq G11'’
-    Suggested fix: Perhaps you intended to use DeriveAnyClass
+    Suggested fix:
+      Perhaps you intended to use the ‘DeriveAnyClass’ extension
diff --git a/testsuite/tests/deriving/should_fail/T3833.stderr b/testsuite/tests/deriving/should_fail/T3833.stderr
index 5db0cf5adff9..f8c341347f53 100644
--- a/testsuite/tests/deriving/should_fail/T3833.stderr
+++ b/testsuite/tests/deriving/should_fail/T3833.stderr
@@ -4,5 +4,5 @@ T3833.hs:10:1: error: [GHC-82023]
         ‘Monoid’ is not a stock derivable class (Eq, Show, etc.)
     • In the stand-alone deriving instance for ‘Monoid (DecodeMap e)’
     Suggested fix:
-      Perhaps you intended to use GeneralizedNewtypeDeriving
+      Perhaps you intended to use the ‘GeneralizedNewtypeDeriving’ extension
       for GHC's newtype-deriving extension
diff --git a/testsuite/tests/deriving/should_fail/T3834.stderr b/testsuite/tests/deriving/should_fail/T3834.stderr
index cd2282101c31..4d0156f5e2b2 100644
--- a/testsuite/tests/deriving/should_fail/T3834.stderr
+++ b/testsuite/tests/deriving/should_fail/T3834.stderr
@@ -4,5 +4,5 @@ T3834.hs:9:1: error: [GHC-82023]
         ‘C’ is not a stock derivable class (Eq, Show, etc.)
     • In the stand-alone deriving instance for ‘C T’
     Suggested fix:
-      Perhaps you intended to use GeneralizedNewtypeDeriving
+      Perhaps you intended to use the ‘GeneralizedNewtypeDeriving’ extension
       for GHC's newtype-deriving extension
diff --git a/testsuite/tests/deriving/should_fail/T7401_fail.stderr b/testsuite/tests/deriving/should_fail/T7401_fail.stderr
index 4b79f4aa5ae0..de7e8a9ad94f 100644
--- a/testsuite/tests/deriving/should_fail/T7401_fail.stderr
+++ b/testsuite/tests/deriving/should_fail/T7401_fail.stderr
@@ -4,5 +4,5 @@ T7401_fail.hs:4:17: error: [GHC-64560]
         ‘D’ must have at least one data constructor
     • In the data declaration for ‘D’
     Suggested fix:
-      Use EmptyDataDeriving
+      Use the ‘EmptyDataDeriving’ extension
       to enable deriving for empty data types
diff --git a/testsuite/tests/deriving/should_fail/T7959.stderr b/testsuite/tests/deriving/should_fail/T7959.stderr
index b0f5c916c0c2..a047b5dd10a6 100644
--- a/testsuite/tests/deriving/should_fail/T7959.stderr
+++ b/testsuite/tests/deriving/should_fail/T7959.stderr
@@ -2,7 +2,8 @@
 T7959.hs:5:1: error: [GHC-38178]
     • Can't make a derived instance of ‘A’:
     • In the stand-alone deriving instance for ‘A’
-    Suggested fix: Perhaps you intended to use DeriveAnyClass
+    Suggested fix:
+      Perhaps you intended to use the ‘DeriveAnyClass’ extension
 
 T7959.hs:6:17: error: [GHC-73993]
     • ‘A’ is not a unary constraint, as expected by a deriving clause
diff --git a/testsuite/tests/deriving/should_fail/T8165_fail2.stderr b/testsuite/tests/deriving/should_fail/T8165_fail2.stderr
index 2187bb01357b..9f0eb43dfb2f 100644
--- a/testsuite/tests/deriving/should_fail/T8165_fail2.stderr
+++ b/testsuite/tests/deriving/should_fail/T8165_fail2.stderr
@@ -3,4 +3,5 @@ T8165_fail2.hs:9:12: error: [GHC-22979]
     • The type-family application ‘T Loop’
         is no smaller than the LHS of the family instance ‘T Loop’
     • In the instance declaration for ‘C Loop’
-    Suggested fix: Perhaps you intended to use UndecidableInstances
+    Suggested fix:
+      Perhaps you intended to use the ‘UndecidableInstances’ extension
diff --git a/testsuite/tests/deriving/should_fail/T9600.stderr b/testsuite/tests/deriving/should_fail/T9600.stderr
index f33a9ad63669..5868cac1d5f4 100644
--- a/testsuite/tests/deriving/should_fail/T9600.stderr
+++ b/testsuite/tests/deriving/should_fail/T9600.stderr
@@ -4,5 +4,5 @@ T9600.hs:4:39: error: [GHC-82023]
         ‘Applicative’ is not a stock derivable class (Eq, Show, etc.)
     • In the newtype declaration for ‘Foo’
     Suggested fix:
-      Perhaps you intended to use GeneralizedNewtypeDeriving
+      Perhaps you intended to use the ‘GeneralizedNewtypeDeriving’ extension
       for GHC's newtype-deriving extension
diff --git a/testsuite/tests/deriving/should_fail/deriving-via-fail3.stderr b/testsuite/tests/deriving/should_fail/deriving-via-fail3.stderr
index b2fb98469a83..7b74425b8d51 100644
--- a/testsuite/tests/deriving/should_fail/deriving-via-fail3.stderr
+++ b/testsuite/tests/deriving/should_fail/deriving-via-fail3.stderr
@@ -1,4 +1,5 @@
 
 deriving-via-fail3.hs:3:20: error: [GHC-87139]
     Illegal deriving strategy: via
-    Suggested fix: Perhaps you intended to use DerivingVia
+    Suggested fix:
+      Perhaps you intended to use the ‘DerivingVia’ extension
diff --git a/testsuite/tests/deriving/should_fail/drvfail008.stderr b/testsuite/tests/deriving/should_fail/drvfail008.stderr
index baa09b5398da..508dcf158175 100644
--- a/testsuite/tests/deriving/should_fail/drvfail008.stderr
+++ b/testsuite/tests/deriving/should_fail/drvfail008.stderr
@@ -4,5 +4,5 @@ drvfail008.hs:11:43: error: [GHC-82023]
         ‘Monad’ is not a stock derivable class (Eq, Show, etc.)
     • In the newtype declaration for ‘M’
     Suggested fix:
-      Perhaps you intended to use GeneralizedNewtypeDeriving
+      Perhaps you intended to use the ‘GeneralizedNewtypeDeriving’ extension
       for GHC's newtype-deriving extension
diff --git a/testsuite/tests/deriving/should_fail/drvfail015.stderr b/testsuite/tests/deriving/should_fail/drvfail015.stderr
index 4b88eef7e0bf..365422453f41 100644
--- a/testsuite/tests/deriving/should_fail/drvfail015.stderr
+++ b/testsuite/tests/deriving/should_fail/drvfail015.stderr
@@ -4,7 +4,8 @@ drvfail015.hs:11:19: error: [GHC-93557]
         All instance types must be of the form (T t1 ... tn)
         where T is not a synonym.
     • In the stand-alone deriving instance for ‘Eq T’
-    Suggested fix: Perhaps you intended to use TypeSynonymInstances
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeSynonymInstances’ extension (implied by ‘FlexibleInstances’)
 
 drvfail015.hs:14:1: error: [GHC-54540]
     • Can't make a derived instance of ‘Eq Handle’:
diff --git a/testsuite/tests/driver/T11381.stderr b/testsuite/tests/driver/T11381.stderr
index aab437a66bd5..2bcb65f092de 100644
--- a/testsuite/tests/driver/T11381.stderr
+++ b/testsuite/tests/driver/T11381.stderr
@@ -1,5 +1,6 @@
 
-T11381.hs:7:23: [GHC-43991]
-     Illegal injectivity annotation
-     In the type family declaration for ‘F’
-     Suggested fix: Perhaps you intended to use TypeFamilyDependencies
+T11381.hs:7:23: error: [GHC-43991]
+    • Illegal injectivity annotation
+    • In the type family declaration for ‘F’
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeFamilyDependencies’ extension
diff --git a/testsuite/tests/driver/json.stderr b/testsuite/tests/driver/json.stderr
index 5fd0092e8e32..32f13f2f6245 100644
--- a/testsuite/tests/driver/json.stderr
+++ b/testsuite/tests/driver/json.stderr
@@ -1 +1 @@
-{"version":"1.0","ghcVersion":"ghc-9.9.20230817","span":{"file":"json.hs","start":{"line":9,"column":11},"end":{"line":9,"column":21}},"severity":"Error","code":48010,"message":["Empty list of alternatives in case expression"],"hints":["Perhaps you intended to use EmptyCase"]}
+{"version":"1.0","ghcVersion":"ghc-9.11.20240329","span":{"file":"json.hs","start":{"line":9,"column":11},"end":{"line":9,"column":21}},"severity":"Error","code":48010,"message":["Empty list of alternatives in case expression"],"hints":["Perhaps you intended to use the `EmptyCase' extension"]}
diff --git a/testsuite/tests/ffi/should_fail/T10461.stderr b/testsuite/tests/ffi/should_fail/T10461.stderr
index cbdac0bb1922..e55a3be0d2be 100644
--- a/testsuite/tests/ffi/should_fail/T10461.stderr
+++ b/testsuite/tests/ffi/should_fail/T10461.stderr
@@ -5,4 +5,5 @@ T10461.hs:6:1: error: [GHC-10964]
         UnliftedFFITypes is required to marshal unlifted types
     • When checking declaration:
         foreign import prim safe cheneycopy :: Any -> Word#
-    Suggested fix: Perhaps you intended to use UnliftedFFITypes
+    Suggested fix:
+      Perhaps you intended to use the ‘UnliftedFFITypes’ extension
diff --git a/testsuite/tests/ffi/should_fail/T20116.stderr b/testsuite/tests/ffi/should_fail/T20116.stderr
index 1c2422bcc881..6cbb4ab128b5 100644
--- a/testsuite/tests/ffi/should_fail/T20116.stderr
+++ b/testsuite/tests/ffi/should_fail/T20116.stderr
@@ -3,4 +3,5 @@ T20116.hs:8:1: error: [GHC-49692]
     • `foreign import prim' requires GHCForeignImportPrim.
     • When checking declaration:
         foreign import prim safe "test_lt" lt_s :: Int64# -> Int64# -> Int#
-    Suggested fix: Perhaps you intended to use GHCForeignImportPrim
+    Suggested fix:
+      Perhaps you intended to use the ‘GHCForeignImportPrim’ extension
diff --git a/testsuite/tests/ffi/should_fail/ccfail001.stderr b/testsuite/tests/ffi/should_fail/ccfail001.stderr
index 2ca03434480f..2109c860d7d8 100644
--- a/testsuite/tests/ffi/should_fail/ccfail001.stderr
+++ b/testsuite/tests/ffi/should_fail/ccfail001.stderr
@@ -1,8 +1,9 @@
-
 ccfail001.hs:10:1: error: [GHC-10964]
     • Unacceptable result type in foreign declaration:
         ‘State# RealWorld’ cannot be marshalled in a foreign call
         UnliftedFFITypes is required to marshal unlifted types
     • When checking declaration:
         foreign import ccall safe foo :: Int -> State# RealWorld
-    Suggested fix: Perhaps you intended to use UnliftedFFITypes
+    Suggested fix:
+      Perhaps you intended to use the ‘UnliftedFFITypes’ extension
+
diff --git a/testsuite/tests/gadt/T20485.stderr b/testsuite/tests/gadt/T20485.stderr
index 375d0540dac0..577cdfdf5940 100644
--- a/testsuite/tests/gadt/T20485.stderr
+++ b/testsuite/tests/gadt/T20485.stderr
@@ -2,14 +2,14 @@
 T20485.hs:7:3: warning: [GHC-58008] [-Wgadt-mono-local-binds (in -Wdefault)]
     Pattern matching on GADTs without MonoLocalBinds is fragile.
     Suggested fix:
-      Enable any of the following extensions: GADTs, TypeFamilies
+      Enable any of the following extensions: ‘GADTs’ or ‘TypeFamilies’ (implied by ‘TypeFamilyDependencies’)
 
 T20485.hs:9:19: warning: [GHC-58008] [-Wgadt-mono-local-binds (in -Wdefault)]
     Pattern matching on GADTs without MonoLocalBinds is fragile.
     Suggested fix:
-      Enable any of the following extensions: GADTs, TypeFamilies
+      Enable any of the following extensions: ‘GADTs’ or ‘TypeFamilies’ (implied by ‘TypeFamilyDependencies’)
 
 T20485.hs:12:3: warning: [GHC-58008] [-Wgadt-mono-local-binds (in -Wdefault)]
     Pattern matching on GADTs without MonoLocalBinds is fragile.
     Suggested fix:
-      Enable any of the following extensions: GADTs, TypeFamilies
+      Enable any of the following extensions: ‘GADTs’ or ‘TypeFamilies’ (implied by ‘TypeFamilyDependencies’)
diff --git a/testsuite/tests/gadt/gadtSyntaxFail001.stderr b/testsuite/tests/gadt/gadtSyntaxFail001.stderr
index c67d860afe8a..5a2abae27616 100644
--- a/testsuite/tests/gadt/gadtSyntaxFail001.stderr
+++ b/testsuite/tests/gadt/gadtSyntaxFail001.stderr
@@ -5,4 +5,4 @@ gadtSyntaxFail001.hs:9:5: error: [GHC-25709]
     • In the definition of data constructor ‘C2’
       In the data type declaration for ‘Foo’
     Suggested fix:
-      Enable any of the following extensions: ExistentialQuantification, GADTs
+      Enable any of the following extensions: ‘ExistentialQuantification’ or ‘GADTs’
diff --git a/testsuite/tests/gadt/gadtSyntaxFail002.stderr b/testsuite/tests/gadt/gadtSyntaxFail002.stderr
index 58e26888fd01..27a80d8f7c04 100644
--- a/testsuite/tests/gadt/gadtSyntaxFail002.stderr
+++ b/testsuite/tests/gadt/gadtSyntaxFail002.stderr
@@ -5,4 +5,4 @@ gadtSyntaxFail002.hs:9:5: error: [GHC-25709]
     • In the definition of data constructor ‘C2’
       In the data type declaration for ‘Foo’
     Suggested fix:
-      Enable any of the following extensions: ExistentialQuantification, GADTs
+      Enable any of the following extensions: ‘ExistentialQuantification’ or ‘GADTs’
diff --git a/testsuite/tests/gadt/gadtSyntaxFail003.stderr b/testsuite/tests/gadt/gadtSyntaxFail003.stderr
index 22f59c7a5b9e..3bf4985a93fb 100644
--- a/testsuite/tests/gadt/gadtSyntaxFail003.stderr
+++ b/testsuite/tests/gadt/gadtSyntaxFail003.stderr
@@ -5,4 +5,4 @@ gadtSyntaxFail003.hs:8:5: error: [GHC-25709]
     • In the definition of data constructor ‘C1’
       In the data type declaration for ‘Foo’
     Suggested fix:
-      Enable any of the following extensions: ExistentialQuantification, GADTs
+      Enable any of the following extensions: ‘ExistentialQuantification’ or ‘GADTs’
diff --git a/testsuite/tests/generics/T10604/T10604_no_PolyKinds.stderr b/testsuite/tests/generics/T10604/T10604_no_PolyKinds.stderr
index 85d62d22ed65..b39d4cbf139b 100644
--- a/testsuite/tests/generics/T10604/T10604_no_PolyKinds.stderr
+++ b/testsuite/tests/generics/T10604/T10604_no_PolyKinds.stderr
@@ -3,4 +3,5 @@ T10604_no_PolyKinds.hs:8:35: error: [GHC-62016]
     • Cannot derive well-kinded instance of form ‘Generic1 (F ...)’
         Class ‘Generic1’ expects an argument of kind ‘* -> *’
     • In the data declaration for ‘F’
-    Suggested fix: Perhaps you intended to use PolyKinds
+    Suggested fix:
+      Perhaps you intended to use the ‘PolyKinds’ extension
diff --git a/testsuite/tests/generics/T5462No1.stderr b/testsuite/tests/generics/T5462No1.stderr
index 48911b7007ba..50da4594aefc 100644
--- a/testsuite/tests/generics/T5462No1.stderr
+++ b/testsuite/tests/generics/T5462No1.stderr
@@ -6,7 +6,7 @@ T5462No1.hs:25:42: error: [GHC-82023]
         ‘GFunctor’ is not a stock derivable class (Eq, Show, etc.)
     • In the newtype declaration for ‘F’
     Suggested fix:
-      Perhaps you intended to use GeneralizedNewtypeDeriving
+      Perhaps you intended to use the ‘GeneralizedNewtypeDeriving’ extension
       for GHC's newtype-deriving extension
 
 T5462No1.hs:27:23: error: [GHC-00158]
@@ -18,4 +18,5 @@ T5462No1.hs:28:23: error: [GHC-00158]
     • Can't make a derived instance of ‘C2 H’:
         ‘C2’ is not a stock derivable class (Eq, Show, etc.)
     • In the data declaration for ‘H’
-    Suggested fix: Perhaps you intended to use DeriveAnyClass
+    Suggested fix:
+      Perhaps you intended to use the ‘DeriveAnyClass’ extension
diff --git a/testsuite/tests/ghci/prog006/prog006.stderr b/testsuite/tests/ghci/prog006/prog006.stderr
index 8347adb80357..75f7c0384b5d 100644
--- a/testsuite/tests/ghci/prog006/prog006.stderr
+++ b/testsuite/tests/ghci/prog006/prog006.stderr
@@ -5,7 +5,7 @@ Boot.hs:6:13: error: [GHC-25709]
     • In the definition of data constructor ‘D’
       In the data type declaration for ‘Data’
     Suggested fix:
-      Enable any of the following extensions: ExistentialQuantification, GADTs
+      Enable any of the following extensions: ‘ExistentialQuantification’ or ‘GADTs’
       You may enable these language extensions in GHCi with:
         :set -XExistentialQuantification
         :set -XGADTs
diff --git a/testsuite/tests/ghci/prog011/prog011.stderr b/testsuite/tests/ghci/prog011/prog011.stderr
index b53736332b4b..494d529e9232 100644
--- a/testsuite/tests/ghci/prog011/prog011.stderr
+++ b/testsuite/tests/ghci/prog011/prog011.stderr
@@ -2,6 +2,6 @@
 prog011.hx:14:22: error: [GHC-82311]
     Empty 'do' block
     Suggested fix:
-      Perhaps you intended to use NondecreasingIndentation
+      Perhaps you intended to use the ‘NondecreasingIndentation’ extension
       You may enable this language extension in GHCi with:
         :set -XNondecreasingIndentation
diff --git a/testsuite/tests/ghci/scripts/T13202a.stderr b/testsuite/tests/ghci/scripts/T13202a.stderr
index cedf46e38795..c5110f0271f9 100644
--- a/testsuite/tests/ghci/scripts/T13202a.stderr
+++ b/testsuite/tests/ghci/scripts/T13202a.stderr
@@ -4,6 +4,6 @@
     • When checking the inferred type
         foo :: forall {r} {a}. HasField "name" r a => r -> a
     Suggested fix:
-      Perhaps you intended to use FlexibleContexts
+      Perhaps you intended to use the ‘FlexibleContexts’ extension
       You may enable this language extension in GHCi with:
         :set -XFlexibleContexts
diff --git a/testsuite/tests/ghci/scripts/T14969.stderr b/testsuite/tests/ghci/scripts/T14969.stderr
index 3b0bf03dfa41..222328e63d92 100644
--- a/testsuite/tests/ghci/scripts/T14969.stderr
+++ b/testsuite/tests/ghci/scripts/T14969.stderr
@@ -5,6 +5,6 @@
     • When checking the inferred type
         it :: forall {t1} {t2} {t3}. (Num t1, Num (t2 -> t1 -> t3)) => t3
     Suggested fix:
-      Perhaps you intended to use FlexibleContexts
+      Perhaps you intended to use the ‘FlexibleContexts’ extension
       You may enable this language extension in GHCi with:
         :set -XFlexibleContexts
diff --git a/testsuite/tests/ghci/scripts/T23686.stderr b/testsuite/tests/ghci/scripts/T23686.stderr
index e8f6b3cefcb7..e298fcdb5c69 100644
--- a/testsuite/tests/ghci/scripts/T23686.stderr
+++ b/testsuite/tests/ghci/scripts/T23686.stderr
@@ -3,7 +3,7 @@ T23686A.hs:4:1: error: [GHC-39191]
     • Illegal family declaration for ‘GMap’
     • In the data family declaration for ‘GMap’
     Suggested fix:
-      Perhaps you intended to use TypeFamilies
+      Perhaps you intended to use the ‘TypeFamilies’ extension (implied by ‘TypeFamilyDependencies’)
       You may enable this language extension in GHCi with:
         :set -XTypeFamilies
 
@@ -12,7 +12,6 @@ T23686B.hs:5:5: error: [GHC-62558]
     • In the Template Haskell quotation
         [| \ left right x -> left (right x) |]
     Suggested fix:
-      Enable any of the following extensions: TemplateHaskell, TemplateHaskellQuotes
-      You may enable these language extensions in GHCi with:
-        :set -XTemplateHaskell
+      Perhaps you intended to use the ‘TemplateHaskellQuotes’ extension (implied by ‘TemplateHaskell’)
+      You may enable this language extension in GHCi with:
         :set -XTemplateHaskellQuotes
diff --git a/testsuite/tests/ghci/scripts/T9293.stderr b/testsuite/tests/ghci/scripts/T9293.stderr
index 865801e8c944..a24791b0006e 100644
--- a/testsuite/tests/ghci/scripts/T9293.stderr
+++ b/testsuite/tests/ghci/scripts/T9293.stderr
@@ -3,7 +3,7 @@
     • Illegal generalised algebraic data declaration for ‘T’
     • In the data declaration for ‘T’
     Suggested fix:
-      Perhaps you intended to use GADTs
+      Perhaps you intended to use the ‘GADTs’ extension
       You may enable this language extension in GHCi with: :set -XGADTs
 
 <interactive>:4:16: error: [GHC-25709]
@@ -12,7 +12,7 @@
     • In the definition of data constructor ‘C’
       In the data type declaration for ‘T’
     Suggested fix:
-      Enable any of the following extensions: ExistentialQuantification, GADTs
+      Enable any of the following extensions: ‘ExistentialQuantification’ or ‘GADTs’
       You may enable these language extensions in GHCi with:
         :set -XExistentialQuantification
         :set -XGADTs
@@ -23,7 +23,7 @@ ghci057.hs:4:3: error: [GHC-25709]
     • In the definition of data constructor ‘C’
       In the data type declaration for ‘T’
     Suggested fix:
-      Enable any of the following extensions: ExistentialQuantification, GADTs
+      Enable any of the following extensions: ‘ExistentialQuantification’ or ‘GADTs’
       You may enable these language extensions in GHCi with:
         :set -XExistentialQuantification
         :set -XGADTs
@@ -34,7 +34,7 @@ ghci057.hs:4:3: error: [GHC-25709]
     • In the definition of data constructor ‘C’
       In the data type declaration for ‘T’
     Suggested fix:
-      Enable any of the following extensions: ExistentialQuantification, GADTs
+      Enable any of the following extensions: ‘ExistentialQuantification’ or ‘GADTs’
       You may enable these language extensions in GHCi with:
         :set -XExistentialQuantification
         :set -XGADTs
diff --git a/testsuite/tests/ghci/scripts/ghci057.stderr b/testsuite/tests/ghci/scripts/ghci057.stderr
index 865801e8c944..a24791b0006e 100644
--- a/testsuite/tests/ghci/scripts/ghci057.stderr
+++ b/testsuite/tests/ghci/scripts/ghci057.stderr
@@ -3,7 +3,7 @@
     • Illegal generalised algebraic data declaration for ‘T’
     • In the data declaration for ‘T’
     Suggested fix:
-      Perhaps you intended to use GADTs
+      Perhaps you intended to use the ‘GADTs’ extension
       You may enable this language extension in GHCi with: :set -XGADTs
 
 <interactive>:4:16: error: [GHC-25709]
@@ -12,7 +12,7 @@
     • In the definition of data constructor ‘C’
       In the data type declaration for ‘T’
     Suggested fix:
-      Enable any of the following extensions: ExistentialQuantification, GADTs
+      Enable any of the following extensions: ‘ExistentialQuantification’ or ‘GADTs’
       You may enable these language extensions in GHCi with:
         :set -XExistentialQuantification
         :set -XGADTs
@@ -23,7 +23,7 @@ ghci057.hs:4:3: error: [GHC-25709]
     • In the definition of data constructor ‘C’
       In the data type declaration for ‘T’
     Suggested fix:
-      Enable any of the following extensions: ExistentialQuantification, GADTs
+      Enable any of the following extensions: ‘ExistentialQuantification’ or ‘GADTs’
       You may enable these language extensions in GHCi with:
         :set -XExistentialQuantification
         :set -XGADTs
@@ -34,7 +34,7 @@ ghci057.hs:4:3: error: [GHC-25709]
     • In the definition of data constructor ‘C’
       In the data type declaration for ‘T’
     Suggested fix:
-      Enable any of the following extensions: ExistentialQuantification, GADTs
+      Enable any of the following extensions: ‘ExistentialQuantification’ or ‘GADTs’
       You may enable these language extensions in GHCi with:
         :set -XExistentialQuantification
         :set -XGADTs
diff --git a/testsuite/tests/ghci/should_run/T10857a.stdout b/testsuite/tests/ghci/should_run/T10857a.stdout
index 51f30615f10f..bcc9eb306b7f 100644
--- a/testsuite/tests/ghci/should_run/T10857a.stdout
+++ b/testsuite/tests/ghci/should_run/T10857a.stdout
@@ -1,4 +1,4 @@
 base language is: GHC2021
 with the following modifiers:
-  -XExtendedDefaultRules
   -XNoMonomorphismRestriction
+  -XExtendedDefaultRules
diff --git a/testsuite/tests/ghci/should_run/T15806.stderr b/testsuite/tests/ghci/should_run/T15806.stderr
index 7e58e48e85ae..cc799cf73597 100644
--- a/testsuite/tests/ghci/should_run/T15806.stderr
+++ b/testsuite/tests/ghci/should_run/T15806.stderr
@@ -2,6 +2,6 @@
 <interactive>:1:1: error: [GHC-91510]
     Illegal polymorphic type: forall a. a -> a
     Suggested fix:
-      Perhaps you intended to use ImpredicativeTypes
+      Perhaps you intended to use the ‘ImpredicativeTypes’ extension
       You may enable this language extension in GHCi with:
         :set -XImpredicativeTypes
diff --git a/testsuite/tests/indexed-types/should_fail/BadFamInstDecl.stderr b/testsuite/tests/indexed-types/should_fail/BadFamInstDecl.stderr
index a0f6157ca550..03140bcda9f3 100644
--- a/testsuite/tests/indexed-types/should_fail/BadFamInstDecl.stderr
+++ b/testsuite/tests/indexed-types/should_fail/BadFamInstDecl.stderr
@@ -1,7 +1,8 @@
 [1 of 2] Compiling BadFamInstDecl_aux ( BadFamInstDecl_aux.hs, BadFamInstDecl_aux.o )
 [2 of 2] Compiling BadFamInstDecl   ( BadFamInstDecl.hs, BadFamInstDecl.o )
 
-BadFamInstDecl.hs:4:1: [GHC-06206]
-     Illegal family instance for ‘T’
-     In the type instance declaration for ‘T’
-     Suggested fix: Perhaps you intended to use TypeFamilies
+BadFamInstDecl.hs:4:1: error: [GHC-06206]
+    • Illegal family instance for ‘T’
+    • In the type instance declaration for ‘T’
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeFamilies’ extension (implied by ‘TypeFamilyDependencies’)
diff --git a/testsuite/tests/indexed-types/should_fail/NotRelaxedExamples.stderr b/testsuite/tests/indexed-types/should_fail/NotRelaxedExamples.stderr
index 372e45d390ec..53c88c8acfbf 100644
--- a/testsuite/tests/indexed-types/should_fail/NotRelaxedExamples.stderr
+++ b/testsuite/tests/indexed-types/should_fail/NotRelaxedExamples.stderr
@@ -3,16 +3,19 @@ NotRelaxedExamples.hs:9:15: error: [GHC-22979]
     • Illegal nested use of type family ‘F1’
         in the arguments of the type-family application ‘F1 (F1 Char)’
     • In the type instance declaration for ‘F1’
-    Suggested fix: Perhaps you intended to use UndecidableInstances
+    Suggested fix:
+      Perhaps you intended to use the ‘UndecidableInstances’ extension
 
 NotRelaxedExamples.hs:10:15: error: [GHC-22979]
     • The type-family application ‘F2 [x]’
         is no smaller than the LHS of the family instance ‘F2 [x]’
     • In the type instance declaration for ‘F2’
-    Suggested fix: Perhaps you intended to use UndecidableInstances
+    Suggested fix:
+      Perhaps you intended to use the ‘UndecidableInstances’ extension
 
 NotRelaxedExamples.hs:11:15: error: [GHC-22979]
     • The type-family application ‘F3 [Char]’
         is no smaller than the LHS of the family instance ‘F3 Bool’
     • In the type instance declaration for ‘F3’
-    Suggested fix: Perhaps you intended to use UndecidableInstances
+    Suggested fix:
+      Perhaps you intended to use the ‘UndecidableInstances’ extension
diff --git a/testsuite/tests/indexed-types/should_fail/SimpleFail15.stderr b/testsuite/tests/indexed-types/should_fail/SimpleFail15.stderr
index 4ae7d99ede83..671d8263189e 100644
--- a/testsuite/tests/indexed-types/should_fail/SimpleFail15.stderr
+++ b/testsuite/tests/indexed-types/should_fail/SimpleFail15.stderr
@@ -2,4 +2,5 @@
 SimpleFail15.hs:6:8: error: [GHC-91510]
     • Illegal qualified type: (a ~ b) => t
     • In the type signature: foo :: (a, b) -> (a ~ b => t) -> (a, b)
-    Suggested fix: Perhaps you intended to use RankNTypes
+    Suggested fix:
+      Perhaps you intended to use the ‘RankNTypes’ extension (implied by ‘ImpredicativeTypes’)
diff --git a/testsuite/tests/indexed-types/should_fail/T10817.stderr b/testsuite/tests/indexed-types/should_fail/T10817.stderr
index 745fa4dcbb37..92b63fb03626 100644
--- a/testsuite/tests/indexed-types/should_fail/T10817.stderr
+++ b/testsuite/tests/indexed-types/should_fail/T10817.stderr
@@ -4,4 +4,5 @@ T10817.hs:9:3: error: [GHC-22979]
         is no smaller than the LHS of the family instance ‘F a’
     • In the default type instance declaration for ‘F’
       In the class declaration for ‘C’
-    Suggested fix: Perhaps you intended to use UndecidableInstances
+    Suggested fix:
+      Perhaps you intended to use the ‘UndecidableInstances’ extension
diff --git a/testsuite/tests/indexed-types/should_fail/T13571.stderr b/testsuite/tests/indexed-types/should_fail/T13571.stderr
index 6723b1932274..0f1746560bef 100644
--- a/testsuite/tests/indexed-types/should_fail/T13571.stderr
+++ b/testsuite/tests/indexed-types/should_fail/T13571.stderr
@@ -2,4 +2,5 @@
 T13571.hs:5:1: error: [GHC-44012]
     • Illegal result type variable r for ‘F’
     • In the type family declaration for ‘F’
-    Suggested fix: Perhaps you intended to use TypeFamilyDependencies
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeFamilyDependencies’ extension
diff --git a/testsuite/tests/indexed-types/should_fail/T13571a.stderr b/testsuite/tests/indexed-types/should_fail/T13571a.stderr
index a12c0ce594b8..64d3fca26204 100644
--- a/testsuite/tests/indexed-types/should_fail/T13571a.stderr
+++ b/testsuite/tests/indexed-types/should_fail/T13571a.stderr
@@ -2,4 +2,5 @@
 T13571a.hs:7:1: error: [GHC-44012]
     • Illegal result type variable (r :: Type) for ‘G’
     • In the type family declaration for ‘G’
-    Suggested fix: Perhaps you intended to use TypeFamilyDependencies
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeFamilyDependencies’ extension
diff --git a/testsuite/tests/indexed-types/should_fail/T15172.stderr b/testsuite/tests/indexed-types/should_fail/T15172.stderr
index 4c064581c571..4adf8d1debb9 100644
--- a/testsuite/tests/indexed-types/should_fail/T15172.stderr
+++ b/testsuite/tests/indexed-types/should_fail/T15172.stderr
@@ -2,4 +2,5 @@
 T15172.hs:11:10: error: [GHC-22979]
     • Illegal use of type family ‘F’ in the constraint ‘F a’
     • In the instance declaration for ‘C [[a]]’
-    Suggested fix: Perhaps you intended to use UndecidableInstances
+    Suggested fix:
+      Perhaps you intended to use the ‘UndecidableInstances’ extension
diff --git a/testsuite/tests/indexed-types/should_fail/TyFamUndec.stderr b/testsuite/tests/indexed-types/should_fail/TyFamUndec.stderr
index d2f07b20045b..5be5cb3700a7 100644
--- a/testsuite/tests/indexed-types/should_fail/TyFamUndec.stderr
+++ b/testsuite/tests/indexed-types/should_fail/TyFamUndec.stderr
@@ -4,16 +4,19 @@ TyFamUndec.hs:6:15: error: [GHC-22979]
         in the type-family application ‘T (b, b)’
         than in the LHS of the family instance ‘T (a, [b])’
     • In the type instance declaration for ‘T’
-    Suggested fix: Perhaps you intended to use UndecidableInstances
+    Suggested fix:
+      Perhaps you intended to use the ‘UndecidableInstances’ extension
 
 TyFamUndec.hs:7:15: error: [GHC-22979]
     • The type-family application ‘T (a, Maybe b)’
         is no smaller than the LHS of the family instance ‘T (a, Maybe b)’
     • In the type instance declaration for ‘T’
-    Suggested fix: Perhaps you intended to use UndecidableInstances
+    Suggested fix:
+      Perhaps you intended to use the ‘UndecidableInstances’ extension
 
 TyFamUndec.hs:8:15: error: [GHC-22979]
     • Illegal nested use of type family ‘T’
         in the arguments of the type-family application ‘T (a, T b)’
     • In the type instance declaration for ‘T’
-    Suggested fix: Perhaps you intended to use UndecidableInstances
+    Suggested fix:
+      Perhaps you intended to use the ‘UndecidableInstances’ extension
diff --git a/testsuite/tests/linear/should_fail/LinearNoExt.stderr b/testsuite/tests/linear/should_fail/LinearNoExt.stderr
index 21bbc6181e36..43b3d316ee51 100644
--- a/testsuite/tests/linear/should_fail/LinearNoExt.stderr
+++ b/testsuite/tests/linear/should_fail/LinearNoExt.stderr
@@ -1,4 +1,5 @@
 
 LinearNoExt.hs:3:14: error: [GHC-31574]
     Illegal use of linear functions
-    Suggested fix: Perhaps you intended to use LinearTypes
+    Suggested fix:
+      Perhaps you intended to use the ‘LinearTypes’ extension
diff --git a/testsuite/tests/linear/should_fail/LinearNoExtU.stderr b/testsuite/tests/linear/should_fail/LinearNoExtU.stderr
index ae769e762687..dde2b6170c11 100644
--- a/testsuite/tests/linear/should_fail/LinearNoExtU.stderr
+++ b/testsuite/tests/linear/should_fail/LinearNoExtU.stderr
@@ -1,4 +1,5 @@
 
 LinearNoExtU.hs:4:14: error: [GHC-31574]
     Illegal use of linear functions
-    Suggested fix: Perhaps you intended to use LinearTypes
+    Suggested fix:
+      Perhaps you intended to use the ‘LinearTypes’ extension
diff --git a/testsuite/tests/linear/should_fail/T18888.stderr b/testsuite/tests/linear/should_fail/T18888.stderr
index aa2032db1d79..b8a95ae1a9e7 100644
--- a/testsuite/tests/linear/should_fail/T18888.stderr
+++ b/testsuite/tests/linear/should_fail/T18888.stderr
@@ -1,4 +1,5 @@
 
-T18888.hs:4:9: [GHC-68567]
-    Illegal type: ‘001’ 
-    Suggested fix: Perhaps you intended to use DataKinds
\ No newline at end of file
+T18888.hs:4:9: error: [GHC-68567]
+    Illegal type: ‘001’
+    Suggested fix:
+      Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’)
diff --git a/testsuite/tests/mdo/should_fail/mdofail005.stderr b/testsuite/tests/mdo/should_fail/mdofail005.stderr
index f05b79311d77..977201071d45 100644
--- a/testsuite/tests/mdo/should_fail/mdofail005.stderr
+++ b/testsuite/tests/mdo/should_fail/mdofail005.stderr
@@ -1,4 +1,5 @@
 
 mdofail005.hs:11:14: error: [GHC-58481]
     parse error on input ‘<-’
-    Suggested fix: Perhaps you intended to use RecursiveDo
+    Suggested fix:
+      Perhaps you intended to use the ‘RecursiveDo’ extension
diff --git a/testsuite/tests/module/T20007.stderr b/testsuite/tests/module/T20007.stderr
index 6405397c0bf9..7b16b59213e7 100644
--- a/testsuite/tests/module/T20007.stderr
+++ b/testsuite/tests/module/T20007.stderr
@@ -1,8 +1,8 @@
 
-T20007.hs:1:29: [GHC-56449]
+T20007.hs:1:29: error: [GHC-56449]
     In the import of ‘Data.Type.Equality’:
       an item called ‘(~)’ is exported, but it is a type.
     Suggested fixes:
-       Use ExplicitNamespaces
-       Add the ‘type’ keyword to the import statement:
+      • Use the ‘ExplicitNamespaces’ extension (implied by ‘TypeFamilies’ and ‘TypeOperators’)
+      • Add the ‘type’ keyword to the import statement:
           import Data.Type.Equality ( type (~) )
diff --git a/testsuite/tests/module/mod182.stderr b/testsuite/tests/module/mod182.stderr
index 01e564c3f775..db773bb60c85 100644
--- a/testsuite/tests/module/mod182.stderr
+++ b/testsuite/tests/module/mod182.stderr
@@ -1,4 +1,5 @@
 
 mod182.hs:6:16: error: [GHC-87491]
     Found ‘qualified’ in postpositive position. 
-    Suggested fix: Perhaps you intended to use ImportQualifiedPost
+    Suggested fix:
+      Perhaps you intended to use the ‘ImportQualifiedPost’ extension
diff --git a/testsuite/tests/module/mod184.stderr b/testsuite/tests/module/mod184.stderr
index ab72b5d0b29e..b4f2c9429e41 100644
--- a/testsuite/tests/module/mod184.stderr
+++ b/testsuite/tests/module/mod184.stderr
@@ -3,4 +3,4 @@ mod184.hs:6:8: warning: [GHC-07924] [-Wprepositive-qualified-module]
     Found ‘qualified’ in prepositive position
     Suggested fixes:
       • Place ‘qualified’ after the module name.
-      • Perhaps you intended to use ImportQualifiedPost
+      • Perhaps you intended to use the ‘ImportQualifiedPost’ extension
diff --git a/testsuite/tests/module/mod39.stderr b/testsuite/tests/module/mod39.stderr
index 2d093f36a432..90c51feaae1b 100644
--- a/testsuite/tests/module/mod39.stderr
+++ b/testsuite/tests/module/mod39.stderr
@@ -4,4 +4,5 @@ mod39.hs:4:17: error: [GHC-25079]
         constrains only the class type variables
     • When checking the class method: f :: forall a. (C a, Eq a) => a
       In the class declaration for ‘C’
-    Suggested fix: Perhaps you intended to use ConstrainedClassMethods
+    Suggested fix:
+      Perhaps you intended to use the ‘ConstrainedClassMethods’ extension (implied by ‘MultiParamTypeClasses’)
diff --git a/testsuite/tests/module/mod40.stderr b/testsuite/tests/module/mod40.stderr
index b434d1276133..427f6fd476d3 100644
--- a/testsuite/tests/module/mod40.stderr
+++ b/testsuite/tests/module/mod40.stderr
@@ -4,11 +4,13 @@ mod40.hs:3:1: error: [GHC-29210]
         one of whose superclasses is ‘C2’
         one of whose superclasses is ‘C1’
     • In the class declaration for ‘C1’
-    Suggested fix: Perhaps you intended to use UndecidableSuperClasses
+    Suggested fix:
+      Perhaps you intended to use the ‘UndecidableSuperClasses’ extension
 
 mod40.hs:4:1: error: [GHC-29210]
     • Superclass cycle for ‘C2’
         one of whose superclasses is ‘C1’
         one of whose superclasses is ‘C2’
     • In the class declaration for ‘C2’
-    Suggested fix: Perhaps you intended to use UndecidableSuperClasses
+    Suggested fix:
+      Perhaps you intended to use the ‘UndecidableSuperClasses’ extension
diff --git a/testsuite/tests/module/mod41.stderr b/testsuite/tests/module/mod41.stderr
index 5ef80e4cf1a5..7dd320f2da99 100644
--- a/testsuite/tests/module/mod41.stderr
+++ b/testsuite/tests/module/mod41.stderr
@@ -5,4 +5,5 @@ mod41.hs:4:18: error: [GHC-48406]
         where a1 ... an are *distinct type variables*,
         and each type variable appears at most once in the instance head.
     • In the instance declaration for ‘Eq (Either a a)’
-    Suggested fix: Perhaps you intended to use FlexibleInstances
+    Suggested fix:
+      Perhaps you intended to use the ‘FlexibleInstances’ extension
diff --git a/testsuite/tests/module/mod42.stderr b/testsuite/tests/module/mod42.stderr
index 6f71eb6dc5d4..e2eac94ffc32 100644
--- a/testsuite/tests/module/mod42.stderr
+++ b/testsuite/tests/module/mod42.stderr
@@ -5,4 +5,5 @@ mod42.hs:4:10: error: [GHC-48406]
         where a1 ... an are *distinct type variables*,
         and each type variable appears at most once in the instance head.
     • In the instance declaration for ‘Eq a’
-    Suggested fix: Perhaps you intended to use FlexibleInstances
+    Suggested fix:
+      Perhaps you intended to use the ‘FlexibleInstances’ extension
diff --git a/testsuite/tests/module/mod43.stderr b/testsuite/tests/module/mod43.stderr
index 6e3de417d616..4f40c60ff2dd 100644
--- a/testsuite/tests/module/mod43.stderr
+++ b/testsuite/tests/module/mod43.stderr
@@ -4,4 +4,5 @@ mod43.hs:4:10: error: [GHC-93557]
         All instance types must be of the form (T t1 ... tn)
         where T is not a synonym.
     • In the instance declaration for ‘Eq String’
-    Suggested fix: Perhaps you intended to use TypeSynonymInstances
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeSynonymInstances’ extension (implied by ‘FlexibleInstances’)
diff --git a/testsuite/tests/module/mod45.stderr b/testsuite/tests/module/mod45.stderr
index 6e159e133ded..98a9a43f5019 100644
--- a/testsuite/tests/module/mod45.stderr
+++ b/testsuite/tests/module/mod45.stderr
@@ -3,4 +3,5 @@ mod45.hs:6:11: error: [GHC-06202]
     • Illegal type signature in instance declaration:
         (==) :: T -> T -> Bool
     • In the instance declaration for ‘Eq T’
-    Suggested fix: Perhaps you intended to use InstanceSigs
+    Suggested fix:
+      Perhaps you intended to use the ‘InstanceSigs’ extension
diff --git a/testsuite/tests/module/mod53.stderr b/testsuite/tests/module/mod53.stderr
index 7e980745fb12..726fa84817da 100644
--- a/testsuite/tests/module/mod53.stderr
+++ b/testsuite/tests/module/mod53.stderr
@@ -3,4 +3,5 @@ mod53.hs:4:22: error: [GHC-00158]
     • Can't make a derived instance of ‘C T’:
         ‘C’ is not a stock derivable class (Eq, Show, etc.)
     • In the data declaration for ‘T’
-    Suggested fix: Perhaps you intended to use DeriveAnyClass
+    Suggested fix:
+      Perhaps you intended to use the ‘DeriveAnyClass’ extension
diff --git a/testsuite/tests/numeric/should_compile/T8542.stderr b/testsuite/tests/numeric/should_compile/T8542.stderr
index aaae8d775f64..410d6cae2626 100644
--- a/testsuite/tests/numeric/should_compile/T8542.stderr
+++ b/testsuite/tests/numeric/should_compile/T8542.stderr
@@ -2,5 +2,5 @@
 T8542.hs:9:5: warning: [GHC-97441] [-Woverflowed-literals (in -Wdefault)]
     Literal 128 is out of the Int8 range -128..127
     Suggested fix:
-      Perhaps you intended to use NegativeLiterals
+      Perhaps you intended to use the ‘NegativeLiterals’ extension
       If you are trying to write a large negative literal
diff --git a/testsuite/tests/overloadedrecflds/should_fail/NoFieldSelectorsFail.stderr b/testsuite/tests/overloadedrecflds/should_fail/NoFieldSelectorsFail.stderr
index cf92d760c276..a22d3e427e81 100644
--- a/testsuite/tests/overloadedrecflds/should_fail/NoFieldSelectorsFail.stderr
+++ b/testsuite/tests/overloadedrecflds/should_fail/NoFieldSelectorsFail.stderr
@@ -18,7 +18,8 @@ NoFieldSelectorsFail.hs:12:15: error: [GHC-56428]
       • record field ‘foo’ of ‘Bar’,
         imported from ‘NoFieldSelectorsFailA’ at NoFieldSelectorsFail.hs:4:1-28
         (and originally defined at NoFieldSelectorsFailA.hs:6:18-20)
-    Suggested fix: Perhaps you intended to use DisambiguateRecordFields
+    Suggested fix:
+      Perhaps you intended to use the ‘DisambiguateRecordFields’ extension (implied by ‘RecordWildCards’ and ‘DuplicateRecordFields’)
 
 NoFieldSelectorsFail.hs:14:15: error: [GHC-56428]
     Ambiguous record field ‘foo’.
@@ -29,7 +30,8 @@ NoFieldSelectorsFail.hs:14:15: error: [GHC-56428]
       • record field ‘foo’ of ‘Bar’,
         imported from ‘NoFieldSelectorsFailA’ at NoFieldSelectorsFail.hs:4:1-28
         (and originally defined at NoFieldSelectorsFailA.hs:6:18-20)
-    Suggested fix: Perhaps you intended to use DisambiguateRecordFields
+    Suggested fix:
+      Perhaps you intended to use the ‘DisambiguateRecordFields’ extension (implied by ‘RecordWildCards’ and ‘DuplicateRecordFields’)
 
 NoFieldSelectorsFail.hs:16:15: error: [GHC-56428]
     Ambiguous record field ‘bar’.
@@ -40,4 +42,5 @@ NoFieldSelectorsFail.hs:16:15: error: [GHC-56428]
       • variable ‘bar’,
         imported from ‘NoFieldSelectorsFailA’ at NoFieldSelectorsFail.hs:4:1-28
         (and originally defined at NoFieldSelectorsFailA.hs:8:1-3)
-    Suggested fix: Perhaps you intended to use DisambiguateRecordFields
+    Suggested fix:
+      Perhaps you intended to use the ‘DisambiguateRecordFields’ extension (implied by ‘RecordWildCards’ and ‘DuplicateRecordFields’)
diff --git a/testsuite/tests/overloadedrecflds/should_fail/T18999_NoDisambiguateRecordFields.stderr b/testsuite/tests/overloadedrecflds/should_fail/T18999_NoDisambiguateRecordFields.stderr
index 6831c7c36573..56b3a4118ce3 100644
--- a/testsuite/tests/overloadedrecflds/should_fail/T18999_NoDisambiguateRecordFields.stderr
+++ b/testsuite/tests/overloadedrecflds/should_fail/T18999_NoDisambiguateRecordFields.stderr
@@ -16,4 +16,5 @@ T18999_NoDisambiguateRecordFields.hs:8:11: error: [GHC-56428]
       • variable ‘not’,
         imported from ‘Prelude’ at T18999_NoDisambiguateRecordFields.hs:2:8-40
         (and originally defined in ‘GHC.Classes’)
-    Suggested fix: Perhaps you intended to use DisambiguateRecordFields
+    Suggested fix:
+      Perhaps you intended to use the ‘DisambiguateRecordFields’ extension (implied by ‘RecordWildCards’ and ‘DuplicateRecordFields’)
diff --git a/testsuite/tests/overloadedrecflds/should_fail/overloadedrecfldsfail10.stderr b/testsuite/tests/overloadedrecflds/should_fail/overloadedrecfldsfail10.stderr
index ad62403ddc94..7b4266db7649 100644
--- a/testsuite/tests/overloadedrecflds/should_fail/overloadedrecfldsfail10.stderr
+++ b/testsuite/tests/overloadedrecflds/should_fail/overloadedrecfldsfail10.stderr
@@ -14,7 +14,8 @@ overloadedrecfldsfail10.hs:6:20: error: [GHC-97219]
          imported from ‘OverloadedRecFldsFail10_C’ at overloadedrecfldsfail10.hs:9:1-32
          (and originally defined in ‘OverloadedRecFldsFail10_A’
             at OverloadedRecFldsFail10_A.hs:5:32-34)
-    Suggested fix: Perhaps you intended to use DuplicateRecordFields
+    Suggested fix:
+      Perhaps you intended to use the ‘DuplicateRecordFields’ extension
 
 overloadedrecfldsfail10.hs:6:20: error: [GHC-97219]
     Duplicate record field ‘foo’ in export list:
@@ -27,4 +28,5 @@ overloadedrecfldsfail10.hs:6:20: error: [GHC-97219]
          imported from ‘OverloadedRecFldsFail10_C’ at overloadedrecfldsfail10.hs:9:1-32
          (and originally defined in ‘OverloadedRecFldsFail10_A’
             at OverloadedRecFldsFail10_A.hs:5:32-34)
-    Suggested fix: Perhaps you intended to use DuplicateRecordFields
+    Suggested fix:
+      Perhaps you intended to use the ‘DuplicateRecordFields’ extension
diff --git a/testsuite/tests/parser/should_fail/ListTuplePunsFail1.stderr b/testsuite/tests/parser/should_fail/ListTuplePunsFail1.stderr
index 21de0aa9aa81..412ddb6bf32d 100644
--- a/testsuite/tests/parser/should_fail/ListTuplePunsFail1.stderr
+++ b/testsuite/tests/parser/should_fail/ListTuplePunsFail1.stderr
@@ -1,8 +1,9 @@
+
 ListTuplePunsFail1.hs:5:10: error: [GHC-52943]
     Disambiguating data constructors of tuples and lists is disabled.
     Remove the quote to use the data constructor.
     Suggested fix:
-      Perhaps you intended to use ListTuplePuns
+      Perhaps you intended to use the ‘ListTuplePuns’ extension
       You may enable this language extension in GHCi with:
         :set -XListTuplePuns
 
@@ -10,7 +11,7 @@ ListTuplePunsFail1.hs:7:10: error: [GHC-52943]
     Disambiguating data constructors of tuples and lists is disabled.
     Remove the quote to use the data constructor.
     Suggested fix:
-      Perhaps you intended to use ListTuplePuns
+      Perhaps you intended to use the ‘ListTuplePuns’ extension
       You may enable this language extension in GHCi with:
         :set -XListTuplePuns
 
@@ -18,7 +19,7 @@ ListTuplePunsFail1.hs:9:10: error: [GHC-52943]
     Disambiguating data constructors of tuples and lists is disabled.
     Remove the quote to use the data constructor.
     Suggested fix:
-      Perhaps you intended to use ListTuplePuns
+      Perhaps you intended to use the ‘ListTuplePuns’ extension
       You may enable this language extension in GHCi with:
         :set -XListTuplePuns
 
@@ -26,7 +27,7 @@ ListTuplePunsFail1.hs:11:11: error: [GHC-52943]
     Disambiguating data constructors of tuples and lists is disabled.
     Remove the quote to use the data constructor.
     Suggested fix:
-      Perhaps you intended to use ListTuplePuns
+      Perhaps you intended to use the ‘ListTuplePuns’ extension
       You may enable this language extension in GHCi with:
         :set -XListTuplePuns
 
@@ -34,7 +35,7 @@ ListTuplePunsFail1.hs:13:11: error: [GHC-52943]
     Disambiguating data constructors of tuples and lists is disabled.
     Remove the quote to use the data constructor.
     Suggested fix:
-      Perhaps you intended to use ListTuplePuns
+      Perhaps you intended to use the ‘ListTuplePuns’ extension
       You may enable this language extension in GHCi with:
         :set -XListTuplePuns
 
@@ -42,7 +43,7 @@ ListTuplePunsFail1.hs:15:11: error: [GHC-52943]
     Disambiguating data constructors of tuples and lists is disabled.
     Remove the quote to use the data constructor.
     Suggested fix:
-      Perhaps you intended to use ListTuplePuns
+      Perhaps you intended to use the ‘ListTuplePuns’ extension
       You may enable this language extension in GHCi with:
         :set -XListTuplePuns
 
@@ -50,30 +51,30 @@ ListTuplePunsFail1.hs:17:11: error: [GHC-52943]
     Disambiguating data constructors of tuples and lists is disabled.
     Remove the quote to use the data constructor.
     Suggested fix:
-      Perhaps you intended to use ListTuplePuns
+      Perhaps you intended to use the ‘ListTuplePuns’ extension
       You may enable this language extension in GHCi with:
         :set -XListTuplePuns
 
-ListTuplePunsFail1.hs:19:12: [GHC-52943]
+ListTuplePunsFail1.hs:19:12: error: [GHC-52943]
     Unboxed tuple data constructors are not supported in types.
     Use ‘Tuple<n># a b c ...’ to refer to the type constructor.
     Suggested fix:
-      Perhaps you intended to use ListTuplePuns
+      Perhaps you intended to use the ‘ListTuplePuns’ extension
       You may enable this language extension in GHCi with:
         :set -XListTuplePuns
 
-ListTuplePunsFail1.hs:21:13: [GHC-52943]
+ListTuplePunsFail1.hs:21:13: error: [GHC-52943]
     Unboxed sum data constructors are not supported in types.
     Use ‘Sum<n># a b c ...’ to refer to the type constructor.
     Suggested fix:
-      Perhaps you intended to use ListTuplePuns
+      Perhaps you intended to use the ‘ListTuplePuns’ extension
       You may enable this language extension in GHCi with:
         :set -XListTuplePuns
 
-ListTuplePunsFail1.hs:23:13: [GHC-52943]
+ListTuplePunsFail1.hs:23:13: error: [GHC-52943]
     Unboxed sum data constructors are not supported in types.
     Use ‘Sum<n># a b c ...’ to refer to the type constructor.
     Suggested fix:
-      Perhaps you intended to use ListTuplePuns
+      Perhaps you intended to use the ‘ListTuplePuns’ extension
       You may enable this language extension in GHCi with:
         :set -XListTuplePuns
diff --git a/testsuite/tests/parser/should_fail/NoBlockArgumentsFail.stderr b/testsuite/tests/parser/should_fail/NoBlockArgumentsFail.stderr
index 4fa84606ac95..34e077491f80 100644
--- a/testsuite/tests/parser/should_fail/NoBlockArgumentsFail.stderr
+++ b/testsuite/tests/parser/should_fail/NoBlockArgumentsFail.stderr
@@ -4,4 +4,4 @@ NoBlockArgumentsFail.hs:6:17: error: [GHC-52095]
         do return ()
     Suggested fixes:
       • Use parentheses.
-      • Perhaps you intended to use BlockArguments
+      • Perhaps you intended to use the ‘BlockArguments’ extension
diff --git a/testsuite/tests/parser/should_fail/NoBlockArgumentsFail2.stderr b/testsuite/tests/parser/should_fail/NoBlockArgumentsFail2.stderr
index f26f73713ead..ab4b97f12e42 100644
--- a/testsuite/tests/parser/should_fail/NoBlockArgumentsFail2.stderr
+++ b/testsuite/tests/parser/should_fail/NoBlockArgumentsFail2.stderr
@@ -4,4 +4,4 @@ NoBlockArgumentsFail2.hs:6:22: error: [GHC-06074]
         \ x -> print x
     Suggested fixes:
       • Use parentheses.
-      • Perhaps you intended to use BlockArguments
+      • Perhaps you intended to use the ‘BlockArguments’ extension
diff --git a/testsuite/tests/parser/should_fail/NoBlockArgumentsFail3.stderr b/testsuite/tests/parser/should_fail/NoBlockArgumentsFail3.stderr
index 6c497a9f6059..675107d98a7c 100644
--- a/testsuite/tests/parser/should_fail/NoBlockArgumentsFail3.stderr
+++ b/testsuite/tests/parser/should_fail/NoBlockArgumentsFail3.stderr
@@ -4,4 +4,4 @@ NoBlockArgumentsFail3.hs:7:22: error: [GHC-06074]
         \case Just 3 -> print x
     Suggested fixes:
       • Use parentheses.
-      • Perhaps you intended to use BlockArguments
+      • Perhaps you intended to use the ‘BlockArguments’ extension
diff --git a/testsuite/tests/parser/should_fail/NoBlockArgumentsFailArrowCmds.stderr b/testsuite/tests/parser/should_fail/NoBlockArgumentsFailArrowCmds.stderr
index fbc86a8edc7e..0351e08a8f05 100644
--- a/testsuite/tests/parser/should_fail/NoBlockArgumentsFailArrowCmds.stderr
+++ b/testsuite/tests/parser/should_fail/NoBlockArgumentsFailArrowCmds.stderr
@@ -4,4 +4,4 @@ NoBlockArgumentsFailArrowCmds.hs:7:27: error: [GHC-12178]
         \ () -> () >- returnA
     Suggested fixes:
       • Use parentheses.
-      • Perhaps you intended to use BlockArguments
+      • Perhaps you intended to use the ‘BlockArguments’ extension
diff --git a/testsuite/tests/parser/should_fail/NoDoAndIfThenElse.stderr b/testsuite/tests/parser/should_fail/NoDoAndIfThenElse.stderr
index d21b25048261..d27b7c3ace32 100644
--- a/testsuite/tests/parser/should_fail/NoDoAndIfThenElse.stderr
+++ b/testsuite/tests/parser/should_fail/NoDoAndIfThenElse.stderr
@@ -2,4 +2,5 @@
 NoDoAndIfThenElse.hs:7:13: error: [GHC-75254]
     Unexpected semi-colons in conditional:
         if True; then return (); else return ()
-    Suggested fix: Perhaps you intended to use DoAndIfThenElse
+    Suggested fix:
+      Perhaps you intended to use the ‘DoAndIfThenElse’ extension
diff --git a/testsuite/tests/parser/should_fail/NoNumericUnderscores0.stderr b/testsuite/tests/parser/should_fail/NoNumericUnderscores0.stderr
index 837688a9bad6..e9fac7ed7310 100644
--- a/testsuite/tests/parser/should_fail/NoNumericUnderscores0.stderr
+++ b/testsuite/tests/parser/should_fail/NoNumericUnderscores0.stderr
@@ -1,4 +1,5 @@
 
 NoNumericUnderscores0.hs:11:3: error: [GHC-62330]
     Illegal underscores in integer literals
-    Suggested fix: Perhaps you intended to use NumericUnderscores
+    Suggested fix:
+      Perhaps you intended to use the ‘NumericUnderscores’ extension
diff --git a/testsuite/tests/parser/should_fail/NoNumericUnderscores1.stderr b/testsuite/tests/parser/should_fail/NoNumericUnderscores1.stderr
index 03a0da4c947f..9bf4809b1acd 100644
--- a/testsuite/tests/parser/should_fail/NoNumericUnderscores1.stderr
+++ b/testsuite/tests/parser/should_fail/NoNumericUnderscores1.stderr
@@ -1,4 +1,5 @@
 
 NoNumericUnderscores1.hs:11:3: error: [GHC-62330]
     Illegal underscores in floating literals
-    Suggested fix: Perhaps you intended to use NumericUnderscores
+    Suggested fix:
+      Perhaps you intended to use the ‘NumericUnderscores’ extension
diff --git a/testsuite/tests/parser/should_fail/NoPatternSynonyms.stderr b/testsuite/tests/parser/should_fail/NoPatternSynonyms.stderr
index 84af9aa95ef5..5e29d6f1e65c 100644
--- a/testsuite/tests/parser/should_fail/NoPatternSynonyms.stderr
+++ b/testsuite/tests/parser/should_fail/NoPatternSynonyms.stderr
@@ -2,4 +2,5 @@
 NoPatternSynonyms.hs:3:1: error: [GHC-94426]
     Invalid type signature:
     A type signature should be of form <variables> :: <type>.
-    Suggested fix: Perhaps you intended to use PatternSynonyms
+    Suggested fix:
+      Perhaps you intended to use the ‘PatternSynonyms’ extension
diff --git a/testsuite/tests/parser/should_fail/NondecreasingIndentationFail.stderr b/testsuite/tests/parser/should_fail/NondecreasingIndentationFail.stderr
index 075ac76ce25b..2874f1eff304 100644
--- a/testsuite/tests/parser/should_fail/NondecreasingIndentationFail.stderr
+++ b/testsuite/tests/parser/should_fail/NondecreasingIndentationFail.stderr
@@ -1,8 +1,10 @@
 
-NondecreasingIndentationFail.hs:7:28: [GHC-82311]
+NondecreasingIndentationFail.hs:7:28: error: [GHC-82311]
     Empty 'do' block
-    Suggested fix: Perhaps you intended to use NondecreasingIndentation
+    Suggested fix:
+      Perhaps you intended to use the ‘NondecreasingIndentation’ extension
 
-NondecreasingIndentationFail.hs:9:28: [GHC-82311]
+NondecreasingIndentationFail.hs:9:28: error: [GHC-82311]
     Empty 'do' block
-    Suggested fix: Perhaps you intended to use NondecreasingIndentation
+    Suggested fix:
+      Perhaps you intended to use the ‘NondecreasingIndentation’ extension
diff --git a/testsuite/tests/parser/should_fail/ParserNoForallUnicode.stderr b/testsuite/tests/parser/should_fail/ParserNoForallUnicode.stderr
index a47b03b1330d..3b60d5905a71 100644
--- a/testsuite/tests/parser/should_fail/ParserNoForallUnicode.stderr
+++ b/testsuite/tests/parser/should_fail/ParserNoForallUnicode.stderr
@@ -2,5 +2,7 @@
 ParserNoForallUnicode.hs:6:8: error: [GHC-25955]
     Illegal symbol ‘∀’ in type
     Suggested fix:
-      Perhaps you intended to use RankNTypes
-      or a similar language extension to enable explicit-forall syntax: ∀ <tvs>. <type>
+      Use the ‘ExplicitForAll’ extension (implied by ‘RankNTypes’,
+                                                     ‘QuantifiedConstraints’, ‘ScopedTypeVariables’,
+                                                     ‘LiberalTypeSynonyms’ and ‘ExistentialQuantification’)
+      to enable syntax: ∀ <tvs>. <type>
diff --git a/testsuite/tests/parser/should_fail/ParserNoLambdaCase.stderr b/testsuite/tests/parser/should_fail/ParserNoLambdaCase.stderr
index 35ea9ecd4717..e8ed2f8d0a2a 100644
--- a/testsuite/tests/parser/should_fail/ParserNoLambdaCase.stderr
+++ b/testsuite/tests/parser/should_fail/ParserNoLambdaCase.stderr
@@ -1,4 +1,5 @@
 
 ParserNoLambdaCase.hs:3:6: error: [GHC-51179]
     Illegal \case
-    Suggested fix: Perhaps you intended to use LambdaCase
+    Suggested fix:
+      Perhaps you intended to use the ‘LambdaCase’ extension
diff --git a/testsuite/tests/parser/should_fail/ParserNoMultiWayIf.stderr b/testsuite/tests/parser/should_fail/ParserNoMultiWayIf.stderr
index 24f39642bd4c..51fb92ee0266 100644
--- a/testsuite/tests/parser/should_fail/ParserNoMultiWayIf.stderr
+++ b/testsuite/tests/parser/should_fail/ParserNoMultiWayIf.stderr
@@ -1,4 +1,5 @@
 
 ParserNoMultiWayIf.hs:4:5: error: [GHC-28985]
     Illegal multi-way if-expression
-    Suggested fix: Perhaps you intended to use MultiWayIf
+    Suggested fix:
+      Perhaps you intended to use the ‘MultiWayIf’ extension
diff --git a/testsuite/tests/parser/should_fail/ParserNoTH1.stderr b/testsuite/tests/parser/should_fail/ParserNoTH1.stderr
index eeb32bffcadc..6a5c62dcda01 100644
--- a/testsuite/tests/parser/should_fail/ParserNoTH1.stderr
+++ b/testsuite/tests/parser/should_fail/ParserNoTH1.stderr
@@ -6,4 +6,5 @@ ParserNoTH1.hs:1:5: warning: [GHC-47082] [-Woperator-whitespace-ext-conflict (in
 
 ParserNoTH1.hs:1:5: error: [GHC-58481]
     parse error on input ‘$’
-    Suggested fix: Perhaps you intended to use TemplateHaskell
+    Suggested fix:
+      Perhaps you intended to use the ‘TemplateHaskell’ extension
diff --git a/testsuite/tests/parser/should_fail/ParserNoTH2.stderr b/testsuite/tests/parser/should_fail/ParserNoTH2.stderr
index 4873078fa812..8ac6d8696429 100644
--- a/testsuite/tests/parser/should_fail/ParserNoTH2.stderr
+++ b/testsuite/tests/parser/should_fail/ParserNoTH2.stderr
@@ -6,4 +6,5 @@ ParserNoTH2.hs:1:5: warning: [GHC-47082] [-Woperator-whitespace-ext-conflict (in
 
 ParserNoTH2.hs:1:5: error: [GHC-58481]
     parse error on input ‘$$’
-    Suggested fix: Perhaps you intended to use TemplateHaskell
+    Suggested fix:
+      Perhaps you intended to use the ‘TemplateHaskell’ extension
diff --git a/testsuite/tests/parser/should_fail/RecordDotSyntaxFail12.stderr b/testsuite/tests/parser/should_fail/RecordDotSyntaxFail12.stderr
index 9c4986935399..5629ebdcb6c7 100644
--- a/testsuite/tests/parser/should_fail/RecordDotSyntaxFail12.stderr
+++ b/testsuite/tests/parser/should_fail/RecordDotSyntaxFail12.stderr
@@ -1,15 +1,18 @@
 
 RecordDotSyntaxFail12.hs:124:25: error: [GHC-44287]
     Illegal use of punning for field ‘quux’
-    Suggested fix: Perhaps you intended to use NamedFieldPuns
+    Suggested fix:
+      Perhaps you intended to use the ‘NamedFieldPuns’ extension
 
 RecordDotSyntaxFail12.hs:124:46: error: [GHC-44287]
     Illegal use of punning for field ‘baz’
-    Suggested fix: Perhaps you intended to use NamedFieldPuns
+    Suggested fix:
+      Perhaps you intended to use the ‘NamedFieldPuns’ extension
 
 RecordDotSyntaxFail12.hs:124:65: error: [GHC-44287]
     Illegal use of punning for field ‘bar’
-    Suggested fix: Perhaps you intended to use NamedFieldPuns
+    Suggested fix:
+      Perhaps you intended to use the ‘NamedFieldPuns’ extension
 
 RecordDotSyntaxFail12.hs:125:11: error: [GHC-57365]
     For this to work enable NamedFieldPuns
diff --git a/testsuite/tests/parser/should_fail/RecordDotSyntaxFail2.stderr b/testsuite/tests/parser/should_fail/RecordDotSyntaxFail2.stderr
index 353ae4bc9016..6660ab6b0078 100644
--- a/testsuite/tests/parser/should_fail/RecordDotSyntaxFail2.stderr
+++ b/testsuite/tests/parser/should_fail/RecordDotSyntaxFail2.stderr
@@ -1,4 +1,5 @@
 
 RecordDotSyntaxFail2.hs:10:10: error: [GHC-82135]
     Illegal overloaded record update
-    Suggested fix: Perhaps you intended to use OverloadedRecordUpdate
+    Suggested fix:
+      Perhaps you intended to use the ‘OverloadedRecordUpdate’ extension
diff --git a/testsuite/tests/parser/should_fail/RecordWildCardsFail.stderr b/testsuite/tests/parser/should_fail/RecordWildCardsFail.stderr
index 5422e429e258..9b9c29d3e28b 100644
--- a/testsuite/tests/parser/should_fail/RecordWildCardsFail.stderr
+++ b/testsuite/tests/parser/should_fail/RecordWildCardsFail.stderr
@@ -1,4 +1,5 @@
 
 RecordWildCardsFail.hs:7:5: error: [GHC-37132]
     Illegal `..' in record pattern
-    Suggested fix: Perhaps you intended to use RecordWildCards
+    Suggested fix:
+      Perhaps you intended to use the ‘RecordWildCards’ extension
diff --git a/testsuite/tests/parser/should_fail/T12429.stderr b/testsuite/tests/parser/should_fail/T12429.stderr
index d6f9ee008891..305abb77e6c1 100644
--- a/testsuite/tests/parser/should_fail/T12429.stderr
+++ b/testsuite/tests/parser/should_fail/T12429.stderr
@@ -1,4 +1,5 @@
 
 T12429.hs:2:29: error: [GHC-58481]
     parse error on input ‘Y’
-    Suggested fix: Perhaps you intended to use PatternSynonyms
+    Suggested fix:
+      Perhaps you intended to use the ‘PatternSynonyms’ extension
diff --git a/testsuite/tests/parser/should_fail/T12446.stderr b/testsuite/tests/parser/should_fail/T12446.stderr
index 262e53415ac3..834bdadc4630 100644
--- a/testsuite/tests/parser/should_fail/T12446.stderr
+++ b/testsuite/tests/parser/should_fail/T12446.stderr
@@ -1,4 +1,5 @@
 
 T12446.hs:4:5: error: [GHC-23482]
     Illegal visible type application: @(_ ~ _)
-    Suggested fix: Perhaps you intended to use TypeApplications
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeApplications’ extension
diff --git a/testsuite/tests/parser/should_fail/T12811.stderr b/testsuite/tests/parser/should_fail/T12811.stderr
index 9f3937d4982b..263f44980eec 100644
--- a/testsuite/tests/parser/should_fail/T12811.stderr
+++ b/testsuite/tests/parser/should_fail/T12811.stderr
@@ -1,7 +1,8 @@
 
 T12811.hs:5:15: error: [GHC-62547]
     Illegal operator ‘.’ in type ‘foral a . a’
-    Suggested fix: Perhaps you intended to use TypeOperators
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeOperators’ extension
 
 T12811.hs:5:15: error: [GHC-76037]
     Not in scope: type constructor or class ‘.’
diff --git a/testsuite/tests/parser/should_fail/T14588.stderr b/testsuite/tests/parser/should_fail/T14588.stderr
index dd947efa543b..16429b11de78 100644
--- a/testsuite/tests/parser/should_fail/T14588.stderr
+++ b/testsuite/tests/parser/should_fail/T14588.stderr
@@ -2,4 +2,5 @@
 T14588.hs:4:19: error: [GHC-79767]
     Illegal bang-pattern
     !x
-    Suggested fix: Perhaps you intended to use BangPatterns
+    Suggested fix:
+      Perhaps you intended to use the ‘BangPatterns’ extension
diff --git a/testsuite/tests/parser/should_fail/T16270.stderr b/testsuite/tests/parser/should_fail/T16270.stderr
index 92da6ea3b2e6..3d29d9d4562d 100644
--- a/testsuite/tests/parser/should_fail/T16270.stderr
+++ b/testsuite/tests/parser/should_fail/T16270.stderr
@@ -9,67 +9,78 @@ T16270.hs:8:1: warning: [GHC-94817] [-Wtabs (in -Wdefault)]
 T16270.hs:8:12: error: [GHC-75254]
     Unexpected semi-colons in conditional:
         if c then False; else True
-    Suggested fix: Perhaps you intended to use DoAndIfThenElse
+    Suggested fix:
+      Perhaps you intended to use the ‘DoAndIfThenElse’ extension
 
 T16270.hs:13:8: error: [GHC-52095]
     Unexpected do block in function application:
         do 1
     Suggested fixes:
       • Use parentheses.
-      • Perhaps you intended to use BlockArguments
+      • Perhaps you intended to use the ‘BlockArguments’ extension
 
 T16270.hs:14:8: error: [GHC-06074]
     Unexpected lambda expression in function application:
         \ x -> x
     Suggested fixes:
       • Use parentheses.
-      • Perhaps you intended to use BlockArguments
+      • Perhaps you intended to use the ‘BlockArguments’ extension
 
 T16270.hs:18:22: error: [GHC-65719]
     Illegal record syntax: {fst :: a, snd :: b}
-    Suggested fix: Perhaps you intended to use TraditionalRecordSyntax
+    Suggested fix:
+      Perhaps you intended to use the ‘TraditionalRecordSyntax’ extension
 
 T16270.hs:19:5: error: [GHC-65719]
     Illegal record syntax: p {fst = 1, snd = True}
-    Suggested fix: Perhaps you intended to use TraditionalRecordSyntax
+    Suggested fix:
+      Perhaps you intended to use the ‘TraditionalRecordSyntax’ extension
 
 T16270.hs:21:6: error: [GHC-25955]
     Illegal symbol ‘forall’ in type
     Suggested fix:
-      Perhaps you intended to use RankNTypes
-      or a similar language extension to enable explicit-forall syntax: forall <tvs>. <type>
+      Use the ‘ExplicitForAll’ extension (implied by ‘RankNTypes’,
+                                                     ‘QuantifiedConstraints’, ‘ScopedTypeVariables’,
+                                                     ‘LiberalTypeSynonyms’ and ‘ExistentialQuantification’)
+      to enable syntax: forall <tvs>. <type>
 
 T16270.hs:22:8: error: [GHC-75254]
     Unexpected semi-colons in conditional:
         if True; then (); else ()
-    Suggested fix: Perhaps you intended to use DoAndIfThenElse
+    Suggested fix:
+      Perhaps you intended to use the ‘DoAndIfThenElse’ extension
 
 T16270.hs:24:10: error: [GHC-36952]
     Illegal keyword 'where' in data declaration
     Suggested fix:
-      Perhaps you intended to use GADTs
-      or a similar language extension to enable syntax: data T where
+      Use the ‘GADTSyntax’ extension (implied by ‘GADTs’)
+      to enable syntax: data T where
 
 T16270.hs:26:12: error: [GHC-79767]
     Illegal bang-pattern
     !i
-    Suggested fix: Perhaps you intended to use BangPatterns
+    Suggested fix:
+      Perhaps you intended to use the ‘BangPatterns’ extension
 
 T16270.hs:28:9: error: [GHC-28985]
     Illegal multi-way if-expression
-    Suggested fix: Perhaps you intended to use MultiWayIf
+    Suggested fix:
+      Perhaps you intended to use the ‘MultiWayIf’ extension
 
 T16270.hs:30:9: error: [GHC-28985]
     Illegal multi-way if-expression
-    Suggested fix: Perhaps you intended to use MultiWayIf
+    Suggested fix:
+      Perhaps you intended to use the ‘MultiWayIf’ extension
 
 T16270.hs:33:6: error: [GHC-51179]
     Illegal \case
-    Suggested fix: Perhaps you intended to use LambdaCase
+    Suggested fix:
+      Perhaps you intended to use the ‘LambdaCase’ extension
 
 T16270.hs:36:5: error: [GHC-62330]
     Illegal underscores in integer literals
-    Suggested fix: Perhaps you intended to use NumericUnderscores
+    Suggested fix:
+      Perhaps you intended to use the ‘NumericUnderscores’ extension
 
 T16270.hs:38:5: error: [GHC-43080]
     primitive string literal must contain only characters <= '\xFF'
diff --git a/testsuite/tests/parser/should_fail/T16270h.stderr b/testsuite/tests/parser/should_fail/T16270h.stderr
index ad24b9bb19ce..509857b8595a 100644
--- a/testsuite/tests/parser/should_fail/T16270h.stderr
+++ b/testsuite/tests/parser/should_fail/T16270h.stderr
@@ -1,7 +1,8 @@
 
 T16270h.hs:8:22: error: [GHC-47007]
     Illegal keyword 'type'
-    Suggested fix: Perhaps you intended to use ExplicitNamespaces
+    Suggested fix:
+      Perhaps you intended to use the ‘ExplicitNamespaces’ extension (implied by ‘TypeFamilies’ and ‘TypeOperators’)
 
 T16270h.hs:10:8: error: [GHC-21926]
     Parse error: ‘pkg?’
diff --git a/testsuite/tests/parser/should_fail/T17162.stderr b/testsuite/tests/parser/should_fail/T17162.stderr
index 84c985fa5598..b271690e3f4b 100644
--- a/testsuite/tests/parser/should_fail/T17162.stderr
+++ b/testsuite/tests/parser/should_fail/T17162.stderr
@@ -2,4 +2,5 @@
 T17162.hs:7:21: error: [GHC-79767]
     Illegal bang-pattern
     !enc
-    Suggested fix: Perhaps you intended to use BangPatterns
+    Suggested fix:
+      Perhaps you intended to use the ‘BangPatterns’ extension
diff --git a/testsuite/tests/parser/should_fail/T18251c.stderr b/testsuite/tests/parser/should_fail/T18251c.stderr
index bcf3c8967ff6..30fdb749d3a1 100644
--- a/testsuite/tests/parser/should_fail/T18251c.stderr
+++ b/testsuite/tests/parser/should_fail/T18251c.stderr
@@ -1,4 +1,5 @@
 
 T18251c.hs:4:5: error: [GHC-23482]
     Illegal visible type application: @Int
-    Suggested fix: Perhaps you intended to use TypeApplications
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeApplications’ extension
diff --git a/testsuite/tests/parser/should_fail/T18251e.stderr b/testsuite/tests/parser/should_fail/T18251e.stderr
index a22c71f6cc0f..2f645a6db280 100644
--- a/testsuite/tests/parser/should_fail/T18251e.stderr
+++ b/testsuite/tests/parser/should_fail/T18251e.stderr
@@ -3,4 +3,4 @@ T18251e.hs:3:5: error: [GHC-62558]
     • Syntax error on [| id |]
     • In the Template Haskell quotation [| id |]
     Suggested fix:
-      Enable any of the following extensions: TemplateHaskell, TemplateHaskellQuotes
+      Perhaps you intended to use the ‘TemplateHaskellQuotes’ extension (implied by ‘TemplateHaskell’)
diff --git a/testsuite/tests/parser/should_fail/T20385A.stderr b/testsuite/tests/parser/should_fail/T20385A.stderr
index 3e5b6c718d1b..620ac2513205 100644
--- a/testsuite/tests/parser/should_fail/T20385A.stderr
+++ b/testsuite/tests/parser/should_fail/T20385A.stderr
@@ -9,4 +9,4 @@ T20385A.hs:10:9: error: [GHC-88464]
     Variable not in scope: mdo :: a -> a
     Suggested fixes:
       • Perhaps use ‘mod’ (imported from Prelude)
-      • Perhaps you intended to use RecursiveDo
+      • Perhaps you intended to use the ‘RecursiveDo’ extension
diff --git a/testsuite/tests/parser/should_fail/T20385B.stderr b/testsuite/tests/parser/should_fail/T20385B.stderr
index 0f7c9be2d658..e16b049dcd01 100644
--- a/testsuite/tests/parser/should_fail/T20385B.stderr
+++ b/testsuite/tests/parser/should_fail/T20385B.stderr
@@ -9,4 +9,4 @@ T20385B.hs:11:9: error: [GHC-88464]
     Variable not in scope: mdo :: a -> a
     Suggested fixes:
       • Perhaps use ‘mod’ (imported from Prelude)
-      • Perhaps you intended to use RecursiveDo
+      • Perhaps you intended to use the ‘RecursiveDo’ extension
diff --git a/testsuite/tests/parser/should_fail/T3095.stderr b/testsuite/tests/parser/should_fail/T3095.stderr
index 5448b9703547..16c43af28e85 100644
--- a/testsuite/tests/parser/should_fail/T3095.stderr
+++ b/testsuite/tests/parser/should_fail/T3095.stderr
@@ -2,8 +2,10 @@
 T3095.hs:8:12: error: [GHC-25955]
     Illegal symbol ‘forall’ in type
     Suggested fix:
-      Perhaps you intended to use RankNTypes
-      or a similar language extension to enable explicit-forall syntax: forall <tvs>. <type>
+      Use the ‘ExplicitForAll’ extension (implied by ‘RankNTypes’,
+                                                     ‘QuantifiedConstraints’, ‘ScopedTypeVariables’,
+                                                     ‘LiberalTypeSynonyms’ and ‘ExistentialQuantification’)
+      to enable syntax: forall <tvs>. <type>
 
 T3095.hs:8:12: error: [GHC-77878]
     Unexpected type ‘forall x. x :: Type’
diff --git a/testsuite/tests/parser/should_fail/T3811e.stderr b/testsuite/tests/parser/should_fail/T3811e.stderr
index 65bfd70f7078..7619156335ca 100644
--- a/testsuite/tests/parser/should_fail/T3811e.stderr
+++ b/testsuite/tests/parser/should_fail/T3811e.stderr
@@ -1,4 +1,5 @@
 
 T3811e.hs:6:6: error: [GHC-87429]
     Illegal datatype context: (Show a, Read a) =>
-    Suggested fix: Perhaps you intended to use DatatypeContexts
+    Suggested fix:
+      Perhaps you intended to use the ‘DatatypeContexts’ extension
diff --git a/testsuite/tests/parser/should_fail/T8258NoGADTs.stderr b/testsuite/tests/parser/should_fail/T8258NoGADTs.stderr
index cb3916149225..30dceba25cc6 100644
--- a/testsuite/tests/parser/should_fail/T8258NoGADTs.stderr
+++ b/testsuite/tests/parser/should_fail/T8258NoGADTs.stderr
@@ -2,5 +2,5 @@
 T8258NoGADTs.hs:4:8: error: [GHC-36952]
     Illegal keyword 'where' in data declaration
     Suggested fix:
-      Perhaps you intended to use GADTs
-      or a similar language extension to enable syntax: data T where
+      Use the ‘GADTSyntax’ extension (implied by ‘GADTs’)
+      to enable syntax: data T where
diff --git a/testsuite/tests/parser/should_fail/T8501a.stderr b/testsuite/tests/parser/should_fail/T8501a.stderr
index 83f456bd417e..437894ccd9d4 100644
--- a/testsuite/tests/parser/should_fail/T8501a.stderr
+++ b/testsuite/tests/parser/should_fail/T8501a.stderr
@@ -2,5 +2,5 @@
 T8501a.hs:5:3: error: [GHC-07626]
     Parse error in pattern: rec
     Suggested fixes:
-      • Perhaps you intended to use RecursiveDo
+      • Perhaps you intended to use the ‘RecursiveDo’ extension
       • Possibly caused by a missing 'do'?
diff --git a/testsuite/tests/parser/should_fail/T8501b.stderr b/testsuite/tests/parser/should_fail/T8501b.stderr
index 1b4bd6a819c9..976f9b25559d 100644
--- a/testsuite/tests/parser/should_fail/T8501b.stderr
+++ b/testsuite/tests/parser/should_fail/T8501b.stderr
@@ -1,4 +1,5 @@
 
 T8501b.hs:5:9: error: [GHC-58481]
     parse error on input ‘<-’
-    Suggested fix: Perhaps you intended to use RecursiveDo
+    Suggested fix:
+      Perhaps you intended to use the ‘RecursiveDo’ extension
diff --git a/testsuite/tests/parser/should_fail/T8501c.stderr b/testsuite/tests/parser/should_fail/T8501c.stderr
index 2d8c74a39919..5ab4df065fc9 100644
--- a/testsuite/tests/parser/should_fail/T8501c.stderr
+++ b/testsuite/tests/parser/should_fail/T8501c.stderr
@@ -3,4 +3,4 @@ T8501c.hs:4:7: error: [GHC-88464]
     Variable not in scope: mdo :: (String -> IO ()) -> String -> IO ()
     Suggested fixes:
       • Perhaps use ‘mod’ (imported from Prelude)
-      • Perhaps you intended to use RecursiveDo
+      • Perhaps you intended to use the ‘RecursiveDo’ extension
diff --git a/testsuite/tests/parser/should_fail/ViewPatternsFail.stderr b/testsuite/tests/parser/should_fail/ViewPatternsFail.stderr
index ae1a4418a120..6b5ec7565551 100644
--- a/testsuite/tests/parser/should_fail/ViewPatternsFail.stderr
+++ b/testsuite/tests/parser/should_fail/ViewPatternsFail.stderr
@@ -1,4 +1,5 @@
 
 ViewPatternsFail.hs:7:6: error: [GHC-22406]
     Illegal view pattern:  a -> l
-    Suggested fix: Perhaps you intended to use ViewPatterns
+    Suggested fix:
+      Perhaps you intended to use the ‘ViewPatterns’ extension
diff --git a/testsuite/tests/parser/should_fail/proposal-229c.stderr b/testsuite/tests/parser/should_fail/proposal-229c.stderr
index 3a240e02b400..a813717c409a 100644
--- a/testsuite/tests/parser/should_fail/proposal-229c.stderr
+++ b/testsuite/tests/parser/should_fail/proposal-229c.stderr
@@ -2,4 +2,5 @@
 proposal-229c.hs:6:3: error: [GHC-79767]
     Illegal bang-pattern
     !x
-    Suggested fix: Perhaps you intended to use BangPatterns
+    Suggested fix:
+      Perhaps you intended to use the ‘BangPatterns’ extension
diff --git a/testsuite/tests/parser/should_fail/readFail001.stderr b/testsuite/tests/parser/should_fail/readFail001.stderr
index 45ee2957f26f..03f5562aa40e 100644
--- a/testsuite/tests/parser/should_fail/readFail001.stderr
+++ b/testsuite/tests/parser/should_fail/readFail001.stderr
@@ -5,13 +5,13 @@ readFail001.hs:25:11: error: [GHC-44432]
 readFail001.hs:38:32: error: [GHC-76037]
     Not in scope: type constructor or class ‘Leaf’
     Suggested fix:
-      Perhaps you intended to use DataKinds
+      Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’)
       to refer to the data constructor of that name?
 
 readFail001.hs:38:41: error: [GHC-76037]
     Not in scope: type constructor or class ‘Leaf’
     Suggested fix:
-      Perhaps you intended to use DataKinds
+      Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’)
       to refer to the data constructor of that name?
 
 readFail001.hs:107:30: error: [GHC-76037]
diff --git a/testsuite/tests/parser/should_fail/readFail035.stderr b/testsuite/tests/parser/should_fail/readFail035.stderr
index e470427eae67..b7288a78ba26 100644
--- a/testsuite/tests/parser/should_fail/readFail035.stderr
+++ b/testsuite/tests/parser/should_fail/readFail035.stderr
@@ -1,5 +1,6 @@
 
-readFail035.hs:6:1: [GHC-32478]
-    ‘Foo’ has no constructors
-    In the data declaration for ‘Foo’
-    Suggested fix: Perhaps you intended to use EmptyDataDecls
+readFail035.hs:6:1: error: [GHC-32478]
+    • ‘Foo’ has no constructors
+    • In the data declaration for ‘Foo’
+    Suggested fix:
+      Perhaps you intended to use the ‘EmptyDataDecls’ extension
diff --git a/testsuite/tests/parser/should_fail/readFail036.stderr b/testsuite/tests/parser/should_fail/readFail036.stderr
index 0a53a4be86e6..e6efe0d86c4b 100644
--- a/testsuite/tests/parser/should_fail/readFail036.stderr
+++ b/testsuite/tests/parser/should_fail/readFail036.stderr
@@ -1,5 +1,6 @@
 
 readFail036.hs:6:16: error: [GHC-49378]
-    Illegal kind signature ‘Type’
-    In the data type declaration for ‘Foo’
-    Suggested fix: Perhaps you intended to use KindSignatures
+    • Illegal kind signature ‘Type’
+    • In the data type declaration for ‘Foo’
+    Suggested fix:
+      Perhaps you intended to use the ‘KindSignatures’ extension (implied by ‘TypeFamilies’ and ‘PolyKinds’)
diff --git a/testsuite/tests/parser/should_fail/readFail037.stderr b/testsuite/tests/parser/should_fail/readFail037.stderr
index fd1ba5e14c3f..b9c877865c02 100644
--- a/testsuite/tests/parser/should_fail/readFail037.stderr
+++ b/testsuite/tests/parser/should_fail/readFail037.stderr
@@ -2,4 +2,5 @@
 readFail037.hs:5:1: error: [GHC-28349]
     • Too many parameters for class ‘Foo’
     • In the class declaration for ‘Foo’
-    Suggested fix: Perhaps you intended to use MultiParamTypeClasses
+    Suggested fix:
+      Perhaps you intended to use the ‘MultiParamTypeClasses’ extension (implied by ‘FunctionalDependencies’)
diff --git a/testsuite/tests/parser/should_fail/readFail038.stderr b/testsuite/tests/parser/should_fail/readFail038.stderr
index 6563c248fc06..5e637dfe2599 100644
--- a/testsuite/tests/parser/should_fail/readFail038.stderr
+++ b/testsuite/tests/parser/should_fail/readFail038.stderr
@@ -1,4 +1,5 @@
 
-readFail038.hs:5:9: [GHC-42026]
+readFail038.hs:5:9: error: [GHC-42026]
     Unexpected parallel statement in a list comprehension
-    Suggested fix: Perhaps you intended to use ParallelListComp
+    Suggested fix:
+      Perhaps you intended to use the ‘ParallelListComp’ extension (implied by ‘ParallelArrays’)
diff --git a/testsuite/tests/parser/should_fail/readFail039.stderr b/testsuite/tests/parser/should_fail/readFail039.stderr
index cdb692487cdb..6011ebde7d86 100644
--- a/testsuite/tests/parser/should_fail/readFail039.stderr
+++ b/testsuite/tests/parser/should_fail/readFail039.stderr
@@ -4,5 +4,5 @@ readFail039.hs:9:14: error: [GHC-82023]
         ‘C’ is not a stock derivable class (Eq, Show, etc.)
     • In the newtype declaration for ‘Foo’
     Suggested fix:
-      Perhaps you intended to use GeneralizedNewtypeDeriving
+      Perhaps you intended to use the ‘GeneralizedNewtypeDeriving’ extension
       for GHC's newtype-deriving extension
diff --git a/testsuite/tests/parser/should_fail/readFail040.stderr b/testsuite/tests/parser/should_fail/readFail040.stderr
index 14f338b6a981..27939db5a0b2 100644
--- a/testsuite/tests/parser/should_fail/readFail040.stderr
+++ b/testsuite/tests/parser/should_fail/readFail040.stderr
@@ -1,4 +1,5 @@
 
 readFail040.hs:7:11: error: [GHC-58481]
     parse error on input ‘<-’
-    Suggested fix: Perhaps you intended to use RecursiveDo
+    Suggested fix:
+      Perhaps you intended to use the ‘RecursiveDo’ extension
diff --git a/testsuite/tests/parser/should_fail/readFail041.stderr b/testsuite/tests/parser/should_fail/readFail041.stderr
index a41ffc880557..475e8acda227 100644
--- a/testsuite/tests/parser/should_fail/readFail041.stderr
+++ b/testsuite/tests/parser/should_fail/readFail041.stderr
@@ -2,4 +2,5 @@
 readFail041.hs:6:1: error: [GHC-15708]
     • Fundeps in class ‘Foo’
     • In the class declaration for ‘Foo’
-    Suggested fix: Perhaps you intended to use FunctionalDependencies
+    Suggested fix:
+      Perhaps you intended to use the ‘FunctionalDependencies’ extension
diff --git a/testsuite/tests/parser/should_fail/readFail042.stderr b/testsuite/tests/parser/should_fail/readFail042.stderr
index 66ec565370bc..f47ec8a057e8 100644
--- a/testsuite/tests/parser/should_fail/readFail042.stderr
+++ b/testsuite/tests/parser/should_fail/readFail042.stderr
@@ -1,8 +1,10 @@
 
-readFail042.hs:9:9: [GHC-42026] error:
+readFail042.hs:9:9: error: [GHC-42026]
     Unexpected transform statement in a list comprehension
-    Suggested fix: Perhaps you intended to use TransformListComp
+    Suggested fix:
+      Perhaps you intended to use the ‘TransformListComp’ extension
 
-readFail042.hs:9:9: [GHC-42026] error:
+readFail042.hs:9:9: error: [GHC-42026]
     Unexpected transform statement in a list comprehension
-    Suggested fix: Perhaps you intended to use TransformListComp
+    Suggested fix:
+      Perhaps you intended to use the ‘TransformListComp’ extension
diff --git a/testsuite/tests/parser/should_fail/readFail043.stderr b/testsuite/tests/parser/should_fail/readFail043.stderr
index 1d0ddb2c4cdb..4308a16c5bf4 100644
--- a/testsuite/tests/parser/should_fail/readFail043.stderr
+++ b/testsuite/tests/parser/should_fail/readFail043.stderr
@@ -1,12 +1,15 @@
 
-readFail043.hs:9:9: [GHC-42026] error:
+readFail043.hs:9:9: error: [GHC-42026]
     Unexpected transform statement in a list comprehension
-    Suggested fix: Perhaps you intended to use TransformListComp
+    Suggested fix:
+      Perhaps you intended to use the ‘TransformListComp’ extension
 
-readFail043.hs:9:9: [GHC-42026] error:
+readFail043.hs:9:9: error: [GHC-42026]
     Unexpected transform statement in a list comprehension
-    Suggested fix: Perhaps you intended to use TransformListComp
+    Suggested fix:
+      Perhaps you intended to use the ‘TransformListComp’ extension
 
-readFail043.hs:9:9: [GHC-42026] error:
+readFail043.hs:9:9: error: [GHC-42026]
     Unexpected transform statement in a list comprehension
-    Suggested fix: Perhaps you intended to use TransformListComp
+    Suggested fix:
+      Perhaps you intended to use the ‘TransformListComp’ extension
diff --git a/testsuite/tests/parser/should_fail/readFailTraditionalRecords1.stderr b/testsuite/tests/parser/should_fail/readFailTraditionalRecords1.stderr
index 1f2fa108adb0..1858112554ad 100644
--- a/testsuite/tests/parser/should_fail/readFailTraditionalRecords1.stderr
+++ b/testsuite/tests/parser/should_fail/readFailTraditionalRecords1.stderr
@@ -1,4 +1,5 @@
 
 readFailTraditionalRecords1.hs:6:16: error: [GHC-65719]
     Illegal record syntax: {i :: Int}
-    Suggested fix: Perhaps you intended to use TraditionalRecordSyntax
+    Suggested fix:
+      Perhaps you intended to use the ‘TraditionalRecordSyntax’ extension
diff --git a/testsuite/tests/parser/should_fail/readFailTraditionalRecords2.stderr b/testsuite/tests/parser/should_fail/readFailTraditionalRecords2.stderr
index c0d4c52d80d1..b30f092651ce 100644
--- a/testsuite/tests/parser/should_fail/readFailTraditionalRecords2.stderr
+++ b/testsuite/tests/parser/should_fail/readFailTraditionalRecords2.stderr
@@ -1,4 +1,5 @@
 
 readFailTraditionalRecords2.hs:6:4: error: [GHC-65719]
     Illegal record syntax: Foo {i = j}
-    Suggested fix: Perhaps you intended to use TraditionalRecordSyntax
+    Suggested fix:
+      Perhaps you intended to use the ‘TraditionalRecordSyntax’ extension
diff --git a/testsuite/tests/parser/should_fail/readFailTraditionalRecords3.stderr b/testsuite/tests/parser/should_fail/readFailTraditionalRecords3.stderr
index 2b946dcdb631..d9b948ab3ecf 100644
--- a/testsuite/tests/parser/should_fail/readFailTraditionalRecords3.stderr
+++ b/testsuite/tests/parser/should_fail/readFailTraditionalRecords3.stderr
@@ -1,4 +1,5 @@
 
 readFailTraditionalRecords3.hs:6:7: error: [GHC-65719]
     Illegal record syntax: x {i = 3}
-    Suggested fix: Perhaps you intended to use TraditionalRecordSyntax
+    Suggested fix:
+      Perhaps you intended to use the ‘TraditionalRecordSyntax’ extension
diff --git a/testsuite/tests/partial-sigs/should_compile/T13324_compile2.stderr b/testsuite/tests/partial-sigs/should_compile/T13324_compile2.stderr
index 5ac4b22df613..9355ded31f10 100644
--- a/testsuite/tests/partial-sigs/should_compile/T13324_compile2.stderr
+++ b/testsuite/tests/partial-sigs/should_compile/T13324_compile2.stderr
@@ -3,5 +3,5 @@ T13324_compile2.hs:7:19: warning: [GHC-60661] [-Wpartial-type-signatures (in -Wd
     • Found type wildcard ‘_’ standing for ‘Show a’
     • In the instance declaration for ‘Show (Option a)’
     Suggested fix:
-      Perhaps you intended to use PartialTypeSignatures
+      Perhaps you intended to use the ‘PartialTypeSignatures’ extension
       to use the inferred type
diff --git a/testsuite/tests/patsyn/should_fail/export-syntax.stderr b/testsuite/tests/patsyn/should_fail/export-syntax.stderr
index 92a538ea081c..bcee29bf10c9 100644
--- a/testsuite/tests/patsyn/should_fail/export-syntax.stderr
+++ b/testsuite/tests/patsyn/should_fail/export-syntax.stderr
@@ -1,4 +1,5 @@
 
 export-syntax.hs:1:12: error: [GHC-89515]
     Illegal export form
-    Suggested fix: Perhaps you intended to use PatternSynonyms
+    Suggested fix:
+      Perhaps you intended to use the ‘PatternSynonyms’ extension
diff --git a/testsuite/tests/polykinds/BadKindVar.stderr b/testsuite/tests/polykinds/BadKindVar.stderr
index a0fcb59fd19d..a00e0b7d92cc 100644
--- a/testsuite/tests/polykinds/BadKindVar.stderr
+++ b/testsuite/tests/polykinds/BadKindVar.stderr
@@ -1,5 +1,6 @@
 
 BadKindVar.hs:9:21: error: [GHC-12875]
-    Unexpected kind variable ‘k’
-    In the type signature for ‘f’
-    Suggested fix: Perhaps you intended to use PolyKinds
+    • Unexpected kind variable ‘k’
+    • In the type signature for ‘f’
+    Suggested fix:
+      Perhaps you intended to use the ‘PolyKinds’ extension
diff --git a/testsuite/tests/polykinds/T12055a.stderr b/testsuite/tests/polykinds/T12055a.stderr
index ed4170424062..24a58331cd1c 100644
--- a/testsuite/tests/polykinds/T12055a.stderr
+++ b/testsuite/tests/polykinds/T12055a.stderr
@@ -4,4 +4,5 @@ T12055a.hs:30:1: error: [GHC-80003]
     • In the context: (Category (Dom f), Category (Cod f))
       While checking the super-classes of class ‘Functor’
       In the class declaration for ‘Functor’
-    Suggested fix: Perhaps you intended to use FlexibleContexts
+    Suggested fix:
+      Perhaps you intended to use the ‘FlexibleContexts’ extension
diff --git a/testsuite/tests/polykinds/T14710.stderr b/testsuite/tests/polykinds/T14710.stderr
index 6fc8866af7e0..9a1f16994242 100644
--- a/testsuite/tests/polykinds/T14710.stderr
+++ b/testsuite/tests/polykinds/T14710.stderr
@@ -1,30 +1,36 @@
 
 T14710.hs:10:21: error: [GHC-12875]
-    Unexpected kind variable ‘a’
-    In a class method signature for ‘c1’
-    Suggested fix: Perhaps you intended to use PolyKinds
+    • Unexpected kind variable ‘a’
+    • In a class method signature for ‘c1’
+    Suggested fix:
+      Perhaps you intended to use the ‘PolyKinds’ extension
 
 T14710.hs:11:22: error: [GHC-12875]
-    Unexpected kind variable ‘a’
-    In a class method signature for ‘c2’
-    Suggested fix: Perhaps you intended to use PolyKinds
+    • Unexpected kind variable ‘a’
+    • In a class method signature for ‘c2’
+    Suggested fix:
+      Perhaps you intended to use the ‘PolyKinds’ extension
 
 T14710.hs:16:23: error: [GHC-12875]
-    Unexpected kind variable ‘a’
-    In the type signature for ‘g1’
-    Suggested fix: Perhaps you intended to use PolyKinds
+    • Unexpected kind variable ‘a’
+    • In the type signature for ‘g1’
+    Suggested fix:
+      Perhaps you intended to use the ‘PolyKinds’ extension
 
 T14710.hs:19:24: error: [GHC-12875]
-    Unexpected kind variable ‘a’
-    In the type signature for ‘g2’
-    Suggested fix: Perhaps you intended to use PolyKinds
+    • Unexpected kind variable ‘a’
+    • In the type signature for ‘g2’
+    Suggested fix:
+      Perhaps you intended to use the ‘PolyKinds’ extension
 
 T14710.hs:22:31: error: [GHC-12875]
-    Unexpected kind variable ‘k’
-    In the type signature for ‘h1’
-    Suggested fix: Perhaps you intended to use PolyKinds
+    • Unexpected kind variable ‘k’
+    • In the type signature for ‘h1’
+    Suggested fix:
+      Perhaps you intended to use the ‘PolyKinds’ extension
 
 T14710.hs:25:22: error: [GHC-12875]
-    Unexpected kind variable ‘k’
-    In the type signature for ‘h2’
-    Suggested fix: Perhaps you intended to use PolyKinds
+    • Unexpected kind variable ‘k’
+    • In the type signature for ‘h2’
+    Suggested fix:
+      Perhaps you intended to use the ‘PolyKinds’ extension
diff --git a/testsuite/tests/polykinds/T16762b.stderr b/testsuite/tests/polykinds/T16762b.stderr
index e77f332f1718..f9dc97b5e2ca 100644
--- a/testsuite/tests/polykinds/T16762b.stderr
+++ b/testsuite/tests/polykinds/T16762b.stderr
@@ -1,5 +1,5 @@
 
 T16762b.hs:8:11: error: [GHC-64861]
     Illegal kind: forall k. Type
-    Suggested fix: Perhaps you intended to use PolyKinds
-
+    Suggested fix:
+      Perhaps you intended to use the ‘PolyKinds’ extension
diff --git a/testsuite/tests/polykinds/T7151.stderr b/testsuite/tests/polykinds/T7151.stderr
index 71a39d2c4f65..b5f88f58ff56 100644
--- a/testsuite/tests/polykinds/T7151.stderr
+++ b/testsuite/tests/polykinds/T7151.stderr
@@ -1,4 +1,5 @@
 
-T7151.hs:3:12: [GHC-68567]
+T7151.hs:3:12: error: [GHC-68567]
     Illegal type: ‘[Int, String]’
-    Suggested fix: Perhaps you intended to use DataKinds
+    Suggested fix:
+      Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’)
diff --git a/testsuite/tests/polykinds/T7433.stderr b/testsuite/tests/polykinds/T7433.stderr
index 347d510adac4..94b9bd7d1655 100644
--- a/testsuite/tests/polykinds/T7433.stderr
+++ b/testsuite/tests/polykinds/T7433.stderr
@@ -1,4 +1,5 @@
 
 T7433.hs:2:10: error: [GHC-68567]
     Illegal type: ‘'Z’
-    Suggested fix: Perhaps you intended to use DataKinds
+    Suggested fix:
+      Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’)
diff --git a/testsuite/tests/polykinds/TidyClassKinds.stderr b/testsuite/tests/polykinds/TidyClassKinds.stderr
index 305e6fc2b4ce..49d65e16c0b3 100644
--- a/testsuite/tests/polykinds/TidyClassKinds.stderr
+++ b/testsuite/tests/polykinds/TidyClassKinds.stderr
@@ -5,4 +5,5 @@ TidyClassKinds.hs:13:10: error: [GHC-93557]
         All instance types must be of the form (T t1 ... tn)
         where T is not a synonym.
     • In the instance declaration for ‘Poly ProxySyn ProxySyn’
-    Suggested fix: Perhaps you intended to use TypeSynonymInstances
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeSynonymInstances’ extension (implied by ‘FlexibleInstances’)
diff --git a/testsuite/tests/qualifieddo/should_fail/qdofail002.stderr b/testsuite/tests/qualifieddo/should_fail/qdofail002.stderr
index a42c112cd2d5..ae0fc08df2be 100644
--- a/testsuite/tests/qualifieddo/should_fail/qdofail002.stderr
+++ b/testsuite/tests/qualifieddo/should_fail/qdofail002.stderr
@@ -1,8 +1,10 @@
 
 qdofail002.hs:8:11: error: [GHC-40280]
     Illegal qualified ‘P.do’ block
-    Suggested fix: Perhaps you intended to use QualifiedDo
+    Suggested fix:
+      Perhaps you intended to use the ‘QualifiedDo’ extension
 
 qdofail002.hs:11:13: error: [GHC-40280]
     Illegal qualified ‘P.mdo’ block
-    Suggested fix: Perhaps you intended to use QualifiedDo
+    Suggested fix:
+      Perhaps you intended to use the ‘QualifiedDo’ extension
diff --git a/testsuite/tests/quantified-constraints/T15231.stderr b/testsuite/tests/quantified-constraints/T15231.stderr
index 9c0fe225d655..0bff58d690c3 100644
--- a/testsuite/tests/quantified-constraints/T15231.stderr
+++ b/testsuite/tests/quantified-constraints/T15231.stderr
@@ -4,4 +4,5 @@ T15231.hs:15:10: error: [GHC-22979]
         in the constraint ‘c’ than in the instance head ‘Z a’
     • In the quantified constraint ‘c => Z a’
       In the instance declaration for ‘Z (ECC c a)’
-    Suggested fix: Perhaps you intended to use UndecidableInstances
+    Suggested fix:
+      Perhaps you intended to use the ‘UndecidableInstances’ extension
diff --git a/testsuite/tests/quantified-constraints/T15316.stderr b/testsuite/tests/quantified-constraints/T15316.stderr
index 0b6eb912fb08..d08d6d08dee4 100644
--- a/testsuite/tests/quantified-constraints/T15316.stderr
+++ b/testsuite/tests/quantified-constraints/T15316.stderr
@@ -3,4 +3,5 @@ T15316.hs:20:13: error: [GHC-22979]
     • The constraint ‘c’ is no smaller than the instance head ‘c’
     • In the quantified constraint ‘c => c’
       In the type signature: subsume' :: Proxy c -> ((c => c) => r) -> r
-    Suggested fix: Perhaps you intended to use UndecidableInstances
+    Suggested fix:
+      Perhaps you intended to use the ‘UndecidableInstances’ extension
diff --git a/testsuite/tests/quotes/TH_double_splice.stderr b/testsuite/tests/quotes/TH_double_splice.stderr
index 4a6f6da4d5c4..e28602e87f0c 100644
--- a/testsuite/tests/quotes/TH_double_splice.stderr
+++ b/testsuite/tests/quotes/TH_double_splice.stderr
@@ -5,4 +5,5 @@ TH_double_splice.hs:6:12: error: [GHC-26759]
       In the untyped splice: $($(error "should not happen"))
       In the Template Haskell quotation
         [| $($(error "should not happen")) |]
-    Suggested fix: Perhaps you intended to use TemplateHaskell
+    Suggested fix:
+      Perhaps you intended to use the ‘TemplateHaskell’ extension
diff --git a/testsuite/tests/quotes/TH_top_splice.stderr b/testsuite/tests/quotes/TH_top_splice.stderr
index cfb46e109c2a..9be72dc8ead9 100644
--- a/testsuite/tests/quotes/TH_top_splice.stderr
+++ b/testsuite/tests/quotes/TH_top_splice.stderr
@@ -2,4 +2,5 @@
 TH_top_splice.hs:6:7: error: [GHC-26759]
     • Unexpected top-level splice.
     • In the untyped splice: $([| 1 |])
-    Suggested fix: Perhaps you intended to use TemplateHaskell
+    Suggested fix:
+      Perhaps you intended to use the ‘TemplateHaskell’ extension
diff --git a/testsuite/tests/quotes/TTH_top_splice.stderr b/testsuite/tests/quotes/TTH_top_splice.stderr
index 4914223a5ce6..2a7c75a9ad5e 100644
--- a/testsuite/tests/quotes/TTH_top_splice.stderr
+++ b/testsuite/tests/quotes/TTH_top_splice.stderr
@@ -2,4 +2,5 @@
 TTH_top_splice.hs:6:7: error: [GHC-26759]
     • Unexpected top-level splice.
     • In the typed splice: $$([|| 1 ||])
-    Suggested fix: Perhaps you intended to use TemplateHaskell
+    Suggested fix:
+      Perhaps you intended to use the ‘TemplateHaskell’ extension
diff --git a/testsuite/tests/rename/should_compile/T15798b.stderr b/testsuite/tests/rename/should_compile/T15798b.stderr
index a2a368b8b7ec..1629425eb46c 100644
--- a/testsuite/tests/rename/should_compile/T15798b.stderr
+++ b/testsuite/tests/rename/should_compile/T15798b.stderr
@@ -1,4 +1,5 @@
 
 T15798b.hs:9:19: warning: [GHC-55631] [-Wmissing-deriving-strategies]
     No deriving strategy specified. Did you want stock, newtype, or anyclass?
-    Suggested fix: Perhaps you intended to use DerivingStrategies
+    Suggested fix:
+      Perhaps you intended to use the ‘DerivingStrategies’ extension (implied by ‘DerivingVia’)
diff --git a/testsuite/tests/rename/should_compile/T15798c.stderr b/testsuite/tests/rename/should_compile/T15798c.stderr
index 5b36d2b73356..0ec0129f0338 100644
--- a/testsuite/tests/rename/should_compile/T15798c.stderr
+++ b/testsuite/tests/rename/should_compile/T15798c.stderr
@@ -1,4 +1,5 @@
 
 T15798c.hs:6:3: warning: [GHC-55631] [-Wmissing-deriving-strategies]
     No deriving strategy specified. Did you want stock, newtype, or anyclass?
-    Suggested fix: Perhaps you intended to use DerivingStrategies
+    Suggested fix:
+      Perhaps you intended to use the ‘DerivingStrategies’ extension (implied by ‘DerivingVia’)
diff --git a/testsuite/tests/rename/should_compile/rn049.stderr b/testsuite/tests/rename/should_compile/rn049.stderr
index 5c13eb3936c8..74dc562a6357 100644
--- a/testsuite/tests/rename/should_compile/rn049.stderr
+++ b/testsuite/tests/rename/should_compile/rn049.stderr
@@ -2,4 +2,5 @@
 rn049.hs:12:6: warning: [GHC-59119]
     accepting non-standard pattern guards
         x <- 1 * 2 + 3 * 4
-    Suggested fix: Perhaps you intended to use PatternGuards
+    Suggested fix:
+      Perhaps you intended to use the ‘PatternGuards’ extension
diff --git a/testsuite/tests/rename/should_fail/PackageImportsDisabled.stderr b/testsuite/tests/rename/should_fail/PackageImportsDisabled.stderr
index 63499309b656..73d7e74115ee 100644
--- a/testsuite/tests/rename/should_fail/PackageImportsDisabled.stderr
+++ b/testsuite/tests/rename/should_fail/PackageImportsDisabled.stderr
@@ -1,3 +1,5 @@
-PackageImportsDisabled.hs:3:1: [GHC-10032]
+
+PackageImportsDisabled.hs:3:1: error: [GHC-10032]
     Package-qualified imports are not enabled
-    Suggested fix: Perhaps you intended to use PackageImports
+    Suggested fix:
+      Perhaps you intended to use the ‘PackageImports’ extension
diff --git a/testsuite/tests/rename/should_fail/RnDefaultSigFail.stderr b/testsuite/tests/rename/should_fail/RnDefaultSigFail.stderr
index fa58838e8813..10fdff96854c 100644
--- a/testsuite/tests/rename/should_fail/RnDefaultSigFail.stderr
+++ b/testsuite/tests/rename/should_fail/RnDefaultSigFail.stderr
@@ -1,4 +1,5 @@
 
 RnDefaultSigFail.hs:5:3: error: [GHC-40700]
     Unexpected default signature: default m :: Num a => a
-    Suggested fix: Perhaps you intended to use DefaultSignatures
+    Suggested fix:
+      Perhaps you intended to use the ‘DefaultSignatures’ extension
diff --git a/testsuite/tests/rename/should_fail/RnEmptyCaseFail.stderr b/testsuite/tests/rename/should_fail/RnEmptyCaseFail.stderr
index d611567a6ea4..b778056af58b 100644
--- a/testsuite/tests/rename/should_fail/RnEmptyCaseFail.stderr
+++ b/testsuite/tests/rename/should_fail/RnEmptyCaseFail.stderr
@@ -1,19 +1,23 @@
 
 RnEmptyCaseFail.hs:6:5: error: [GHC-48010]
     Empty list of alternatives in case expression
-    Suggested fix: Perhaps you intended to use EmptyCase
+    Suggested fix:
+      Perhaps you intended to use the ‘EmptyCase’ extension
 
 RnEmptyCaseFail.hs:8:5: error: [GHC-48010]
     Empty list of alternatives in \case expression
-    Suggested fix: Perhaps you intended to use EmptyCase
+    Suggested fix:
+      Perhaps you intended to use the ‘EmptyCase’ extension
 
 RnEmptyCaseFail.hs:10:5: error: [GHC-48010]
     Empty list of alternatives is not allowed in \cases expression
 
 RnEmptyCaseFail.hs:12:18: error: [GHC-48010]
     Empty list of alternatives in \case command
-    Suggested fix: Perhaps you intended to use EmptyCase
+    Suggested fix:
+      Perhaps you intended to use the ‘EmptyCase’ extension
 
 RnEmptyCaseFail.hs:14:18: error: [GHC-48010]
     Empty list of alternatives in case command
-    Suggested fix: Perhaps you intended to use EmptyCase
+    Suggested fix:
+      Perhaps you intended to use the ‘EmptyCase’ extension
diff --git a/testsuite/tests/rename/should_fail/RnEmptyStatementGroup1.stderr b/testsuite/tests/rename/should_fail/RnEmptyStatementGroup1.stderr
index 835a82a222a1..38232b2ad427 100644
--- a/testsuite/tests/rename/should_fail/RnEmptyStatementGroup1.stderr
+++ b/testsuite/tests/rename/should_fail/RnEmptyStatementGroup1.stderr
@@ -4,7 +4,8 @@ RnEmptyStatementGroup1.hs:6:13: error: [GHC-92693]
 
 RnEmptyStatementGroup1.hs:8:7: error: [GHC-82311]
     Empty 'do' block
-    Suggested fix: Perhaps you intended to use NondecreasingIndentation
+    Suggested fix:
+      Perhaps you intended to use the ‘NondecreasingIndentation’ extension
 
 RnEmptyStatementGroup1.hs:10:20: error: [GHC-19442]
     Empty 'do' block in an arrow command
diff --git a/testsuite/tests/rename/should_fail/RnPatternSynonymFail.stderr b/testsuite/tests/rename/should_fail/RnPatternSynonymFail.stderr
index 0bf8f16f04b3..90a98c3234ed 100644
--- a/testsuite/tests/rename/should_fail/RnPatternSynonymFail.stderr
+++ b/testsuite/tests/rename/should_fail/RnPatternSynonymFail.stderr
@@ -1,4 +1,5 @@
 
 RnPatternSynonymFail.hs:6:2: error: [GHC-41507]
     Illegal pattern synonym declaration
-    Suggested fix: Perhaps you intended to use PatternSynonyms
+    Suggested fix:
+      Perhaps you intended to use the ‘PatternSynonyms’ extension
diff --git a/testsuite/tests/rename/should_fail/RnUnexpectedStandaloneDeriving.stderr b/testsuite/tests/rename/should_fail/RnUnexpectedStandaloneDeriving.stderr
index 33cbd49a29e8..697a2cf3c5ea 100644
--- a/testsuite/tests/rename/should_fail/RnUnexpectedStandaloneDeriving.stderr
+++ b/testsuite/tests/rename/should_fail/RnUnexpectedStandaloneDeriving.stderr
@@ -1,4 +1,5 @@
 
 RnUnexpectedStandaloneDeriving.hs:7:1: error: [GHC-95159]
     Illegal standalone deriving declaration
-    Suggested fix: Perhaps you intended to use StandaloneDeriving
+    Suggested fix:
+      Perhaps you intended to use the ‘StandaloneDeriving’ extension
diff --git a/testsuite/tests/rename/should_fail/T11663.stderr b/testsuite/tests/rename/should_fail/T11663.stderr
index 4602d1992aeb..6a3931cdd851 100644
--- a/testsuite/tests/rename/should_fail/T11663.stderr
+++ b/testsuite/tests/rename/should_fail/T11663.stderr
@@ -2,19 +2,23 @@
 T11663.hs:6:12: error: [GHC-74097]
     Illegal type signature: ‘Int’
       Type signatures are only allowed in patterns with ScopedTypeVariables
-    Suggested fix: Perhaps you intended to use ScopedTypeVariables
+    Suggested fix:
+      Perhaps you intended to use the ‘ScopedTypeVariables’ extension
 
 T11663.hs:7:9: error: [GHC-74097]
     Illegal type signature: ‘Int’
       Type signatures are only allowed in patterns with ScopedTypeVariables
-    Suggested fix: Perhaps you intended to use ScopedTypeVariables
+    Suggested fix:
+      Perhaps you intended to use the ‘ScopedTypeVariables’ extension
 
 T11663.hs:8:22: error: [GHC-74097]
     Illegal type signature: ‘Int’
       Type signatures are only allowed in patterns with ScopedTypeVariables
-    Suggested fix: Perhaps you intended to use ScopedTypeVariables
+    Suggested fix:
+      Perhaps you intended to use the ‘ScopedTypeVariables’ extension
 
 T11663.hs:9:32: error: [GHC-74097]
     Illegal type signature: ‘Int’
       Type signatures are only allowed in patterns with ScopedTypeVariables
-    Suggested fix: Perhaps you intended to use ScopedTypeVariables
+    Suggested fix:
+      Perhaps you intended to use the ‘ScopedTypeVariables’ extension
diff --git a/testsuite/tests/rename/should_fail/T13568.stderr b/testsuite/tests/rename/should_fail/T13568.stderr
index 7682b8836fc2..eae9faf68cd8 100644
--- a/testsuite/tests/rename/should_fail/T13568.stderr
+++ b/testsuite/tests/rename/should_fail/T13568.stderr
@@ -2,5 +2,5 @@
 T13568.hs:7:8: error: [GHC-76037]
     Not in scope: type constructor or class ‘A’
     Suggested fix:
-      Perhaps you intended to use DataKinds
+      Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’)
       to refer to the data constructor of that name?
diff --git a/testsuite/tests/rename/should_fail/T14032c.stderr b/testsuite/tests/rename/should_fail/T14032c.stderr
index bd52709ff9b1..37c8509b13f8 100644
--- a/testsuite/tests/rename/should_fail/T14032c.stderr
+++ b/testsuite/tests/rename/should_fail/T14032c.stderr
@@ -3,10 +3,12 @@ T14032c.hs:1:1: error: [GHC-78534]
     Illegal use of the ‘type’ keyword:
       infix 0 $
     in a fixity signature
-    Suggested fix: Perhaps you intended to use ExplicitNamespaces
+    Suggested fix:
+      Perhaps you intended to use the ‘ExplicitNamespaces’ extension (implied by ‘TypeFamilies’ and ‘TypeOperators’)
 
 T14032c.hs:1:1: error: [GHC-78534]
     Illegal use of the ‘data’ keyword:
       infix 0 $
     in a fixity signature
-    Suggested fix: Perhaps you intended to use ExplicitNamespaces
+    Suggested fix:
+      Perhaps you intended to use the ‘ExplicitNamespaces’ extension (implied by ‘TypeFamilies’ and ‘TypeOperators’)
diff --git a/testsuite/tests/rename/should_fail/T17594b.stderr b/testsuite/tests/rename/should_fail/T17594b.stderr
index 5682c42ffb15..5363d78bed46 100644
--- a/testsuite/tests/rename/should_fail/T17594b.stderr
+++ b/testsuite/tests/rename/should_fail/T17594b.stderr
@@ -1,84 +1,105 @@
 
 T17594b.hs:7:5: error: [GHC-78249]
     Illegal invisible type pattern: t
-    Suggested fix: Perhaps you intended to use TypeAbstractions
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeAbstractions’ extension
 
 T17594b.hs:10:5: error: [GHC-78249]
     Illegal invisible type pattern: t
-    Suggested fix: Perhaps you intended to use TypeAbstractions
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeAbstractions’ extension
 
 T17594b.hs:14:5: error: [GHC-78249]
     Illegal invisible type pattern: t
-    Suggested fix: Perhaps you intended to use TypeAbstractions
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeAbstractions’ extension
 
 T17594b.hs:17:5: error: [GHC-78249]
     Illegal invisible type pattern: t1
-    Suggested fix: Perhaps you intended to use TypeAbstractions
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeAbstractions’ extension
 
 T17594b.hs:17:9: error: [GHC-78249]
     Illegal invisible type pattern: t2
-    Suggested fix: Perhaps you intended to use TypeAbstractions
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeAbstractions’ extension
 
 T17594b.hs:17:13: error: [GHC-78249]
     Illegal invisible type pattern: t3
-    Suggested fix: Perhaps you intended to use TypeAbstractions
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeAbstractions’ extension
 
 T17594b.hs:17:26: error: [GHC-78249]
     Illegal invisible type pattern: t4
-    Suggested fix: Perhaps you intended to use TypeAbstractions
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeAbstractions’ extension
 
 T17594b.hs:17:30: error: [GHC-78249]
     Illegal invisible type pattern: t5
-    Suggested fix: Perhaps you intended to use TypeAbstractions
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeAbstractions’ extension
 
 T17594b.hs:17:34: error: [GHC-78249]
     Illegal invisible type pattern: t6
-    Suggested fix: Perhaps you intended to use TypeAbstractions
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeAbstractions’ extension
 
 T17594b.hs:20:10: error: [GHC-78249]
     Illegal invisible type pattern: t
-    Suggested fix: Perhaps you intended to use TypeAbstractions
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeAbstractions’ extension
 
 T17594b.hs:22:19: error: [GHC-78249]
     Illegal invisible type pattern: t
-    Suggested fix: Perhaps you intended to use TypeAbstractions
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeAbstractions’ extension
 
 T17594b.hs:25:9: error: [GHC-78249]
     Illegal invisible type pattern: t
-    Suggested fix: Perhaps you intended to use TypeAbstractions
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeAbstractions’ extension
 
 T17594b.hs:28:5: error: [GHC-78249]
     Illegal invisible type pattern: t1
-    Suggested fix: Perhaps you intended to use TypeAbstractions
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeAbstractions’ extension
 
 T17594b.hs:28:9: error: [GHC-78249]
     Illegal invisible type pattern: t2
-    Suggested fix: Perhaps you intended to use TypeAbstractions
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeAbstractions’ extension
 
 T17594b.hs:28:31: error: [GHC-78249]
     Illegal invisible type pattern: t3
-    Suggested fix: Perhaps you intended to use TypeAbstractions
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeAbstractions’ extension
 
 T17594b.hs:28:57: error: [GHC-78249]
     Illegal invisible type pattern: t4
-    Suggested fix: Perhaps you intended to use TypeAbstractions
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeAbstractions’ extension
 
 T17594b.hs:28:61: error: [GHC-78249]
     Illegal invisible type pattern: t5
-    Suggested fix: Perhaps you intended to use TypeAbstractions
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeAbstractions’ extension
 
 T17594b.hs:28:70: error: [GHC-78249]
     Illegal invisible type pattern: t6
-    Suggested fix: Perhaps you intended to use TypeAbstractions
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeAbstractions’ extension
 
 T17594b.hs:31:10: error: [GHC-78249]
     Illegal invisible type pattern: t
-    Suggested fix: Perhaps you intended to use TypeAbstractions
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeAbstractions’ extension
 
 T17594b.hs:34:10: error: [GHC-78249]
     Illegal invisible type pattern: t
-    Suggested fix: Perhaps you intended to use TypeAbstractions
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeAbstractions’ extension
 
 T17594b.hs:37:6: error: [GHC-78249]
     Illegal invisible type pattern: ($(TH.varT (TH.mkName "t")))
-    Suggested fix: Perhaps you intended to use TypeAbstractions
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeAbstractions’ extension
diff --git a/testsuite/tests/rename/should_fail/T20147.stderr b/testsuite/tests/rename/should_fail/T20147.stderr
index 0e782f902b70..312b87e21ec3 100644
--- a/testsuite/tests/rename/should_fail/T20147.stderr
+++ b/testsuite/tests/rename/should_fail/T20147.stderr
@@ -1,4 +1,5 @@
 
 T20147.hs:6:28: error: [GHC-82311]
     Empty 'do' block
-    Suggested fix: Perhaps you intended to use NondecreasingIndentation
+    Suggested fix:
+      Perhaps you intended to use the ‘NondecreasingIndentation’ extension
diff --git a/testsuite/tests/rename/should_fail/T22478e.stderr b/testsuite/tests/rename/should_fail/T22478e.stderr
index dbd2a9845fce..db0db738a1ed 100644
--- a/testsuite/tests/rename/should_fail/T22478e.stderr
+++ b/testsuite/tests/rename/should_fail/T22478e.stderr
@@ -1,65 +1,81 @@
 
 T22478e.hs:6:4: error: [GHC-68567]
     Illegal type: ‘[a, b]’
-    Suggested fix: Perhaps you intended to use DataKinds
+    Suggested fix:
+      Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’)
 
 T22478e.hs:6:4: error: [GHC-17916]
     Illegal visible type application in a pattern: @[a, b]
-    Suggested fix: Perhaps you intended to use TypeAbstractions
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeAbstractions’ extension
 
 T22478e.hs:7:4: error: [GHC-68567]
     Illegal type: ‘1’
-    Suggested fix: Perhaps you intended to use DataKinds
+    Suggested fix:
+      Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’)
 
 T22478e.hs:7:4: error: [GHC-17916]
     Illegal visible type application in a pattern: @1
-    Suggested fix: Perhaps you intended to use TypeAbstractions
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeAbstractions’ extension
 
 T22478e.hs:8:4: error: [GHC-23482]
     Illegal visible kind application: @k
-    Suggested fix: Perhaps you intended to use TypeApplications
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeApplications’ extension
 
 T22478e.hs:8:4: error: [GHC-17916]
     Illegal visible type application in a pattern: @(t @k)
-    Suggested fix: Perhaps you intended to use TypeAbstractions
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeAbstractions’ extension
 
 T22478e.hs:9:4: error: [GHC-17916]
     Illegal visible type application in a pattern: @(t :: k)
-    Suggested fix: Perhaps you intended to use TypeAbstractions
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeAbstractions’ extension
 
 T22478e.hs:9:13: error: [GHC-49378]
     • Illegal kind signature ‘k’
     • In a type argument in a pattern
-    Suggested fix: Perhaps you intended to use KindSignatures
+    Suggested fix:
+      Perhaps you intended to use the ‘KindSignatures’ extension (implied by ‘TypeFamilies’ and ‘PolyKinds’)
 
 T22478e.hs:10:4: error: [GHC-68567]
     Illegal type: ‘'(a, b)’
-    Suggested fix: Perhaps you intended to use DataKinds
+    Suggested fix:
+      Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’)
 
 T22478e.hs:10:4: error: [GHC-17916]
     Illegal visible type application in a pattern: @('(a, b))
-    Suggested fix: Perhaps you intended to use TypeAbstractions
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeAbstractions’ extension
 
 T22478e.hs:11:4: error: [GHC-68567]
     Illegal type: ‘"str"’
-    Suggested fix: Perhaps you intended to use DataKinds
+    Suggested fix:
+      Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’)
 
 T22478e.hs:11:4: error: [GHC-17916]
     Illegal visible type application in a pattern: @"str"
-    Suggested fix: Perhaps you intended to use TypeAbstractions
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeAbstractions’ extension
 
 T22478e.hs:12:4: error: [GHC-68567]
     Illegal type: ‘'c'’
-    Suggested fix: Perhaps you intended to use DataKinds
+    Suggested fix:
+      Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’)
 
 T22478e.hs:12:4: error: [GHC-17916]
     Illegal visible type application in a pattern: @'c'
-    Suggested fix: Perhaps you intended to use TypeAbstractions
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeAbstractions’ extension
 
 T22478e.hs:13:4: error: [GHC-68567]
     Illegal type: ‘'True’
-    Suggested fix: Perhaps you intended to use DataKinds
+    Suggested fix:
+      Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’)
 
 T22478e.hs:13:4: error: [GHC-17916]
     Illegal visible type application in a pattern: @'True
-    Suggested fix: Perhaps you intended to use TypeAbstractions
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeAbstractions’ extension
diff --git a/testsuite/tests/rename/should_fail/T3265.stderr b/testsuite/tests/rename/should_fail/T3265.stderr
index dfe09aa9868b..cecf25131c3d 100644
--- a/testsuite/tests/rename/should_fail/T3265.stderr
+++ b/testsuite/tests/rename/should_fail/T3265.stderr
@@ -1,8 +1,10 @@
 
 T3265.hs:8:8: error: [GHC-50649]
     Illegal declaration of a type or class operator ‘:+:’
-    Suggested fix: Perhaps you intended to use TypeOperators
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeOperators’ extension
 
 T3265.hs:10:9: error: [GHC-50649]
     Illegal declaration of a type or class operator ‘:*:’
-    Suggested fix: Perhaps you intended to use TypeOperators
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeOperators’ extension
diff --git a/testsuite/tests/rename/should_fail/rnfail052.stderr b/testsuite/tests/rename/should_fail/rnfail052.stderr
index db9aaeb92326..293223c52bcb 100644
--- a/testsuite/tests/rename/should_fail/rnfail052.stderr
+++ b/testsuite/tests/rename/should_fail/rnfail052.stderr
@@ -2,17 +2,23 @@
 rnfail052.hs:7:6: error: [GHC-25955]
     Illegal symbol ‘forall’ in type
     Suggested fix:
-      Perhaps you intended to use RankNTypes
-      or a similar language extension to enable explicit-forall syntax: forall <tvs>. <type>
+      Use the ‘ExplicitForAll’ extension (implied by ‘RankNTypes’,
+                                                     ‘QuantifiedConstraints’, ‘ScopedTypeVariables’,
+                                                     ‘LiberalTypeSynonyms’ and ‘ExistentialQuantification’)
+      to enable syntax: forall <tvs>. <type>
 
 rnfail052.hs:10:14: error: [GHC-25955]
     Illegal symbol ‘forall’ in type
     Suggested fix:
-      Perhaps you intended to use RankNTypes
-      or a similar language extension to enable explicit-forall syntax: forall <tvs>. <type>
+      Use the ‘ExplicitForAll’ extension (implied by ‘RankNTypes’,
+                                                     ‘QuantifiedConstraints’, ‘ScopedTypeVariables’,
+                                                     ‘LiberalTypeSynonyms’ and ‘ExistentialQuantification’)
+      to enable syntax: forall <tvs>. <type>
 
 rnfail052.hs:13:15: error: [GHC-25955]
     Illegal symbol ‘forall’ in type
     Suggested fix:
-      Perhaps you intended to use RankNTypes
-      or a similar language extension to enable explicit-forall syntax: forall <tvs>. <type>
+      Use the ‘ExplicitForAll’ extension (implied by ‘RankNTypes’,
+                                                     ‘QuantifiedConstraints’, ‘ScopedTypeVariables’,
+                                                     ‘LiberalTypeSynonyms’ and ‘ExistentialQuantification’)
+      to enable syntax: forall <tvs>. <type>
diff --git a/testsuite/tests/rename/should_fail/rnfail053.stderr b/testsuite/tests/rename/should_fail/rnfail053.stderr
index c3ed331955cc..f279dee350cd 100644
--- a/testsuite/tests/rename/should_fail/rnfail053.stderr
+++ b/testsuite/tests/rename/should_fail/rnfail053.stderr
@@ -5,4 +5,4 @@ rnfail053.hs:6:10: error: [GHC-25709]
     • In the definition of data constructor ‘MkT’
       In the data type declaration for ‘T’
     Suggested fix:
-      Enable any of the following extensions: ExistentialQuantification, GADTs
+      Enable any of the following extensions: ‘ExistentialQuantification’ or ‘GADTs’
diff --git a/testsuite/tests/rename/should_fail/rnfail056.stderr b/testsuite/tests/rename/should_fail/rnfail056.stderr
index 7d3e1eb5bb4e..3ae66857e868 100644
--- a/testsuite/tests/rename/should_fail/rnfail056.stderr
+++ b/testsuite/tests/rename/should_fail/rnfail056.stderr
@@ -1,8 +1,10 @@
 
-rnfail056.hs:7:7: [GHC-59155] error:
+rnfail056.hs:7:7: error: [GHC-59155]
     Illegal tuple section
-    Suggested fix: Perhaps you intended to use TupleSections
+    Suggested fix:
+      Perhaps you intended to use the ‘TupleSections’ extension
 
-rnfail056.hs:9:7: [GHC-59155] error:
+rnfail056.hs:9:7: error: [GHC-59155]
     Illegal tuple section
-    Suggested fix: Perhaps you intended to use TupleSections
+    Suggested fix:
+      Perhaps you intended to use the ‘TupleSections’ extension
diff --git a/testsuite/tests/roles/should_fail/Roles5.stderr b/testsuite/tests/roles/should_fail/Roles5.stderr
index 052e2d3fa94d..627514276a35 100644
--- a/testsuite/tests/roles/should_fail/Roles5.stderr
+++ b/testsuite/tests/roles/should_fail/Roles5.stderr
@@ -1,19 +1,22 @@
 
-Roles5.hs:7:1: [GHC-17779]
-    Illegal role annotation for T
-    while checking a role annotation for ‘T’
-    Suggested fix: Perhaps you intended to use RoleAnnotations
+Roles5.hs:7:1: error: [GHC-17779]
+    • Illegal role annotation for T
+    • while checking a role annotation for ‘T’
+    Suggested fix:
+      Perhaps you intended to use the ‘RoleAnnotations’ extension
 
-Roles5.hs:8:1: [GHC-18273]
-     Roles other than ‘nominal’ for class parameters can lead to incoherence.
-     while checking a role annotation for ‘C’
-    Suggested fix: Perhaps you intended to use IncoherentInstances
+Roles5.hs:8:1: error: [GHC-18273]
+    • Roles other than ‘nominal’ for class parameters can lead to incoherence.
+    • while checking a role annotation for ‘C’
+    Suggested fix:
+      Perhaps you intended to use the ‘IncoherentInstances’ extension
 
-Roles5.hs:8:1: [GHC-17779]
-    Illegal role annotation for C
-    while checking a role annotation for ‘C’
-    Suggested fix: Perhaps you intended to use RoleAnnotations
+Roles5.hs:8:1: error: [GHC-17779]
+    • Illegal role annotation for C
+    • while checking a role annotation for ‘C’
+    Suggested fix:
+      Perhaps you intended to use the ‘RoleAnnotations’ extension
 
-Roles5.hs:9:1: [GHC-77192]
+Roles5.hs:9:1: error: [GHC-77192]
     Illegal role annotation for S;
     they are allowed only for datatypes and classes.
diff --git a/testsuite/tests/roles/should_fail/T8773.stderr b/testsuite/tests/roles/should_fail/T8773.stderr
index 7cf09c4253bc..238e8f210e86 100644
--- a/testsuite/tests/roles/should_fail/T8773.stderr
+++ b/testsuite/tests/roles/should_fail/T8773.stderr
@@ -1,5 +1,6 @@
 
-T8773.hs:5:1: [GHC-18273]
-    Roles other than ‘nominal’ for class parameters can lead to incoherence.
-    while checking a role annotation for ‘C2’
-    Suggested fix: Perhaps you intended to use IncoherentInstances
+T8773.hs:5:1: error: [GHC-18273]
+    • Roles other than ‘nominal’ for class parameters can lead to incoherence.
+    • while checking a role annotation for ‘C2’
+    Suggested fix:
+      Perhaps you intended to use the ‘IncoherentInstances’ extension
diff --git a/testsuite/tests/safeHaskell/ghci/p16.stderr b/testsuite/tests/safeHaskell/ghci/p16.stderr
index 0ca13a3414da..74ccaec07c74 100644
--- a/testsuite/tests/safeHaskell/ghci/p16.stderr
+++ b/testsuite/tests/safeHaskell/ghci/p16.stderr
@@ -7,7 +7,7 @@
         ‘Op’ is not a stock derivable class (Eq, Show, etc.)
     • In the newtype declaration for ‘T2’
     Suggested fix:
-      Perhaps you intended to use GeneralizedNewtypeDeriving
+      Perhaps you intended to use the ‘GeneralizedNewtypeDeriving’ extension
       for GHC's newtype-deriving extension
       You may enable this language extension in GHCi with:
         :set -XGeneralizedNewtypeDeriving
diff --git a/testsuite/tests/safeHaskell/safeLanguage/SafeLang12.stderr b/testsuite/tests/safeHaskell/safeLanguage/SafeLang12.stderr
index 109653a80c7e..ad2a0a3c16e0 100644
--- a/testsuite/tests/safeHaskell/safeLanguage/SafeLang12.stderr
+++ b/testsuite/tests/safeHaskell/safeLanguage/SafeLang12.stderr
@@ -10,4 +10,5 @@ SafeLang12_B.hs:3:14: warning: [GHC-98887]
 
 SafeLang12.hs:1:1: error: [GHC-26759]
     Unexpected top-level splice.
-    Suggested fix: Perhaps you intended to use TemplateHaskell
+    Suggested fix:
+      Perhaps you intended to use the ‘TemplateHaskell’ extension
diff --git a/testsuite/tests/saks/should_fail/T16722.stderr b/testsuite/tests/saks/should_fail/T16722.stderr
index 94bb0bc82ae8..16ad413e563e 100644
--- a/testsuite/tests/saks/should_fail/T16722.stderr
+++ b/testsuite/tests/saks/should_fail/T16722.stderr
@@ -1,5 +1,6 @@
 
 T16722.hs:8:11: error: [GHC-12875]
-    Unexpected kind variable ‘k’
-    In the standalone kind signature for D
-    Suggested fix: Perhaps you intended to use PolyKinds
\ No newline at end of file
+    • Unexpected kind variable ‘k’
+    • In the standalone kind signature for D
+    Suggested fix:
+      Perhaps you intended to use the ‘PolyKinds’ extension
diff --git a/testsuite/tests/saks/should_fail/saks_fail001.stderr b/testsuite/tests/saks/should_fail/saks_fail001.stderr
index a85605cafc71..30cc33c310cf 100644
--- a/testsuite/tests/saks/should_fail/saks_fail001.stderr
+++ b/testsuite/tests/saks/should_fail/saks_fail001.stderr
@@ -1,4 +1,5 @@
 
 saks_fail001.hs:8:1: error: [GHC-45906]
     Illegal standalone kind signature
-    Suggested fix: Perhaps you intended to use StandaloneKindSignatures
+    Suggested fix:
+      Perhaps you intended to use the ‘StandaloneKindSignatures’ extension (implied by ‘UnliftedDatatypes’)
diff --git a/testsuite/tests/th/T12411.stderr b/testsuite/tests/th/T12411.stderr
index 21db663966e8..8e650aca70fe 100644
--- a/testsuite/tests/th/T12411.stderr
+++ b/testsuite/tests/th/T12411.stderr
@@ -1,7 +1,8 @@
 
 T12411.hs:5:1: error: [GHC-23482]
     Illegal visible type application: @Q
-    Suggested fix: Perhaps you intended to use TypeApplications
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeApplications’ extension
 
 T12411.hs:5:7: error: [GHC-76037]
     Not in scope: type constructor or class ‘Q’
diff --git a/testsuite/tests/th/T14204.stderr b/testsuite/tests/th/T14204.stderr
index 8f9638071fb3..7e0ddfde043e 100644
--- a/testsuite/tests/th/T14204.stderr
+++ b/testsuite/tests/th/T14204.stderr
@@ -1,5 +1,6 @@
 
-T14204.hs:8:34: [GHC-23800] error:
+T14204.hs:8:34: error: [GHC-23800]
     • Illegal static expression: static "wat"
     • In the untyped splice: $(pure (StaticE (LitE (StringL "wat"))))
-    Suggested fix: Perhaps you intended to use StaticPointers
+    Suggested fix:
+      Perhaps you intended to use the ‘StaticPointers’ extension
diff --git a/testsuite/tests/th/T16133.stderr b/testsuite/tests/th/T16133.stderr
index 360a07e513c2..c11eca32b6aa 100644
--- a/testsuite/tests/th/T16133.stderr
+++ b/testsuite/tests/th/T16133.stderr
@@ -1,8 +1,10 @@
 
 T16133.hs:11:2: error: [GHC-23482]
     Illegal visible type application: @Int
-    Suggested fix: Perhaps you intended to use TypeApplications
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeApplications’ extension
 
 T16133.hs:11:2: error: [GHC-23482]
     Illegal visible kind application: @Type
-    Suggested fix: Perhaps you intended to use TypeApplications
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeApplications’ extension
diff --git a/testsuite/tests/th/TH_Promoted1Tuple.stderr b/testsuite/tests/th/TH_Promoted1Tuple.stderr
index fa5d55ebbfa2..a94f1616ede1 100644
--- a/testsuite/tests/th/TH_Promoted1Tuple.stderr
+++ b/testsuite/tests/th/TH_Promoted1Tuple.stderr
@@ -1,4 +1,5 @@
 
 TH_Promoted1Tuple.hs:7:2: error: [GHC-68567]
     Illegal type: ‘'MkSolo Int’
-    Suggested fix: Perhaps you intended to use DataKinds
\ No newline at end of file
+    Suggested fix:
+      Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’)
diff --git a/testsuite/tests/th/TH_Roles1.stderr b/testsuite/tests/th/TH_Roles1.stderr
index e7b138c2c6e1..721973bd3dfa 100644
--- a/testsuite/tests/th/TH_Roles1.stderr
+++ b/testsuite/tests/th/TH_Roles1.stderr
@@ -2,4 +2,5 @@
 TH_Roles1.hs:7:2: error: [GHC-17779]
     • Illegal role annotation for T
     • while checking a role annotation for ‘T’
-    Suggested fix: Perhaps you intended to use RoleAnnotations
+    Suggested fix:
+      Perhaps you intended to use the ‘RoleAnnotations’ extension
diff --git a/testsuite/tests/type-data/should_fail/TDNoPragma.stderr b/testsuite/tests/type-data/should_fail/TDNoPragma.stderr
index 62b47da4d1bc..683fbd755d34 100644
--- a/testsuite/tests/type-data/should_fail/TDNoPragma.stderr
+++ b/testsuite/tests/type-data/should_fail/TDNoPragma.stderr
@@ -1,4 +1,4 @@
 
-TDNoPragma.hs:4:1: [GHC-15013]
+TDNoPragma.hs:4:1: error: [GHC-15013]
     Illegal type-level data declaration
-    Suggested fix: Perhaps you intended to use TypeData
+    Suggested fix: Perhaps you intended to use the ‘TypeData’ extension
diff --git a/testsuite/tests/typecheck/should_compile/T15473.stderr b/testsuite/tests/typecheck/should_compile/T15473.stderr
index f5cf2f41f9c5..2c71627f0f4f 100644
--- a/testsuite/tests/typecheck/should_compile/T15473.stderr
+++ b/testsuite/tests/typecheck/should_compile/T15473.stderr
@@ -6,4 +6,5 @@ T15473.hs:11:3: error: [GHC-22979]
                                                   xs t ts is y z’
     • In the equations for closed type family ‘LetInterleave’
       In the type family declaration for ‘LetInterleave’
-    Suggested fix: Perhaps you intended to use UndecidableInstances
+    Suggested fix:
+      Perhaps you intended to use the ‘UndecidableInstances’ extension
diff --git a/testsuite/tests/typecheck/should_compile/T15839a.stderr b/testsuite/tests/typecheck/should_compile/T15839a.stderr
index b9330044f5b2..3bfa4df4efdd 100644
--- a/testsuite/tests/typecheck/should_compile/T15839a.stderr
+++ b/testsuite/tests/typecheck/should_compile/T15839a.stderr
@@ -4,5 +4,5 @@ T15839a.hs:6:30: warning: [GHC-20042] [-Wderiving-defaults (in -Wdefault)]
       Defaulting to the DeriveAnyClass strategy for instantiating C
     • In the newtype declaration for ‘T’
     Suggested fix:
-      Use DerivingStrategies
+      Use the ‘DerivingStrategies’ extension (implied by ‘DerivingVia’)
       to pick a different strategy
diff --git a/testsuite/tests/typecheck/should_compile/T22141a.stderr b/testsuite/tests/typecheck/should_compile/T22141a.stderr
index 8c26dea1d10e..da32796ad371 100644
--- a/testsuite/tests/typecheck/should_compile/T22141a.stderr
+++ b/testsuite/tests/typecheck/should_compile/T22141a.stderr
@@ -4,4 +4,5 @@ T22141a.hs:8:1: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)]
       Future versions of GHC will turn this warning into an error.
     • In the expansion of type synonym ‘Nat’
       In the data type declaration for ‘Vector’
-    Suggested fix: Perhaps you intended to use DataKinds
+    Suggested fix:
+      Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’)
diff --git a/testsuite/tests/typecheck/should_compile/T22141b.stderr b/testsuite/tests/typecheck/should_compile/T22141b.stderr
index f3d2471bbaf9..338591bc7842 100644
--- a/testsuite/tests/typecheck/should_compile/T22141b.stderr
+++ b/testsuite/tests/typecheck/should_compile/T22141b.stderr
@@ -5,4 +5,5 @@ T22141b.hs:10:1: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)]
     • In the expansion of type synonym ‘Nat’
       In the expansion of type synonym ‘MyNat’
       In the data type declaration for ‘Vector’
-    Suggested fix: Perhaps you intended to use DataKinds
+    Suggested fix:
+      Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’)
diff --git a/testsuite/tests/typecheck/should_compile/T22141c.stderr b/testsuite/tests/typecheck/should_compile/T22141c.stderr
index e82c57fd3ef7..8ba57f0c3dec 100644
--- a/testsuite/tests/typecheck/should_compile/T22141c.stderr
+++ b/testsuite/tests/typecheck/should_compile/T22141c.stderr
@@ -4,29 +4,34 @@ T22141c.hs:10:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)]
       Future versions of GHC will turn this warning into an error.
     • In the expansion of type synonym ‘T’
       In a standalone kind signature for ‘D’: Proxy T -> Type
-    Suggested fix: Perhaps you intended to use DataKinds
+    Suggested fix:
+      Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’)
 
 T22141c.hs:10:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)]
     • An occurrence of ‘'[]’ in a kind requires DataKinds.
       Future versions of GHC will turn this warning into an error.
     • In a standalone kind signature for ‘D’: Proxy T -> Type
-    Suggested fix: Perhaps you intended to use DataKinds
+    Suggested fix:
+      Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’)
 
 T22141c.hs:10:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)]
     • An occurrence of ‘'[GHC.Types.LiftedRep]’ in a kind requires DataKinds.
       Future versions of GHC will turn this warning into an error.
     • In a standalone kind signature for ‘D’: Proxy T -> Type
-    Suggested fix: Perhaps you intended to use DataKinds
+    Suggested fix:
+      Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’)
 
 T22141c.hs:10:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)]
     • An occurrence of ‘[GHC.Types.LiftedRep,
                          GHC.Types.LiftedRep]’ in a kind requires DataKinds.
       Future versions of GHC will turn this warning into an error.
     • In a standalone kind signature for ‘D’: Proxy T -> Type
-    Suggested fix: Perhaps you intended to use DataKinds
+    Suggested fix:
+      Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’)
 
 T22141c.hs:10:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)]
     • An occurrence of ‘Proxy T’ in a kind requires DataKinds.
       Future versions of GHC will turn this warning into an error.
     • In a standalone kind signature for ‘D’: Proxy T -> Type
-    Suggested fix: Perhaps you intended to use DataKinds
+    Suggested fix:
+      Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’)
diff --git a/testsuite/tests/typecheck/should_compile/T22141d.stderr b/testsuite/tests/typecheck/should_compile/T22141d.stderr
index d3f57e4304be..7864afa505ac 100644
--- a/testsuite/tests/typecheck/should_compile/T22141d.stderr
+++ b/testsuite/tests/typecheck/should_compile/T22141d.stderr
@@ -4,29 +4,34 @@ T22141d.hs:10:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)]
       Future versions of GHC will turn this warning into an error.
     • In the expansion of type synonym ‘T’
       In a standalone kind signature for ‘D’: Proxy T -> Type
-    Suggested fix: Perhaps you intended to use DataKinds
+    Suggested fix:
+      Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’)
 
 T22141d.hs:10:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)]
     • An occurrence of ‘'[]’ in a kind requires DataKinds.
       Future versions of GHC will turn this warning into an error.
     • In a standalone kind signature for ‘D’: Proxy T -> Type
-    Suggested fix: Perhaps you intended to use DataKinds
+    Suggested fix:
+      Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’)
 
 T22141d.hs:10:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)]
     • An occurrence of ‘'[GHC.Types.LiftedRep]’ in a kind requires DataKinds.
       Future versions of GHC will turn this warning into an error.
     • In a standalone kind signature for ‘D’: Proxy T -> Type
-    Suggested fix: Perhaps you intended to use DataKinds
+    Suggested fix:
+      Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’)
 
 T22141d.hs:10:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)]
     • An occurrence of ‘[GHC.Types.LiftedRep,
                          GHC.Types.LiftedRep]’ in a kind requires DataKinds.
       Future versions of GHC will turn this warning into an error.
     • In a standalone kind signature for ‘D’: Proxy T -> Type
-    Suggested fix: Perhaps you intended to use DataKinds
+    Suggested fix:
+      Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’)
 
 T22141d.hs:10:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)]
     • An occurrence of ‘Proxy T’ in a kind requires DataKinds.
       Future versions of GHC will turn this warning into an error.
     • In a standalone kind signature for ‘D’: Proxy T -> Type
-    Suggested fix: Perhaps you intended to use DataKinds
+    Suggested fix:
+      Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’)
diff --git a/testsuite/tests/typecheck/should_compile/T22141e.stderr b/testsuite/tests/typecheck/should_compile/T22141e.stderr
index 94b1ccc126c1..453397c74250 100644
--- a/testsuite/tests/typecheck/should_compile/T22141e.stderr
+++ b/testsuite/tests/typecheck/should_compile/T22141e.stderr
@@ -4,16 +4,19 @@ T22141e.hs:8:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)]
       Future versions of GHC will turn this warning into an error.
     • In the expansion of type synonym ‘T’
       In a standalone kind signature for ‘D’: Proxy T -> Type
-    Suggested fix: Perhaps you intended to use DataKinds
+    Suggested fix:
+      Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’)
 
 T22141e.hs:8:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)]
     • An occurrence of ‘GHC.Num.Natural.Natural’ in a kind requires DataKinds.
       Future versions of GHC will turn this warning into an error.
     • In a standalone kind signature for ‘D’: Proxy T -> Type
-    Suggested fix: Perhaps you intended to use DataKinds
+    Suggested fix:
+      Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’)
 
 T22141e.hs:8:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)]
     • An occurrence of ‘Proxy T’ in a kind requires DataKinds.
       Future versions of GHC will turn this warning into an error.
     • In a standalone kind signature for ‘D’: Proxy T -> Type
-    Suggested fix: Perhaps you intended to use DataKinds
+    Suggested fix:
+      Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’)
diff --git a/testsuite/tests/typecheck/should_fail/LazyFieldsDisabled.stderr b/testsuite/tests/typecheck/should_fail/LazyFieldsDisabled.stderr
index 5e1b44dd1205..e36d9700982d 100644
--- a/testsuite/tests/typecheck/should_fail/LazyFieldsDisabled.stderr
+++ b/testsuite/tests/typecheck/should_fail/LazyFieldsDisabled.stderr
@@ -1,6 +1,8 @@
-LazyFieldsDisabled.hs:3:10: [GHC-81601]
-     Lazy field annotations (~) are disabled
+
+LazyFieldsDisabled.hs:3:10: error: [GHC-81601]
+    • Lazy field annotations (~) are disabled
         on the first argument of ‘A’
-     In the definition of data constructor ‘A’
+    • In the definition of data constructor ‘A’
       In the data type declaration for ‘A’
-    Suggested fix: Perhaps you intended to use StrictData
+    Suggested fix:
+      Perhaps you intended to use the ‘StrictData’ extension (implied by ‘Strict’)
diff --git a/testsuite/tests/typecheck/should_fail/T10351.stderr b/testsuite/tests/typecheck/should_fail/T10351.stderr
index d749801f338e..9202f8002ca1 100644
--- a/testsuite/tests/typecheck/should_fail/T10351.stderr
+++ b/testsuite/tests/typecheck/should_fail/T10351.stderr
@@ -3,4 +3,5 @@ T10351.hs:7:1: error: [GHC-80003]
     • Non type-variable argument in the constraint: C [a]
     • When checking the inferred type
         f :: forall {a}. C [a] => a -> ()
-    Suggested fix: Perhaps you intended to use FlexibleContexts
+    Suggested fix:
+      Perhaps you intended to use the ‘FlexibleContexts’ extension
diff --git a/testsuite/tests/typecheck/should_fail/T11355.stderr b/testsuite/tests/typecheck/should_fail/T11355.stderr
index f9a5964b534b..a5f62596d7f4 100644
--- a/testsuite/tests/typecheck/should_fail/T11355.stderr
+++ b/testsuite/tests/typecheck/should_fail/T11355.stderr
@@ -6,4 +6,5 @@ T11355.hs:5:7: error: [GHC-91510]
       In an equation for ‘foo’:
           foo
             = const @_ @((forall a. a) -> forall a. a) () (id @(forall a. a))
-    Suggested fix: Perhaps you intended to use ImpredicativeTypes
+    Suggested fix:
+      Perhaps you intended to use the ‘ImpredicativeTypes’ extension
diff --git a/testsuite/tests/typecheck/should_fail/T12083a.stderr b/testsuite/tests/typecheck/should_fail/T12083a.stderr
index 34b411850cb2..6ae4de5ee61c 100644
--- a/testsuite/tests/typecheck/should_fail/T12083a.stderr
+++ b/testsuite/tests/typecheck/should_fail/T12083a.stderr
@@ -2,7 +2,8 @@
 T12083a.hs:6:1: error: [GHC-91510]
     • Illegal qualified type: Num a => a
     • In the type synonym declaration for ‘Constrd’
-    Suggested fix: Perhaps you intended to use RankNTypes
+    Suggested fix:
+      Perhaps you intended to use the ‘RankNTypes’ extension (implied by ‘ImpredicativeTypes’)
 
 T12083a.hs:10:26: error: [GHC-25709]
     • Data constructor ‘ExistentiallyLost’ has existential type variables, a context, or a specialised result type
@@ -10,4 +11,4 @@ T12083a.hs:10:26: error: [GHC-25709]
     • In the definition of data constructor ‘ExistentiallyLost’
       In the data type declaration for ‘ExistentiallyLost’
     Suggested fix:
-      Enable any of the following extensions: ExistentialQuantification, GADTs
+      Enable any of the following extensions: ‘ExistentialQuantification’ or ‘GADTs’
diff --git a/testsuite/tests/typecheck/should_fail/T12083b.stderr b/testsuite/tests/typecheck/should_fail/T12083b.stderr
index 5359fbec8735..17832a26aaef 100644
--- a/testsuite/tests/typecheck/should_fail/T12083b.stderr
+++ b/testsuite/tests/typecheck/should_fail/T12083b.stderr
@@ -4,4 +4,5 @@ T12083b.hs:7:5: error: [GHC-91510]
     • When checking the class method:
         test :: forall a r. Class a => a -> (Eq a => r) -> r
       In the class declaration for ‘Class’
-    Suggested fix: Perhaps you intended to use RankNTypes
+    Suggested fix:
+      Perhaps you intended to use the ‘RankNTypes’ extension (implied by ‘ImpredicativeTypes’)
diff --git a/testsuite/tests/typecheck/should_fail/T12729.stderr b/testsuite/tests/typecheck/should_fail/T12729.stderr
index d638aa7e7c11..b01db9c2bd4f 100644
--- a/testsuite/tests/typecheck/should_fail/T12729.stderr
+++ b/testsuite/tests/typecheck/should_fail/T12729.stderr
@@ -2,4 +2,5 @@
 T12729.hs:7:1: error: [GHC-55233]
     • Newtype has non-* return kind ‘TYPE IntRep’
     • In the newtype declaration for ‘A’
-    Suggested fix: Perhaps you intended to use UnliftedNewtypes
+    Suggested fix:
+      Perhaps you intended to use the ‘UnliftedNewtypes’ extension
diff --git a/testsuite/tests/typecheck/should_fail/T15527.stderr b/testsuite/tests/typecheck/should_fail/T15527.stderr
index beb494c3be2b..637972ae9a5a 100644
--- a/testsuite/tests/typecheck/should_fail/T15527.stderr
+++ b/testsuite/tests/typecheck/should_fail/T15527.stderr
@@ -1,4 +1,5 @@
 
 T15527.hs:5:6: error: [GHC-23482]
     Illegal visible type application: @Int
-    Suggested fix: Perhaps you intended to use TypeApplications
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeApplications’ extension
diff --git a/testsuite/tests/typecheck/should_fail/T15552a.stderr b/testsuite/tests/typecheck/should_fail/T15552a.stderr
index 053c7ff41274..71a520cc008c 100644
--- a/testsuite/tests/typecheck/should_fail/T15552a.stderr
+++ b/testsuite/tests/typecheck/should_fail/T15552a.stderr
@@ -5,7 +5,8 @@ T15552a.hs:26:9: error: [GHC-22979]
                                                            (FirstEntryOfVal v kvs)’
     • In the equations for closed type family ‘FirstEntryOfVal’
       In the type family declaration for ‘FirstEntryOfVal’
-    Suggested fix: Perhaps you intended to use UndecidableInstances
+    Suggested fix:
+      Perhaps you intended to use the ‘UndecidableInstances’ extension
 
 T15552a.hs:26:9: error: [GHC-22979]
     • Illegal nested use of type family ‘FirstEntryOfVal’
@@ -13,7 +14,8 @@ T15552a.hs:26:9: error: [GHC-22979]
                                                            (FirstEntryOfVal v kvs)’
     • In the equations for closed type family ‘FirstEntryOfVal’
       In the type family declaration for ‘FirstEntryOfVal’
-    Suggested fix: Perhaps you intended to use UndecidableInstances
+    Suggested fix:
+      Perhaps you intended to use the ‘UndecidableInstances’ extension
 
 T15552a.hs:26:9: error: [GHC-22979]
     • Illegal nested use of type family ‘FirstEntryOfVal’
@@ -21,4 +23,5 @@ T15552a.hs:26:9: error: [GHC-22979]
                                                            (FirstEntryOfVal v kvs)’
     • In the equations for closed type family ‘FirstEntryOfVal’
       In the type family declaration for ‘FirstEntryOfVal’
-    Suggested fix: Perhaps you intended to use UndecidableInstances
+    Suggested fix:
+      Perhaps you intended to use the ‘UndecidableInstances’ extension
diff --git a/testsuite/tests/typecheck/should_fail/T15883.stderr b/testsuite/tests/typecheck/should_fail/T15883.stderr
index b0c28a2eed3a..41a5a8be41d4 100644
--- a/testsuite/tests/typecheck/should_fail/T15883.stderr
+++ b/testsuite/tests/typecheck/should_fail/T15883.stderr
@@ -2,4 +2,5 @@
 T15883.hs:9:1: error: [GHC-55233]
     • Newtype has non-* return kind ‘TYPE rep’
     • In the newtype declaration for ‘Foo’
-    Suggested fix: Perhaps you intended to use UnliftedNewtypes
+    Suggested fix:
+      Perhaps you intended to use the ‘UnliftedNewtypes’ extension
diff --git a/testsuite/tests/typecheck/should_fail/T16059c.stderr b/testsuite/tests/typecheck/should_fail/T16059c.stderr
index 626f58318680..bcd19e928550 100644
--- a/testsuite/tests/typecheck/should_fail/T16059c.stderr
+++ b/testsuite/tests/typecheck/should_fail/T16059c.stderr
@@ -3,4 +3,5 @@ T16059c.hs:6:6: error: [GHC-91510]
     • Illegal polymorphic type: forall a1. a1
     • In the expansion of type synonym ‘Foo’
       In the type signature: f :: Foo -> a -> f
-    Suggested fix: Perhaps you intended to use RankNTypes
+    Suggested fix:
+      Perhaps you intended to use the ‘RankNTypes’ extension (implied by ‘ImpredicativeTypes’)
diff --git a/testsuite/tests/typecheck/should_fail/T16059d.stderr b/testsuite/tests/typecheck/should_fail/T16059d.stderr
index af4c881a9c40..6aa0800863e5 100644
--- a/testsuite/tests/typecheck/should_fail/T16059d.stderr
+++ b/testsuite/tests/typecheck/should_fail/T16059d.stderr
@@ -3,4 +3,5 @@ T16059d.hs:5:1: error: [GHC-19590]
     • Illegal unboxed tuple type as function argument: (# #)
     • In the expansion of type synonym ‘Bar’
       In the type synonym declaration for ‘Bar'’
-    Suggested fix: Perhaps you intended to use UnboxedTuples
+    Suggested fix:
+      Perhaps you intended to use the ‘UnboxedTuples’ extension
diff --git a/testsuite/tests/typecheck/should_fail/T16059e.stderr b/testsuite/tests/typecheck/should_fail/T16059e.stderr
index e98712f8db18..f11ffba750f0 100644
--- a/testsuite/tests/typecheck/should_fail/T16059e.stderr
+++ b/testsuite/tests/typecheck/should_fail/T16059e.stderr
@@ -4,4 +4,5 @@ T16059e.hs:15:6: error: [GHC-91510]
     • In the expansion of type synonym ‘Foo’
       In the expansion of type synonym ‘Const’
       In the type signature: g :: Const Foo Foo -> Int
-    Suggested fix: Perhaps you intended to use RankNTypes
+    Suggested fix:
+      Perhaps you intended to use the ‘RankNTypes’ extension (implied by ‘ImpredicativeTypes’)
diff --git a/testsuite/tests/typecheck/should_fail/T16512b.stderr b/testsuite/tests/typecheck/should_fail/T16512b.stderr
index 2335aa66fdec..08ad32ee545c 100644
--- a/testsuite/tests/typecheck/should_fail/T16512b.stderr
+++ b/testsuite/tests/typecheck/should_fail/T16512b.stderr
@@ -6,4 +6,5 @@ T16512b.hs:6:3: error: [GHC-05175]
         G [a] = [G a] -- Defined at T16512b.hs:6:3
     • In the equations for closed type family ‘G’
       In the type family declaration for ‘G’
-    Suggested fix: Perhaps you intended to use UndecidableInstances
+    Suggested fix:
+      Perhaps you intended to use the ‘UndecidableInstances’ extension
diff --git a/testsuite/tests/typecheck/should_fail/T16829a.stderr b/testsuite/tests/typecheck/should_fail/T16829a.stderr
index 863434410876..14e2658156e0 100644
--- a/testsuite/tests/typecheck/should_fail/T16829a.stderr
+++ b/testsuite/tests/typecheck/should_fail/T16829a.stderr
@@ -2,4 +2,5 @@
 T16829a.hs:9:1: error: [GHC-55233]
     • Newtype has non-* return kind ‘TYPE IntRep’
     • In the newtype declaration for ‘T’
-    Suggested fix: Perhaps you intended to use UnliftedNewtypes
+    Suggested fix:
+      Perhaps you intended to use the ‘UnliftedNewtypes’ extension
diff --git a/testsuite/tests/typecheck/should_fail/T16829b.stderr b/testsuite/tests/typecheck/should_fail/T16829b.stderr
index 711a2c795134..649de3c6e885 100644
--- a/testsuite/tests/typecheck/should_fail/T16829b.stderr
+++ b/testsuite/tests/typecheck/should_fail/T16829b.stderr
@@ -2,4 +2,5 @@
 T16829b.hs:10:1: error: [GHC-55233]
     • Newtype instance has non-* return kind ‘TYPE IntRep’
     • In the newtype instance declaration for ‘T’
-    Suggested fix: Perhaps you intended to use UnliftedNewtypes
+    Suggested fix:
+      Perhaps you intended to use the ‘UnliftedNewtypes’ extension
diff --git a/testsuite/tests/typecheck/should_fail/T17213.stderr b/testsuite/tests/typecheck/should_fail/T17213.stderr
index ec2078d7badc..48cc7f286ea2 100644
--- a/testsuite/tests/typecheck/should_fail/T17213.stderr
+++ b/testsuite/tests/typecheck/should_fail/T17213.stderr
@@ -3,4 +3,5 @@ T17213.hs:6:1: error: [GHC-91510]
     • Illegal polymorphic type: forall a. a -> a
     • When checking the inferred type
         g :: (forall a. a -> a) -> Int
-    Suggested fix: Perhaps you intended to use RankNTypes
+    Suggested fix:
+      Perhaps you intended to use the ‘RankNTypes’ extension (implied by ‘ImpredicativeTypes’)
diff --git a/testsuite/tests/typecheck/should_fail/T17563.stderr b/testsuite/tests/typecheck/should_fail/T17563.stderr
index 7f6462b83993..a85dd65bfcc0 100644
--- a/testsuite/tests/typecheck/should_fail/T17563.stderr
+++ b/testsuite/tests/typecheck/should_fail/T17563.stderr
@@ -3,4 +3,5 @@ T17563.hs:8:9: error: [GHC-80003]
     • Non type-variable argument in the constraint: Num (T a x)
     • In the quantified constraint ‘forall x. Num (T a x)’
       In the type signature: blah :: (forall x. Num (T a x)) => T a b
-    Suggested fix: Perhaps you intended to use FlexibleContexts
+    Suggested fix:
+      Perhaps you intended to use the ‘FlexibleContexts’ extension
diff --git a/testsuite/tests/typecheck/should_fail/T18939_Fail.stderr b/testsuite/tests/typecheck/should_fail/T18939_Fail.stderr
index d49c7dcc9d9f..a54b85e0c4de 100644
--- a/testsuite/tests/typecheck/should_fail/T18939_Fail.stderr
+++ b/testsuite/tests/typecheck/should_fail/T18939_Fail.stderr
@@ -2,4 +2,5 @@
 T18939_Fail.hs:6:1: error: [GHC-91510]
     • Illegal polymorphic type: forall a -> a
     • In the data type declaration for ‘F’
-    Suggested fix: Perhaps you intended to use RankNTypes
+    Suggested fix:
+      Perhaps you intended to use the ‘RankNTypes’ extension (implied by ‘ImpredicativeTypes’)
diff --git a/testsuite/tests/typecheck/should_fail/T19109.stderr b/testsuite/tests/typecheck/should_fail/T19109.stderr
index 709c3f4637fa..e1bd8b2fdff3 100644
--- a/testsuite/tests/typecheck/should_fail/T19109.stderr
+++ b/testsuite/tests/typecheck/should_fail/T19109.stderr
@@ -1,4 +1,5 @@
 
 T19109.hs:6:4: error: [GHC-17916]
     Illegal visible type application in a pattern: @Int
-    Suggested fix: Perhaps you intended to use TypeAbstractions
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeAbstractions’ extension
diff --git a/testsuite/tests/typecheck/should_fail/T19187.stderr b/testsuite/tests/typecheck/should_fail/T19187.stderr
index 7740d9ebe0af..6ea26c54e774 100644
--- a/testsuite/tests/typecheck/should_fail/T19187.stderr
+++ b/testsuite/tests/typecheck/should_fail/T19187.stderr
@@ -2,4 +2,5 @@
 T19187.hs:8:10: error: [GHC-80003]
     • Non type-variable argument in the constraint: Eq Int
     • In the instance declaration for ‘Eq T’
-    Suggested fix: Perhaps you intended to use FlexibleContexts
+    Suggested fix:
+      Perhaps you intended to use the ‘FlexibleContexts’ extension
diff --git a/testsuite/tests/typecheck/should_fail/T19187a.stderr b/testsuite/tests/typecheck/should_fail/T19187a.stderr
index a0b77e08175e..6999fe1cbdfc 100644
--- a/testsuite/tests/typecheck/should_fail/T19187a.stderr
+++ b/testsuite/tests/typecheck/should_fail/T19187a.stderr
@@ -3,4 +3,5 @@ T19187a.hs:7:10: error: [GHC-22979]
     • The constraint ‘Eq Int’
         is no smaller than the instance head ‘Eq T’
     • In the instance declaration for ‘Eq T’
-    Suggested fix: Perhaps you intended to use UndecidableInstances
+    Suggested fix:
+      Perhaps you intended to use the ‘UndecidableInstances’ extension
diff --git a/testsuite/tests/typecheck/should_fail/T20873c.stderr b/testsuite/tests/typecheck/should_fail/T20873c.stderr
index 58b98d32ef16..0e48f945a841 100644
--- a/testsuite/tests/typecheck/should_fail/T20873c.stderr
+++ b/testsuite/tests/typecheck/should_fail/T20873c.stderr
@@ -2,4 +2,5 @@
 T20873c.hs:10:1: error: [GHC-49378]
     • Illegal kind signature ‘Foo :: U Int’
     • In the data declaration for ‘Foo’
-    Suggested fix: Perhaps you intended to use KindSignatures
+    Suggested fix:
+      Perhaps you intended to use the ‘KindSignatures’ extension (implied by ‘TypeFamilies’ and ‘PolyKinds’)
diff --git a/testsuite/tests/typecheck/should_fail/T20873d.stderr b/testsuite/tests/typecheck/should_fail/T20873d.stderr
index 8511e4607127..130246ceb736 100644
--- a/testsuite/tests/typecheck/should_fail/T20873d.stderr
+++ b/testsuite/tests/typecheck/should_fail/T20873d.stderr
@@ -2,4 +2,5 @@
 T20873d.hs:10:1: error: [GHC-49378]
     • Illegal kind signature ‘Foo :: U Type’
     • In the data declaration for ‘Foo’
-    Suggested fix: Perhaps you intended to use KindSignatures
+    Suggested fix:
+      Perhaps you intended to use the ‘KindSignatures’ extension (implied by ‘TypeFamilies’ and ‘PolyKinds’)
diff --git a/testsuite/tests/typecheck/should_fail/T22560_fail_ext.stderr b/testsuite/tests/typecheck/should_fail/T22560_fail_ext.stderr
index 890c356d4e6f..6afbe424744c 100644
--- a/testsuite/tests/typecheck/should_fail/T22560_fail_ext.stderr
+++ b/testsuite/tests/typecheck/should_fail/T22560_fail_ext.stderr
@@ -1,8 +1,10 @@
 
 T22560_fail_ext.hs:7:1: error: [GHC-58589]
     Illegal invisible type variable binder: @(j :: Type)
-    Suggested fix: Perhaps you intended to use TypeAbstractions
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeAbstractions’ extension
 
 T22560_fail_ext.hs:7:1: error: [GHC-58589]
     Illegal invisible type variable binder: @k
-    Suggested fix: Perhaps you intended to use TypeAbstractions
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeAbstractions’ extension
diff --git a/testsuite/tests/typecheck/should_fail/T23776.stderr b/testsuite/tests/typecheck/should_fail/T23776.stderr
index cd734bc880a0..adceb3159da8 100644
--- a/testsuite/tests/typecheck/should_fail/T23776.stderr
+++ b/testsuite/tests/typecheck/should_fail/T23776.stderr
@@ -2,4 +2,5 @@
 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.14.
-    Suggested fix: Perhaps you intended to use TypeAbstractions
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeAbstractions’ extension
diff --git a/testsuite/tests/typecheck/should_fail/T2538.stderr b/testsuite/tests/typecheck/should_fail/T2538.stderr
index 0eb8a95d3341..278ea1f65f25 100644
--- a/testsuite/tests/typecheck/should_fail/T2538.stderr
+++ b/testsuite/tests/typecheck/should_fail/T2538.stderr
@@ -2,14 +2,17 @@
 T2538.hs:7:6: error: [GHC-91510]
     • Illegal qualified type: Eq a => a -> a
     • In the type signature: f :: (Eq a => a -> a) -> Int
-    Suggested fix: Perhaps you intended to use RankNTypes
+    Suggested fix:
+      Perhaps you intended to use the ‘RankNTypes’ extension (implied by ‘ImpredicativeTypes’)
 
 T2538.hs:10:6: error: [GHC-91510]
     • Illegal qualified type: Eq a => a -> a
     • In the type signature: g :: [Eq a => a -> a] -> Int
-    Suggested fix: Perhaps you intended to use ImpredicativeTypes
+    Suggested fix:
+      Perhaps you intended to use the ‘ImpredicativeTypes’ extension
 
 T2538.hs:13:6: error: [GHC-91510]
     • Illegal qualified type: Eq a => a -> a
     • In the type signature: h :: Ix (Eq a => a -> a) => Int
-    Suggested fix: Perhaps you intended to use ImpredicativeTypes
+    Suggested fix:
+      Perhaps you intended to use the ‘ImpredicativeTypes’ extension
diff --git a/testsuite/tests/typecheck/should_fail/T3155.stderr b/testsuite/tests/typecheck/should_fail/T3155.stderr
index 7c2ad8ce6f26..5cc759d051bc 100644
--- a/testsuite/tests/typecheck/should_fail/T3155.stderr
+++ b/testsuite/tests/typecheck/should_fail/T3155.stderr
@@ -2,5 +2,7 @@
 T3155.hs:14:9: error: [GHC-25955]
     Illegal symbol ‘forall’ in type
     Suggested fix:
-      Perhaps you intended to use RankNTypes
-      or a similar language extension to enable explicit-forall syntax: forall <tvs>. <type>
+      Use the ‘ExplicitForAll’ extension (implied by ‘RankNTypes’,
+                                                     ‘QuantifiedConstraints’, ‘ScopedTypeVariables’,
+                                                     ‘LiberalTypeSynonyms’ and ‘ExistentialQuantification’)
+      to enable syntax: forall <tvs>. <type>
diff --git a/testsuite/tests/typecheck/should_fail/T5957.stderr b/testsuite/tests/typecheck/should_fail/T5957.stderr
index c9da7f92974f..9d48afe76d0e 100644
--- a/testsuite/tests/typecheck/should_fail/T5957.stderr
+++ b/testsuite/tests/typecheck/should_fail/T5957.stderr
@@ -2,4 +2,5 @@
 T5957.hs:4:9: error: [GHC-91510]
     • Illegal qualified type: Show a => a -> String
     • In the type signature: flex :: Int -> Show a => a -> String
-    Suggested fix: Perhaps you intended to use RankNTypes
+    Suggested fix:
+      Perhaps you intended to use the ‘RankNTypes’ extension (implied by ‘ImpredicativeTypes’)
diff --git a/testsuite/tests/typecheck/should_fail/T6022.stderr b/testsuite/tests/typecheck/should_fail/T6022.stderr
index 70e4b708de7d..8047dcdc9dcb 100644
--- a/testsuite/tests/typecheck/should_fail/T6022.stderr
+++ b/testsuite/tests/typecheck/should_fail/T6022.stderr
@@ -3,4 +3,5 @@ T6022.hs:4:1: error: [GHC-80003]
     • Non type-variable argument in the constraint: Eq ([a] -> a)
     • When checking the inferred type
         f :: forall {a}. Eq ([a] -> a) => ([a] -> a) -> Bool
-    Suggested fix: Perhaps you intended to use FlexibleContexts
+    Suggested fix:
+      Perhaps you intended to use the ‘FlexibleContexts’ extension
diff --git a/testsuite/tests/typecheck/should_fail/T7019.stderr b/testsuite/tests/typecheck/should_fail/T7019.stderr
index 7234e39985fc..f106aa9345c5 100644
--- a/testsuite/tests/typecheck/should_fail/T7019.stderr
+++ b/testsuite/tests/typecheck/should_fail/T7019.stderr
@@ -3,4 +3,5 @@ T7019.hs:11:1: error: [GHC-91510]
     • Illegal polymorphic type: forall a. c (Free c a)
       A constraint must be a monotype
     • In the type synonym declaration for ‘C’
-    Suggested fix: Perhaps you intended to use QuantifiedConstraints
+    Suggested fix:
+      Perhaps you intended to use the ‘QuantifiedConstraints’ extension
diff --git a/testsuite/tests/typecheck/should_fail/T7019a.stderr b/testsuite/tests/typecheck/should_fail/T7019a.stderr
index 2f503ed044dd..136201afcc65 100644
--- a/testsuite/tests/typecheck/should_fail/T7019a.stderr
+++ b/testsuite/tests/typecheck/should_fail/T7019a.stderr
@@ -5,4 +5,5 @@ T7019a.hs:11:1: error: [GHC-91510]
     • In the context: forall b. Context (Associated a b)
       While checking the super-classes of class ‘Class’
       In the class declaration for ‘Class’
-    Suggested fix: Perhaps you intended to use QuantifiedConstraints
+    Suggested fix:
+      Perhaps you intended to use the ‘QuantifiedConstraints’ extension
diff --git a/testsuite/tests/typecheck/should_fail/T7809.stderr b/testsuite/tests/typecheck/should_fail/T7809.stderr
index 8cb3506dc0bc..b61360c5a979 100644
--- a/testsuite/tests/typecheck/should_fail/T7809.stderr
+++ b/testsuite/tests/typecheck/should_fail/T7809.stderr
@@ -3,4 +3,5 @@ T7809.hs:8:8: error: [GHC-91510]
     • Illegal polymorphic type: forall a. a -> a
     • In the expansion of type synonym ‘PolyId’
       In the type signature: foo :: F PolyId
-    Suggested fix: Perhaps you intended to use ImpredicativeTypes
+    Suggested fix:
+      Perhaps you intended to use the ‘ImpredicativeTypes’ extension
diff --git a/testsuite/tests/typecheck/should_fail/T8883.stderr b/testsuite/tests/typecheck/should_fail/T8883.stderr
index b2c544342a1e..e31ddc427515 100644
--- a/testsuite/tests/typecheck/should_fail/T8883.stderr
+++ b/testsuite/tests/typecheck/should_fail/T8883.stderr
@@ -5,4 +5,5 @@ T8883.hs:21:1: error: [GHC-80003]
         fold :: forall {a} {b}.
                 (Functor (PF a), Regular a) =>
                 (PF a b -> b) -> a -> b
-    Suggested fix: Perhaps you intended to use FlexibleContexts
+    Suggested fix:
+      Perhaps you intended to use the ‘FlexibleContexts’ extension
diff --git a/testsuite/tests/typecheck/should_fail/T9196.stderr b/testsuite/tests/typecheck/should_fail/T9196.stderr
index dab40b1c74e5..d008378e9593 100644
--- a/testsuite/tests/typecheck/should_fail/T9196.stderr
+++ b/testsuite/tests/typecheck/should_fail/T9196.stderr
@@ -3,10 +3,12 @@ T9196.hs:4:6: error: [GHC-91510]
     • Illegal polymorphic type: forall a1. Eq a1
       A constraint must be a monotype
     • In the type signature: f :: (forall a. Eq a) => a -> a
-    Suggested fix: Perhaps you intended to use QuantifiedConstraints
+    Suggested fix:
+      Perhaps you intended to use the ‘QuantifiedConstraints’ extension
 
 T9196.hs:7:6: error: [GHC-91510]
     • Illegal qualified type: Eq a => Ord a
       A constraint must be a monotype
     • In the type signature: g :: (Eq a => Ord a) => a -> a
-    Suggested fix: Perhaps you intended to use QuantifiedConstraints
+    Suggested fix:
+      Perhaps you intended to use the ‘QuantifiedConstraints’ extension
diff --git a/testsuite/tests/typecheck/should_fail/T9415.stderr b/testsuite/tests/typecheck/should_fail/T9415.stderr
index 0606c5a5a042..d9cbfd904251 100644
--- a/testsuite/tests/typecheck/should_fail/T9415.stderr
+++ b/testsuite/tests/typecheck/should_fail/T9415.stderr
@@ -4,11 +4,13 @@ T9415.hs:3:1: error: [GHC-29210]
         one of whose superclasses is ‘D’
         one of whose superclasses is ‘C’
     • In the class declaration for ‘C’
-    Suggested fix: Perhaps you intended to use UndecidableSuperClasses
+    Suggested fix:
+      Perhaps you intended to use the ‘UndecidableSuperClasses’ extension
 
 T9415.hs:5:1: error: [GHC-29210]
     • Superclass cycle for ‘D’
         one of whose superclasses is ‘C’
         one of whose superclasses is ‘D’
     • In the class declaration for ‘D’
-    Suggested fix: Perhaps you intended to use UndecidableSuperClasses
+    Suggested fix:
+      Perhaps you intended to use the ‘UndecidableSuperClasses’ extension
diff --git a/testsuite/tests/typecheck/should_fail/T9739.stderr b/testsuite/tests/typecheck/should_fail/T9739.stderr
index ae91c4b00f7f..73b4d9dca8d4 100644
--- a/testsuite/tests/typecheck/should_fail/T9739.stderr
+++ b/testsuite/tests/typecheck/should_fail/T9739.stderr
@@ -4,11 +4,13 @@ T9739.hs:4:1: error: [GHC-29210]
         one of whose superclasses is ‘Class3’
         one of whose superclasses is ‘Class1’
     • In the class declaration for ‘Class1’
-    Suggested fix: Perhaps you intended to use UndecidableSuperClasses
+    Suggested fix:
+      Perhaps you intended to use the ‘UndecidableSuperClasses’ extension
 
 T9739.hs:9:1: error: [GHC-29210]
     • Superclass cycle for ‘Class3’
         one of whose superclasses is ‘Class1’
         one of whose superclasses is ‘Class3’
     • In the class declaration for ‘Class3’
-    Suggested fix: Perhaps you intended to use UndecidableSuperClasses
+    Suggested fix:
+      Perhaps you intended to use the ‘UndecidableSuperClasses’ extension
diff --git a/testsuite/tests/typecheck/should_fail/TcNoNullaryTC.stderr b/testsuite/tests/typecheck/should_fail/TcNoNullaryTC.stderr
index 700db442714d..76beb7f62d98 100644
--- a/testsuite/tests/typecheck/should_fail/TcNoNullaryTC.stderr
+++ b/testsuite/tests/typecheck/should_fail/TcNoNullaryTC.stderr
@@ -2,4 +2,5 @@
 TcNoNullaryTC.hs:4:1: error: [GHC-28349]
     • No parameters for class ‘A’
     • In the class declaration for ‘A’
-    Suggested fix: Perhaps you intended to use MultiParamTypeClasses
+    Suggested fix:
+      Perhaps you intended to use the ‘MultiParamTypeClasses’ extension (implied by ‘FunctionalDependencies’)
diff --git a/testsuite/tests/typecheck/should_fail/TyfamsDisabled.stderr b/testsuite/tests/typecheck/should_fail/TyfamsDisabled.stderr
index e9d756f9a79a..2e44c6671731 100644
--- a/testsuite/tests/typecheck/should_fail/TyfamsDisabled.stderr
+++ b/testsuite/tests/typecheck/should_fail/TyfamsDisabled.stderr
@@ -1,4 +1,6 @@
-TyfamsDisabled.hs:3:1: [GHC-39191]
-     Illegal family declaration for ‘A’
-     In the type family declaration for ‘A’
-    Suggested fix: Perhaps you intended to use TypeFamilies
+
+TyfamsDisabled.hs:3:1: error: [GHC-39191]
+    • Illegal family declaration for ‘A’
+    • In the type family declaration for ‘A’
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeFamilies’ extension (implied by ‘TypeFamilyDependencies’)
diff --git a/testsuite/tests/typecheck/should_fail/UnliftedNewtypesNotEnabled.stderr b/testsuite/tests/typecheck/should_fail/UnliftedNewtypesNotEnabled.stderr
index 27652f03fa4f..dcf6de06e6c5 100644
--- a/testsuite/tests/typecheck/should_fail/UnliftedNewtypesNotEnabled.stderr
+++ b/testsuite/tests/typecheck/should_fail/UnliftedNewtypesNotEnabled.stderr
@@ -2,4 +2,5 @@
 UnliftedNewtypesNotEnabled.hs:9:1: error: [GHC-55233]
     • Newtype has non-* return kind ‘TYPE GHC.Types.IntRep’
     • In the newtype declaration for ‘Baz’
-    Suggested fix: Perhaps you intended to use UnliftedNewtypes
+    Suggested fix:
+      Perhaps you intended to use the ‘UnliftedNewtypes’ extension
diff --git a/testsuite/tests/typecheck/should_fail/fd-loop.stderr b/testsuite/tests/typecheck/should_fail/fd-loop.stderr
index 758c249a8a79..3942be9d4b13 100644
--- a/testsuite/tests/typecheck/should_fail/fd-loop.stderr
+++ b/testsuite/tests/typecheck/should_fail/fd-loop.stderr
@@ -3,4 +3,5 @@ fd-loop.hs:12:10: error: [GHC-22979]
     • The constraint ‘C a b’
         is no smaller than the instance head ‘Eq (T a)’
     • In the instance declaration for ‘Eq (T a)’
-    Suggested fix: Perhaps you intended to use UndecidableInstances
+    Suggested fix:
+      Perhaps you intended to use the ‘UndecidableInstances’ extension
diff --git a/testsuite/tests/typecheck/should_fail/tcfail027.stderr b/testsuite/tests/typecheck/should_fail/tcfail027.stderr
index 2ce8d99dde1c..731f8ed36e11 100644
--- a/testsuite/tests/typecheck/should_fail/tcfail027.stderr
+++ b/testsuite/tests/typecheck/should_fail/tcfail027.stderr
@@ -4,11 +4,13 @@ tcfail027.hs:4:1: error: [GHC-29210]
         one of whose superclasses is ‘B’
         one of whose superclasses is ‘A’
     • In the class declaration for ‘A’
-    Suggested fix: Perhaps you intended to use UndecidableSuperClasses
+    Suggested fix:
+      Perhaps you intended to use the ‘UndecidableSuperClasses’ extension
 
 tcfail027.hs:7:1: error: [GHC-29210]
     • Superclass cycle for ‘B’
         one of whose superclasses is ‘A’
         one of whose superclasses is ‘B’
     • In the class declaration for ‘B’
-    Suggested fix: Perhaps you intended to use UndecidableSuperClasses
+    Suggested fix:
+      Perhaps you intended to use the ‘UndecidableSuperClasses’ extension
diff --git a/testsuite/tests/typecheck/should_fail/tcfail044.stderr b/testsuite/tests/typecheck/should_fail/tcfail044.stderr
index 8af979633503..2074b57544ad 100644
--- a/testsuite/tests/typecheck/should_fail/tcfail044.stderr
+++ b/testsuite/tests/typecheck/should_fail/tcfail044.stderr
@@ -5,7 +5,8 @@ tcfail044.hs:6:20: error: [GHC-48406]
         where a1 ... an are *distinct type variables*,
         and each type variable appears at most once in the instance head.
     • In the instance declaration for ‘Eq (a -> a)’
-    Suggested fix: Perhaps you intended to use FlexibleInstances
+    Suggested fix:
+      Perhaps you intended to use the ‘FlexibleInstances’ extension
 
 tcfail044.hs:9:21: error: [GHC-48406]
     • Illegal instance declaration for ‘Num (a -> a)’:
@@ -13,4 +14,5 @@ tcfail044.hs:9:21: error: [GHC-48406]
         where a1 ... an are *distinct type variables*,
         and each type variable appears at most once in the instance head.
     • In the instance declaration for ‘Num (a -> a)’
-    Suggested fix: Perhaps you intended to use FlexibleInstances
+    Suggested fix:
+      Perhaps you intended to use the ‘FlexibleInstances’ extension
diff --git a/testsuite/tests/typecheck/should_fail/tcfail047.stderr b/testsuite/tests/typecheck/should_fail/tcfail047.stderr
index 172abb3bd125..47fd75965a8b 100644
--- a/testsuite/tests/typecheck/should_fail/tcfail047.stderr
+++ b/testsuite/tests/typecheck/should_fail/tcfail047.stderr
@@ -5,4 +5,5 @@ tcfail047.hs:7:10: error: [GHC-48406]
         where a1 ... an are *distinct type variables*,
         and each type variable appears at most once in the instance head.
     • In the instance declaration for ‘A (a, (b, c))’
-    Suggested fix: Perhaps you intended to use FlexibleInstances
+    Suggested fix:
+      Perhaps you intended to use the ‘FlexibleInstances’ extension
diff --git a/testsuite/tests/typecheck/should_fail/tcfail079.stderr b/testsuite/tests/typecheck/should_fail/tcfail079.stderr
index b9e7a8390f08..6a7fb47225a8 100644
--- a/testsuite/tests/typecheck/should_fail/tcfail079.stderr
+++ b/testsuite/tests/typecheck/should_fail/tcfail079.stderr
@@ -2,4 +2,5 @@
 tcfail079.hs:9:1: error: [GHC-55233]
     • Newtype has non-* return kind ‘TYPE GHC.Types.IntRep’
     • In the newtype declaration for ‘Unboxed’
-    Suggested fix: Perhaps you intended to use UnliftedNewtypes
+    Suggested fix:
+      Perhaps you intended to use the ‘UnliftedNewtypes’ extension
diff --git a/testsuite/tests/typecheck/should_fail/tcfail094.stderr b/testsuite/tests/typecheck/should_fail/tcfail094.stderr
index 19285827272b..04a78511a683 100644
--- a/testsuite/tests/typecheck/should_fail/tcfail094.stderr
+++ b/testsuite/tests/typecheck/should_fail/tcfail094.stderr
@@ -1,4 +1,5 @@
 
-tcfail094.hs:7:14: [GHC-68567]
+tcfail094.hs:7:14: error: [GHC-68567]
     Illegal type: ‘1’
-    Suggested fix: Perhaps you intended to use DataKinds
+    Suggested fix:
+      Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’)
diff --git a/testsuite/tests/typecheck/should_fail/tcfail108.stderr b/testsuite/tests/typecheck/should_fail/tcfail108.stderr
index f358370dfd6d..309657bf234d 100644
--- a/testsuite/tests/typecheck/should_fail/tcfail108.stderr
+++ b/testsuite/tests/typecheck/should_fail/tcfail108.stderr
@@ -3,4 +3,5 @@ tcfail108.hs:7:10: error: [GHC-22979]
     • The constraint ‘Eq (f (Rec f))’
         is no smaller than the instance head ‘Eq (Rec f)’
     • In the instance declaration for ‘Eq (Rec f)’
-    Suggested fix: Perhaps you intended to use UndecidableInstances
+    Suggested fix:
+      Perhaps you intended to use the ‘UndecidableInstances’ extension
diff --git a/testsuite/tests/typecheck/should_fail/tcfail117.stderr b/testsuite/tests/typecheck/should_fail/tcfail117.stderr
index ce2e4c250e91..580a66909e05 100644
--- a/testsuite/tests/typecheck/should_fail/tcfail117.stderr
+++ b/testsuite/tests/typecheck/should_fail/tcfail117.stderr
@@ -5,7 +5,7 @@ tcfail117.hs:6:32: error: [GHC-30750]
         (an enumeration consists of one or more nullary, non-GADT constructors)
     • In the newtype declaration for ‘N1’
     Suggested fix:
-      Perhaps you intended to use GeneralizedNewtypeDeriving
+      Perhaps you intended to use the ‘GeneralizedNewtypeDeriving’ extension
       for GHC's newtype-deriving extension
 
 tcfail117.hs:7:32: error: [GHC-30750]
diff --git a/testsuite/tests/typecheck/should_fail/tcfail127.stderr b/testsuite/tests/typecheck/should_fail/tcfail127.stderr
index 4312175ce275..e44555c488eb 100644
--- a/testsuite/tests/typecheck/should_fail/tcfail127.stderr
+++ b/testsuite/tests/typecheck/should_fail/tcfail127.stderr
@@ -2,4 +2,5 @@
 tcfail127.hs:3:8: error: [GHC-91510]
     • Illegal qualified type: Num a => a -> a
     • In the type signature: foo :: IO (Num a => a -> a)
-    Suggested fix: Perhaps you intended to use ImpredicativeTypes
+    Suggested fix:
+      Perhaps you intended to use the ‘ImpredicativeTypes’ extension
diff --git a/testsuite/tests/typecheck/should_fail/tcfail139.stderr b/testsuite/tests/typecheck/should_fail/tcfail139.stderr
index 968525306612..9869369a009e 100644
--- a/testsuite/tests/typecheck/should_fail/tcfail139.stderr
+++ b/testsuite/tests/typecheck/should_fail/tcfail139.stderr
@@ -4,4 +4,5 @@ tcfail139.hs:7:10: error: [GHC-93557]
         All instance types must be of the form (T t1 ... tn)
         where T is not a synonym.
     • In the instance declaration for ‘Bounded Foo’
-    Suggested fix: Perhaps you intended to use TypeSynonymInstances
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeSynonymInstances’ extension (implied by ‘FlexibleInstances’)
diff --git a/testsuite/tests/typecheck/should_fail/tcfail150.stderr b/testsuite/tests/typecheck/should_fail/tcfail150.stderr
index b7729c04d7d0..e15d4ce76cf4 100644
--- a/testsuite/tests/typecheck/should_fail/tcfail150.stderr
+++ b/testsuite/tests/typecheck/should_fail/tcfail150.stderr
@@ -5,4 +5,5 @@ tcfail150.hs:7:3: error: [GHC-25079]
     • When checking the class method:
         op :: forall a. (Foo a, Eq a) => a -> a
       In the class declaration for ‘Foo’
-    Suggested fix: Perhaps you intended to use ConstrainedClassMethods
+    Suggested fix:
+      Perhaps you intended to use the ‘ConstrainedClassMethods’ extension (implied by ‘MultiParamTypeClasses’)
diff --git a/testsuite/tests/typecheck/should_fail/tcfail154.stderr b/testsuite/tests/typecheck/should_fail/tcfail154.stderr
index 9dea9d917031..eff2a4382501 100644
--- a/testsuite/tests/typecheck/should_fail/tcfail154.stderr
+++ b/testsuite/tests/typecheck/should_fail/tcfail154.stderr
@@ -3,4 +3,5 @@ tcfail154.hs:13:10: error: [GHC-22979]
     • The constraint ‘C a a’
         is no smaller than the instance head ‘Eq (T a)’
     • In the instance declaration for ‘Eq (T a)’
-    Suggested fix: Perhaps you intended to use UndecidableInstances
+    Suggested fix:
+      Perhaps you intended to use the ‘UndecidableInstances’ extension
diff --git a/testsuite/tests/typecheck/should_fail/tcfail157.stderr b/testsuite/tests/typecheck/should_fail/tcfail157.stderr
index ef1604a7a94f..249db358fcdf 100644
--- a/testsuite/tests/typecheck/should_fail/tcfail157.stderr
+++ b/testsuite/tests/typecheck/should_fail/tcfail157.stderr
@@ -4,4 +4,5 @@ tcfail157.hs:27:10: error: [GHC-22979]
         in the constraint ‘E m a b’
         than in the instance head ‘Foo m (a -> ())’
     • In the instance declaration for ‘Foo m (a -> ())’
-    Suggested fix: Perhaps you intended to use UndecidableInstances
+    Suggested fix:
+      Perhaps you intended to use the ‘UndecidableInstances’ extension
diff --git a/testsuite/tests/typecheck/should_fail/tcfail166.stderr b/testsuite/tests/typecheck/should_fail/tcfail166.stderr
index d00f3d259c69..ce7a24747757 100644
--- a/testsuite/tests/typecheck/should_fail/tcfail166.stderr
+++ b/testsuite/tests/typecheck/should_fail/tcfail166.stderr
@@ -2,5 +2,7 @@
 tcfail166.hs:6:13: error: [GHC-25955]
     Illegal symbol ‘forall’ in type
     Suggested fix:
-      Perhaps you intended to use RankNTypes
-      or a similar language extension to enable explicit-forall syntax: forall <tvs>. <type>
+      Use the ‘ExplicitForAll’ extension (implied by ‘RankNTypes’,
+                                                     ‘QuantifiedConstraints’, ‘ScopedTypeVariables’,
+                                                     ‘LiberalTypeSynonyms’ and ‘ExistentialQuantification’)
+      to enable syntax: forall <tvs>. <type>
diff --git a/testsuite/tests/typecheck/should_fail/tcfail173.stderr b/testsuite/tests/typecheck/should_fail/tcfail173.stderr
index 2b9189198616..c48bca295208 100644
--- a/testsuite/tests/typecheck/should_fail/tcfail173.stderr
+++ b/testsuite/tests/typecheck/should_fail/tcfail173.stderr
@@ -1,4 +1,5 @@
 
 tcfail173.hs:6:12: error: [GHC-50649]
     Illegal declaration of a type or class operator ‘<.>’
-    Suggested fix: Perhaps you intended to use TypeOperators
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeOperators’ extension
diff --git a/testsuite/tests/typecheck/should_fail/tcfail183.stderr b/testsuite/tests/typecheck/should_fail/tcfail183.stderr
index f2ea02e5c310..4816db938d2b 100644
--- a/testsuite/tests/typecheck/should_fail/tcfail183.stderr
+++ b/testsuite/tests/typecheck/should_fail/tcfail183.stderr
@@ -2,5 +2,7 @@
 tcfail183.hs:5:30: error: [GHC-25955]
     Illegal symbol ‘forall’ in type
     Suggested fix:
-      Perhaps you intended to use RankNTypes
-      or a similar language extension to enable explicit-forall syntax: forall <tvs>. <type>
+      Use the ‘ExplicitForAll’ extension (implied by ‘RankNTypes’,
+                                                     ‘QuantifiedConstraints’, ‘ScopedTypeVariables’,
+                                                     ‘LiberalTypeSynonyms’ and ‘ExistentialQuantification’)
+      to enable syntax: forall <tvs>. <type>
diff --git a/testsuite/tests/typecheck/should_fail/tcfail184.stderr b/testsuite/tests/typecheck/should_fail/tcfail184.stderr
index bd38317e2cc7..8a0a4effcbbd 100644
--- a/testsuite/tests/typecheck/should_fail/tcfail184.stderr
+++ b/testsuite/tests/typecheck/should_fail/tcfail184.stderr
@@ -3,4 +3,5 @@ tcfail184.hs:9:19: error: [GHC-91510]
     • Illegal polymorphic type: forall a. Ord a => [a] -> [a]
     • In the definition of data constructor ‘MkSwizzle’
       In the newtype declaration for ‘Swizzle’
-    Suggested fix: Perhaps you intended to use RankNTypes
+    Suggested fix:
+      Perhaps you intended to use the ‘RankNTypes’ extension (implied by ‘ImpredicativeTypes’)
diff --git a/testsuite/tests/typecheck/should_fail/tcfail196.stderr b/testsuite/tests/typecheck/should_fail/tcfail196.stderr
index 4f751a47a8e0..9c44ae0e2aa3 100644
--- a/testsuite/tests/typecheck/should_fail/tcfail196.stderr
+++ b/testsuite/tests/typecheck/should_fail/tcfail196.stderr
@@ -2,4 +2,5 @@
 tcfail196.hs:5:8: error: [GHC-91510]
     • Illegal polymorphic type: forall a. a
     • In the type signature: bar :: Num (forall a. a) => Int -> Int
-    Suggested fix: Perhaps you intended to use ImpredicativeTypes
+    Suggested fix:
+      Perhaps you intended to use the ‘ImpredicativeTypes’ extension
diff --git a/testsuite/tests/typecheck/should_fail/tcfail197.stderr b/testsuite/tests/typecheck/should_fail/tcfail197.stderr
index 180599526a02..95fc2f75dbb0 100644
--- a/testsuite/tests/typecheck/should_fail/tcfail197.stderr
+++ b/testsuite/tests/typecheck/should_fail/tcfail197.stderr
@@ -2,4 +2,5 @@
 tcfail197.hs:5:8: error: [GHC-91510]
     • Illegal polymorphic type: forall a. a
     • In the type signature: foo :: [forall a. a] -> Int
-    Suggested fix: Perhaps you intended to use ImpredicativeTypes
+    Suggested fix:
+      Perhaps you intended to use the ‘ImpredicativeTypes’ extension
diff --git a/testsuite/tests/typecheck/should_fail/tcfail209.stderr b/testsuite/tests/typecheck/should_fail/tcfail209.stderr
index 1cd9bef1260c..69e2c05feb40 100644
--- a/testsuite/tests/typecheck/should_fail/tcfail209.stderr
+++ b/testsuite/tests/typecheck/should_fail/tcfail209.stderr
@@ -2,4 +2,5 @@
 tcfail209.hs:4:1: error: [GHC-75844]
     • Illegal constraint synonym of kind: ‘* -> Constraint’
     • In the type synonym declaration for ‘Showish’
-    Suggested fix: Perhaps you intended to use ConstraintKinds
+    Suggested fix:
+      Perhaps you intended to use the ‘ConstraintKinds’ extension
diff --git a/testsuite/tests/typecheck/should_fail/tcfail209a.stderr b/testsuite/tests/typecheck/should_fail/tcfail209a.stderr
index 79376e1629d2..f6f46cf96ea0 100644
--- a/testsuite/tests/typecheck/should_fail/tcfail209a.stderr
+++ b/testsuite/tests/typecheck/should_fail/tcfail209a.stderr
@@ -2,4 +2,5 @@
 tcfail209a.hs:4:6: error: [GHC-77539]
     • Illegal tuple constraint: (Show a, Num a)
     • In the type signature: g :: ((Show a, Num a), Eq a) => a -> a
-    Suggested fix: Perhaps you intended to use ConstraintKinds
+    Suggested fix:
+      Perhaps you intended to use the ‘ConstraintKinds’ extension
diff --git a/testsuite/tests/typecheck/should_fail/tcfail213.stderr b/testsuite/tests/typecheck/should_fail/tcfail213.stderr
index 7d7e2d7da55c..67c6fbc76fb5 100644
--- a/testsuite/tests/typecheck/should_fail/tcfail213.stderr
+++ b/testsuite/tests/typecheck/should_fail/tcfail213.stderr
@@ -4,4 +4,5 @@ tcfail213.hs:8:1: error: [GHC-29210]
         one of whose superclass constraints is headed by a type family:
           ‘F a’
     • In the class declaration for ‘C’
-    Suggested fix: Perhaps you intended to use UndecidableSuperClasses
+    Suggested fix:
+      Perhaps you intended to use the ‘UndecidableSuperClasses’ extension
diff --git a/testsuite/tests/typecheck/should_fail/tcfail214.stderr b/testsuite/tests/typecheck/should_fail/tcfail214.stderr
index 72e2de329b85..d01e353ecf9b 100644
--- a/testsuite/tests/typecheck/should_fail/tcfail214.stderr
+++ b/testsuite/tests/typecheck/should_fail/tcfail214.stderr
@@ -2,4 +2,5 @@
 tcfail214.hs:9:10: error: [GHC-22979]
     • Illegal use of type family ‘F’ in the constraint ‘F a’
     • In the instance declaration for ‘C [a]’
-    Suggested fix: Perhaps you intended to use UndecidableInstances
+    Suggested fix:
+      Perhaps you intended to use the ‘UndecidableInstances’ extension
diff --git a/testsuite/tests/typecheck/should_fail/tcfail216.stderr b/testsuite/tests/typecheck/should_fail/tcfail216.stderr
index 4c9fbf57127a..00bd24d23c8e 100644
--- a/testsuite/tests/typecheck/should_fail/tcfail216.stderr
+++ b/testsuite/tests/typecheck/should_fail/tcfail216.stderr
@@ -4,4 +4,5 @@ tcfail216.hs:4:1: error: [GHC-29210]
         one of whose superclass constraints is headed by a type variable:
           ‘cls (A cls)’
     • In the class declaration for ‘A’
-    Suggested fix: Perhaps you intended to use UndecidableSuperClasses
+    Suggested fix:
+      Perhaps you intended to use the ‘UndecidableSuperClasses’ extension
diff --git a/testsuite/tests/typecheck/should_fail/tcfail217.stderr b/testsuite/tests/typecheck/should_fail/tcfail217.stderr
index 57afa3edab64..4d609384dbcd 100644
--- a/testsuite/tests/typecheck/should_fail/tcfail217.stderr
+++ b/testsuite/tests/typecheck/should_fail/tcfail217.stderr
@@ -3,4 +3,5 @@ tcfail217.hs:7:1: error: [GHC-29210]
     • Superclass cycle for ‘A’
         one of whose superclasses is ‘A’
     • In the class declaration for ‘A’
-    Suggested fix: Perhaps you intended to use UndecidableSuperClasses
+    Suggested fix:
+      Perhaps you intended to use the ‘UndecidableSuperClasses’ extension
diff --git a/testsuite/tests/vdq-rta/should_fail/T22326_fail_ext1.stderr b/testsuite/tests/vdq-rta/should_fail/T22326_fail_ext1.stderr
index fed2bb02f328..6404c6a85ad9 100644
--- a/testsuite/tests/vdq-rta/should_fail/T22326_fail_ext1.stderr
+++ b/testsuite/tests/vdq-rta/should_fail/T22326_fail_ext1.stderr
@@ -1,4 +1,5 @@
 
 T22326_fail_ext1.hs:12:16: error: [GHC-47007]
     Illegal keyword 'type'
-    Suggested fix: Perhaps you intended to use ExplicitNamespaces
+    Suggested fix:
+      Perhaps you intended to use the ‘ExplicitNamespaces’ extension (implied by ‘TypeFamilies’ and ‘TypeOperators’)
diff --git a/testsuite/tests/vdq-rta/should_fail/T22326_fail_ext2.stderr b/testsuite/tests/vdq-rta/should_fail/T22326_fail_ext2.stderr
index a3a199698143..2830eb12495e 100644
--- a/testsuite/tests/vdq-rta/should_fail/T22326_fail_ext2.stderr
+++ b/testsuite/tests/vdq-rta/should_fail/T22326_fail_ext2.stderr
@@ -3,4 +3,5 @@ T22326_fail_ext2.hs:8:6: error: [GHC-51580]
     • Illegal visible, dependent quantification in the type of a term:
         forall {k}. forall (x :: k) -> ()
     • In the type signature: f :: forall x -> ()
-    Suggested fix: Perhaps you intended to use RequiredTypeArguments
+    Suggested fix:
+      Perhaps you intended to use the ‘RequiredTypeArguments’ extension
diff --git a/testsuite/tests/warnings/should_compile/T18862a.stderr b/testsuite/tests/warnings/should_compile/T18862a.stderr
index 2a60962bcb6e..252c606b3df5 100644
--- a/testsuite/tests/warnings/should_compile/T18862a.stderr
+++ b/testsuite/tests/warnings/should_compile/T18862a.stderr
@@ -2,4 +2,5 @@
 T18862a.hs:5:9: warning: [GHC-58520] [-Wtype-equality-requires-operators (in -Wdefault)]
     The use of ‘~’ without TypeOperators
     will become an error in a future GHC release.
-    Suggested fix: Perhaps you intended to use TypeOperators
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeOperators’ extension
diff --git a/testsuite/tests/warnings/should_fail/T24396c.stderr b/testsuite/tests/warnings/should_fail/T24396c.stderr
index ee4f56bcc1d3..7c099ded0388 100644
--- a/testsuite/tests/warnings/should_fail/T24396c.stderr
+++ b/testsuite/tests/warnings/should_fail/T24396c.stderr
@@ -3,22 +3,26 @@ 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
+    Suggested fix:
+      Perhaps you intended to use the ‘ExplicitNamespaces’ extension (implied by ‘TypeFamilies’ and ‘TypeOperators’)
 
 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
+    Suggested fix:
+      Perhaps you intended to use the ‘ExplicitNamespaces’ extension (implied by ‘TypeFamilies’ and ‘TypeOperators’)
 
 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
+    Suggested fix:
+      Perhaps you intended to use the ‘ExplicitNamespaces’ extension (implied by ‘TypeFamilies’ and ‘TypeOperators’)
 
 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
+    Suggested fix:
+      Perhaps you intended to use the ‘ExplicitNamespaces’ extension (implied by ‘TypeFamilies’ and ‘TypeOperators’)
diff --git a/testsuite/tests/wcompat-warnings/WCompatWarningsOn.stderr b/testsuite/tests/wcompat-warnings/WCompatWarningsOn.stderr
index b9b5bbe23960..8d4b65a7b766 100644
--- a/testsuite/tests/wcompat-warnings/WCompatWarningsOn.stderr
+++ b/testsuite/tests/wcompat-warnings/WCompatWarningsOn.stderr
@@ -12,4 +12,5 @@ Template.hs:9:29: warning: [GHC-16382] [-Wimplicit-rhs-quantification (in -Wcomp
 Template.hs:12:6: warning: [GHC-69797] [-Wdeprecated-type-abstractions (in -Wcompat)]
     Type applications in constructor patterns will require
     the TypeAbstractions extension starting from GHC 9.14.
-    Suggested fix: Perhaps you intended to use TypeAbstractions
+    Suggested fix:
+      Perhaps you intended to use the ‘TypeAbstractions’ extension
-- 
GitLab