[Git][ghc/ghc][wip/romes/25636] 101%
Rodrigo Mesquita pushed to branch wip/romes/25636 at Glasgow Haskell Compiler / GHC Commits: 0018ec46 by Rodrigo Mesquita at 2025-12-19T18:00:31+00:00 101% - - - - - 3 changed files: - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/Cmm/Liveness.hs - libraries/ghci/GHCi/CreateBCO.hs Changes: ===================================== compiler/GHC/Builtin/primops.txt.pp ===================================== @@ -3948,7 +3948,7 @@ primop NewBCOOp "newBCO#" GenPrimOp out_of_line = True primop NewConAppObjOp "newConAppObj#" GenPrimOp - Addr# -> ByteArray# -> Array# a -> Word# -> State# s -> (# State# s, a #) + Addr# -> ByteArray# -> Array# a -> Word# -> State# s -> (# State# s, b #) { @'newConAppObj#' datacon_itbl lits ptrs arity@ creates a new constructor application object on the heap from the info table pointer of the data constructor and the data arguments given in @ptrs@ and @lits@. The ===================================== compiler/GHC/Cmm/Liveness.hs ===================================== @@ -65,7 +65,7 @@ cmmGlobalLiveness platform graph = -- | On entry to the procedure, there had better not be any LocalReg's live-in. -- If you see this error it most likely means you are trying to use a variable --- without it being defined in the given scope. +-- without it being defined, or initialized, in the given scope. noLiveOnEntry :: BlockId -> CmmLive LocalReg -> a -> a noLiveOnEntry bid in_fact x = if nullRegSet in_fact then x ===================================== libraries/ghci/GHCi/CreateBCO.hs ===================================== @@ -20,7 +20,6 @@ import Prelude -- See note [Why do we import Prelude here?] import GHCi.ResolvedBCO import GHCi.RemoteTypes import GHCi.BreakArray -import GHCi.InfoTable import GHC.Data.SizedSeq import System.IO (fixIO) @@ -33,8 +32,6 @@ import GHC.Exts hiding ( BCO, mkApUpd0#, newBCO# ) import GHC.Internal.Base ( BCO, mkApUpd0#, newBCO# ) import GHC.IO import Control.Exception ( ErrorCall(..) ) -import Data.Kind -import Data.Maybe createBCOs :: [ResolvedBCO] -> IO [HValueRef] createBCOs bcos = do @@ -54,7 +51,7 @@ createBCO _ obj | resolvedBCOIsLE obj /= isLittleEndian createBCO arr bco = do linked_thing <- linkBCO' arr bco case linked_thing of - Left linked_bco -> do + LinkedBCO bco_arity linked_bco -> do -- Note [Updatable CAF BCOs] -- ~~~~~~~~~~~~~~~~~~~~~~~~~ -- Why do we need mkApUpd0 here? Otherwise top-level @@ -70,14 +67,18 @@ createBCO arr bco -- non-zero arity BCOs in an AP thunk. -- -- See #17424. - if (resolvedBCOArity bco > 0) + if (bco_arity > 0) then return (HValue (unsafeCoerce linked_bco)) else case mkApUpd0# linked_bco of { (# final_bco #) -> return (HValue final_bco) } - Right linked_static_con -> do + LinkedStaticCon linked_static_con -> do return linked_static_con -linkBCO' :: Array Int HValue -> ResolvedBCO -> IO (Either BCO HValue) +data LinkedBCO + = LinkedBCO !Int{-BCO arity-} BCO + | LinkedStaticCon HValue + +linkBCO' :: Array Int HValue -> ResolvedBCO -> IO LinkedBCO linkBCO' arr resolved_obj = case resolved_obj of ResolvedBCO{..} -> do @@ -94,7 +95,8 @@ linkBCO' arr resolved_obj = PtrsArr marr <- mkPtrsArray arr n_ptrs ptrs IO $ \s -> case unsafeFreezeArray# marr s of { (# s, arr #) -> - case Left <$> newBCO insns_barr literals_barr arr arity# bitmap_barr of { IO io -> + case LinkedBCO resolvedBCOArity <$> + newBCO insns_barr literals_barr arr arity# bitmap_barr of { IO io -> io s }} ResolvedStaticCon{..} -> do @@ -114,7 +116,7 @@ linkBCO' arr resolved_obj = IO $ \s -> case unsafeFreezeArray# marr s of { (# s, arr #) -> case newConAppObj# itbl_ptr# literals_barr arr data_size# s of - (# s, hval #) -> (# s, Right (HValue hval) #) + (# s, hval #) -> (# s, LinkedStaticCon (HValue hval) #) } where !(EmptyArr empty#) = emptyArr -- See Note [BCO empty array] View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0018ec46e901cdbc381196bca5b946eb... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0018ec46e901cdbc381196bca5b946eb... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Rodrigo Mesquita (@alt-romes)