diff --git a/haddock-api/haddock-api.cabal b/haddock-api/haddock-api.cabal
index be84f8ceee988de6a3cb5a915428ab7221b8dec1..206b9aa2393d052580677d22adc32324b803f131 100644
--- a/haddock-api/haddock-api.cabal
+++ b/haddock-api/haddock-api.cabal
@@ -1,10 +1,10 @@
-cabal-version:        2.0
+cabal-version:        3.0
 name:                 haddock-api
-version:              2.26.1
+version:              2.27.0
 synopsis:             A documentation-generation tool for Haskell libraries
 description:          Haddock is a documentation-generation tool for Haskell
                       libraries
-license:              BSD2
+license:              BSD-2-Clause
 license-file:         LICENSE
 author:               Simon Marlow, David Waern
 maintainer:           Alec Theriault <alec.theriault@gmail.com>, Alex Biehl <alexbiehl@gmail.com>, Simon Hengel <sol@typeful.net>, Mateusz Kowalczyk <fuuzetsu@fuuzetsu.co.uk>
@@ -13,7 +13,7 @@ bug-reports:          https://github.com/haskell/haddock/issues
 copyright:            (c) Simon Marlow, David Waern
 category:             Documentation
 build-type:           Simple
-tested-with:          GHC==9.2.*
+tested-with:          GHC==9.4.*
 
 extra-source-files:
   CHANGES.md
@@ -44,9 +44,9 @@ library
 
   -- this package typically supports only single major versions
   build-depends: base            ^>= 4.16.0
-               , ghc             ^>= 9.3
+               , ghc             ^>= 9.4
                , ghc-paths       ^>= 0.1.0.9
-               , haddock-library ^>= 1.10.0
+               , haddock-library ^>= 1.10
                , xhtml           ^>= 3000.2.2
                , parsec          ^>= 3.1.13.0
 
@@ -180,7 +180,7 @@ test-suite spec
     Haddock.Backends.Hyperlinker.Parser
     Haddock.Backends.Hyperlinker.Types
 
-  build-depends: ghc             ^>= 9.3
+  build-depends: ghc             ^>= 9.4
                , ghc-paths       ^>= 0.1.0.12
                , haddock-library ^>= 1.10.0
                , xhtml           ^>= 3000.2.2
diff --git a/haddock-api/src/Haddock.hs b/haddock-api/src/Haddock.hs
index 989ca03f90a545ed651958623d7e11e7a2ec1c46..ea664bcf77f0859115c9584d2805a707e86abdf0 100644
--- a/haddock-api/src/Haddock.hs
+++ b/haddock-api/src/Haddock.hs
@@ -80,7 +80,6 @@ import GHC.Utils.Error
 import GHC.Utils.Logger
 import GHC.Types.Name.Cache
 import GHC.Unit
-import GHC.Unit.State (lookupUnit)
 import GHC.Utils.Panic (handleGhcException)
 import GHC.Data.FastString
 
diff --git a/haddock-api/src/Haddock/Backends/Hyperlinker.hs b/haddock-api/src/Haddock/Backends/Hyperlinker.hs
index 89828e3017727ece412894ccebbde8c00548cc54..9316da6dc32061a1ffd0563475796588af81e557 100644
--- a/haddock-api/src/Haddock/Backends/Hyperlinker.hs
+++ b/haddock-api/src/Haddock/Backends/Hyperlinker.hs
@@ -26,8 +26,6 @@ import GHC.Types.SrcLoc     ( realSrcLocSpan, mkRealSrcLoc, srcSpanFile )
 import Data.Map as M
 import GHC.Data.FastString     ( mkFastString )
 import GHC.Unit.Module         ( Module, moduleName )
-import GHC.Types.Name.Cache    ( initNameCache )
-import GHC.Types.Unique.Supply ( mkSplitUniqSupply )
 
 
 -- | Generate hyperlinked source for given interfaces.
