Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: f0a19d74 by fendor at 2025-08-20T19:55:00-04:00 Remove deprecated functions from the ghci package - - - - - ebeb991b by fendor at 2025-08-20T19:55:00-04:00 base: Remove unstable heap representation details from GHC.Exts - - - - - e368e247 by Rodrigo Mesquita at 2025-08-20T19:55:42-04:00 bytecode: Use 32bits for breakpoint index Fixes #26325 - - - - - c938ca38 by Simon Hengel at 2025-08-21T14:01:47-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) - - - - - b5431ced by Cheng Shao at 2025-08-21T14:01:51-04:00 compiler: fix closure C type in SPT init code This patch fixes the closure C type in SPT init code to StgClosure, instead of the previously incorrect StgPtr. Having an incorrect C type makes SPT init code not compatible with other foreign stub generation logic, which may also emit their own extern declarations for the same closure symbols and thus will clash with the incorrect prototypes in SPT init code. - - - - - 14 changed files: - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Iface/Ext/Binary.hs - compiler/GHC/Iface/Ext/Types.hs - compiler/GHC/Iface/Tidy/StaticPtrTable.hs - compiler/GHC/Types/Name/Cache.hs - libraries/base/changelog.md - libraries/base/src/GHC/Exts.hs - libraries/ghci/GHCi/CreateBCO.hs - libraries/ghci/GHCi/TH.hs - libraries/ghci/ghci.cabal.in - rts/Disassembler.c - rts/Interpreter.c - − testsuite/tests/module/T21752.stderr - utils/haddock/haddock-api/src/Haddock/InterfaceFile.hs Changes: ===================================== compiler/GHC/ByteCode/Asm.hs ===================================== @@ -843,16 +843,18 @@ assembleI platform i = case i of BRK_FUN ibi@(InternalBreakpointId info_mod infox) -> do p1 <- ptr $ BCOPtrBreakArray info_mod - let -- cast that checks that round-tripping through Word16 doesn't change the value - toW16 x = let r = fromIntegral x :: Word16 - in if fromIntegral r == x + let -- cast that checks that round-tripping through Word32 doesn't change the value + infoW32 = let r = fromIntegral infox :: Word32 + in if fromIntegral r == infox then r - else pprPanic "schemeER_wrk: breakpoint tick/info index too large!" (ppr x) + else pprPanic "schemeER_wrk: breakpoint tick/info index too large!" (ppr infox) + ix_hi = fromIntegral (infoW32 `shiftR` 16) + ix_lo = fromIntegral (infoW32 .&. 0xffff) info_addr <- lit1 $ BCONPtrFS $ moduleNameFS $ moduleName info_mod info_unitid_addr <- lit1 $ BCONPtrFS $ unitIdFS $ moduleUnitId info_mod np <- lit1 $ BCONPtrCostCentre ibi emit_ bci_BRK_FUN [ Op p1, Op info_addr, Op info_unitid_addr - , SmallOp (toW16 infox), Op np ] + , SmallOp ix_hi, SmallOp ix_lo, Op np ] BRK_ALTS active -> emit_ bci_BRK_ALTS [SmallOp (if active then 1 else 0)] ===================================== 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/Iface/Tidy/StaticPtrTable.hs ===================================== @@ -17,18 +17,18 @@ -- > static void hs_hpc_init_Main(void) { -- > -- > static StgWord64 k0[2] = {16252233372134256ULL,7370534374096082ULL}; --- > extern StgPtr Main_r2wb_closure; +-- > extern StgClosure Main_r2wb_closure; -- > hs_spt_insert(k0, &Main_r2wb_closure); -- > -- > static StgWord64 k1[2] = {12545634534567898ULL,5409674567544151ULL}; --- > extern StgPtr Main_r2wc_closure; +-- > extern StgClosure Main_r2wc_closure; -- > hs_spt_insert(k1, &Main_r2wc_closure); -- > -- > } -- -- where the constants are fingerprints produced from the static forms. -- --- The linker must find the definitions matching the @extern StgPtr <name>@ +-- The linker must find the definitions matching the @extern StgClosure <name>@ -- declarations. For this to work, the identifiers of static pointers need to be -- exported. This is done in 'GHC.Core.Opt.SetLevels.newLvlVar'. -- @@ -263,7 +263,7 @@ sptModuleInitCode platform this_mod entries -- CLabel. Regardless, MayHaveCafRefs/NoCafRefs wouldn't make -- any difference here, they would pretty-print to the same -- foreign stub content. - $$ text "extern StgPtr " + $$ text "extern StgClosure " <> (pprCLabel platform $ mkClosureLabel n MayHaveCafRefs) <> semi $$ text "hs_spt_insert" <> parens (hcat $ punctuate comma ===================================== 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 ===================================== libraries/base/changelog.md ===================================== @@ -1,6 +1,7 @@ # Changelog for [`base` package](http://hackage.haskell.org/package/base) ## 4.23.0.0 *TBA* + * Remove deprecated, unstable heap representation details from `GHC.Exts` ([CLC proposal #212](https://github.com/haskell/core-libraries-committee/issues/212)) * Add `Data.List.NonEmpty.mapMaybe`. ([CLC proposal #337](https://github.com/haskell/core-libraries-committee/issues/337)) * Fix issues with toRational for types capable to represent infinite and not-a-number values ([CLC proposal #338](https://github.com/haskell/core-libraries-committee/issues/338)) * Modify the implementation of `Data.List.sortOn` to use `(>)` instead of `compare`. ([CLC proposal #332](https://github.com/haskell/core-libraries-committee/issues/332)) ===================================== libraries/base/src/GHC/Exts.hs ===================================== @@ -26,12 +26,6 @@ module GHC.Exts -- ** Legacy interface for arrays of arrays module GHC.Internal.ArrayArray, -- * Primitive operations - {-# DEPRECATED ["The BCO, mkApUpd0#, and newBCO# re-exports from GHC.Exts have been deprecated and will be removed in 9.14", "These symbols should be imported from ghc-internal instead if needed."] #-} - Prim.BCO, - {-# DEPRECATED ["The BCO, mkApUpd0#, and newBCO# re-exports from GHC.Exts have been deprecated and will be removed in 9.14", "These symbols should be imported from ghc-internal instead if needed."] #-} - Prim.mkApUpd0#, - {-# DEPRECATED ["The BCO, mkApUpd0#, and newBCO# re-exports from GHC.Exts have been deprecated and will be removed in 9.14", "These symbols should be imported from ghc-internal instead if needed."] #-} - Prim.newBCO#, module GHC.Prim, module GHC.Prim.Ext, -- ** Running 'RealWorld' state thread @@ -130,9 +124,6 @@ import GHC.Prim hiding , whereFrom# , isByteArrayWeaklyPinned#, isMutableByteArrayWeaklyPinned# - -- deprecated - , BCO, mkApUpd0#, newBCO# - -- Don't re-export vector FMA instructions , fmaddFloatX4# , fmsubFloatX4# @@ -255,8 +246,6 @@ import GHC.Prim hiding , minWord8X32# , minWord8X64# ) -import qualified GHC.Prim as Prim - ( BCO, mkApUpd0#, newBCO# ) import GHC.Prim.Ext ===================================== libraries/ghci/GHCi/CreateBCO.hs ===================================== @@ -6,10 +6,6 @@ {-# LANGUAGE UnboxedTuples #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE CPP #-} -{-# OPTIONS_GHC -Wno-warnings-deprecations #-} --- TODO We want to import GHC.Internal.Base (BCO, mkApUpd0#, newBCO#) instead --- of from GHC.Exts when we can require of the bootstrap compiler to have --- ghc-internal. -- -- (c) The University of Glasgow 2002-2006 @@ -30,7 +26,8 @@ import Data.Array.Base import Foreign hiding (newArray) import Unsafe.Coerce (unsafeCoerce) import GHC.Arr ( Array(..) ) -import GHC.Exts +import GHC.Exts hiding ( BCO, mkApUpd0#, newBCO# ) +import GHC.Internal.Base ( BCO, mkApUpd0#, newBCO# ) import GHC.IO import Control.Exception ( ErrorCall(..) ) ===================================== libraries/ghci/GHCi/TH.hs ===================================== @@ -1,9 +1,6 @@ {-# LANGUAGE ScopedTypeVariables, StandaloneDeriving, DeriveGeneric, TupleSections, RecordWildCards, InstanceSigs, CPP #-} {-# OPTIONS_GHC -fno-warn-name-shadowing #-} -{-# OPTIONS_GHC -Wno-warnings-deprecations #-} --- TODO We want to import GHC.Internal.Desugar instead of GHC.Desugar when we --- can require of the bootstrap compiler to have ghc-internal. -- | -- Running TH splices @@ -112,7 +109,7 @@ import Data.IORef import Data.Map (Map) import qualified Data.Map as M import Data.Maybe -import GHC.Desugar (AnnotationWrapper(..)) +import GHC.Internal.Desugar (AnnotationWrapper(..)) import qualified GHC.Boot.TH.Syntax as TH import Unsafe.Coerce ===================================== libraries/ghci/ghci.cabal.in ===================================== @@ -86,11 +86,7 @@ library rts, array == 0.5.*, base >= 4.8 && < 4.23, - -- ghc-internal == @ProjectVersionForLib@.* - -- TODO: Use GHC.Internal.Desugar and GHC.Internal.Base from - -- ghc-internal instead of ignoring the deprecation warning in GHCi.TH - -- and GHCi.CreateBCO when we require ghc-internal of the bootstrap - -- compiler + ghc-internal >= 9.1001.0 && <=@ProjectVersionForLib@.0, ghc-prim >= 0.5.0 && < 0.14, binary == 0.8.*, bytestring >= 0.10 && < 0.13, ===================================== rts/Disassembler.c ===================================== @@ -89,7 +89,7 @@ disInstr ( StgBCO *bco, int pc ) p1 = BCO_GET_LARGE_ARG; info_mod = BCO_GET_LARGE_ARG; info_unit_id = BCO_GET_LARGE_ARG; - info_wix = BCO_NEXT; + info_wix = BCO_READ_NEXT_32; np = BCO_GET_LARGE_ARG; debugBelch ("BRK_FUN " ); printPtr( ptrs[p1] ); debugBelch("%" FMT_Word, literals[info_mod] ); ===================================== rts/Interpreter.c ===================================== @@ -720,7 +720,7 @@ interpretBCO (Capability* cap) arg1_brk_array = BCO_GET_LARGE_ARG; /* info_mod_name = */ BCO_GET_LARGE_ARG; /* info_mod_id = */ BCO_GET_LARGE_ARG; - arg4_info_index = BCO_NEXT; + arg4_info_index = BCO_READ_NEXT_32; StgPtr* ptrs = (StgPtr*)(&bco->ptrs->payload[0]); StgArrBytes* breakPoints = (StgArrBytes *) BCO_PTR(arg1_brk_array); @@ -1542,7 +1542,7 @@ run_BCO: arg1_brk_array = BCO_GET_LARGE_ARG; arg2_info_mod_name = BCO_GET_LARGE_ARG; arg3_info_mod_id = BCO_GET_LARGE_ARG; - arg4_info_index = BCO_NEXT; + arg4_info_index = BCO_READ_NEXT_32; #if defined(PROFILING) arg5_cc = BCO_GET_LARGE_ARG; #else ===================================== testsuite/tests/module/T21752.stderr deleted ===================================== @@ -1,32 +0,0 @@ -T21752A.hs:4:5: warning: [GHC-68441] [-Wdeprecations (in -Wextended-warnings)] - In the use of ‘newBCO#’ (imported from GHC.Exts): - Deprecated: "The BCO, mkApUpd0#, and newBCO# re-exports from GHC.Exts have been deprecated and will be removed in 9.14 - These symbols should be imported from ghc-internal instead if needed." - -T21752A.hs:4:5: warning: [GHC-68441] [-Wdeprecations (in -Wextended-warnings)] - In the use of ‘newBCO#’ (imported from GHC.Exts): - Deprecated: "The BCO, mkApUpd0#, and newBCO# re-exports from GHC.Exts have been deprecated and will be removed in 9.14 - These symbols should be imported from ghc-internal instead if needed." - -T21752A.hs:4:5: warning: [GHC-68441] [-Wdeprecations (in -Wextended-warnings)] - In the use of ‘mkApUpd0#’ (imported from GHC.Exts): - Deprecated: "The BCO, mkApUpd0#, and newBCO# re-exports from GHC.Exts have been deprecated and will be removed in 9.14 - These symbols should be imported from ghc-internal instead if needed." - -T21752A.hs:4:5: warning: [GHC-68441] [-Wdeprecations (in -Wextended-warnings)] - In the use of ‘mkApUpd0#’ (imported from GHC.Exts): - Deprecated: "The BCO, mkApUpd0#, and newBCO# re-exports from GHC.Exts have been deprecated and will be removed in 9.14 - These symbols should be imported from ghc-internal instead if needed." - -T21752A.hs:4:5: warning: [GHC-68441] [-Wdeprecations (in -Wextended-warnings)] - In the use of type constructor or class ‘BCO’ - (imported from GHC.Exts): - Deprecated: "The BCO, mkApUpd0#, and newBCO# re-exports from GHC.Exts have been deprecated and will be removed in 9.14 - These symbols should be imported from ghc-internal instead if needed." - -T21752A.hs:4:5: warning: [GHC-68441] [-Wdeprecations (in -Wextended-warnings)] - In the use of type constructor or class ‘BCO’ - (imported from GHC.Exts): - Deprecated: "The BCO, mkApUpd0#, and newBCO# re-exports from GHC.Exts have been deprecated and will be removed in 9.14 - These symbols should be imported from ghc-internal instead if needed." - ===================================== 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/-/compare/1bfe81288fe9932253919504b969d52... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1bfe81288fe9932253919504b969d52... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Marge Bot (@marge-bot)