diff --git a/Cabal/src/Distribution/Simple/Haddock.hs b/Cabal/src/Distribution/Simple/Haddock.hs
index 8c6fd86a691b627789e083e92e1b2c851608ba4f..e8537e97eb3048d8d3e53fcd773718a21794ccf4 100644
--- a/Cabal/src/Distribution/Simple/Haddock.hs
+++ b/Cabal/src/Distribution/Simple/Haddock.hs
@@ -83,7 +83,6 @@ import Distribution.Types.ComponentLocalBuildInfo
 import Distribution.Types.ExposedModule
 import Distribution.Types.LocalBuildInfo
 import Distribution.Types.TargetInfo
-import Distribution.Utils.NubList
 import Distribution.Utils.Path hiding
   ( Dir
   )
@@ -92,8 +91,6 @@ import qualified Distribution.Utils.ShortText as ShortText
 import Distribution.Verbosity
 import Distribution.Version
 
-import Language.Haskell.Extension
-
 import Control.Monad
 import Data.Either (rights)
 import System.Directory (doesDirectoryExist, doesFileExist)
@@ -329,11 +326,6 @@ haddock_setupHooks
           [] -> allTargetsInBuildOrder' pkg_descr lbi
           _ -> targets
 
-      version' =
-        if flag haddockVersionCPP
-          then Just version
-          else Nothing
-
       mtmp
         | version >= mkVersion [2, 28, 0] = const Nothing
         | otherwise = Just
@@ -380,7 +372,6 @@ haddock_setupHooks
                     lbi'
                     clbi
                     htmlTemplate
-                    version'
                     exe
                 let exeArgs' = commonArgs `mappend` exeArgs
                 runHaddock
@@ -420,7 +411,6 @@ haddock_setupHooks
                   lbi'
                   clbi
                   htmlTemplate
-                  version'
                   lib
               let libArgs' = commonArgs `mappend` libArgs
               runHaddock verbosity mbWorkDir tmpFileOpts comp platform haddockProg True libArgs'
@@ -467,7 +457,6 @@ haddock_setupHooks
                         lbi'
                         clbi
                         htmlTemplate
-                        version'
                         flib
                 let libArgs' = commonArgs `mappend` flibArgs
                 runHaddock verbosity mbWorkDir tmpFileOpts comp platform haddockProg True libArgs'
@@ -613,17 +602,13 @@ mkHaddockArgs
   -> ComponentLocalBuildInfo
   -> Maybe PathTemplate
   -- ^ template for HTML location
-  -> Maybe Version
-  -- ^ 'Nothing' if the user requested not to define the __HADDOCK_VERSION__
-  -- macro
   -> [SymbolicPath Pkg File]
   -> BuildInfo
   -> IO HaddockArgs
-mkHaddockArgs verbosity mtmp lbi clbi htmlTemplate haddockVersion inFiles bi = do
+mkHaddockArgs verbosity mtmp lbi clbi htmlTemplate inFiles bi = do
   ifaceArgs <- getInterfaces verbosity lbi clbi htmlTemplate
   let vanillaOpts' =
         componentGhcOptions normal lbi bi clbi (buildDir lbi)