diff --git a/haddock-api/src/Haddock/Interface.hs b/haddock-api/src/Haddock/Interface.hs
index 19113107f81c6a45d5aa527b92568fcdcaff854f..92b727acd2e479206577e53d25bc5f7430e02b56 100644
--- a/haddock-api/src/Haddock/Interface.hs
+++ b/haddock-api/src/Haddock/Interface.hs
@@ -46,7 +46,7 @@ import Haddock.Types (DocOption (..), Documentation (..), ExportItem (..), Iface
 import Haddock.Utils (Verbosity (..), normal, out, verbose)
 
 import Control.Monad (unless, when)
-import Control.Monad.IO.Class (MonadIO, liftIO)
+import Control.Monad.IO.Class (MonadIO)
 import Data.IORef (atomicModifyIORef', newIORef, readIORef)
 import Data.List (foldl', isPrefixOf, nub)
 import Text.Printf (printf)
@@ -54,7 +54,6 @@ import qualified Data.Map as Map
 import qualified Data.Set as Set
 
 import GHC hiding (verbosity)
-import GHC.Data.FastString (unpackFS)
 import GHC.Data.Graph.Directed
 import GHC.Driver.Env
 import GHC.Driver.Monad (modifySession, withTimingM)
@@ -64,13 +63,7 @@ import GHC.Plugins
 import GHC.Tc.Types (TcGblEnv (..), TcM)
 import GHC.Tc.Utils.Env (tcLookupGlobal)
 import GHC.Tc.Utils.Monad (getTopEnv, setGblEnv)
-import GHC.Types.Name (nameIsFromExternalPackage, nameOccName)
-import GHC.Types.Name.Occurrence (isTcOcc)
-import GHC.Types.Name.Reader (globalRdrEnvElts, greMangledName, unQualOK)
-import GHC.Unit.Module.Env (ModuleSet, emptyModuleSet, mkModuleSet, unionModuleSet)
 import GHC.Unit.Module.Graph
-import GHC.Unit.Module.ModSummary (isBootSummary)
-import GHC.Unit.Types (IsBootInterface (..))
 import GHC.Utils.Error (withTiming)
 
 #if defined(mingw32_HOST_OS)
diff --git a/haddock-api/src/Haddock/Interface/Create.hs b/haddock-api/src/Haddock/Interface/Create.hs
index b832128f77c42cd02c35e99d693e403093f39810..e3c4a52952c52845226b5564cfebd65e2716b419 100644
--- a/haddock-api/src/Haddock/Interface/Create.hs
+++ b/haddock-api/src/Haddock/Interface/Create.hs
@@ -54,7 +54,7 @@ import Data.Traversable (for)
 import GHC hiding (lookupName)
 import GHC.Core.Class (ClassMinimalDef, classMinimalDef)
 import GHC.Core.ConLike (ConLike (..))
-import GHC.Data.FastString (bytesFS, unpackFS)
+import GHC.Data.FastString (unpackFS)
 import GHC.Driver.Ppr (showSDoc)
 import GHC.HsToCore.Docs hiding (mkMaps, unionArgMaps)
 import GHC.IORef (readIORef)
@@ -1137,8 +1137,7 @@ extractDecl declMap name decl
               _ -> Left "internal: extractDecl (ClsInstD)"
       _ -> Left ("extractDecl: Unhandled decl for " ++ getOccString name)
 
-extractPatternSyn :: HasCallStack
-                  => Name -> Name
+extractPatternSyn :: Name -> Name
                   -> [LHsTypeArg GhcRn] -> [LConDecl GhcRn]
                   -> Either ErrMsg (LSig GhcRn)
 extractPatternSyn nm t tvs cons =
diff --git a/haddock-api/src/Haddock/Interface/LexParseRn.hs b/haddock-api/src/Haddock/Interface/LexParseRn.hs
index 4e1964afef7cc9e45a068b5f74713e72f6f3adb2..455f331405f064f179a925efde90c95461c69eba 100644
--- a/haddock-api/src/Haddock/Interface/LexParseRn.hs
+++ b/haddock-api/src/Haddock/Interface/LexParseRn.hs
@@ -39,7 +39,6 @@ import GHC.Parser.PostProcess
 import GHC.Driver.Ppr ( showPpr, showSDoc )
 import GHC.Types.Name.Reader
 import GHC.Data.EnumSet as EnumSet
-import GHC.Utils.Trace
 
 processDocStrings :: DynFlags -> Maybe Package -> GlobalRdrEnv -> [HsDocString]
                   -> ErrMsgM (Maybe (MDoc Name))
diff --git a/haddock-api/src/Haddock/Interface/Specialize.hs b/haddock-api/src/Haddock/Interface/Specialize.hs
index d116485873ad29df63fa4400c3e465c6b18f3440..ca6b9e74567bb2f1075f202da577e422b75ae074 100644
--- a/haddock-api/src/Haddock/Interface/Specialize.hs
+++ b/haddock-api/src/Haddock/Interface/Specialize.hs
@@ -16,7 +16,6 @@ import Haddock.Syb
 import Haddock.Types
 
 import GHC
-import GHC.Types.Basic ( PromotionFlag(..) )
 import GHC.Types.Name
 import GHC.Data.FastString
 import GHC.Builtin.Types ( listTyConName, unrestrictedFunTyConName )
diff --git a/haddock-api/src/Haddock/InterfaceFile.hs b/haddock-api/src/Haddock/InterfaceFile.hs
index f98617082c58ef097f97e7aabed01569f30aac8c..e6db49c059c083d22991a7cfe0d6b5c3cdc31405 100644
--- a/haddock-api/src/Haddock/InterfaceFile.hs
+++ b/haddock-api/src/Haddock/InterfaceFile.hs
@@ -309,19 +309,6 @@ putInterfaceFile_ bh (InterfaceFile env info ifaces) = do
   put_ bh info
   put_ bh ifaces
 
-getInterfaceFile :: BinHandle -> Word16 -> IO InterfaceFile
-getInterfaceFile bh v | v <= 38 = do
-  env    <- get bh
-  let info = PackageInfo (PackageName mempty) (makeVersion [])
-  ifaces <- get bh
-  return (InterfaceFile env info ifaces)
-getInterfaceFile bh _ = do
-  env    <- get bh
-  info   <- get bh
-  ifaces <- get bh
-  return (InterfaceFile env info ifaces)
-
-
 instance Binary InstalledInterface where
   put_ bh (InstalledInterface modu is_sig info docMap argMap
            exps visExps opts fixMap) = do
diff --git a/html-test/ref/Bug1004.html b/html-test/ref/Bug1004.html
index 9fe6f84e1e710e7c2dd5f47c586909ba76ef99b8..bbe2f5993e04ffba8bc76010f18fa6deb83c44fc 100644
--- a/html-test/ref/Bug1004.html
+++ b/html-test/ref/Bug1004.html
@@ -48,26 +48,6 @@
 	><p class="caption"
 	>Bug1004</p
 	></div
-      ><div id="synopsis"
-      ><details id="syn"
-	><summary
-	  >Synopsis</summary
-	  ><ul class="details-toggle" data-details-id="syn"
-	  ><li class="src short"
-	    ><span class="keyword"
-	      >data</span
-	      > <a href="#"
-	      >Product</a
-	      > (f :: k -&gt; <a href="#" title="Data.Kind"
-	      >Type</a
-	      >) (g :: k -&gt; <a href="#" title="Data.Kind"
-	      >Type</a
-	      >) (a :: k) = <a href="#"
-	      >Pair</a
-	      > (f a) (g a)</li
-	    ></ul
-	  ></details
-	></div
       ><div id="interface"
       ><h1
 	>Documentation</h1
@@ -84,10 +64,6 @@
 	    >) (a :: k) <a href="#" class="selflink"
 	    >#</a
 	    ></p
-	  ><div class="doc"
-	  ><p
-	    >Lifted product of functors.</p
-	    ></div
 	  ><div class="subs constructors"
 	  ><p class="caption"
 	    >Constructors</p
@@ -200,12 +176,8 @@
 		      >Product</a
 		      > f g)</span
 		    ></td
-		  ><td class="doc"
-		  ><p
-		    ><em
-		      >Since: base-4.9.0.0</em
-		      ></p
-		    ></td
+		  ><td class="doc empty"
+		  >&nbsp;</td
 		  ></tr
 		><tr
 		><td colspan="2"
@@ -248,12 +220,8 @@
 		      >Product</a
 		      > f g)</span
 		    ></td
