diff --git a/Cabal/src/Distribution/Simple/Program.hs b/Cabal/src/Distribution/Simple/Program.hs
index f5a609f3b7e47961b9bb8fedce2ca4ee72f102d5..e81501d2c393ccf341445bc554e5407527e8bccd 100644
--- a/Cabal/src/Distribution/Simple/Program.hs
+++ b/Cabal/src/Distribution/Simple/Program.hs
@@ -1,3 +1,10 @@
+{- FUTUREWORK:
+ -
+ - Currently the logic in this module is not tested.
+ -
+ - Ideally, a set of unit tests that check whether certain
+ - flags trigger recompilation should be added.
+ - -}
 {-# LANGUAGE DataKinds #-}
 {-# LANGUAGE FlexibleContexts #-}
 {-# LANGUAGE RankNTypes #-}
diff --git a/Cabal/src/Distribution/Simple/Program/GHC.hs b/Cabal/src/Distribution/Simple/Program/GHC.hs
index 84d6b0ccfaa5eec9d1ad169bf13ccbe2183272aa..c42eb18e3b1140313626b74c79dd305680e0049e 100644
--- a/Cabal/src/Distribution/Simple/Program/GHC.hs
+++ b/Cabal/src/Distribution/Simple/Program/GHC.hs
@@ -1,6 +1,7 @@
 {-# LANGUAGE DataKinds #-}
 {-# LANGUAGE DeriveGeneric #-}
 {-# LANGUAGE FlexibleContexts #-}
+{-# LANGUAGE MultiWayIf #-}
 {-# LANGUAGE RankNTypes #-}
 {-# LANGUAGE RecordWildCards #-}
 {-# LANGUAGE ScopedTypeVariables #-}
@@ -227,8 +228,27 @@ normaliseGhcArgs (Just ghcVersion) PackageDescription{..} ghcArgs
                   , "keep-going" -- try harder, the build will still fail if it's erroneous
                   , "print-axiom-incomps" -- print more debug info for closed type families
                   ]
+              , from
+                  [9, 2]
+                  [ "family-application-cache"
+                  ]
+              , from
+                  [9, 6]
+                  [ "print-redundant-promotion-ticks"
+                  , "show-error-context"
+                  ]
+              , from
+                  [9, 8]
+                  [ "unoptimized-core-for-interpreter"
+                  ]
+              , from
+                  [9, 10]
+                  [ "diagnostics-as-json"
+                  , "print-error-index-links"
+                  , "break-points"
+                  ]
               ]
-          , flagIn . invertibleFlagSet "-d" $ ["ppr-case-as-let", "ppr-ticks"]
+          , flagIn $ invertibleFlagSet "-d" ["ppr-case-as-let", "ppr-ticks"]
           , isOptIntFlag
           , isIntFlag
           , if safeToFilterWarnings
@@ -289,6 +309,7 @@ normaliseGhcArgs (Just ghcVersion) PackageDescription{..} ghcArgs
         , from [8, 6] ["-dhex-word-literals"]
         , from [8, 8] ["-fshow-docs-of-hole-fits", "-fno-show-docs-of-hole-fits"]
         , from [9, 0] ["-dlinear-core-lint"]
+        , from [9, 10] ["-dipe-stats"]
         ]
 
     isOptIntFlag :: String -> Any
@@ -709,7 +730,10 @@ renderGhcOptions comp _platform@(Platform _arch os) opts
               | flagProfAuto implInfo -> ["-fprof-auto-exported"]
               | otherwise -> ["-auto"]
         , ["-split-sections" | flagBool ghcOptSplitSections]
-        , ["-split-objs" | flagBool ghcOptSplitObjs]
+        , case compilerCompatVersion GHC comp of
+            -- the -split-objs flag was removed in GHC 9.8
+            Just ver | ver >= mkVersion [9, 8] -> []
+            _ -> ["-split-objs" | flagBool ghcOptSplitObjs]
         , case flagToMaybe (ghcOptHPCDir opts) of
             Nothing -> []
             Just hpcdir -> ["-fhpc", "-hpcdir", u hpcdir]
@@ -799,8 +823,7 @@ renderGhcOptions comp _platform@(Platform _arch os) opts
           -- Packages
 
           concat
-            [ [ case () of
-                  _
+            [ [ if
                     | unitIdSupported comp -> "-this-unit-id"
                     | packageKeySupported comp -> "-this-package-key"
                     | otherwise -> "-package-name"
diff --git a/changelog.d/pr-10014 b/changelog.d/pr-10014
new file mode 100644
index 0000000000000000000000000000000000000000..541b4c72d18725507d4558464b44da2411be4e23
--- /dev/null
+++ b/changelog.d/pr-10014
@@ -0,0 +1,11 @@
+synopsis: Update ghc args normalization and ghc option rendering
+packages: Cabal
+issues: #9729
+prs: #10014
+
+description: {
+
+The flags -fdiagnostics-as-json, -fprint-error-index-lists, -fbreak-points, -dipe-stats, -ffamily-application-cache, -fprint-redundant-promotion-ticks, -fshow-error-context and -funoptimized-core-for-interpreter have been added to the flags that do not cause recompilation. 
+
+--{enable,disable}-split-objs is not shown on in the helper for GHC >= 9.8
+}