-          `mappend` getGhcCppOpts haddockVersion bi
       vanillaOpts =
         vanillaOpts'
           { -- Starting with Haddock 2.28, we no longer want to run Haddock's
@@ -635,7 +620,6 @@ mkHaddockArgs verbosity mtmp lbi clbi htmlTemplate haddockVersion inFiles bi = d
           , ghcOptHiDir = maybe (ghcOptHiDir vanillaOpts') (toFlag . coerceSymbolicPath) mtmp
           , ghcOptStubDir = maybe (ghcOptStubDir vanillaOpts') (toFlag . coerceSymbolicPath) mtmp
           }
-          `mappend` getGhcCppOpts haddockVersion bi
       sharedOpts =
         vanillaOpts
           { ghcOptDynLinkMode = toFlag GhcDynamicOnly
@@ -668,12 +652,9 @@ fromLibrary
   -> ComponentLocalBuildInfo
   -> Maybe PathTemplate
   -- ^ template for HTML location
-  -> Maybe Version
-  -- ^ 'Nothing' if the user requested not to define the __HADDOCK_VERSION__
-  -- macro
   -> Library
   -> IO HaddockArgs
-fromLibrary verbosity mtmp lbi clbi htmlTemplate haddockVersion lib = do
+fromLibrary verbosity mtmp lbi clbi htmlTemplate lib = do
   inFiles <- map snd `fmap` getLibSourceFiles verbosity lbi lib clbi
   args <-
     mkHaddockArgs
@@ -682,7 +663,6 @@ fromLibrary verbosity mtmp lbi clbi htmlTemplate haddockVersion lib = do
       lbi
       clbi
       htmlTemplate
-      haddockVersion
       inFiles
       (libBuildInfo lib)
   return
@@ -699,12 +679,9 @@ fromExecutable
   -> ComponentLocalBuildInfo
   -> Maybe PathTemplate
   -- ^ template for HTML location
-  -> Maybe Version
-  -- ^ 'Nothing' if the user requested not to define the __HADDOCK_VERSION__
-  -- macro
   -> Executable
   -> IO HaddockArgs
-fromExecutable verbosity mtmp lbi clbi htmlTemplate haddockVersion exe = do
+fromExecutable verbosity mtmp lbi clbi htmlTemplate exe = do
   inFiles <- map snd `fmap` getExeSourceFiles verbosity lbi exe clbi
   args <-
     mkHaddockArgs
@@ -713,7 +690,6 @@ fromExecutable verbosity mtmp lbi clbi htmlTemplate haddockVersion exe = do
       lbi
       clbi
       htmlTemplate
-      haddockVersion
       inFiles
       (buildInfo exe)
   return
@@ -731,12 +707,9 @@ fromForeignLib
   -> ComponentLocalBuildInfo
   -> Maybe PathTemplate
   -- ^ template for HTML location
-  -> Maybe Version
-  -- ^ 'Nothing' if the user requested not to define the __HADDOCK_VERSION__
-  -- macro
   -> ForeignLib
   -> IO HaddockArgs
-fromForeignLib verbosity mtmp lbi clbi htmlTemplate haddockVersion flib = do
+fromForeignLib verbosity mtmp lbi clbi htmlTemplate flib = do
   inFiles <- map snd `fmap` getFLibSourceFiles verbosity lbi flib clbi
   args <-
     mkHaddockArgs
@@ -745,7 +718,6 @@ fromForeignLib verbosity mtmp lbi clbi htmlTemplate haddockVersion flib = do
       lbi
       clbi
       htmlTemplate
-      haddockVersion
       inFiles
       (foreignLibBuildInfo flib)
   return
@@ -796,35 +768,6 @@ getReexports LibComponentLocalBuildInfo{componentExposedModules = mods} =
   mapMaybe exposedReexport mods
 getReexports _ = []
 
-getGhcCppOpts
-  :: Maybe Version
-  -- ^ 'Nothing' if the user requested not to define the __HADDOCK_VERSION__
-  -- macro
-  -> BuildInfo
-  -> GhcOptions
-getGhcCppOpts haddockVersion bi =
-  mempty
-    { ghcOptExtensions = toNubListR [EnableExtension CPP | needsCpp]
-    , ghcOptCppOptions = defines
-    }
-  where
-    needsCpp = EnableExtension CPP `elem` usedExtensions bi
-    defines =
-      [ "-D__HADDOCK_VERSION__=" ++ show vn
-      | Just vn <- [versionInt . versionNumbers <$> haddockVersion]
-      ]
-      where
-        -- For some list xs = [x, y, z ...], versionInt xs results in
-        -- x * 1000 + y * 10 + z. E.g.:
-        -- >>> versionInt [2, 29, 0]
-        -- 2290
-        -- >>> versionInt [3, 4]
-        -- 3040
-        -- >>> versionInt []
-        -- 0
-        versionInt :: [Int] -> Int
-        versionInt = foldr ((+) . uncurry (*)) 0 . zip [1000, 10, 1]
-
 getGhcLibDir
   :: Verbosity
   -> LocalBuildInfo
diff --git a/Cabal/src/Distribution/Simple/Setup/Haddock.hs b/Cabal/src/Distribution/Simple/Setup/Haddock.hs
index 5b1a6a0999e7ccfa115fb0bf32606f89b775d74a..402544ce5111754648a86b1260fd59dcc21c8d67 100644
--- a/Cabal/src/Distribution/Simple/Setup/Haddock.hs
+++ b/Cabal/src/Distribution/Simple/Setup/Haddock.hs
@@ -115,7 +115,6 @@ data HaddockFlags = HaddockFlags
   , haddockBaseUrl :: Flag String
   , haddockResourcesDir :: Flag String
   , haddockOutputDir :: Flag FilePath
-  , haddockVersionCPP :: Flag Bool
   }
   deriving (Show, Generic, Typeable)
 
@@ -171,7 +170,6 @@ defaultHaddockFlags =
     , haddockBaseUrl = NoFlag
     , haddockResourcesDir = NoFlag
     , haddockOutputDir = NoFlag
-    , haddockVersionCPP = Flag False
     }
 
 haddockCommand :: CommandUI HaddockFlags
@@ -380,13 +378,6 @@ haddockOptions showOrParseArgs =
         haddockOutputDir
         (\v flags -> flags{haddockOutputDir = v})
         (reqArgFlag "DIR")
-    , option
-        ""
-        ["version-cpp"]
-        "Define the __HADDOCK_VERSION__ macro when invoking GHC through Haddock. This will likely trigger recompilation during documentation generation."
-        haddockVersionCPP
-        (\v flags -> flags{haddockVersionCPP = v})
-        trueArg
     ]
 
 emptyHaddockFlags :: HaddockFlags