-		  ><td class="doc"
-		  ><p
-		    ><em
-		      >Since: base-4.9.0.0</em
-		      ></p
-		    ></td
+		  ><td class="doc empty"
+		  >&nbsp;</td
 		  ></tr
 		><tr
 		><td colspan="2"
@@ -322,12 +290,8 @@
 		      >Product</a
 		      > f g)</span
 		    ></td
-		  ><td class="doc"
-		  ><p
-		    ><em
-		      >Since: base-4.9.0.0</em
-		      ></p
-		    ></td
+		  ><td class="doc empty"
+		  >&nbsp;</td
 		  ></tr
 		><tr
 		><td colspan="2"
@@ -518,12 +482,8 @@
 		      >Product</a
 		      > f g)</span
 		    ></td
-		  ><td class="doc"
-		  ><p
-		    ><em
-		      >Since: base-4.9.0.0</em
-		      ></p
-		    ></td
+		  ><td class="doc empty"
+		  >&nbsp;</td
 		  ></tr
 		><tr
 		><td colspan="2"
@@ -570,12 +530,8 @@
 		      >Product</a
 		      > f g)</span
 		    ></td
-		  ><td class="doc"
-		  ><p
-		    ><em
-		      >Since: base-4.9.0.0</em
-		      ></p
-		    ></td
+		  ><td class="doc empty"
+		  >&nbsp;</td
 		  ></tr
 		><tr
 		><td colspan="2"
