diff --git a/ghcide/src/Development/IDE/GHC/Compat.hs b/ghcide/src/Development/IDE/GHC/Compat.hs
index 98391f6364..0bc0204821 100644
--- a/ghcide/src/Development/IDE/GHC/Compat.hs
+++ b/ghcide/src/Development/IDE/GHC/Compat.hs
@@ -14,7 +14,6 @@ module Development.IDE.GHC.Compat(
     HieFile(..),
     NameCacheUpdater(..),
     hieExportNames,
-    mkHieFile,
     mkHieFile',
     enrichHie,
     writeHieFile,
@@ -159,7 +158,7 @@ import           Module                 (InstalledUnitId,
                                          toInstalledUnitId)
 import           TcType                 (pprSigmaType)
 #endif
-import           Compat.HieAst          (enrichHie, mkHieFile)
+import           Compat.HieAst          (enrichHie)
 import           Compat.HieBin
 import           Compat.HieTypes
 import           Compat.HieUtils
diff --git a/hie-compat/hie-compat.cabal b/hie-compat/hie-compat.cabal
index 6dd9375b74..0e06785319 100644
--- a/hie-compat/hie-compat.cabal
+++ b/hie-compat/hie-compat.cabal
@@ -30,6 +30,8 @@ library
     build-depends: ghc, ghc-boot
   if (impl(ghc >= 9.0) && impl(ghc < 9.1))
     ghc-options: -Wall -Wno-name-shadowing
+  else
+    ghc-options: -Wall -Wno-name-shadowing
 
   exposed-modules:
     Compat.HieAst
@@ -45,5 +47,8 @@ library
   if (impl(ghc > 8.9) && impl(ghc < 8.11))
     hs-source-dirs: src-ghc810 src-reexport
   if (impl(ghc >= 9.0) && impl(ghc < 9.1) || flag(ghc-lib))
-    hs-source-dirs: src-ghc901
+    hs-source-dirs: src-reexport-ghc9
+  if (impl(ghc >= 9.2) && impl(ghc < 9.3))
+    hs-source-dirs: src-reexport-ghc9
+
 
diff --git a/hie-compat/src-ghc810/Compat/HieAst.hs b/hie-compat/src-ghc810/Compat/HieAst.hs
index 3b713cbe12..3d2eba2feb 100644
--- a/hie-compat/src-ghc810/Compat/HieAst.hs
+++ b/hie-compat/src-ghc810/Compat/HieAst.hs
@@ -17,7 +17,7 @@ Main functions for .hie file generation
 {-# LANGUAGE AllowAmbiguousTypes #-}
 {-# LANGUAGE ViewPatterns #-}
 {-# LANGUAGE DeriveDataTypeable #-}
-module Compat.HieAst ( mkHieFile, enrichHie ) where
+module Compat.HieAst ( enrichHie ) where
 
 import GhcPrelude
 
@@ -32,7 +32,7 @@ import Desugar                    ( deSugarExpr )
 import FieldLabel
 import GHC.Hs
 import HscTypes
-import Module                     ( ModuleName, ml_hs_file )
+import Module                     ( ModuleName )
 import MonadUtils                 ( concatMapM, liftIO )
 import Name                       ( Name, nameSrcSpan )
 import NameEnv                    ( NameEnv, emptyNameEnv, extendNameEnv, lookupNameEnv )
@@ -41,15 +41,11 @@ import TcHsSyn                    ( hsLitType, hsPatType )
 import Type                       ( mkVisFunTys, Type )
 import TysWiredIn                 ( mkListTy, mkSumTy )
 import Var                        ( Id, Var, setVarName, varName, varType )
-import TcRnTypes
-import MkIface                    ( mkIfaceExports )
 import Panic
 
 import HieTypes
 import HieUtils
 
-import qualified Data.Array as A
-import qualified Data.ByteString as BS
 import qualified Data.Map as M
 import qualified Data.Set as S
 import Data.Data                  ( Data, Typeable )
@@ -223,31 +219,6 @@ modifyState = foldr go id
 
 type HieM = ReaderT HieState Hsc
 
--- | Construct an 'HieFile' from the outputs of the typechecker.
-mkHieFile :: ModSummary
-          -> TcGblEnv
-          -> RenamedSource
-          -> BS.ByteString -> Hsc HieFile
-mkHieFile ms ts rs src = do
-  let tc_binds = tcg_binds ts
-  (asts', arr) <- getCompressedAsts tc_binds rs
-  let Just src_file = ml_hs_file $ ms_location ms
-  return $ HieFile
-      { hie_hs_file = src_file
-      , hie_module = ms_mod ms
-      , hie_types = arr
-      , hie_asts = asts'
-      -- mkIfaceExports sorts the AvailInfos for stability
-      , hie_exports = mkIfaceExports (tcg_exports ts)
-      , hie_hs_src = src
-      }
-
-getCompressedAsts :: TypecheckedSource -> RenamedSource
-  -> Hsc (HieASTs TypeIndex, A.Array TypeIndex HieTypeFlat)
-getCompressedAsts ts rs = do
-  asts <- enrichHie ts rs
-  return $ compressTypes asts
-
 enrichHie :: TypecheckedSource -> RenamedSource -> Hsc (HieASTs Type)
 enrichHie ts (hsGrp, imports, exports, _) = flip runReaderT initState $ do
     tasts <- toHie $ fmap (BC RegularBind ModuleScope) ts
diff --git a/hie-compat/src-ghc86/Compat/HieAst.hs b/hie-compat/src-ghc86/Compat/HieAst.hs
index 6b019a0dbf..8fdae7ecb0 100644
--- a/hie-compat/src-ghc86/Compat/HieAst.hs
+++ b/hie-compat/src-ghc86/Compat/HieAst.hs
@@ -17,7 +17,7 @@ Main functions for .hie file generation
 {-# LANGUAGE ViewPatterns #-}
 {-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE DataKinds #-}
-module Compat.HieAst ( mkHieFile, enrichHie ) where
+module Compat.HieAst ( enrichHie ) where
 
 import Avail                      ( Avails )
 import Bag                        ( Bag, bagToList )
@@ -30,7 +30,7 @@ import Desugar                    ( deSugarExpr )
 import FieldLabel
 import HsSyn
 import HscTypes
-import Module                     ( ModuleName, ml_hs_file )
+import Module                     ( ModuleName )
 import MonadUtils                 ( concatMapM, liftIO )
 import Name                       ( Name, nameSrcSpan )
 import SrcLoc
@@ -38,14 +38,10 @@ import TcHsSyn                    ( hsLitType, hsPatType )
 import Type                       ( mkFunTys, Type )
 import TysWiredIn                 ( mkListTy, mkSumTy )
 import Var                        ( Id, Var, setVarName, varName, varType )
-import TcRnTypes
-import MkIface                    ( mkIfaceExports )
 
 import Compat.HieTypes
 import Compat.HieUtils
 
-import qualified Data.Array as A
-import qualified Data.ByteString as BS
 import qualified Data.Map as M
 import qualified Data.Set as S
 import Data.Data                  ( Data, Typeable )
@@ -101,32 +97,6 @@ modifyState = foldr go id
 
 type HieM = ReaderT HieState Hsc
 
--- | Construct an 'HieFile' from the outputs of the typechecker.
-mkHieFile :: ModSummary
-          -> TcGblEnv
-          -> RenamedSource
-          -> BS.ByteString
-          -> Hsc HieFile
-mkHieFile ms ts rs src = do
-  let tc_binds = tcg_binds ts
-  (asts', arr) <- getCompressedAsts tc_binds rs
-  let Just src_file = ml_hs_file $ ms_location ms
-  return $ HieFile
-      { hie_hs_file = src_file
-      , hie_module = ms_mod ms
-      , hie_types = arr
-      , hie_asts = asts'
-      -- mkIfaceExports sorts the AvailInfos for stability
-      , hie_exports = mkIfaceExports (tcg_exports ts)
-      , hie_hs_src = src
-      }
-
-getCompressedAsts :: TypecheckedSource -> RenamedSource
-  -> Hsc (HieASTs TypeIndex, A.Array TypeIndex HieTypeFlat)
-getCompressedAsts ts rs = do
-  asts <- enrichHie ts rs
-  return $ compressTypes asts
-
 enrichHie :: TypecheckedSource -> RenamedSource -> Hsc (HieASTs Type)
 enrichHie ts (hsGrp, imports, exports, _) = flip runReaderT initState $ do
     tasts <- toHie $ fmap (BC RegularBind ModuleScope) ts
diff --git a/hie-compat/src-ghc88/Compat/HieAst.hs b/hie-compat/src-ghc88/Compat/HieAst.hs
index c9092184b1..f1fab23db3 100644
--- a/hie-compat/src-ghc88/Compat/HieAst.hs
+++ b/hie-compat/src-ghc88/Compat/HieAst.hs
@@ -16,7 +16,7 @@ Main functions for .hie file generation
 {-# LANGUAGE AllowAmbiguousTypes #-}
 {-# LANGUAGE ViewPatterns #-}
 {-# LANGUAGE DeriveDataTypeable #-}
-module Compat.HieAst ( mkHieFile, enrichHie ) where
+module Compat.HieAst ( enrichHie ) where
 
 import Avail                      ( Avails )
 import Bag                        ( Bag, bagToList )
@@ -90,32 +90,6 @@ modifyState = foldr go id
 
 type HieM = ReaderT HieState Hsc
 
--- | Construct an 'HieFile' from the outputs of the typechecker.
-mkHieFile :: ModSummary
-          -> TcGblEnv
-          -> RenamedSource
-          -> BS.ByteString
-          -> Hsc HieFile
-mkHieFile ms ts rs src = do
-  let tc_binds = tcg_binds ts
-  (asts', arr) <- getCompressedAsts tc_binds rs
-  let Just src_file = ml_hs_file $ ms_location ms
-  return $ HieFile
-      { hie_hs_file = src_file
-      , hie_module = ms_mod ms
-      , hie_types = arr
-      , hie_asts = asts'
-      -- mkIfaceExports sorts the AvailInfos for stability
-      , hie_exports = mkIfaceExports (tcg_exports ts)
-      , hie_hs_src = src
-      }
-
-getCompressedAsts :: TypecheckedSource -> RenamedSource
-  -> Hsc (HieASTs TypeIndex, A.Array TypeIndex HieTypeFlat)
-getCompressedAsts ts rs = do
-  asts <- enrichHie ts rs
-  return $ compressTypes asts
-
 enrichHie :: TypecheckedSource -> RenamedSource -> Hsc (HieASTs Type)
 enrichHie ts (hsGrp, imports, exports, _) = flip runReaderT initState $ do
     tasts <- toHie $ fmap (BC RegularBind ModuleScope) ts
diff --git a/hie-compat/src-ghc901/Compat/HieAst.hs b/hie-compat/src-ghc901/Compat/HieAst.hs
deleted file mode 100644
index 26f315caef..0000000000
--- a/hie-compat/src-ghc901/Compat/HieAst.hs
+++ /dev/null
@@ -1,35 +0,0 @@
-{-
-Forked from GHC v9.0.1 to work around the readFile side effect in mkHiefile
-
-Main functions for .hie file generation
--}
-{- HLINT ignore -}
-{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
-
-module Compat.HieAst ( mkHieFile, enrichHie ) where
-
-import           GHC.Data.Maybe      (expectJust)
-import           GHC.Driver.Types
-import           GHC.Hs
-import           GHC.Tc.Types        (TcGblEnv)
-import           GHC.Types.Avail     (Avails)
-import           GHC.Unit.Module     (ml_hs_file)
-
-import           GHC.Iface.Ext.Ast   (enrichHie, mkHieFileWithSource)
-import           GHC.Iface.Ext.Types
-
-import qualified Data.ByteString     as BS
-
-
-type RenamedSource     = ( HsGroup GhcRn, [LImportDecl GhcRn]
-                         , Maybe [(LIE GhcRn, Avails)]
-                         , Maybe LHsDocString )
-
--- | Construct an 'HieFile' from the outputs of the typechecker.
-mkHieFile :: ModSummary
-          -> TcGblEnv
-          -> RenamedSource
-          -> BS.ByteString -> Hsc HieFile
-mkHieFile ms ts rs src = do
-  let src_file = expectJust "mkHieFile" (ml_hs_file $ ms_location ms)
-  mkHieFileWithSource src_file src ms ts rs
diff --git a/hie-compat/src-reexport-ghc9/Compat/HieAst.hs b/hie-compat/src-reexport-ghc9/Compat/HieAst.hs
new file mode 100644
index 0000000000..c6d0260f6b
--- /dev/null
+++ b/hie-compat/src-reexport-ghc9/Compat/HieAst.hs
@@ -0,0 +1,3 @@
+module Compat.HieAst ( enrichHie ) where
+
+import           GHC.Iface.Ext.Ast   (enrichHie)
diff --git a/hie-compat/src-ghc901/Compat/HieBin.hs b/hie-compat/src-reexport-ghc9/Compat/HieBin.hs
similarity index 100%
rename from hie-compat/src-ghc901/Compat/HieBin.hs
rename to hie-compat/src-reexport-ghc9/Compat/HieBin.hs
diff --git a/hie-compat/src-ghc901/Compat/HieDebug.hs b/hie-compat/src-reexport-ghc9/Compat/HieDebug.hs
similarity index 100%
rename from hie-compat/src-ghc901/Compat/HieDebug.hs
rename to hie-compat/src-reexport-ghc9/Compat/HieDebug.hs
diff --git a/hie-compat/src-ghc901/Compat/HieTypes.hs b/hie-compat/src-reexport-ghc9/Compat/HieTypes.hs
similarity index 100%
rename from hie-compat/src-ghc901/Compat/HieTypes.hs
rename to hie-compat/src-reexport-ghc9/Compat/HieTypes.hs
diff --git a/hie-compat/src-ghc901/Compat/HieUtils.hs b/hie-compat/src-reexport-ghc9/Compat/HieUtils.hs
similarity index 100%
rename from hie-compat/src-ghc901/Compat/HieUtils.hs
rename to hie-compat/src-reexport-ghc9/Compat/HieUtils.hs