Cheng Shao pushed to branch wip/batch-loaddll at Glasgow Haskell Compiler / GHC
Commits:
42724462 by Simon Hengel at 2025-08-21T17:52:11-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)
- - - - -
6a43f8ec by Cheng Shao at 2025-08-21T17:52:52-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.
- - - - -
65384837 by Cheng Shao at 2025-08-22T20:09:08+02:00
ghci: LoadDLL -> LoadDLLs
Closes #25407.
Co-authored-by: Codex
- - - - -
6bd22d2c by Cheng Shao at 2025-08-22T20:09:08+02:00
loadPackages': separate downsweep/upsweep
- - - - -
1f88562c by Cheng Shao at 2025-08-22T20:09:08+02:00
driver: parallelize DLL loading
- - - - -
15 changed files:
- compiler/GHC/Driver/Plugins.hs
- compiler/GHC/Iface/Ext/Binary.hs
- compiler/GHC/Iface/Ext/Types.hs
- compiler/GHC/Iface/Tidy/StaticPtrTable.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Linker/MacOS.hs
- compiler/GHC/Linker/Types.hs
- compiler/GHC/Runtime/Interpreter.hs
- compiler/GHC/Types/Name/Cache.hs
- libraries/ghci/GHCi/Message.hs
- libraries/ghci/GHCi/ObjLink.hs
- libraries/ghci/GHCi/Run.hs
- testsuite/tests/rts/linker/T2615.hs
- utils/haddock/haddock-api/src/Haddock/InterfaceFile.hs
- utils/jsffi/dyld.mjs
Changes:
=====================================
compiler/GHC/Driver/Plugins.hs
=====================================
@@ -421,7 +421,7 @@ loadExternalPlugins ps = do
loadExternalPluginLib :: FilePath -> IO ()
loadExternalPluginLib path = do
-- load library
- loadDLL path >>= \case
+ loadDLLs [path] >>= \case
Left errmsg -> pprPanic "loadExternalPluginLib"
(vcat [ text "Can't load plugin library"
, text " Library path: " <> text path
=====================================
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/Linker/Loader.hs
=====================================
@@ -1,6 +1,7 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE ViewPatterns #-}
--
-- (c) The University of Glasgow 2002-2006
@@ -103,6 +104,7 @@ import Data.Array
import Data.ByteString (ByteString)
import qualified Data.Set as Set
import Data.Char (isSpace)
+import Data.Foldable (for_)
import qualified Data.Foldable as Foldable
import Data.IORef
import Data.List (intercalate, isPrefixOf, nub, partition)
@@ -534,7 +536,7 @@ preloadLib interp hsc_env lib_paths framework_paths pls lib_spec = do
return pls
DLL dll_unadorned -> do
- maybe_errstr <- loadDLL interp (platformSOName platform dll_unadorned)
+ maybe_errstr <- loadDLLs interp [platformSOName platform dll_unadorned]
case maybe_errstr of
Right _ -> maybePutStrLn logger "done"
Left mm | platformOS platform /= OSDarwin ->
@@ -544,14 +546,14 @@ preloadLib interp hsc_env lib_paths framework_paths pls lib_spec = do
-- since (apparently) some things install that way - see
-- ticket #8770.
let libfile = ("lib" ++ dll_unadorned) <.> "so"
- err2 <- loadDLL interp libfile
+ err2 <- loadDLLs interp [libfile]
case err2 of
Right _ -> maybePutStrLn logger "done"
Left _ -> preloadFailed mm lib_paths lib_spec
return pls
DLLPath dll_path -> do
- do maybe_errstr <- loadDLL interp dll_path
+ do maybe_errstr <- loadDLLs interp [dll_path]
case maybe_errstr of
Right _ -> maybePutStrLn logger "done"
Left mm -> preloadFailed mm lib_paths lib_spec
@@ -891,7 +893,7 @@ dynLoadObjs interp hsc_env pls@LoaderState{..} objs = do
-- if we got this far, extend the lifetime of the library file
changeTempFilesLifetime tmpfs TFL_GhcSession [soFile]
- m <- loadDLL interp soFile
+ m <- loadDLLs interp [soFile]
case m of
Right _ -> return $! pls { temp_sos = (libPath, libName) : temp_sos }
Left err -> linkFail msg (text err)
@@ -1128,51 +1130,76 @@ loadPackages interp hsc_env new_pkgs = do
loadPackages' :: Interp -> HscEnv -> [UnitId] -> LoaderState -> IO LoaderState
loadPackages' interp hsc_env new_pks pls = do
- pkgs' <- link (pkgs_loaded pls) new_pks
- return $! pls { pkgs_loaded = pkgs'
- }
+ (reverse -> pkgs_info_list, pkgs_almost_loaded) <-
+ downsweep
+ ([], pkgs_loaded pls)
+ new_pks
+ loaded_pkgs_info_list <- loadPackage interp hsc_env pkgs_info_list
+ evaluate $
+ pls
+ { pkgs_loaded =
+ foldl'
+ ( \pkgs (new_pkg_info, (loaded_pkg_hs_objs, loaded_pkg_non_hs_objs, loaded_pkg_hs_dlls)) ->
+ adjustUDFM
+ ( \old_pkg_info ->
+ old_pkg_info
+ { loaded_pkg_hs_objs,
+ loaded_pkg_non_hs_objs,
+ loaded_pkg_hs_dlls
+ }
+ )
+ pkgs
+ (Packages.unitId new_pkg_info)
+ )
+ pkgs_almost_loaded
+ (zip pkgs_info_list loaded_pkgs_info_list)
+ }
where
- link :: PkgsLoaded -> [UnitId] -> IO PkgsLoaded
- link pkgs new_pkgs =
- foldM link_one pkgs new_pkgs
-
- link_one pkgs new_pkg
- | new_pkg `elemUDFM` pkgs -- Already linked
- = return pkgs
-
- | Just pkg_cfg <- lookupUnitId (hsc_units hsc_env) new_pkg
- = do { let deps = unitDepends pkg_cfg
- -- Link dependents first
- ; pkgs' <- link pkgs deps
- -- Now link the package itself
- ; (hs_cls, extra_cls, loaded_dlls) <- loadPackage interp hsc_env pkg_cfg
- ; let trans_deps = unionManyUniqDSets [ addOneToUniqDSet (loaded_pkg_trans_deps loaded_pkg_info) dep_pkg
- | dep_pkg <- deps
- , Just loaded_pkg_info <- pure (lookupUDFM pkgs' dep_pkg)
- ]
- ; return (addToUDFM pkgs' new_pkg (LoadedPkgInfo new_pkg hs_cls extra_cls loaded_dlls trans_deps)) }
-
- | otherwise
- = throwGhcExceptionIO (CmdLineError ("unknown package: " ++ unpackFS (unitIdFS new_pkg)))
-
-
-loadPackage :: Interp -> HscEnv -> UnitInfo -> IO ([LibrarySpec], [LibrarySpec], [RemotePtr LoadedDLL])
-loadPackage interp hsc_env pkg
+ downsweep = foldlM downsweep_one
+
+ downsweep_one (pkgs_info_list, pkgs) new_pkg
+ | new_pkg `elemUDFM` pkgs = pure (pkgs_info_list, pkgs)
+ | Just new_pkg_info <- lookupUnitId (hsc_units hsc_env) new_pkg = do
+ let new_pkg_deps = unitDepends new_pkg_info
+ (pkgs_info_list', pkgs') <- downsweep (pkgs_info_list, pkgs) new_pkg_deps
+ let new_pkg_trans_deps =
+ unionManyUniqDSets
+ [ addOneToUniqDSet (loaded_pkg_trans_deps loaded_pkg_info) dep_pkg
+ | dep_pkg <- new_pkg_deps,
+ loaded_pkg_info <- maybeToList $ pkgs' `lookupUDFM` dep_pkg
+ ]
+ pure
+ ( new_pkg_info : pkgs_info_list',
+ addToUDFM pkgs' new_pkg $
+ LoadedPkgInfo
+ { loaded_pkg_uid = new_pkg,
+ loaded_pkg_hs_objs = [],
+ loaded_pkg_non_hs_objs = [],
+ loaded_pkg_hs_dlls = [],
+ loaded_pkg_trans_deps = new_pkg_trans_deps
+ }
+ )
+ | otherwise =
+ throwGhcExceptionIO
+ (CmdLineError ("unknown package: " ++ unpackFS (unitIdFS new_pkg)))
+
+loadPackage :: Interp -> HscEnv -> [UnitInfo] -> IO [([LibrarySpec], [LibrarySpec], [RemotePtr LoadedDLL])]
+loadPackage interp hsc_env pkgs
= do
let dflags = hsc_dflags hsc_env
let logger = hsc_logger hsc_env
platform = targetPlatform dflags
is_dyn = interpreterDynamic interp
- dirs | is_dyn = map ST.unpack $ Packages.unitLibraryDynDirs pkg
- | otherwise = map ST.unpack $ Packages.unitLibraryDirs pkg
+ dirs | is_dyn = [map ST.unpack $ Packages.unitLibraryDynDirs pkg | pkg <- pkgs]
+ | otherwise = [map ST.unpack $ Packages.unitLibraryDirs pkg | pkg <- pkgs]
- let hs_libs = map ST.unpack $ Packages.unitLibraries pkg
+ let hs_libs = [map ST.unpack $ Packages.unitLibraries pkg | pkg <- pkgs]
-- The FFI GHCi import lib isn't needed as
-- GHC.Linker.Loader + rts/Linker.c link the
-- interpreted references to FFI to the compiled FFI.
-- We therefore filter it out so that we don't get
-- duplicate symbol errors.
- hs_libs' = filter ("HSffi" /=) hs_libs
+ hs_libs' = filter ("HSffi" /=) <$> hs_libs
-- Because of slight differences between the GHC dynamic linker and
-- the native system linker some packages have to link with a
@@ -1181,51 +1208,54 @@ loadPackage interp hsc_env pkg
-- libs do not exactly match the .so/.dll equivalents. So if the
-- package file provides an "extra-ghci-libraries" field then we use
-- that instead of the "extra-libraries" field.
- extdeplibs = map ST.unpack (if null (Packages.unitExtDepLibsGhc pkg)
+ extdeplibs = [map ST.unpack (if null (Packages.unitExtDepLibsGhc pkg)
then Packages.unitExtDepLibsSys pkg
- else Packages.unitExtDepLibsGhc pkg)
- linkerlibs = [ lib | '-':'l':lib <- (map ST.unpack $ Packages.unitLinkerOptions pkg) ]
- extra_libs = extdeplibs ++ linkerlibs
+ else Packages.unitExtDepLibsGhc pkg) | pkg <- pkgs]
+ linkerlibs = [[ lib | '-':'l':lib <- (map ST.unpack $ Packages.unitLinkerOptions pkg) ] | pkg <- pkgs]
+ extra_libs = zipWith (++) extdeplibs linkerlibs
-- See Note [Fork/Exec Windows]
gcc_paths <- getGCCPaths logger dflags (platformOS platform)
- dirs_env <- addEnvPaths "LIBRARY_PATH" dirs
+ dirs_env <- traverse (addEnvPaths "LIBRARY_PATH") dirs
hs_classifieds
- <- mapM (locateLib interp hsc_env True dirs_env gcc_paths) hs_libs'
+ <- sequenceA [mapM (locateLib interp hsc_env True dirs_env_ gcc_paths) hs_libs'_ | (dirs_env_, hs_libs'_) <- zip dirs_env hs_libs' ]
extra_classifieds
- <- mapM (locateLib interp hsc_env False dirs_env gcc_paths) extra_libs
- let classifieds = hs_classifieds ++ extra_classifieds
+ <- sequenceA [mapM (locateLib interp hsc_env False dirs_env_ gcc_paths) extra_libs_ | (dirs_env_, extra_libs_) <- zip dirs_env extra_libs]
+ let classifieds = zipWith (++) hs_classifieds extra_classifieds
-- Complication: all the .so's must be loaded before any of the .o's.
- let known_hs_dlls = [ dll | DLLPath dll <- hs_classifieds ]
- known_extra_dlls = [ dll | DLLPath dll <- extra_classifieds ]
- known_dlls = known_hs_dlls ++ known_extra_dlls
+ let known_hs_dlls = [[ dll | DLLPath dll <- hs_classifieds_ ] | hs_classifieds_ <- hs_classifieds]
+ known_extra_dlls = [ dll | extra_classifieds_ <- extra_classifieds, DLLPath dll <- extra_classifieds_ ]
+ known_dlls = concat known_hs_dlls ++ known_extra_dlls
#if defined(CAN_LOAD_DLL)
- dlls = [ dll | DLL dll <- classifieds ]
+ dlls = [ dll | classifieds_ <- classifieds, DLL dll <- classifieds_ ]
#endif
- objs = [ obj | Objects objs <- classifieds
- , obj <- objs ]
- archs = [ arch | Archive arch <- classifieds ]
+ objs = [ obj | classifieds_ <- classifieds, Objects objs <- classifieds_
+ , obj <- objs]
+ archs = [ arch | classifieds_ <- classifieds, Archive arch <- classifieds_ ]
-- Add directories to library search paths
let dll_paths = map takeDirectory known_dlls
- all_paths = nub $ map normalise $ dll_paths ++ dirs
+ all_paths = nub $ map normalise $ dll_paths ++ concat dirs
all_paths_env <- addEnvPaths "LD_LIBRARY_PATH" all_paths
pathCache <- mapM (addLibrarySearchPath interp) all_paths_env
maybePutSDoc logger
- (text "Loading unit " <> pprUnitInfoForUser pkg <> text " ... ")
+ (text "Loading units " <> vcat (map pprUnitInfoForUser pkgs) <> text " ... ")
#if defined(CAN_LOAD_DLL)
- loadFrameworks interp platform pkg
+ for_ pkgs $ loadFrameworks interp platform
-- See Note [Crash early load_dyn and locateLib]
-- Crash early if can't load any of `known_dlls`
- mapM_ (load_dyn interp hsc_env True) known_extra_dlls
- loaded_dlls <- mapMaybeM (load_dyn interp hsc_env True) known_hs_dlls
+ _ <- load_dyn interp hsc_env True known_extra_dlls
+ let regroup :: [[a]] -> [b] -> [[b]]
+ regroup [] _ = []
+ regroup (l:ls) xs = xs0: regroup ls xs1 where (xs0, xs1) = splitAt (length l) xs
+ loaded_dlls <- regroup known_hs_dlls <$> load_dyn interp hsc_env True (concat known_hs_dlls)
-- For remaining `dlls` crash early only when there is surely
-- no package's DLL around ... (not is_dyn)
- mapM_ (load_dyn interp hsc_env (not is_dyn) . platformSOName platform) dlls
+ _ <- load_dyn interp hsc_env (not is_dyn) $ map (platformSOName platform) dlls
#else
let loaded_dlls = []
#endif
@@ -1247,9 +1277,9 @@ loadPackage interp hsc_env pkg
if succeeded ok
then do
maybePutStrLn logger "done."
- return (hs_classifieds, extra_classifieds, loaded_dlls)
- else let errmsg = text "unable to load unit `"
- <> pprUnitInfoForUser pkg <> text "'"
+ pure $ zip3 hs_classifieds extra_classifieds loaded_dlls
+ else let errmsg = text "unable to load units `"
+ <> vcat (map pprUnitInfoForUser pkgs) <> text "'"
in throwGhcExceptionIO (InstallationError (showSDoc dflags errmsg))
{-
@@ -1299,12 +1329,12 @@ restriction very easily.
-- we have already searched the filesystem; the strings passed to load_dyn
-- can be passed directly to loadDLL. They are either fully-qualified
-- ("/usr/lib/libfoo.so"), or unqualified ("libfoo.so"). In the latter case,
--- loadDLL is going to search the system paths to find the library.
-load_dyn :: Interp -> HscEnv -> Bool -> FilePath -> IO (Maybe (RemotePtr LoadedDLL))
-load_dyn interp hsc_env crash_early dll = do
- r <- loadDLL interp dll
+-- loadDLLs is going to search the system paths to find the library.
+load_dyn :: Interp -> HscEnv -> Bool -> [FilePath] -> IO [RemotePtr LoadedDLL]
+load_dyn interp hsc_env crash_early dlls = do
+ r <- loadDLLs interp dlls
case r of
- Right loaded_dll -> pure (Just loaded_dll)
+ Right loaded_dlls -> pure loaded_dlls
Left err ->
if crash_early
then cmdLineErrorIO err
@@ -1313,7 +1343,7 @@ load_dyn interp hsc_env crash_early dll = do
$ reportDiagnostic logger
neverQualify diag_opts
noSrcSpan (WarningWithFlag Opt_WarnMissedExtraSharedLib) $ withPprStyle defaultUserStyle (note err)
- pure Nothing
+ pure []
where
diag_opts = initDiagOpts (hsc_dflags hsc_env)
logger = hsc_logger hsc_env
@@ -1369,7 +1399,7 @@ locateLib interp hsc_env is_hs lib_dirs gcc_dirs lib0
-- then look in library-dirs and inplace GCC for a static library (libfoo.a)
-- then try "gcc --print-file-name" to search gcc's search path
-- for a dynamic library (#5289)
- -- otherwise, assume loadDLL can find it
+ -- otherwise, assume loadDLLs can find it
--
-- The logic is a bit complicated, but the rationale behind it is that
-- loading a shared library for us is O(1) while loading an archive is
=====================================
compiler/GHC/Linker/MacOS.hs
=====================================
@@ -162,7 +162,7 @@ loadFramework interp extraPaths rootname
-- sorry for the hardcoded paths, I hope they won't change anytime soon:
defaultFrameworkPaths = ["/Library/Frameworks", "/System/Library/Frameworks"]
- -- Try to call loadDLL for each candidate path.
+ -- Try to call loadDLLs for each candidate path.
--
-- See Note [macOS Big Sur dynamic libraries]
findLoadDLL [] errs =
@@ -170,7 +170,7 @@ loadFramework interp extraPaths rootname
-- has no built-in paths for frameworks: give up
return $ Just errs
findLoadDLL (p:ps) errs =
- do { dll <- loadDLL interp (p > fwk_file)
+ do { dll <- loadDLLs interp [p > fwk_file]
; case dll of
Right _ -> return Nothing
Left err -> findLoadDLL ps ((p ++ ": " ++ err):errs)
=====================================
compiler/GHC/Linker/Types.hs
=====================================
@@ -494,7 +494,7 @@ data LibrarySpec
| DLL String -- "Unadorned" name of a .DLL/.so
-- e.g. On unix "qt" denotes "libqt.so"
-- On Windows "burble" denotes "burble.DLL" or "libburble.dll"
- -- loadDLL is platform-specific and adds the lib/.so/.DLL
+ -- loadDLLs is platform-specific and adds the lib/.so/.DLL
-- suffixes platform-dependently
| DLLPath FilePath -- Absolute or relative pathname to a dynamic library
=====================================
compiler/GHC/Runtime/Interpreter.hs
=====================================
@@ -38,7 +38,7 @@ module GHC.Runtime.Interpreter
, lookupSymbol
, lookupSymbolInDLL
, lookupClosure
- , loadDLL
+ , loadDLLs
, loadArchive
, loadObj
, unloadObj
@@ -559,13 +559,13 @@ withSymbolCache interp str determine_addr = do
purgeLookupSymbolCache :: Interp -> IO ()
purgeLookupSymbolCache interp = purgeInterpSymbolCache (interpSymbolCache interp)
--- | loadDLL loads a dynamic library using the OS's native linker
+-- | 'loadDLLs' loads dynamic libraries using the OS's native linker
-- (i.e. dlopen() on Unix, LoadLibrary() on Windows). It takes either
--- an absolute pathname to the file, or a relative filename
--- (e.g. "libfoo.so" or "foo.dll"). In the latter case, loadDLL
--- searches the standard locations for the appropriate library.
-loadDLL :: Interp -> String -> IO (Either String (RemotePtr LoadedDLL))
-loadDLL interp str = interpCmd interp (LoadDLL str)
+-- absolute pathnames to the files, or relative filenames
+-- (e.g. "libfoo.so" or "foo.dll"). In the latter case, 'loadDLLs'
+-- searches the standard locations for the appropriate libraries.
+loadDLLs :: Interp -> [String] -> IO (Either String [RemotePtr LoadedDLL])
+loadDLLs interp strs = interpCmd interp (LoadDLLs strs)
loadArchive :: Interp -> String -> IO ()
loadArchive interp path = do
@@ -761,4 +761,3 @@ readIModModBreaks hug mod = imodBreaks_modBreaks . expectJust <$> readIModBreaks
fromEvalResult :: EvalResult a -> IO a
fromEvalResult (EvalException e) = throwIO (fromSerializableException e)
fromEvalResult (EvalSuccess a) = return a
-
=====================================
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/ghci/GHCi/Message.hs
=====================================
@@ -84,7 +84,7 @@ data Message a where
LookupSymbol :: String -> Message (Maybe (RemotePtr ()))
LookupSymbolInDLL :: RemotePtr LoadedDLL -> String -> Message (Maybe (RemotePtr ()))
LookupClosure :: String -> Message (Maybe HValueRef)
- LoadDLL :: String -> Message (Either String (RemotePtr LoadedDLL))
+ LoadDLLs :: [String] -> Message (Either String [RemotePtr LoadedDLL])
LoadArchive :: String -> Message () -- error?
LoadObj :: String -> Message () -- error?
UnloadObj :: String -> Message () -- error?
@@ -441,7 +441,7 @@ data BreakModule
-- that type isn't available here.
data BreakUnitId
--- | A dummy type that tags pointers returned by 'LoadDLL'.
+-- | A dummy type that tags pointers returned by 'LoadDLLs'.
data LoadedDLL
-- SomeException can't be serialized because it contains dynamic
@@ -555,7 +555,7 @@ getMessage = do
1 -> Msg <$> return InitLinker
2 -> Msg <$> LookupSymbol <$> get
3 -> Msg <$> LookupClosure <$> get
- 4 -> Msg <$> LoadDLL <$> get
+ 4 -> Msg <$> LoadDLLs <$> get
5 -> Msg <$> LoadArchive <$> get
6 -> Msg <$> LoadObj <$> get
7 -> Msg <$> UnloadObj <$> get
@@ -601,7 +601,7 @@ putMessage m = case m of
InitLinker -> putWord8 1
LookupSymbol str -> putWord8 2 >> put str
LookupClosure str -> putWord8 3 >> put str
- LoadDLL str -> putWord8 4 >> put str
+ LoadDLLs strs -> putWord8 4 >> put strs
LoadArchive str -> putWord8 5 >> put str
LoadObj str -> putWord8 6 >> put str
UnloadObj str -> putWord8 7 >> put str
=====================================
libraries/ghci/GHCi/ObjLink.hs
=====================================
@@ -12,7 +12,7 @@
-- dynamic linker.
module GHCi.ObjLink
( initObjLinker, ShouldRetainCAFs(..)
- , loadDLL
+ , loadDLLs
, loadArchive
, loadObj
, unloadObj
@@ -43,6 +43,10 @@ import Control.Exception (catch, evaluate)
import GHC.Wasm.Prim
#endif
+#if defined(wasm32_HOST_ARCH)
+import Data.List (intercalate)
+#endif
+
-- ---------------------------------------------------------------------------
-- RTS Linker Interface
-- ---------------------------------------------------------------------------
@@ -67,20 +71,25 @@ data ShouldRetainCAFs
initObjLinker :: ShouldRetainCAFs -> IO ()
initObjLinker _ = pure ()
-loadDLL :: String -> IO (Either String (Ptr LoadedDLL))
-loadDLL f =
+-- Batch load multiple DLLs at once via dyld to enable a single
+-- dependency resolution and more parallel compilation. We pass a
+-- NUL-delimited JSString to avoid array marshalling on wasm.
+loadDLLs :: [String] -> IO (Either String [Ptr LoadedDLL])
+loadDLLs fs =
m `catch` \(err :: JSException) ->
- pure $ Left $ "loadDLL failed for " <> f <> ": " <> show err
+ pure $ Left $ "loadDLLs failed: " <> show err
where
+ packed :: JSString
+ packed = toJSString (intercalate ['\0'] fs)
m = do
- evaluate =<< js_loadDLL (toJSString f)
- pure $ Right nullPtr
+ evaluate =<< js_loadDLLs packed
+ pure $ Right (replicate (length fs) nullPtr)
-- See Note [Variable passing in JSFFI] for where
-- __ghc_wasm_jsffi_dyld comes from
-foreign import javascript safe "__ghc_wasm_jsffi_dyld.loadDLL($1)"
- js_loadDLL :: JSString -> IO ()
+foreign import javascript safe "__ghc_wasm_jsffi_dyld.loadDLLs($1)"
+ js_loadDLLs :: JSString -> IO ()
loadArchive :: String -> IO ()
loadArchive f = throwIO $ ErrorCall $ "loadArchive: unsupported on wasm for " <> f
@@ -241,6 +250,16 @@ resolveObjs = do
r <- c_resolveObjs
return (r /= 0)
+loadDLLs :: [String] -> IO (Either String [Ptr LoadedDLL])
+loadDLLs = go []
+ where
+ go acc [] = pure (Right (reverse acc))
+ go acc (p:ps) = do
+ r <- loadDLL p
+ case r of
+ Left err -> pure (Left err)
+ Right h -> go (h:acc) ps
+
-- ---------------------------------------------------------------------------
-- Foreign declarations to RTS entry points which does the real work;
-- ---------------------------------------------------------------------------
=====================================
libraries/ghci/GHCi/Run.hs
=====================================
@@ -57,7 +57,7 @@ run m = case m of
#if defined(javascript_HOST_ARCH)
LoadObj p -> withCString p loadJS
InitLinker -> notSupportedJS m
- LoadDLL {} -> notSupportedJS m
+ LoadDLLs {} -> notSupportedJS m
LoadArchive {} -> notSupportedJS m
UnloadObj {} -> notSupportedJS m
AddLibrarySearchPath {} -> notSupportedJS m
@@ -69,7 +69,7 @@ run m = case m of
LookupClosure str -> lookupJSClosure str
#else
InitLinker -> initObjLinker RetainCAFs
- LoadDLL str -> fmap toRemotePtr <$> loadDLL str
+ LoadDLLs strs -> fmap (map toRemotePtr) <$> loadDLLs strs
LoadArchive str -> loadArchive str
LoadObj str -> loadObj str
UnloadObj str -> unloadObj str
=====================================
testsuite/tests/rts/linker/T2615.hs
=====================================
@@ -4,7 +4,7 @@ library_name = "libfoo_script_T2615.so" -- this is really a linker script
main = do
initObjLinker RetainCAFs
- result <- loadDLL library_name
+ result <- loadDLLs [library_name]
case result of
Right _ -> putStrLn (library_name ++ " loaded successfully")
Left x -> putStrLn ("error: " ++ x)
=====================================
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.
=====================================
utils/jsffi/dyld.mjs
=====================================
@@ -9,7 +9,7 @@
// iserv (GHCi.Server.defaultServer). This part only runs in
// nodejs.
// 2. Dynamic linker: provide RTS linker interfaces like
-// loadDLL/lookupSymbol etc which are imported by wasm iserv. This
+// loadDLLs/lookupSymbol etc which are imported by wasm iserv. This
// part can run in browsers as well.
//
// When GHC starts external interpreter for the wasm target, it starts
@@ -50,7 +50,7 @@
//
// *** What works right now and what doesn't work yet?
//
-// loadDLL & bytecode interpreter work. Template Haskell & ghci work.
+// loadDLLs & bytecode interpreter work. Template Haskell & ghci work.
// Profiled dynamic code works. Compiled code and bytecode can all be
// loaded, though the side effects are constrained to what's supported
// by wasi preview1: we map the full host filesystem into wasm cause
@@ -801,17 +801,17 @@ class DyLD {
return this.#rpc.findSystemLibrary(f);
}
- // When we do loadDLL, we first perform "downsweep" which return a
+ // When we do loadDLLs, we first perform "downsweep" which return a
// toposorted array of dependencies up to itself, then sequentially
// load the downsweep result.
//
// The rationale of a separate downsweep phase, instead of a simple
- // recursive loadDLL function is: V8 delegates async
+ // recursive loadDLLs function is: V8 delegates async
// WebAssembly.compile to a background worker thread pool. To
// maintain consistent internal linker state, we *must* load each so
// file sequentially, but it's okay to kick off compilation asap,
// store the Promise in downsweep result and await for the actual
- // WebAssembly.Module in loadDLL logic. This way we can harness some
+ // WebAssembly.Module in loadDLLs logic. This way we can harness some
// background parallelism.
async #downsweep(p) {
const toks = p.split("/");
@@ -852,8 +852,26 @@ class DyLD {
return acc;
}
- // The real stuff
- async loadDLL(p) {
+ // Batch load multiple DLLs in one go.
+ // Accepts a NUL-delimited string of paths to avoid array marshalling.
+ // Each path can be absolute or a soname; dependency resolution is
+ // performed across the full set to enable maximal parallel compile
+ // while maintaining sequential instantiation order.
+ async loadDLLs(packed) {
+ // Normalize input to an array of strings. When called from Haskell
+ // we pass a single JSString containing NUL-separated paths.
+ const paths = (typeof packed === "string"
+ ? (packed.length === 0 ? [] : packed.split("\0"))
+ : [packed] // tolerate an accidental single path object
+ ).filter((s) => s.length > 0);
+
+ // Compute a single downsweep plan for the whole batch.
+ // Note: #downsweep mutates #loadedSos to break cycles and dedup.
+ const plan = [];
+ for (const p of paths) {
+ plan.push(...(await this.#downsweep(p)));
+ }
+
for (const {
memSize,
memP2Align,
@@ -861,7 +879,7 @@ class DyLD {
tableP2Align,
modp,
soname,
- } of await this.#downsweep(p)) {
+ } of plan) {
const import_obj = {
wasi_snapshot_preview1: this.#wasi.wasiImport,
env: {
@@ -1138,7 +1156,7 @@ export async function main({ rpc, libdir, ghciSoPath, args }) {
rpc,
});
await dyld.addLibrarySearchPath(libdir);
- await dyld.loadDLL(ghciSoPath);
+ await dyld.loadDLLs(ghciSoPath);
const reader = rpc.readStream.getReader();
const writer = rpc.writeStream.getWriter();
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/57467d9e32336bc1b0ace323dd0084d...
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/57467d9e32336bc1b0ace323dd0084d...
You're receiving this email because of your account on gitlab.haskell.org.