[Git][ghc/ghc][master] Serialize wired-in names as external names when creating HIE files

Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 42724462 by Simon Hengel at 2025-08-21T17:52:11-04:00 Serialize wired-in names as external names when creating HIE files Note that the domain of de-serialized names stays the same. Specifically, for known-key names, before `lookupKnownKeyName` was used, while now this is handled by `lookupOrigNameCache` which captures the same range provided that the OrigNameCache has been initialized with `knownKeyNames` (which is the case by default). (fixes #26238) - - - - - 4 changed files: - compiler/GHC/Iface/Ext/Binary.hs - compiler/GHC/Iface/Ext/Types.hs - compiler/GHC/Types/Name/Cache.hs - utils/haddock/haddock-api/src/Haddock/InterfaceFile.hs Changes: ===================================== compiler/GHC/Iface/Ext/Binary.hs ===================================== @@ -17,7 +17,6 @@ where import GHC.Prelude -import GHC.Builtin.Utils import GHC.Settings.Utils ( maybeRead ) import GHC.Settings.Config ( cProjectVersion ) import GHC.Utils.Binary @@ -28,10 +27,8 @@ import GHC.Iface.Binary ( putAllTables ) import GHC.Types.Name import GHC.Types.Name.Cache import GHC.Types.SrcLoc as SrcLoc -import GHC.Types.Unique import GHC.Types.Unique.FM import qualified GHC.Utils.Binary as Binary -import GHC.Utils.Outputable import GHC.Utils.Panic import qualified Data.Array as A @@ -290,6 +287,9 @@ fromHieName nc hie_name = do case hie_name of ExternalName mod occ span -> updateNameCache nc mod occ $ \cache -> do case lookupOrigNameCache cache mod occ of + -- Note that this may be a wired-in name (provided that the NameCache + -- was initialized with known-key names, which is always the case if you + -- use `newNameCache`). Just name -> pure (cache, name) Nothing -> do uniq <- takeUniqFromNameCache nc @@ -302,11 +302,6 @@ fromHieName nc hie_name = do -- don't update the NameCache for local names pure $ mkInternalName uniq occ span - KnownKeyName u -> case lookupKnownKeyName u of - Nothing -> pprPanic "fromHieName:unknown known-key unique" - (ppr u) - Just n -> pure n - -- ** Reading and writing `HieName`'s putHieName :: WriteBinHandle -> HieName -> IO () @@ -316,9 +311,6 @@ putHieName bh (ExternalName mod occ span) = do putHieName bh (LocalName occName span) = do putByte bh 1 put_ bh (occName, BinSrcSpan span) -putHieName bh (KnownKeyName uniq) = do - putByte bh 2 - put_ bh $ unpkUnique uniq getHieName :: ReadBinHandle -> IO HieName getHieName bh = do @@ -330,7 +322,4 @@ getHieName bh = do 1 -> do (occ, span) <- get bh return $ LocalName occ $ unBinSrcSpan span - 2 -> do - (c,i) <- get bh - return $ KnownKeyName $ mkUnique c i _ -> panic "GHC.Iface.Ext.Binary.getHieName: invalid tag" ===================================== compiler/GHC/Iface/Ext/Types.hs ===================================== @@ -19,14 +19,12 @@ import GHC.Prelude import GHC.Settings.Config import GHC.Utils.Binary import GHC.Data.FastString -import GHC.Builtin.Utils import GHC.Iface.Type import GHC.Unit.Module ( ModuleName, Module ) import GHC.Types.Name import GHC.Utils.Outputable hiding ( (<>) ) import GHC.Types.SrcLoc import GHC.Types.Avail -import GHC.Types.Unique import qualified GHC.Utils.Outputable as O ( (<>) ) import GHC.Utils.Panic import GHC.Core.ConLike ( ConLike(..) ) @@ -766,7 +764,6 @@ instance Binary TyVarScope where data HieName = ExternalName !Module !OccName !SrcSpan | LocalName !OccName !SrcSpan - | KnownKeyName !Unique deriving (Eq) instance Ord HieName where @@ -774,34 +771,28 @@ instance Ord HieName where -- TODO (int-index): Perhaps use RealSrcSpan in HieName? compare (LocalName a b) (LocalName c d) = compare a c S.<> leftmost_smallest b d -- TODO (int-index): Perhaps use RealSrcSpan in HieName? - compare (KnownKeyName a) (KnownKeyName b) = nonDetCmpUnique a b - -- Not actually non deterministic as it is a KnownKey compare ExternalName{} _ = LT compare LocalName{} ExternalName{} = GT - compare LocalName{} _ = LT - compare KnownKeyName{} _ = GT instance Outputable HieName where ppr (ExternalName m n sp) = text "ExternalName" <+> ppr m <+> ppr n <+> ppr sp ppr (LocalName n sp) = text "LocalName" <+> ppr n <+> ppr sp - ppr (KnownKeyName u) = text "KnownKeyName" <+> ppr u hieNameOcc :: HieName -> OccName hieNameOcc (ExternalName _ occ _) = occ hieNameOcc (LocalName occ _) = occ -hieNameOcc (KnownKeyName u) = - case lookupKnownKeyName u of - Just n -> nameOccName n - Nothing -> pprPanic "hieNameOcc:unknown known-key unique" - (ppr u) toHieName :: Name -> HieName -toHieName name - | isKnownKeyName name = KnownKeyName (nameUnique name) - | isExternalName name = ExternalName (nameModule name) - (nameOccName name) - (removeBufSpan $ nameSrcSpan name) - | otherwise = LocalName (nameOccName name) (removeBufSpan $ nameSrcSpan name) +toHieName name = + case nameModule_maybe name of + Nothing -> LocalName occName span + Just m -> ExternalName m occName span + where + occName :: OccName + occName = nameOccName name + + span :: SrcSpan + span = removeBufSpan $ nameSrcSpan name {- Note [Capture Entity Information] ===================================== compiler/GHC/Types/Name/Cache.hs ===================================== @@ -101,9 +101,14 @@ OrigNameCache at all? Good question; after all, 3) Loading of interface files encodes names via Uniques, as detailed in Note [Symbol table representation of names] in GHC.Iface.Binary -It turns out that we end up looking up built-in syntax in the cache when we -generate Haddock documentation. E.g. if we don't find tuple data constructors -there, hyperlinks won't work as expected. Test case: haddockHtmlTest (Bug923.hs) + +However note that: + 1) It turns out that we end up looking up built-in syntax in the cache when + we generate Haddock documentation. E.g. if we don't find tuple data + constructors there, hyperlinks won't work as expected. Test case: + haddockHtmlTest (Bug923.hs) + 2) HIE de-serialization relies on wired-in names, including built-in syntax, + being present in the OrigNameCache. -} -- | The NameCache makes sure that there is just one Unique assigned for ===================================== utils/haddock/haddock-api/src/Haddock/InterfaceFile.hs ===================================== @@ -229,10 +229,7 @@ writeInterfaceFile filename iface = do return () freshNameCache :: IO NameCache -freshNameCache = - initNameCache - 'a' -- ?? - [] +freshNameCache = newNameCache -- | Read a Haddock (@.haddock@) interface file. Return either an -- 'InterfaceFile' or an error message. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/42724462e3cfaba426882711c869e4f8... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/42724462e3cfaba426882711c869e4f8... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Marge Bot (@marge-bot)