| ... |
... |
@@ -27,6 +27,7 @@ module GHC.Linker.Loader |
|
27
|
27
|
, withExtendedLoadedEnv
|
|
28
|
28
|
, extendLoadedEnv
|
|
29
|
29
|
, deleteFromLoadedEnv
|
|
|
30
|
+ , lookupFromLoadedEnv
|
|
30
|
31
|
-- * Internals
|
|
31
|
32
|
, allocateBreakArrays
|
|
32
|
33
|
, rmDupLinkables
|
| ... |
... |
@@ -212,6 +213,15 @@ deleteFromLoadedEnv interp to_remove = |
|
212
|
213
|
return $ modifyClosureEnv pls $ \ce ->
|
|
213
|
214
|
delListFromNameEnv ce to_remove
|
|
214
|
215
|
|
|
|
216
|
+-- | Have we already loaded a name into the interpreter?
|
|
|
217
|
+lookupFromLoadedEnv :: Interp -> Name -> IO (Maybe ForeignHValue)
|
|
|
218
|
+lookupFromLoadedEnv interp name = do
|
|
|
219
|
+ mstate <- getLoaderState interp
|
|
|
220
|
+ return $ do
|
|
|
221
|
+ pls <- mstate
|
|
|
222
|
+ res <- lookupNameEnv (closure_env (linker_env pls)) name
|
|
|
223
|
+ return (snd res)
|
|
|
224
|
+
|
|
215
|
225
|
-- | Load the module containing the given Name and get its associated 'HValue'.
|
|
216
|
226
|
--
|
|
217
|
227
|
-- Throws a 'ProgramError' if loading fails or the name cannot be found.
|
| ... |
... |
@@ -257,7 +267,7 @@ loadDependencies interp hsc_env pls span needed_mods = do |
|
257
|
267
|
|
|
258
|
268
|
-- Link the packages and modules required
|
|
259
|
269
|
pls1 <- loadPackages' interp hsc_env (ldUnits deps) pls
|
|
260
|
|
- (pls2, succ) <- loadModuleLinkables interp hsc_env pls1 (ldNeededLinkables deps)
|
|
|
270
|
+ (pls2, succ) <- loadExternalModuleLinkables interp hsc_env pls1 (ldNeededLinkables deps)
|
|
261
|
271
|
let this_pkgs_loaded = udfmRestrictKeys all_pkgs_loaded $ getUniqDSet trans_pkgs_needed
|
|
262
|
272
|
all_pkgs_loaded = pkgs_loaded pls2
|
|
263
|
273
|
trans_pkgs_needed = unionManyUniqDSets (this_pkgs_needed : [ loaded_pkg_trans_deps pkg
|
| ... |
... |
@@ -683,41 +693,23 @@ get_reachable_nodes hsc_env mods |
|
683
|
693
|
|
|
684
|
694
|
********************************************************************* -}
|
|
685
|
695
|
|
|
686
|
|
-loadDecls :: Interp -> HscEnv -> SrcSpan -> Linkable -> IO ([(Name, ForeignHValue)], [Linkable], PkgsLoaded)
|
|
|
696
|
+-- | Load the dependencies of a linkable, and then load the linkable itself.
|
|
|
697
|
+loadDecls :: Interp -> HscEnv -> SrcSpan -> Linkable -> IO ([Linkable], PkgsLoaded)
|
|
687
|
698
|
loadDecls interp hsc_env span linkable = do
|
|
688
|
699
|
-- Initialise the linker (if it's not been done already)
|
|
689
|
700
|
initLoaderState interp hsc_env
|
|
690
|
701
|
|
|
691
|
702
|
-- Take lock for the actual work.
|
|
692
|
703
|
modifyLoaderState interp $ \pls0 -> do
|
|
693
|
|
- -- Link the foreign objects first; BCOs in linkable are ignored here.
|
|
694
|
|
- (pls1, objs_ok) <- loadObjects interp hsc_env pls0 [linkable]
|
|
695
|
|
- when (failed objs_ok) $ throwGhcExceptionIO $ ProgramError "loadDecls: failed to load foreign objects"
|
|
696
|
|
-
|
|
697
|
704
|
-- Link the packages and modules required
|
|
698
|
|
- (pls, ok, links_needed, units_needed) <- loadDependencies interp hsc_env pls1 span needed_mods
|
|
|
705
|
+ (pls, ok, links_needed, units_needed) <- loadDependencies interp hsc_env pls0 span needed_mods
|
|
699
|
706
|
if failed ok
|
|
700
|
|
- then throwGhcExceptionIO (ProgramError "")
|
|
|
707
|
+ then throwGhcExceptionIO (ProgramError "could not load dependencies for decls")
|
|
701
|
708
|
else do
|
|
702
|
|
- -- Link the expression itself
|
|
703
|
|
- let le = linker_env pls
|
|
704
|
|
- let lb = linked_breaks pls
|
|
705
|
|
- le2_itbl_env <- linkITbls interp (itbl_env le) (concat $ map bc_itbls cbcs)
|
|
706
|
|
- le2_addr_env <- foldlM (\env cbc -> allocateTopStrings interp (bc_strs cbc) env) (addr_env le) cbcs
|
|
707
|
|
- le2_breakarray_env <- allocateBreakArrays interp (breakarray_env lb) (catMaybes $ map bc_breaks cbcs)
|
|
708
|
|
- le2_ccs_env <- allocateCCS interp (ccs_env lb) (catMaybes $ map bc_breaks cbcs)
|
|
709
|
|
- let le2 = le { itbl_env = le2_itbl_env
|
|
710
|
|
- , addr_env = le2_addr_env }
|
|
711
|
|
- let lb2 = lb { breakarray_env = le2_breakarray_env
|
|
712
|
|
- , ccs_env = le2_ccs_env }
|
|
713
|
|
-
|
|
714
|
|
- -- Link the necessary packages and linkables
|
|
715
|
|
- new_bindings <- linkSomeBCOs interp (pkgs_loaded pls) le2 lb2 cbcs
|
|
716
|
|
- nms_fhvs <- makeForeignNamedHValueRefs interp new_bindings
|
|
717
|
|
- let ce2 = extendClosureEnv (closure_env le2) nms_fhvs
|
|
718
|
|
- !pls2 = pls { linker_env = le2 { closure_env = ce2 }
|
|
719
|
|
- , linked_breaks = lb2 }
|
|
720
|
|
- return (pls2, (nms_fhvs, links_needed, units_needed))
|
|
|
709
|
+ (pls2, ok2) <- loadInternalModuleLinkables interp hsc_env pls [linkable]
|
|
|
710
|
+ when (failed ok2) $
|
|
|
711
|
+ throwGhcExceptionIO (ProgramError "could not load linkable for decls")
|
|
|
712
|
+ return (pls2, (links_needed, units_needed))
|
|
721
|
713
|
where
|
|
722
|
714
|
cbcs = linkableBCOs linkable
|
|
723
|
715
|
|
| ... |
... |
@@ -759,8 +751,29 @@ loadModule interp hsc_env mod = do |
|
759
|
751
|
|
|
760
|
752
|
********************************************************************* -}
|
|
761
|
753
|
|
|
762
|
|
-loadModuleLinkables :: Interp -> HscEnv -> LoaderState -> [Linkable] -> IO (LoaderState, SuccessFlag)
|
|
763
|
|
-loadModuleLinkables interp hsc_env pls linkables
|
|
|
754
|
+-- | Which closures from a Linkable to add to the 'ClosureEnv' in the 'LoaderState'
|
|
|
755
|
+data KeepModuleLinkableDefinitions = KeepAllDefinitions -- ^ Keep all definitions
|
|
|
756
|
+ | KeepExternalDefinitions -- ^ Only keep external definitions
|
|
|
757
|
+
|
|
|
758
|
+-- | Interpret a 'KeepModuleLinkableDefinitions' specification to a predictate on 'Name'
|
|
|
759
|
+keepDefinitions :: KeepModuleLinkableDefinitions -> (Name -> Bool)
|
|
|
760
|
+keepDefinitions KeepAllDefinitions = const True
|
|
|
761
|
+keepDefinitions KeepExternalDefinitions = isExternalName
|
|
|
762
|
+
|
|
|
763
|
+-- | Load a linkable from a module, and only add externally visible names to the
|
|
|
764
|
+-- environment.
|
|
|
765
|
+loadExternalModuleLinkables :: Interp -> HscEnv -> LoaderState -> [Linkable] -> IO (LoaderState, SuccessFlag)
|
|
|
766
|
+loadExternalModuleLinkables interp hsc_env pls linkables =
|
|
|
767
|
+ loadModuleLinkables interp hsc_env pls KeepExternalDefinitions linkables
|
|
|
768
|
+
|
|
|
769
|
+-- | Load a linkable from a module, and add all the names from the linkable into the
|
|
|
770
|
+-- closure environment.
|
|
|
771
|
+loadInternalModuleLinkables :: Interp -> HscEnv -> LoaderState -> [Linkable] -> IO (LoaderState, SuccessFlag)
|
|
|
772
|
+loadInternalModuleLinkables interp hsc_env pls linkables =
|
|
|
773
|
+ loadModuleLinkables interp hsc_env pls KeepAllDefinitions linkables
|
|
|
774
|
+
|
|
|
775
|
+loadModuleLinkables :: Interp -> HscEnv -> LoaderState -> KeepModuleLinkableDefinitions -> [Linkable] -> IO (LoaderState, SuccessFlag)
|
|
|
776
|
+loadModuleLinkables interp hsc_env pls keep_spec linkables
|
|
764
|
777
|
= mask_ $ do -- don't want to be interrupted by ^C in here
|
|
765
|
778
|
|
|
766
|
779
|
debugTraceMsg (hsc_logger hsc_env) 3 $
|
| ... |
... |
@@ -775,7 +788,7 @@ loadModuleLinkables interp hsc_env pls linkables |
|
775
|
788
|
if failed ok_flag then
|
|
776
|
789
|
return (pls1, Failed)
|
|
777
|
790
|
else do
|
|
778
|
|
- pls2 <- dynLinkBCOs interp pls1 bcos
|
|
|
791
|
+ pls2 <- dynLinkBCOs interp pls1 keep_spec bcos
|
|
779
|
792
|
return (pls2, Succeeded)
|
|
780
|
793
|
where
|
|
781
|
794
|
(objs, bcos) = partitionLinkables linkables
|
| ... |
... |
@@ -918,8 +931,8 @@ rmDupLinkables already ls |
|
918
|
931
|
********************************************************************* -}
|
|
919
|
932
|
|
|
920
|
933
|
|
|
921
|
|
-dynLinkBCOs :: Interp -> LoaderState -> [Linkable] -> IO LoaderState
|
|
922
|
|
-dynLinkBCOs interp pls bcos = do
|
|
|
934
|
+dynLinkBCOs :: Interp -> LoaderState -> KeepModuleLinkableDefinitions -> [Linkable] -> IO LoaderState
|
|
|
935
|
+dynLinkBCOs interp pls keep_spec bcos = do
|
|
923
|
936
|
|
|
924
|
937
|
let (bcos_loaded', new_bcos) = rmDupLinkables (bcos_loaded pls) bcos
|
|
925
|
938
|
pls1 = pls { bcos_loaded = bcos_loaded' }
|
| ... |
... |
@@ -943,7 +956,7 @@ dynLinkBCOs interp pls bcos = do |
|
943
|
956
|
names_and_refs <- linkSomeBCOs interp (pkgs_loaded pls) le2 lb2 cbcs
|
|
944
|
957
|
|
|
945
|
958
|
-- We only want to add the external ones to the ClosureEnv
|
|
946
|
|
- let (to_add, to_drop) = partition (isExternalName.fst) names_and_refs
|
|
|
959
|
+ let (to_add, to_drop) = partition (keepDefinitions keep_spec . fst) names_and_refs
|
|
947
|
960
|
|
|
948
|
961
|
-- Immediately release any HValueRefs we're not going to add
|
|
949
|
962
|
freeHValueRefs interp (map snd to_drop)
|