@@ -622,12 +578,8 @@
 		      >Product</a
 		      > f g)</span
 		    ></td
-		  ><td class="doc"
-		  ><p
-		    ><em
-		      >Since: base-4.9.0.0</em
-		      ></p
-		    ></td
+		  ><td class="doc empty"
+		  >&nbsp;</td
 		  ></tr
 		><tr
 		><td colspan="2"
@@ -722,12 +674,8 @@
 		      >Product</a
 		      > f g)</span
 		    ></td
-		  ><td class="doc"
-		  ><p
-		    ><em
-		      >Since: base-4.9.0.0</em
-		      ></p
-		    ></td
+		  ><td class="doc empty"
+		  >&nbsp;</td
 		  ></tr
 		><tr
 		><td colspan="2"
@@ -794,12 +742,8 @@
 		      >Product</a
 		      > f g)</span
 		    ></td
-		  ><td class="doc"
-		  ><p
-		    ><em
-		      >Since: base-4.9.0.0</em
-		      ></p
-		    ></td
+		  ><td class="doc empty"
+		  >&nbsp;</td
 		  ></tr
 		><tr
 		><td colspan="2"
@@ -880,12 +824,8 @@
 		      >Product</a
 		      > f g)</span
 		    ></td
-		  ><td class="doc"
-		  ><p
-		    ><em
-		      >Since: base-4.9.0.0</em
-		      ></p
-		    ></td
+		  ><td class="doc empty"
+		  >&nbsp;</td
 		  ></tr
 		><tr
 		><td colspan="2"
@@ -958,12 +898,8 @@
 		      >Product</a
 		      > f g)</span
 		    ></td
-		  ><td class="doc"
-		  ><p
-		    ><em
-		      >Since: base-4.9.0.0</em
-		      ></p
-		    ></td
+		  ><td class="doc empty"
+		  >&nbsp;</td
 		  ></tr
 		><tr
 		><td colspan="2"
@@ -1052,12 +988,8 @@
 		      >Product</a
 		      > f g)</span
 		    ></td
-		  ><td class="doc"
-		  ><p
-		    ><em
-		      >Since: base-4.9.0.0</em
-		      ></p
-		    ></td
+		  ><td class="doc empty"
+		  >&nbsp;</td
 		  ></tr
 		><tr
 		><td colspan="2"
@@ -1110,12 +1042,8 @@
 		      >Product</a
 		      > f g)</span
 		    ></td
