[Git][ghc/ghc][wip/fix-25636] Converting naming to NullaryClosure
recursion-ninja pushed to branch wip/fix-25636 at Glasgow Haskell Compiler / GHC Commits: 3022392c by Recursion Ninja at 2025-12-02T13:09:14-05:00 Converting naming to NullaryClosure - - - - - 14 changed files: - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Linker.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Linker/Loader.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToJS/Prim.hs - libraries/ghci/GHCi/CreateBCO.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/ResolvedBCO.hs - libraries/ghci/GHCi/Run.hs - libraries/ghci/ghci.cabal.in - rts/PrimOps.cmm Changes: ===================================== compiler/GHC/Builtin/primops.txt.pp ===================================== @@ -3937,9 +3937,9 @@ primop MkApUpd0_Op "mkApUpd0#" GenPrimOp with out_of_line = True -primop NewUDCOp "newUDC#" GenPrimOp +primop NewNullaryClosureOp "newNullaryClosure#" GenPrimOp Addr# -> State# s -> (# State# s, a #) - { @newUDC#@ allocates a new application of an + { @newNullaryClosure#@ allocates a new application of an unlifted data constructor (identified by its info table). } with effect = ReadWriteEffect ===================================== compiler/GHC/ByteCode/Asm.hs ===================================== @@ -107,7 +107,7 @@ bcoFreeNames bco assembleBCOs :: Profile -> FlatBag (ProtoBCO Name) - -> FlatBag UnlinkedUDC + -> FlatBag UnlinkedNullaryClosure -> [TyCon] -> [(Name, ByteString)] -> Maybe InternalModBreaks ===================================== compiler/GHC/ByteCode/Linker.hs ===================================== @@ -59,7 +59,7 @@ linkBCO -> PkgsLoaded -> LinkerEnv -> LinkedBreaks - -> NameEnv Int -- Named UDCs + -> NameEnv Int -- Named NullaryClosures -> NameEnv Int -- Named BCOs -> UnlinkedBCO -> IO ResolvedBCO @@ -161,13 +161,13 @@ resolvePtr -> PkgsLoaded -> LinkerEnv -> LinkedBreaks - -> NameEnv Int -- Named UDCs + -> NameEnv Int -- Named NullaryClosures -> NameEnv Int -- Named BCOs -> BCOPtr -> IO ResolvedBCOPtr resolvePtr interp pkgs_loaded le lb udc_ix bco_ix ptr = case ptr of BCOPtrName nm - | Just ix <- lookupNameEnv udc_ix nm -- ref to another UDC in this group + | Just ix <- lookupNameEnv udc_ix nm -- ref to another NullaryClosure in this group -> return (ResolvedBCORefUnlifted ix) | Just ix <- lookupNameEnv bco_ix nm -- ref to another BCO in this group ===================================== compiler/GHC/ByteCode/Types.hs ===================================== @@ -16,7 +16,7 @@ module GHC.ByteCode.Types , RegBitmap(..) , NativeCallType(..), NativeCallInfo(..), voidTupleReturnInfo, voidPrimCallInfo , ByteOff(..), WordOff(..), HalfWord(..) - , UnlinkedUDC(..) + , UnlinkedNullaryClosure(..) , UnlinkedBCO(..), BCOPtr(..), BCONPtr(..) , ItblEnv, ItblPtr(..) , AddrEnv, AddrPtr(..) @@ -62,7 +62,7 @@ data CompiledByteCode = CompiledByteCode { bc_bcos :: FlatBag UnlinkedBCO -- ^ Bunch of interpretable bindings - , bc_udcs :: FlatBag UnlinkedUDC + , bc_udcs :: FlatBag UnlinkedNullaryClosure , bc_itbls :: [(Name, ConInfoTable)] -- ^ Mapping from DataCons to their info tables @@ -178,16 +178,16 @@ newtype AddrPtr = AddrPtr (RemotePtr ()) {- | Named reference to an unlifted data constructor -} -data UnlinkedUDC - = UnlinkedUDC { - unlinkedUDCName :: !Name, - unlinkedUDCInfo :: !ConInfoTable +data UnlinkedNullaryClosure + = UnlinkedNullaryClosure { + unlinkedNullaryClosureName :: !Name, + unlinkedNullaryClosureInfo :: !ConInfoTable } -instance NFData UnlinkedUDC where - rnf UnlinkedUDC{..} = - rnf unlinkedUDCName `seq` - rnf unlinkedUDCInfo +instance NFData UnlinkedNullaryClosure where + rnf UnlinkedNullaryClosure{..} = + rnf unlinkedNullaryClosureName `seq` + rnf unlinkedNullaryClosureInfo {- -------------------------------------------------------------------------------- ===================================== compiler/GHC/Linker/Loader.hs ===================================== @@ -1019,21 +1019,21 @@ linkSomeBCOs :: Interp linkSomeBCOs interp pkgs_loaded le lb mods = foldr fun do_link mods [] where - fun :: CompiledByteCode -> ([([UnlinkedUDC], [UnlinkedBCO])] -> t) -> [([UnlinkedUDC], [UnlinkedBCO])] -> t + fun :: CompiledByteCode -> ([([UnlinkedNullaryClosure], [UnlinkedBCO])] -> t) -> [([UnlinkedNullaryClosure], [UnlinkedBCO])] -> t fun CompiledByteCode{..} inner accum = inner ((Foldable.toList bc_udcs, Foldable.toList bc_bcos) : accum) - do_link :: [([UnlinkedUDC], [UnlinkedBCO])] -> IO [(Name, HValueRef)] + do_link :: [([UnlinkedNullaryClosure], [UnlinkedBCO])] -> IO [(Name, HValueRef)] do_link [] = return [] do_link mods = do - let flat_UDCs = [ udc | (udcs, _) <- mods, udc <- udcs ] + let flat_NullaryClosures = [ udc | (udcs, _) <- mods, udc <- udcs ] flat_BCOs = [ bco | (_, bcos) <- mods, bco <- bcos ] - names_UDCs = map unlinkedUDCName flat_UDCs + names_NullaryClosures = map unlinkedNullaryClosureName flat_NullaryClosures names_BCOs = map unlinkedBCOName flat_BCOs index_BCO = mkNameEnv (zip names_BCOs [0 ..]) - index_UDC = mkNameEnv (zip names_UDCs [length names_BCOs ..]) + index_NullaryClosure = mkNameEnv (zip names_NullaryClosures [length names_BCOs ..]) - resolved_BCOs <- sequence [ linkBCO interp pkgs_loaded le lb index_UDC index_BCO bco | bco <- flat_BCOs ] + resolved_BCOs <- sequence [ linkBCO interp pkgs_loaded le lb index_NullaryClosure index_BCO bco | bco <- flat_BCOs ] hvrefs <- createBCOs interp resolved_BCOs return (zip names_BCOs hvrefs) ===================================== compiler/GHC/StgToByteCode.hs ===================================== @@ -103,7 +103,7 @@ import Control.Monad.Trans.Reader (ReaderT(..)) import Control.Monad.Trans.State (StateT(..)) import Data.Bifunctor (Bifunctor(..)) -import GHCi.ResolvedBCO (ResolvedUDC(..)) +import GHCi.ResolvedBCO (ResolvedNullaryClosure(..)) -- ----------------------------------------------------------------------------- @@ -310,7 +310,7 @@ argBits platform (rep : args) -- Compile code for the right-hand side of a top-level binding -schemeTopBind :: (Id, CgStgRhs) -> BcM (Either UnlinkedUDC (ProtoBCO Name)) +schemeTopBind :: (Id, CgStgRhs) -> BcM (Either UnlinkedNullaryClosure (ProtoBCO Name)) schemeTopBind (id, rhs) | isUnliftedType (varType id), StgRhsCon _ dCon conNo _ _ _ <- rhs = do profile <- getProfile @@ -334,8 +334,8 @@ schemeTopBind (id, rhs) Numbered i -> i NoNumber -> 0 -- This defaulting seems unsafe? - finalizer :: ConInfoTable -> Either UnlinkedUDC a - finalizer = Left . UnlinkedUDC (getName id) + finalizer :: ConInfoTable -> Either UnlinkedNullaryClosure a + finalizer = Left . UnlinkedNullaryClosure (getName id) pure . finalizer $ ConInfoTable tables_next_to_code ===================================== compiler/GHC/StgToCmm/Prim.hs ===================================== @@ -1771,7 +1771,7 @@ emitPrimOp cfg primop = DataToTagSmallOp -> alwaysExternal DataToTagLargeOp -> alwaysExternal MkApUpd0_Op -> alwaysExternal - NewUDCOp -> alwaysExternal + NewNullaryClosureOp -> alwaysExternal NewBCOOp -> alwaysExternal UnpackClosureOp -> alwaysExternal ListThreadsOp -> alwaysExternal ===================================== compiler/GHC/StgToJS/Prim.hs ===================================== @@ -1164,7 +1164,7 @@ genPrim prof bound ty op = case op of GetSparkOp -> unhandledPrimop op AnyToAddrOp -> unhandledPrimop op MkApUpd0_Op -> unhandledPrimop op - NewUDCOp -> unhandledPrimop op + NewNullaryClosureOp -> unhandledPrimop op NewBCOOp -> unhandledPrimop op UnpackClosureOp -> unhandledPrimop op ClosureSizeOp -> unhandledPrimop op ===================================== libraries/ghci/GHCi/CreateBCO.hs ===================================== @@ -14,7 +14,7 @@ -- -- | Create real byte-code objects from 'ResolvedBCO's and 'NullaryDataConApp's. -module GHCi.CreateBCO (createBCOs, createUDCs) where +module GHCi.CreateBCO (createBCOs, createNullaryClosures) where import Prelude -- See note [Why do we import Prelude here?] import GHCi.BreakArray @@ -28,20 +28,20 @@ import Data.Array.Base import Foreign hiding (newArray) import Unsafe.Coerce (unsafeCoerce) import GHC.Arr ( Array(..) ) -import GHC.Exts hiding ( BCO, mkApUpd0#, newBCO#, newUDC# ) -import GHC.Internal.Base ( BCO, mkApUpd0#, newBCO#, newUDC# ) +import GHC.Exts hiding ( BCO, mkApUpd0#, newBCO#, newNullaryClosure# ) +import GHC.Internal.Base ( BCO, mkApUpd0#, newBCO#, newNullaryClosure# ) import GHC.IO import GHC.Exts.Heap ( StgInfoTable ) import Control.Exception ( ErrorCall(..) ) -createUDCs :: [RemotePtr StgInfoTable] -> IO [HValueRef] -createUDCs dcas = do - mapM createUnliftedDataConstructor dcas +createNullaryClosures :: [RemotePtr StgInfoTable] -> IO [HValueRef] +createNullaryClosures dcas = do + mapM createNullaryClosure dcas -createUnliftedDataConstructor :: RemotePtr StgInfoTable -> IO HValueRef -createUnliftedDataConstructor infoTablePtr = +createNullaryClosure :: RemotePtr StgInfoTable -> IO HValueRef +createNullaryClosure infoTablePtr = let !(Ptr !addr#) = fromRemotePtr infoTablePtr - in IO $ \s -> newUDC# addr# s + in IO $ \s -> newNullaryClosure# addr# s createBCOs :: [ResolvedBCO] -> IO [HValueRef] createBCOs bcos = do ===================================== libraries/ghci/GHCi/Message.hs ===================================== @@ -106,7 +106,7 @@ data Message a where -- see Note [Parallelize CreateBCOs serialization] CreateBCOs :: [ResolvedBCO] -> Message [HValueRef] - CreateUDCs :: [ResolvedUDC] -> Message [HValueRef] + CreateNullaryClosures :: [ResolvedNullaryClosure] -> Message [HValueRef] -- | Release 'HValueRef's FreeHValueRefs :: [HValueRef] -> Message () @@ -588,7 +588,7 @@ getMessage = do 38 -> Msg <$> (ResumeSeq <$> get) 39 -> Msg <$> (LookupSymbolInDLL <$> get <*> get) 40 -> Msg <$> (WhereFrom <$> get) - 41 -> Msg <$> (CreateUDCs <$> get) + 41 -> Msg <$> (CreateNullaryClosures <$> get) _ -> error $ "Unknown Message code " ++ (show b) putMessage :: Message a -> Put @@ -635,7 +635,7 @@ putMessage m = case m of ResumeSeq a -> putWord8 38 >> put a LookupSymbolInDLL dll str -> putWord8 39 >> put dll >> put str WhereFrom a -> putWord8 40 >> put a - CreateUDCs ptr -> putWord8 41 >> put ptr + CreateNullaryClosures ptr -> putWord8 41 >> put ptr {- Note [Parallelize CreateBCOs serialization] ===================================== libraries/ghci/GHCi/ResolvedBCO.hs ===================================== @@ -4,7 +4,7 @@ module GHCi.ResolvedBCO ( ResolvedBCO(..) , ResolvedBCOPtr(..) - , ResolvedUDC(..) + , ResolvedNullaryClosure(..) , isLittleEndian , BCOByteArray(..) , mkBCOByteArray @@ -52,7 +52,7 @@ instance Binary ConInfoTable instance NFData ConInfoTable -- ----------------------------------------------------------------------------- --- ResolvedUDC +-- ResolvedNullaryClosure -- | A 'ResolvedBCO' is one in which all the 'Name' references have been -- resolved to actual addresses or 'RemoteHValues'. @@ -69,11 +69,11 @@ data ResolvedBCO } deriving (Generic, Show) --- | A 'ResolvedUDC' is one in which all arguments have been applied to +-- | A 'ResolvedNullaryClosure' is one in which all arguments have been applied to -- a (potentially unlifted) data constructor. -newtype ResolvedUDC - = ResolvedUDC { - unliftedDataConInfo :: ConInfoTable -- RemotePtr StgInfoTable +newtype ResolvedNullaryClosure + = ResolvedNullaryClosure { + unliftedDataConInfo :: ConInfoTable } deriving (Binary, Generic, NFData, Show) ===================================== libraries/ghci/GHCi/Run.hs ===================================== @@ -79,8 +79,8 @@ run m = case m of MkConInfoTable infoTable -> convertInfoTable infoTable ResolveObjs -> resolveObjs FindSystemLibrary str -> findSystemLibrary str - CreateUDCs dcas -> - traverse (convertInfoTable . unliftedDataConInfo) dcas >>= createUDCs + CreateNullaryClosures dcas -> + traverse (convertInfoTable . unliftedDataConInfo) dcas >>= createNullaryClosures CreateBCOs bcos -> createBCOs bcos LookupClosure str -> lookupClosure str #endif ===================================== libraries/ghci/ghci.cabal.in ===================================== @@ -83,6 +83,7 @@ library GHCi.Utils Build-Depends: + rts, array == 0.5.*, base >= 4.8 && < 4.23, binary == 0.8.*, @@ -94,7 +95,6 @@ library ghc-heap >= 9.10.1 && <=@ProjectVersionMunged@, ghc-internal >= 9.1001.0 && <=@ProjectVersionForLib@.0, ghc-prim >= 0.5.0 && < 0.14, - rts, transformers >= 0.5 && < 0.7 if flag(bootstrap) ===================================== rts/PrimOps.cmm ===================================== @@ -2145,7 +2145,7 @@ stg_deRefStablePtrzh ( P_ sp ) Bytecode object primitives ------------------------------------------------------------------------- */ -stg_newUDHzh ( W_ datacon_itbl ) +stg_newNullaryClosurezh ( W_ datacon_itbl ) { W_ p; ALLOC_PRIM(SIZEOF_StgHeader); View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3022392cd8909a164dd528d85fb13a4b... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3022392cd8909a164dd528d85fb13a4b... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
recursion-ninja (@recursion-ninja)