@@ -451,7 +442,6 @@ data HaddockProjectFlags = HaddockProjectFlags
   , -- haddockBaseUrl is not supported, a fixed value is provided
     haddockProjectResourcesDir :: Flag String
   , haddockProjectOutputDir :: Flag FilePath
-  , haddockProjectVersionCPP :: Flag Bool
   }
   deriving (Show, Generic, Typeable)
 
@@ -477,7 +467,6 @@ defaultHaddockProjectFlags =
     , haddockProjectResourcesDir = NoFlag
     , haddockProjectOutputDir = NoFlag
     , haddockProjectInterfaces = NoFlag
-    , haddockProjectVersionCPP = Flag False
     }
 
 haddockProjectCommand :: CommandUI HaddockProjectFlags
@@ -631,13 +620,6 @@ haddockProjectOptions _showOrParseArgs =
       haddockProjectOutputDir
       (\v flags -> flags{haddockProjectOutputDir = v})
       (reqArgFlag "DIR")
-  , option
-      ""
-      ["version-cpp"]
-      "Define the __HADDOCK_VERSION__ macro when invoking GHC through Haddock. This will likely trigger recompilation during documentation generation."
-      haddockProjectVersionCPP
-      (\v flags -> flags{haddockProjectVersionCPP = v})
-      trueArg
   ]
 
 emptyHaddockProjectFlags :: HaddockProjectFlags
diff --git a/cabal-install/src/Distribution/Client/CmdHaddockProject.hs b/cabal-install/src/Distribution/Client/CmdHaddockProject.hs
index c2f31c6300ac58d5f77da64641af9d658b94c36f..8c0c21a54272f8221f4041dce9bcdd19657ed592 100644
--- a/cabal-install/src/Distribution/Client/CmdHaddockProject.hs
+++ b/cabal-install/src/Distribution/Client/CmdHaddockProject.hs
@@ -150,7 +150,6 @@ haddockProjectAction flags _extraArgs globalFlags = do
           , haddockKeepTempFiles = haddockProjectKeepTempFiles flags
           , haddockResourcesDir = haddockProjectResourcesDir flags
           , haddockOutputDir = haddockProjectOutputDir flags
-          , haddockVersionCPP = haddockProjectVersionCPP flags
           }
       nixFlags =
         (commandDefaultFlags CmdHaddock.haddockCommand)
diff --git a/cabal-install/src/Distribution/Client/Config.hs b/cabal-install/src/Distribution/Client/Config.hs
index 454c765b911761b4fae4246211f5774027d34fc8..d9b91c959d023e6ac83710b4aa199a6ea878c2d5 100644
--- a/cabal-install/src/Distribution/Client/Config.hs
+++ b/cabal-install/src/Distribution/Client/Config.hs
@@ -632,7 +632,6 @@ instance Semigroup SavedConfig where
           , haddockBaseUrl = combine haddockBaseUrl
           , haddockResourcesDir = combine haddockResourcesDir
           , haddockOutputDir = combine haddockOutputDir
-          , haddockVersionCPP = combine haddockVersionCPP
           }
         where
           combine = combine' savedHaddockFlags