-		  ><td class="doc"
-		  ><p
-		    ><em
-		      >Since: base-4.9.0.0</em
-		      ></p
-		    ></td
+		  ><td class="doc empty"
+		  >&nbsp;</td
 		  ></tr
 		><tr
 		><td colspan="2"
@@ -1180,12 +1108,8 @@
 		      >Product</a
 		      > f g)</span
 		    ></td
-		  ><td class="doc"
-		  ><p
-		    ><em
-		      >Since: base-4.9.0.0</em
-		      ></p
-		    ></td
+		  ><td class="doc empty"
+		  >&nbsp;</td
 		  ></tr
 		><tr
 		><td colspan="2"
@@ -1246,12 +1170,8 @@
 		      >Product</a
 		      > f g a)</span
 		    ></td
-		  ><td class="doc"
-		  ><p
-		    ><em
-		      >Since: base-4.9.0.0</em
-		      ></p
-		    ></td
+		  ><td class="doc empty"
+		  >&nbsp;</td
 		  ></tr
 		><tr
 		><td colspan="2"
@@ -1484,12 +1404,8 @@
 		      >Product</a
 		      > f g a)</span
 		    ></td
-		  ><td class="doc"
-		  ><p
-		    ><em
-		      >Since: base-4.16.0.0</em
-		      ></p
-		    ></td
+		  ><td class="doc empty"
+		  >&nbsp;</td
 		  ></tr
 		><tr
 		><td colspan="2"
@@ -1552,12 +1468,8 @@
 		      >Product</a
 		      > f g a)</span
 		    ></td
-		  ><td class="doc"
-		  ><p
-		    ><em
-		      >Since: base-4.16.0.0</em
-		      ></p
-		    ></td
+		  ><td class="doc empty"
+		  >&nbsp;</td
 		  ></tr
 		><tr
 		><td colspan="2"
@@ -1700,12 +1612,8 @@
 		      >Product</a
 		      > f g a)</span
 		    ></td
-		  ><td class="doc"
-		  ><p
-		    ><em
-		      >Since: base-4.9.0.0</em
-		      ></p
-		    ></td
+		  ><td class="doc empty"
+		  >&nbsp;</td
 		  ></tr
 		><tr
 		><td colspan="2"
@@ -1782,12 +1690,8 @@
 		      >Product</a
 		      > f g a)</span
 		    ></td
-		  ><td class="doc"
-		  ><p
-		    ><em
-		      >Since: base-4.9.0.0</em
-		      ></p
-		    ></td
+		  ><td class="doc empty"
+		  >&nbsp;</td
 		  ></tr
 		><tr
 		><td colspan="2"
@@ -1854,12 +1758,8 @@
 		      >Product</a
 		      > f g a)</span
 		    ></td
-		  ><td class="doc"
-		  ><p
-		    ><em
-		      >Since: base-4.9.0.0</em
-		      ></p
-		    ></td
+		  ><td class="doc empty"
+		  >&nbsp;</td
 		  ></tr
 		><tr
 		><td colspan="2"
@@ -1918,12 +1818,8 @@
 		      >Product</a
 		      > f g a)</span
 		    ></td
-		  ><td class="doc"
-		  ><p
-		    ><em
-		      >Since: base-4.9.0.0</em
-		      ></p
-		    ></td
+		  ><td class="doc empty"
+		  >&nbsp;</td
 		  ></tr
 		><tr
 		><td colspan="2"
@@ -2040,12 +1936,8 @@
 		      >Type</a
 		      >)</span
 		    ></td
-		  ><td class="doc"
-		  ><p
-		    ><em
-		      >Since: base-4.9.0.0</em
-		      ></p
-		    ></td
+		  ><td class="doc empty"
+		  >&nbsp;</td
 		  ></tr
 		><tr
 		><td colspan="2"
@@ -2134,12 +2026,8 @@
 		      >Product</a
 		      > f g a)</span
 		    ></td
-		  ><td class="doc"
-		  ><p
-		    ><em
-		      >Since: base-4.9.0.0</em
-		      ></p
-		    ></td
+		  ><td class="doc empty"
+		  >&nbsp;</td
 		  ></tr
 		><tr
 		><td colspan="2"
