Matthew Pickering pushed to branch wip/ghc-upsweep-spt at Glasgow Haskell Compiler / GHC
Commits:
-
290f8357
by Matthew Pickering at 2025-09-29T11:50:38+01:00
4 changed files:
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Iface/Tidy/StaticPtrTable.hs
- compiler/GHC/Linker/Loader.hs
Changes:
... | ... | @@ -102,7 +102,6 @@ module GHC.Driver.Main |
102 | 102 | , dumpIfaceStats
|
103 | 103 | , ioMsgMaybe
|
104 | 104 | , showModuleIndex
|
105 | - , hscAddSptEntries
|
|
106 | 105 | , writeInterfaceOnlyMode
|
107 | 106 | , loadByteCode
|
108 | 107 | , genModDetails
|
... | ... | @@ -2515,9 +2514,6 @@ hscParsedDecls hsc_env decls = runInteractiveHsc hsc_env $ do |
2515 | 2514 | let src_span = srcLocSpan interactiveSrcLoc
|
2516 | 2515 | _ <- liftIO $ loadDecls interp hsc_env src_span linkable
|
2517 | 2516 | |
2518 | - {- Load static pointer table entries -}
|
|
2519 | - liftIO $ hscAddSptEntries hsc_env (cg_spt_entries tidy_cg)
|
|
2520 | - |
|
2521 | 2517 | let tcs = filterOut isImplicitTyCon (mg_tcs simpl_mg)
|
2522 | 2518 | patsyns = mg_patsyns simpl_mg
|
2523 | 2519 | |
... | ... | @@ -2539,18 +2535,6 @@ hscParsedDecls hsc_env decls = runInteractiveHsc hsc_env $ do |
2539 | 2535 | fam_insts defaults fix_env
|
2540 | 2536 | return (new_tythings, new_ictxt)
|
2541 | 2537 | |
2542 | --- | Load the given static-pointer table entries into the interpreter.
|
|
2543 | --- See Note [Grand plan for static forms] in "GHC.Iface.Tidy.StaticPtrTable".
|
|
2544 | -hscAddSptEntries :: HscEnv -> [SptEntry] -> IO ()
|
|
2545 | -hscAddSptEntries hsc_env entries = do
|
|
2546 | - let interp = hscInterp hsc_env
|
|
2547 | - let add_spt_entry :: SptEntry -> IO ()
|
|
2548 | - add_spt_entry (SptEntry n fpr) = do
|
|
2549 | - -- These are only names from the current module
|
|
2550 | - (val, _, _) <- loadName interp hsc_env n
|
|
2551 | - addSptEntry interp fpr val
|
|
2552 | - mapM_ add_spt_entry entries
|
|
2553 | - |
|
2554 | 2538 | {-
|
2555 | 2539 | Note [Fixity declarations in GHCi]
|
2556 | 2540 | ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
|
... | ... | @@ -56,8 +56,6 @@ import GHC.Tc.Utils.Monad ( initIfaceCheck, concatMapM ) |
56 | 56 | |
57 | 57 | import GHC.Runtime.Interpreter
|
58 | 58 | import qualified GHC.Linker.Loader as Linker
|
59 | -import GHC.Linker.Types
|
|
60 | - |
|
61 | 59 | |
62 | 60 | import GHC.Driver.Config.Diagnostic
|
63 | 61 | import GHC.Driver.Pipeline
|
... | ... | @@ -72,8 +70,6 @@ import GHC.Driver.MakeSem |
72 | 70 | import GHC.Driver.Downsweep
|
73 | 71 | import GHC.Driver.MakeAction
|
74 | 72 | |
75 | -import GHC.ByteCode.Types
|
|
76 | - |
|
77 | 73 | import GHC.Iface.Load ( cannotFindModule, readIface )
|
78 | 74 | import GHC.IfaceToCore ( typecheckIface )
|
79 | 75 | import GHC.Iface.Recomp ( RecompileRequired(..), CompileReason(..) )
|
... | ... | @@ -1232,31 +1228,9 @@ upsweep_mod :: HscEnv |
1232 | 1228 | upsweep_mod hsc_env mHscMessage old_hmi summary mod_index nmods = do
|
1233 | 1229 | hmi <- compileOne' mHscMessage hsc_env summary
|
1234 | 1230 | mod_index nmods (hm_iface <$> old_hmi) (maybe emptyHomeModInfoLinkable hm_linkable old_hmi)
|
1235 | - |
|
1236 | - -- MP: This is a bit janky, because before you add the entries you have to extend the HPT with the module
|
|
1237 | - -- you just compiled. Another option, would be delay adding anything until after upsweep has finished, but I
|
|
1238 | - -- am unsure if this is sound (wrt running TH splices for example).
|
|
1239 | - -- This function only does anything if the linkable produced is a BCO, which
|
|
1240 | - -- used to only happen with the bytecode backend, but with
|
|
1241 | - -- @-fprefer-byte-code@, @HomeModInfo@ has bytecode even when generating
|
|
1242 | - -- object code, see #25230.
|
|
1243 | 1231 | hscInsertHPT hmi hsc_env
|
1244 | - addSptEntries (hsc_env)
|
|
1245 | - (homeModInfoByteCode hmi)
|
|
1246 | - |
|
1247 | 1232 | return hmi
|
1248 | 1233 | |
1249 | --- | Add the entries from a BCO linkable to the SPT table, see
|
|
1250 | --- See Note [Grand plan for static forms] in GHC.Iface.Tidy.StaticPtrTable.
|
|
1251 | -addSptEntries :: HscEnv -> Maybe Linkable -> IO ()
|
|
1252 | -addSptEntries hsc_env mlinkable =
|
|
1253 | - hscAddSptEntries hsc_env
|
|
1254 | - [ spt
|
|
1255 | - | linkable <- maybeToList mlinkable
|
|
1256 | - , bco <- linkableBCOs linkable
|
|
1257 | - , spt <- bc_spt_entries bco
|
|
1258 | - ]
|
|
1259 | - |
|
1260 | 1234 | |
1261 | 1235 | -- Note [When source is considered modified]
|
1262 | 1236 | -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
|
... | ... | @@ -124,7 +124,7 @@ Here is a running example: |
124 | 124 | * If we are compiling for the byte-code interpreter, we instead explicitly add
|
125 | 125 | the SPT entries (recorded in CgGuts' cg_spt_entries field) to the interpreter
|
126 | 126 | process' SPT table using the addSptEntry interpreter message. This happens
|
127 | - in upsweep after we have compiled the module (see GHC.Driver.Make.upsweep').
|
|
127 | + when the bytecode object is linked in `dynLinkBCOs`.
|
|
128 | 128 | -}
|
129 | 129 | |
130 | 130 | import GHC.Prelude
|
... | ... | @@ -717,6 +717,7 @@ loadDecls interp hsc_env span linkable = do |
717 | 717 | let ce2 = extendClosureEnv (closure_env le2) nms_fhvs
|
718 | 718 | !pls2 = pls { linker_env = le2 { closure_env = ce2 }
|
719 | 719 | , linked_breaks = lb2 }
|
720 | + mapM_ (linkSptEntry interp ce2) (concatMap bc_spt_entries cbcs)
|
|
720 | 721 | return (pls2, (nms_fhvs, links_needed, units_needed))
|
721 | 722 | where
|
722 | 723 | cbcs = linkableBCOs linkable
|
... | ... | @@ -950,10 +951,28 @@ dynLinkBCOs interp pls bcos = do |
950 | 951 | -- Wrap finalizers on the ones we want to keep
|
951 | 952 | new_binds <- makeForeignNamedHValueRefs interp to_add
|
952 | 953 | |
954 | + |
|
953 | 955 | let ce2 = extendClosureEnv (closure_env le2) new_binds
|
956 | + |
|
957 | + -- Add SPT entries
|
|
958 | + mapM_ (linkSptEntry interp ce2) (concatMap bc_spt_entries cbcs)
|
|
959 | + |
|
954 | 960 | return $! pls1 { linker_env = le2 { closure_env = ce2 }
|
955 | 961 | , linked_breaks = lb2 }
|
956 | 962 | |
963 | +-- | Register SPT entries for this module in the interpreter
|
|
964 | +-- Assumes that the name from the SPT has already been loaded into the interpreter.
|
|
965 | +linkSptEntry :: Interp -> ClosureEnv -> SptEntry -> IO ()
|
|
966 | +linkSptEntry interp ce (SptEntry name fpr) = do
|
|
967 | + case lookupNameEnv ce name of
|
|
968 | + -- The SPT entries only point to locally defined names, which should have already been
|
|
969 | + -- loaded into the interpreter before this function is called.
|
|
970 | + Nothing -> pprPanic "linkSptEntry" (ppr name)
|
|
971 | + Just (_, hval) -> addSptEntry interp fpr hval
|
|
972 | + |
|
973 | + |
|
974 | + |
|
975 | + |
|
957 | 976 | -- Link a bunch of BCOs and return references to their values
|
958 | 977 | linkSomeBCOs :: Interp
|
959 | 978 | -> PkgsLoaded
|