diff --git a/cabal-install/src/Distribution/Client/PackageHash.hs b/cabal-install/src/Distribution/Client/PackageHash.hs
index 5ced7e1823ad3509669a7f596263944753f361c9..2e7b9320e3dec4008384694274aaaaefa0710c4a 100644
--- a/cabal-install/src/Distribution/Client/PackageHash.hs
+++ b/cabal-install/src/Distribution/Client/PackageHash.hs
@@ -240,7 +240,6 @@ data PackageHashConfigInputs = PackageHashConfigInputs
   , pkgHashHaddockBaseUrl :: Maybe String
   , pkgHashHaddockResourcesDir :: Maybe String
   , pkgHashHaddockOutputDir :: Maybe FilePath
-  , pkgHashHaddockVersionCPP :: Bool
   --     TODO: [required eventually] pkgHashToolsVersions     ?
   --     TODO: [required eventually] pkgHashToolsExtraOptions ?
   }
@@ -350,7 +349,6 @@ renderPackageHashInputs
           , opt "haddock-base-url" Nothing (fromMaybe "") pkgHashHaddockBaseUrl
           , opt "haddock-resources-dir" Nothing (fromMaybe "") pkgHashHaddockResourcesDir
           , opt "haddock-output-dir" Nothing (fromMaybe "") pkgHashHaddockOutputDir
-          , opt "haddock-version-cpp" False prettyShow pkgHashHaddockVersionCPP
           ]
             ++ Map.foldrWithKey (\prog args acc -> opt (prog ++ "-options") [] unwords args : acc) [] pkgHashProgramArgs
     where
diff --git a/cabal-install/src/Distribution/Client/ProjectConfig/Legacy.hs b/cabal-install/src/Distribution/Client/ProjectConfig/Legacy.hs
index 50e7f0feb9a79e8113d330aed69632fa2288ca0c..ddb6f6152649f66a3f2b62d986a411708cda1c31 100644
--- a/cabal-install/src/Distribution/Client/ProjectConfig/Legacy.hs
+++ b/cabal-install/src/Distribution/Client/ProjectConfig/Legacy.hs
@@ -823,7 +823,6 @@ convertLegacyPerPackageFlags
         , haddockBaseUrl = packageConfigHaddockBaseUrl
         , haddockResourcesDir = packageConfigHaddockResourcesDir
         , haddockOutputDir = packageConfigHaddockOutputDir
-        , haddockVersionCPP = packageConfigHaddockVersionCPP
         } = haddockFlags
 
       TestFlags
@@ -1221,7 +1220,6 @@ convertToLegacyPerPackageConfig PackageConfig{..} =
         , haddockBaseUrl = packageConfigHaddockBaseUrl
         , haddockResourcesDir = packageConfigHaddockResourcesDir
         , haddockOutputDir = packageConfigHaddockOutputDir
-        , haddockVersionCPP = packageConfigHaddockVersionCPP
         }
 
     testFlags =
@@ -1623,7 +1621,6 @@ legacyPackageConfigFieldDescrs =
             , "base-url"
             , "resources-dir"
             , "output-dir"
-            , "version-cpp"
             ]
           . commandOptionsToFields
        )
diff --git a/cabal-install/src/Distribution/Client/ProjectConfig/Types.hs b/cabal-install/src/Distribution/Client/ProjectConfig/Types.hs
index 8fc4f2b21c35aac9ca77ba65050ee3c8d5ad7199..2a6f9589cbb5104453952d5d13de6e20c6463a24 100644
--- a/cabal-install/src/Distribution/Client/ProjectConfig/Types.hs
+++ b/cabal-install/src/Distribution/Client/ProjectConfig/Types.hs
@@ -307,7 +307,6 @@ data PackageConfig = PackageConfig
   , packageConfigHaddockBaseUrl :: Flag String -- TODO: [required eventually] use this
   , packageConfigHaddockResourcesDir :: Flag String -- TODO: [required eventually] use this
   , packageConfigHaddockOutputDir :: Flag FilePath -- TODO: [required eventually] use this
-  , packageConfigHaddockVersionCPP :: Flag Bool -- TODO: [required eventually] use this
   , packageConfigHaddockForHackage :: Flag HaddockTarget
   , -- Test options
     packageConfigTestHumanLog :: Flag PathTemplate