diff --git a/html-test/ref/Bug310.html b/html-test/ref/Bug310.html
index 57c820778e8bfe09a70a04466437ac02096552e0..a844d855e332cd2a61b1168eda5bb220cd20a861 100644
--- a/html-test/ref/Bug310.html
+++ b/html-test/ref/Bug310.html
@@ -48,28 +48,6 @@
 	><p class="caption"
 	>Bug310</p
 	></div
-      ><div id="synopsis"
-      ><details id="syn"
-	><summary
-	  >Synopsis</summary
-	  ><ul class="details-toggle" data-details-id="syn"
-	  ><li class="src short"
-	    ><span class="keyword"
-	      >type family</span
-	      > (a :: <a href="#" title="Numeric.Natural"
-	      >Natural</a
-	      >) <a href="#"
-	      >+</a
-	      > (b :: <a href="#" title="Numeric.Natural"
-	      >Natural</a
-	      >) :: <a href="#" title="Numeric.Natural"
-	      >Natural</a
-	      > <span class="keyword"
-	      >where ...</span
-	      ></li
-	    ></ul
-	  ></details
-	></div
       ><div id="interface"
       ><h1
 	>Documentation</h1
@@ -87,21 +65,9 @@
 	    >Natural</a
 	    > <span class="keyword"
 	    >where ...</span
-	    > <span class="fixity"
-	    >infixl 6</span
-	    ><span class="rightedge"
-	    ></span
 	    > <a href="#" class="selflink"
 	    >#</a
 	    ></p
-	  ><div class="doc"
-	  ><p
-	    >Addition of type-level naturals.</p
-	    ><p
-	    ><em
-	      >Since: base-4.7.0.0</em
-	      ></p
-	    ></div
 	  ></div
 	></div
       ></div
diff --git a/html-test/ref/Bug548.html b/html-test/ref/Bug548.html
index 594480c7f62e43ccdd1c42092d2947d76e7d77b3..99bd540293e5b647dba18334716147d28da1ce5a 100644
--- a/html-test/ref/Bug548.html
+++ b/html-test/ref/Bug548.html
@@ -198,12 +198,8 @@
 		      >WrappedArrow</a
 		      > a b)</span
 		    ></td
-		  ><td class="doc"
-		  ><p
-		    ><em
-		      >Since: base-2.1</em
-		      ></p
-		    ></td
+		  ><td class="doc empty"
+		  >&nbsp;</td
 		  ></tr
 		><tr
 		><td colspan="2"
@@ -274,12 +270,8 @@
 		      >WrappedArrow</a
 		      > a b)</span
 		    ></td
-		  ><td class="doc"
-		  ><p
-		    ><em
-		      >Since: base-2.1</em
-		      ></p
-		    ></td
+		  ><td class="doc empty"
+		  >&nbsp;</td
 		  ></tr
 		><tr
 		><td colspan="2"
@@ -366,12 +358,8 @@
 		      >WrappedArrow</a
 		      > a b)</span
 		    ></td
-		  ><td class="doc"
-		  ><p
-		    ><em
-		      >Since: base-2.1</em
-		      ></p
-		    ></td
+		  ><td class="doc empty"
+		  >&nbsp;</td
 		  ></tr
 		><tr
 		><td colspan="2"
@@ -498,12 +486,8 @@
 		      >Type</a
 		      >)</span
 		    ></td
-		  ><td class="doc"
-		  ><p
-		    ><em
-		      >Since: base-4.7.0.0</em
-		      ></p
-		    ></td
+		  ><td class="doc empty"
+		  >&nbsp;</td
 		  ></tr
 		><tr
 		><td colspan="2"
@@ -570,12 +554,8 @@
 		      >WrappedArrow</a
 		      > a b c)</span
 		    ></td
-		  ><td class="doc"
-		  ><p
-		    ><em
-		      >Since: base-4.7.0.0</em
-		      ></p
-		    ></td
+		  ><td class="doc empty"
+		  >&nbsp;</td
 		  ></tr
 		><tr
 		><td colspan="2"