diff --git a/cabal-install/src/Distribution/Client/ProjectPlanning.hs b/cabal-install/src/Distribution/Client/ProjectPlanning.hs
index b5f5e94567d8e728c2809513d526ab014e2ed99e..43c835f7a0dcc58611748fb518f68bcf64b98805 100644
--- a/cabal-install/src/Distribution/Client/ProjectPlanning.hs
+++ b/cabal-install/src/Distribution/Client/ProjectPlanning.hs
@@ -2280,7 +2280,6 @@ elaborateInstallPlan
             elabHaddockBaseUrl = perPkgOptionMaybe pkgid packageConfigHaddockBaseUrl
             elabHaddockResourcesDir = perPkgOptionMaybe pkgid packageConfigHaddockResourcesDir
             elabHaddockOutputDir = perPkgOptionMaybe pkgid packageConfigHaddockOutputDir
-            elabHaddockVersionCPP = perPkgOptionFlag pkgid False packageConfigHaddockVersionCPP
 
             elabTestMachineLog = perPkgOptionMaybe pkgid packageConfigTestMachineLog
             elabTestHumanLog = perPkgOptionMaybe pkgid packageConfigTestHumanLog
@@ -4148,7 +4147,6 @@ setupHsHaddockFlags
       , haddockBaseUrl = maybe mempty toFlag elabHaddockBaseUrl
       , haddockResourcesDir = maybe mempty toFlag elabHaddockResourcesDir
       , haddockOutputDir = maybe mempty toFlag elabHaddockOutputDir
-      , haddockVersionCPP = maybe mempty toFlag elabHaddockVersionCPP
       }
 
 setupHsHaddockArgs :: ElaboratedConfiguredPackage -> [String]
@@ -4307,7 +4305,6 @@ packageHashConfigInputs shared@ElaboratedSharedConfig{..} pkg =
     , pkgHashHaddockBaseUrl = elabHaddockBaseUrl
     , pkgHashHaddockResourcesDir = elabHaddockResourcesDir
     , pkgHashHaddockOutputDir = elabHaddockOutputDir
-    , pkgHashHaddockVersionCPP = elabHaddockVersionCPP
     }
   where
     ElaboratedConfiguredPackage{..} = normaliseConfiguredPackage shared pkg
diff --git a/cabal-install/src/Distribution/Client/ProjectPlanning/Types.hs b/cabal-install/src/Distribution/Client/ProjectPlanning/Types.hs
index a5a3640457d2e9bb77407deca688afbefcb620dd..352e35d415017304d47b49e513bb8b2669ac590a 100644
--- a/cabal-install/src/Distribution/Client/ProjectPlanning/Types.hs
+++ b/cabal-install/src/Distribution/Client/ProjectPlanning/Types.hs
@@ -302,7 +302,6 @@ data ElaboratedConfiguredPackage = ElaboratedConfiguredPackage
   , elabHaddockBaseUrl :: Maybe String
   , elabHaddockResourcesDir :: Maybe String
   , elabHaddockOutputDir :: Maybe FilePath
-  , elabHaddockVersionCPP :: Bool
   , elabTestMachineLog :: Maybe PathTemplate
   , elabTestHumanLog :: Maybe PathTemplate
   , elabTestShowDetails :: Maybe TestShowDetails
diff --git a/cabal-install/src/Distribution/Client/Setup.hs b/cabal-install/src/Distribution/Client/Setup.hs
index d2992f5ad61365e116f70d29877f6d1cd049abe5..8fea76bae3b99bd9cd55a7dbad21940b5419de6a 100644
--- a/cabal-install/src/Distribution/Client/Setup.hs
+++ b/cabal-install/src/Distribution/Client/Setup.hs
@@ -2437,7 +2437,6 @@ haddockOptions showOrParseArgs =
              , "base-url"
              , "resources-dir"
              , "output-dir"
-             , "version-cpp"
              ]
   ]
 
diff --git a/cabal-install/tests/IntegrationTests2.hs b/cabal-install/tests/IntegrationTests2.hs
index 4021059fd649915b00e796905e4f5785efbe7592..b5b49053b6d67200c17522c6e8298fe770202038 100644
--- a/cabal-install/tests/IntegrationTests2.hs
+++ b/cabal-install/tests/IntegrationTests2.hs
@@ -2101,7 +2101,6 @@ testConfigOptionComments = do
   "  -- base-url" @=? findLineWith True "base-url" defaultConfigFile
   "  -- resources-dir" @=? findLineWith True "resources-dir" defaultConfigFile
   "  -- output-dir" @=? findLineWith True "output-dir" defaultConfigFile
-  "  -- version-cpp" @=? findLineWith True "version-cpp" defaultConfigFile
 
   "  -- interactive" @=? findLineWith True "interactive" defaultConfigFile
   "  -- quiet" @=? findLineWith True "quiet" defaultConfigFile
diff --git a/cabal-install/tests/UnitTests/Distribution/Client/ProjectConfig.hs b/cabal-install/tests/UnitTests/Distribution/Client/ProjectConfig.hs
index 47b4392e0d80b85078f12ced406b21f21840b7a6..946e0bf48fdba46321ed2182f5adb7caa7cd1548 100644
--- a/cabal-install/tests/UnitTests/Distribution/Client/ProjectConfig.hs
+++ b/cabal-install/tests/UnitTests/Distribution/Client/ProjectConfig.hs
@@ -726,7 +726,6 @@ instance Arbitrary PackageConfig where
       <*> arbitrary
       <*> arbitrary
       <*> arbitrary
-      <*> arbitrary
       <*> arbitraryFlag arbitraryShortToken
       <*> arbitrary
       <*> shortListOf 5 arbitrary
@@ -794,7 +793,6 @@ instance Arbitrary PackageConfig where
       , packageConfigHaddockBaseUrl = x55
       , packageConfigHaddockResourcesDir = x56
       , packageConfigHaddockOutputDir = x57
-      , packageConfigHaddockVersionCPP = x58
       , packageConfigTestHumanLog = x44
       , packageConfigTestMachineLog = x45
       , packageConfigTestShowDetails = x46
@@ -858,7 +856,6 @@ instance Arbitrary PackageConfig where
         , packageConfigHaddockBaseUrl = x55'
         , packageConfigHaddockResourcesDir = x56'
         , packageConfigHaddockOutputDir = x57'
-        , packageConfigHaddockVersionCPP = x58'
         , packageConfigTestHumanLog = x44'
         , packageConfigTestMachineLog = x45'
         , packageConfigTestShowDetails = x46'
@@ -881,7 +878,6 @@ instance Arbitrary PackageConfig where
               , (x44', x45', x46', x47', x48', x49', x51', x52', x54', x55')
               , x56'
               , x57'
-              , x58'
               )
           ) <-
           shrink
@@ -907,7 +903,6 @@ instance Arbitrary PackageConfig where
               , (x44, x45, x46, x47, x48, x49, x51, x52, x54, x55)
               , x56
               , x57
-              , x58
               )
             )
       ]
diff --git a/changelog.d/pr-9177 b/changelog.d/pr-9177
index b4f205a1f329e1d992958ee316899cb4050f1d23..6b1eb227350e94149769c44fb7e0ea68e0ee5eeb 100644
--- a/changelog.d/pr-9177
+++ b/changelog.d/pr-9177
@@ -13,10 +13,13 @@ description: {
 
 * We no longer define the `__HADDOCK_VERSION__` macro when invoking GHC through
   Haddock, since doing so essentially guarantees recompilation during
-  documentation generation. Since a very limited set of users may still rely on
-  this flag, we introduce the `--haddock-version-cpp` flag and
-  `haddock-version-cpp:` cabal.project field, which enables the definition of
-  the `__HADDOCK_VERSION__` macro when invoking GHC through Haddock.
+  documentation generation. We audited all uses of `__HADDOCK_VERSION__` in
+  hackage, ensuring there was a reasonable path forward to migrate away from
+  using `__HADDOCK_VERSION__` for each, while generating the same documentation
+  as it did before.
+  If you are a user of `__HADDOCK_VERSION__`, please take a look at the
+  discussion in https://github.com/haskell/cabal/pull/9177 and reach out to us
+  if your use case is not covered.
 
 * Rename the `--haddock-lib` flag to `--haddock-resources-dir` (and
   `haddock-lib:` cabal.project field to `haddock-resources-dir:`), and add this
diff --git a/doc/cabal-project-description-file.rst b/doc/cabal-project-description-file.rst
index 16fce6b4545e7dca8e227ac5f68cfa702d7676dd..c1f29bfc052e93a1be82c3121b8f9b8d74c2be9c 100644
--- a/doc/cabal-project-description-file.rst
+++ b/doc/cabal-project-description-file.rst
@@ -1619,16 +1619,6 @@ running ``setup haddock``.
     be automatically inferred. For Haddock built from source, however, this path
     should likely be explicitly set for every Haddock invocation.
 
-.. cfg-field:: haddock-no-version-cpp: boolean
-               --haddock-no-version-cpp
-    :synopsis: Do not define the ``__HADDOCK_VERSION__`` macro when invoking GHC
-               through Haddock.
-
-    Do not define the ``__HADDOCK_VERSION__`` macro when invoking GHC through
-    Haddock. This is critical for avoiding recompilation during documentation
-    generation, since such a macro definition will trigger recompilation if the
-    interface files on disk were compiled without it, as they likely were.
-
 .. cfg-field:: open: boolean
                --open
     :synopsis: Open generated documentation in-browser.
diff --git a/release-notes/WIP-Cabal-3.12.x.0.md b/release-notes/WIP-Cabal-3.12.x.0.md
new file mode 100644
index 0000000000000000000000000000000000000000..d1f2d17f04f12f70cc67b09fb60074f88a3e56f0
--- /dev/null
+++ b/release-notes/WIP-Cabal-3.12.x.0.md
@@ -0,0 +1,19 @@
+Cabal 3.12.1.0 changelog and release notes.
+
+This file will be edited and the changes incorprated into the official
+3.12.1.0 Cabal and Cabal-syntax release notes.
+
+---
+
+### Significant changes
+
+- Deprecation of the `__HADDOCK_VERSION__` macro:
+    In the next major version of Cabal, we no longer define the
+    `__HADDOCK_VERSION__` macro when invoking GHC through Haddock, since doing
+    so essentially guarantees recompilation during documentation generation. We
+    audited all uses of `__HADDOCK_VERSION__` in hackage, ensuring there was a
+    reasonable path forward to migrate away from using `__HADDOCK_VERSION__` for
+    each, while generating the same documentation as it did before.  If you are
+    a user of `__HADDOCK_VERSION__`, please take a look at the discussion in
+    https://github.com/haskell/cabal/pull/9177 and reach out to us if your use
+    case is not covered.
diff --git a/test/IntegrationTests2/config/default-config b/test/IntegrationTests2/config/default-config
index 1e4301a14eaf3ae550fd710ca31a135e8ddce2e4..e74a2c9776411decebb13ff291f3bd15403c86b2 100644
--- a/test/IntegrationTests2/config/default-config
+++ b/test/IntegrationTests2/config/default-config
@@ -143,7 +143,6 @@ haddock
   -- base-url:
   -- resources-dir:
   -- output-dir:
-  -- version-cpp: False
 
 init
   -- interactive: False
diff --git a/test/IntegrationTests2/nix-config/default-config b/test/IntegrationTests2/nix-config/default-config
index 1e4301a14eaf3ae550fd710ca31a135e8ddce2e4..e74a2c9776411decebb13ff291f3bd15403c86b2 100644
--- a/test/IntegrationTests2/nix-config/default-config
+++ b/test/IntegrationTests2/nix-config/default-config
@@ -143,7 +143,6 @@ haddock
   -- base-url:
   -- resources-dir:
   -- output-dir:
-  -- version-cpp: False
 
 init
   -- interactive: False
diff --git a/tests/IntegrationTests2/config/default-config b/tests/IntegrationTests2/config/default-config
index cd2dcc601e246b2fb3d5503102cd36c65c0bdc55..8d5b2ea1df658565ce9a2cb9cf8dd8594d739246 100644
--- a/tests/IntegrationTests2/config/default-config
+++ b/tests/IntegrationTests2/config/default-config
@@ -145,7 +145,6 @@ haddock
   -- base-url:
   -- resources-dir:
   -- output-dir:
-  -- version-cpp: False
 
 init
   -- interactive: False
diff --git a/tests/IntegrationTests2/nix-config/default-config b/tests/IntegrationTests2/nix-config/default-config
index 1e4301a14eaf3ae550fd710ca31a135e8ddce2e4..e74a2c9776411decebb13ff291f3bd15403c86b2 100644
--- a/tests/IntegrationTests2/nix-config/default-config
+++ b/tests/IntegrationTests2/nix-config/default-config
@@ -143,7 +143,6 @@ haddock
   -- base-url:
   -- resources-dir:
   -- output-dir:
-  -- version-cpp: False
 
 init
   -- interactive: False