X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2Fghci%2FLinker.lhs;h=3a5ecf8a6d62f508d37cd0449d162112dcaedfcc;hb=28a464a75e14cece5db40f2765a29348273ff2d2;hp=2b45436deb1803c3eec7911ae8ee972a489441e7;hpb=428bc7ee806bb4a1b29a487854d54bd6ff5a931e;p=ghc-hetmet.git diff --git a/ghc/compiler/ghci/Linker.lhs b/ghc/compiler/ghci/Linker.lhs index 2b45436..3a5ecf8 100644 --- a/ghc/compiler/ghci/Linker.lhs +++ b/ghc/compiler/ghci/Linker.lhs @@ -1,5 +1,5 @@ % -% (c) The University of Glasgow 2000 +% (c) The University of Glasgow 2005 % -- -------------------------------------- @@ -13,53 +13,49 @@ necessary. \begin{code} -{-# OPTIONS -optc-DNON_POSIX_SOURCE #-} +{-# OPTIONS -optc-DNON_POSIX_SOURCE -#include "Linker.h" #-} -module Linker ( HValue, initLinker, showLinkerState, - linkPackages, linkLibraries, - linkModules, unload, extendLinkEnv, linkExpr, - LibrarySpec(..) +module Linker ( HValue, showLinkerState, + linkExpr, unload, extendLinkEnv, withExtendedLinkEnv, + extendLoadedPkgs, + linkPackages,initDynLinker ) where -#include "../includes/config.h" #include "HsVersions.h" -import ObjLink ( loadDLL, loadObj, unloadObj, resolveObjs, initLinker ) +import ObjLink ( loadDLL, loadObj, unloadObj, resolveObjs, initObjLinker ) import ByteCodeLink ( HValue, ClosureEnv, extendClosureEnv, linkBCO ) import ByteCodeItbls ( ItblEnv ) -import ByteCodeAsm ( CompiledByteCode(..), bcosFreeNames, - UnlinkedBCO, UnlinkedBCOExpr, nameOfUnlinkedBCO ) - -import Packages ( PackageConfig(..), PackageName, PackageConfigMap, lookupPkg, - packageDependents, packageNameString ) -import DriverState ( v_Library_paths, v_Cmdline_libraries, getPackageConfigMap ) - -import HscTypes ( Linkable(..), isObjectLinkable, nameOfObject, byteCodeOfObject, - Unlinked(..), isInterpretable, isObject, - HscEnv(..), PersistentCompilerState(..), ExternalPackageState(..), - HomePackageTable, PackageIfaceTable, ModIface(..), HomeModInfo(..) ) -import Name ( Name, nameModule, isExternalName ) +import ByteCodeAsm ( CompiledByteCode(..), bcoFreeNames, UnlinkedBCO(..)) + +import Packages +import DriverPhases ( isObjectFilename, isDynLibFilename ) +import Finder ( findModule, findObjectLinkableMaybe, FindResult(..) ) +import HscTypes +import Name ( Name, nameModule, isExternalName, isWiredInName ) import NameEnv import NameSet ( nameSetToList ) -import Module ( Module, ModuleName, moduleName, lookupModuleEnvByName ) -import FastString ( FastString(..), unpackFS ) -import CmdLineOpts ( DynFlags(verbosity) ) +import Module +import ListSetOps ( minusList ) +import DynFlags ( DynFlags(..), getOpts ) import BasicTypes ( SuccessFlag(..), succeeded, failed ) import Outputable import Panic ( GhcException(..) ) -import Util ( zipLazy, global ) -import ErrUtils ( Message ) +import Util ( zipLazy, global, joinFileExt, joinFileName, suffixOf ) +import StaticFlags ( v_Ld_inputs ) +import ErrUtils ( debugTraceMsg ) -- Standard libraries import Control.Monad ( when, filterM, foldM ) -import Data.IORef ( IORef, readIORef, writeIORef ) -import Data.List ( partition ) +import Data.IORef ( IORef, readIORef, writeIORef, modifyIORef ) +import Data.List ( partition, nub ) import System.IO ( putStr, putStrLn, hPutStrLn, stderr, fixIO ) import System.Directory ( doesFileExist ) -import Control.Exception ( block, throwDyn ) +import Control.Exception ( block, throwDyn, bracket ) +import Maybe ( isJust, fromJust ) #if __GLASGOW_HASKELL__ >= 503 import GHC.IOBase ( IO(..) ) @@ -83,7 +79,8 @@ The PersistentLinkerState maps Names to actual closures (for interpreted code only), for use during linking. \begin{code} -GLOBAL_VAR(v_PersistentLinkerState, emptyPLS, PersistentLinkerState) +GLOBAL_VAR(v_PersistentLinkerState, panic "Dynamic linker not initialised", PersistentLinkerState) +GLOBAL_VAR(v_InitLinkerDone, False, Bool) -- Set True when dynamic linker is initialised data PersistentLinkerState = PersistentLinkerState { @@ -107,22 +104,31 @@ data PersistentLinkerState -- The currently-loaded packages; always object code -- Held, as usual, in dependency order; though I am not sure if -- that is really important - pkgs_loaded :: [PackageName] + pkgs_loaded :: [PackageId] } -emptyPLS :: PersistentLinkerState -emptyPLS = PersistentLinkerState { closure_env = emptyNameEnv, - itbl_env = emptyNameEnv, - pkgs_loaded = init_pkgs_loaded, - bcos_loaded = [], - objs_loaded = [] } - --- Packages that don't need loading, because the compiler --- shares them with the interpreted program. -init_pkgs_loaded = [ FSLIT("rts") ] +emptyPLS :: DynFlags -> PersistentLinkerState +emptyPLS dflags = PersistentLinkerState { + closure_env = emptyNameEnv, + itbl_env = emptyNameEnv, + pkgs_loaded = init_pkgs, + bcos_loaded = [], + objs_loaded = [] } + -- Packages that don't need loading, because the compiler + -- shares them with the interpreted program. + -- + -- The linker's symbol table is populated with RTS symbols using an + -- explicit list. See rts/Linker.c for details. + where init_pkgs + | ExtPackage rts_id <- rtsPackageId (pkgState dflags) = [rts_id] + | otherwise = [] \end{code} \begin{code} +extendLoadedPkgs :: [PackageId] -> IO () +extendLoadedPkgs pkgs + = modifyIORef v_PersistentLinkerState (\s -> s{pkgs_loaded = pkgs ++ pkgs_loaded s}) + extendLinkEnv :: [(Name,HValue)] -> IO () -- Automatically discards shadowed bindings extendLinkEnv new_bindings @@ -131,18 +137,30 @@ extendLinkEnv new_bindings new_pls = pls { closure_env = new_closure_env } writeIORef v_PersistentLinkerState new_pls +withExtendedLinkEnv :: [(Name,HValue)] -> IO a -> IO a +withExtendedLinkEnv new_env action + = bracket set_new_env + reset_old_env + (const action) + where set_new_env = do pls <- readIORef v_PersistentLinkerState + let new_closure_env = extendClosureEnv (closure_env pls) new_env + new_pls = pls { closure_env = new_closure_env } + writeIORef v_PersistentLinkerState new_pls + return pls + reset_old_env pls = writeIORef v_PersistentLinkerState pls + -- filterNameMap removes from the environment all entries except -- those for a given set of modules; -- Note that this removes all *local* (i.e. non-isExternal) names too -- (these are the temporary bindings from the command line). -- Used to filter both the ClosureEnv and ItblEnv -filterNameMap :: [ModuleName] -> NameEnv (Name, a) -> NameEnv (Name, a) +filterNameMap :: [Module] -> NameEnv (Name, a) -> NameEnv (Name, a) filterNameMap mods env = filterNameEnv keep_elt env where keep_elt (n,_) = isExternalName n - && (moduleName (nameModule n) `elem` mods) + && (nameModule n `elem` mods) \end{code} @@ -159,6 +177,139 @@ showLinkerState + +%************************************************************************ +%* * +\subsection{Initialisation} +%* * +%************************************************************************ + +We initialise the dynamic linker by + +a) calling the C initialisation procedure + +b) Loading any packages specified on the command line, + now held in v_ExplicitPackages + +c) Loading any packages specified on the command line, + now held in the -l options in v_Opt_l + +d) Loading any .o/.dll files specified on the command line, + now held in v_Ld_inputs + +e) Loading any MacOS frameworks + +\begin{code} +initDynLinker :: DynFlags -> IO () +-- This function is idempotent; if called more than once, it does nothing +-- This is useful in Template Haskell, where we call it before trying to link +initDynLinker dflags + = do { done <- readIORef v_InitLinkerDone + ; if done then return () + else do { writeIORef v_InitLinkerDone True + ; reallyInitDynLinker dflags } + } + +reallyInitDynLinker dflags + = do { -- Initialise the linker state + ; writeIORef v_PersistentLinkerState (emptyPLS dflags) + + -- (a) initialise the C dynamic linker + ; initObjLinker + + -- (b) Load packages from the command-line + ; linkPackages dflags (explicitPackages (pkgState dflags)) + + -- (c) Link libraries from the command-line + ; let optl = getOpts dflags opt_l + ; let minus_ls = [ lib | '-':'l':lib <- optl ] + + -- (d) Link .o files from the command-line + ; let lib_paths = libraryPaths dflags + ; cmdline_ld_inputs <- readIORef v_Ld_inputs + + ; classified_ld_inputs <- mapM classifyLdInput cmdline_ld_inputs + + -- (e) Link any MacOS frameworks +#ifdef darwin_TARGET_OS + ; let framework_paths = frameworkPaths dflags + ; let frameworks = cmdlineFrameworks dflags +#else + ; let frameworks = [] + ; let framework_paths = [] +#endif + -- Finally do (c),(d),(e) + ; let cmdline_lib_specs = [ l | Just l <- classified_ld_inputs ] + ++ map DLL minus_ls + ++ map Framework frameworks + ; if null cmdline_lib_specs then return () + else do + + { mapM_ (preloadLib dflags lib_paths framework_paths) cmdline_lib_specs + ; maybePutStr dflags "final link ... " + ; ok <- resolveObjs + + ; if succeeded ok then maybePutStrLn dflags "done" + else throwDyn (InstallationError "linking extra libraries/objects failed") + }} + +classifyLdInput :: FilePath -> IO (Maybe LibrarySpec) +classifyLdInput f + | isObjectFilename f = return (Just (Object f)) + | isDynLibFilename f = return (Just (DLLPath f)) + | otherwise = do + hPutStrLn stderr ("Warning: ignoring unrecognised input `" ++ f ++ "'") + return Nothing + +preloadLib :: DynFlags -> [String] -> [String] -> LibrarySpec -> IO () +preloadLib dflags lib_paths framework_paths lib_spec + = do maybePutStr dflags ("Loading object " ++ showLS lib_spec ++ " ... ") + case lib_spec of + Object static_ish + -> do b <- preload_static lib_paths static_ish + maybePutStrLn dflags (if b then "done" + else "not found") + + DLL dll_unadorned + -> do maybe_errstr <- loadDynamic lib_paths dll_unadorned + case maybe_errstr of + Nothing -> maybePutStrLn dflags "done" + Just mm -> preloadFailed mm lib_paths lib_spec + + DLLPath dll_path + -> do maybe_errstr <- loadDLL dll_path + case maybe_errstr of + Nothing -> maybePutStrLn dflags "done" + Just mm -> preloadFailed mm lib_paths lib_spec + +#ifdef darwin_TARGET_OS + Framework framework + -> do maybe_errstr <- loadFramework framework_paths framework + case maybe_errstr of + Nothing -> maybePutStrLn dflags "done" + Just mm -> preloadFailed mm framework_paths lib_spec +#endif + where + preloadFailed :: String -> [String] -> LibrarySpec -> IO () + preloadFailed sys_errmsg paths spec + = do maybePutStr dflags + ("failed.\nDynamic linker error message was:\n " + ++ sys_errmsg ++ "\nWhilst trying to load: " + ++ showLS spec ++ "\nDirectories to search are:\n" + ++ unlines (map (" "++) paths) ) + give_up + + -- Not interested in the paths in the static case. + preload_static paths name + = do b <- doesFileExist name + if not b then return False + else loadObj name >> return True + + give_up = throwDyn $ + CmdLineError "user specified .o/.so/.DLL could not be loaded." +\end{code} + + %************************************************************************ %* * Link a byte-code expression @@ -166,8 +317,7 @@ showLinkerState %************************************************************************ \begin{code} -linkExpr :: HscEnv -> PersistentCompilerState - -> UnlinkedBCOExpr -> IO HValue -- IO BCO# really +linkExpr :: HscEnv -> UnlinkedBCO -> IO HValue -- Link a single expression, *including* first linking packages and -- modules that this expression depends on. @@ -175,14 +325,19 @@ linkExpr :: HscEnv -> PersistentCompilerState -- Raises an IO exception if it can't find a compiled version of the -- dependents to link. -linkExpr hsc_env pcs (root_ul_bco, aux_ul_bcos) - = -- Find what packages and linkables are required - case getLinkDeps hpt pit needed_mods of { - Left msg -> dieWith (msg $$ ptext SLIT("When linking an expression")) ; - Right (lnks, pkgs) -> do { +linkExpr hsc_env root_ul_bco + = do { + -- Initialise the linker (if it's not been done already) + let dflags = hsc_dflags hsc_env + ; initDynLinker dflags + + -- Find what packages and linkables are required + ; eps <- readIORef (hsc_EPS hsc_env) + ; (lnks, pkgs) <- getLinkDeps hsc_env hpt (eps_PIT eps) needed_mods - linkPackages dflags pkgs - ; ok <- linkModules dflags lnks + -- Link the packages and modules required + ; linkPackages dflags pkgs + ; ok <- linkModules dflags lnks ; if failed ok then dieWith empty else do { @@ -193,62 +348,95 @@ linkExpr hsc_env pcs (root_ul_bco, aux_ul_bcos) ce = closure_env pls -- Link the necessary packages and linkables - ; (_, (root_hval:_)) <- linkSomeBCOs False ie ce all_bcos + ; (_, (root_hval:_)) <- linkSomeBCOs False ie ce [root_ul_bco] ; return root_hval - }}} + }} where - pit = eps_PIT (pcs_EPS pcs) hpt = hsc_HPT hsc_env dflags = hsc_dflags hsc_env - all_bcos = root_ul_bco : aux_ul_bcos - free_names = nameSetToList (bcosFreeNames all_bcos) - + free_names = nameSetToList (bcoFreeNames root_ul_bco) + needed_mods :: [Module] - needed_mods = [ nameModule n | n <- free_names, isExternalName n ] + needed_mods = [ nameModule n | n <- free_names, + isExternalName n, -- Names from other modules + not (isWiredInName n) -- Exclude wired-in names + ] -- (see note below) + -- Exclude wired-in names because we may not have read + -- their interface files, so getLinkDeps will fail + -- All wired-in names are in the base package, which we link + -- by default, so we can safely ignore them here. -dieWith msg = throwDyn (UsageError (showSDoc msg)) +dieWith msg = throwDyn (ProgramError (showSDoc msg)) -getLinkDeps :: HomePackageTable -> PackageIfaceTable - -> [Module] -- If you need these - -> Either Message - ([Linkable], [PackageName]) -- ... then link these first +getLinkDeps :: HscEnv -> HomePackageTable -> PackageIfaceTable + -> [Module] -- If you need these + -> IO ([Linkable], [PackageId]) -- ... then link these first +-- Fails with an IO exception if it can't find enough files +getLinkDeps hsc_env hpt pit mods -- Find all the packages and linkables that a set of modules depends on + = do { pls <- readIORef v_PersistentLinkerState ; + let { + -- 1. Find the dependent home-pkg-modules/packages from each iface + (mods_s, pkgs_s) = unzip (map get_deps mods) ; + + -- 2. Exclude ones already linked + -- Main reason: avoid findModule calls in get_linkable + mods_needed = nub (concat mods_s) `minusList` linked_mods ; + pkgs_needed = nub (concat pkgs_s) `minusList` pkgs_loaded pls ; + + linked_mods = map linkableModule (objs_loaded pls ++ bcos_loaded pls) + } ; + + -- 3. For each dependent module, find its linkable + -- This will either be in the HPT or (in the case of one-shot + -- compilation) we may need to use maybe_getFileLinkable + lnks_needed <- mapM get_linkable mods_needed ; -getLinkDeps hpt pit mods - = go [] -- Linkables so far - [] -- Packages so far - [] -- Modules dealt with - (map moduleName mods) -- The usage info that we use for - -- dependencies has ModuleNames not Modules + return (lnks_needed, pkgs_needed) } where - go lnks pkgs _ [] = Right (lnks,pkgs) - go lnks pkgs mods_done (mod:mods) - | mod `elem` mods_done - = -- Already dealt with - go lnks pkgs mods_done mods - - | Just mod_info <- lookupModuleEnvByName hpt mod - = -- OK, so it's a home module - let - mod_deps = [m | (m,_,_,_) <- mi_usages (hm_iface mod_info)] - -- Get the modules that this one depends on - in - go (hm_linkable mod_info : lnks) pkgs (mod : mods_done) (mod_deps ++ mods) - - | Just pkg_iface <- lookupModuleEnvByName pit mod - = -- It's a package module, so add it to the package list - let - pkg_name = mi_package pkg_iface - pkgs' | pkg_name `elem` pkgs = pkgs - | otherwise = pkg_name : pkgs - in - go lnks pkgs' (mod : mods_done) mods - + get_deps :: Module -> ([Module],[PackageId]) + -- Get the things needed for the specified module + -- This is rather similar to the code in RnNames.importsFromImportDecl + get_deps mod + | ExtPackage p <- mi_package iface + = ([], p : dep_pkgs deps) | otherwise - = -- Not in either table - Left (ptext SLIT("Can't find compiled code for dependent module") <+> ppr mod) -\end{code} + = (mod : [m | (m,_) <- dep_mods deps], dep_pkgs deps) + where + iface = get_iface mod + deps = mi_deps iface + + get_iface mod = case lookupIface hpt pit mod of + Just iface -> iface + Nothing -> pprPanic "getLinkDeps" (no_iface mod) + no_iface mod = ptext SLIT("No iface for") <+> ppr mod + -- This one is a GHC bug + + no_obj mod = dieWith (ptext SLIT("No compiled code for") <+> ppr mod) + -- This one is a build-system bug + + get_linkable mod_name -- A home-package module + | Just mod_info <- lookupModuleEnv hpt mod_name + = ASSERT(isJust (hm_linkable mod_info)) + return (fromJust (hm_linkable mod_info)) + | otherwise + = -- It's not in the HPT because we are in one shot mode, + -- so use the Finder to get a ModLocation... + do { mb_stuff <- findModule hsc_env mod_name False ; + case mb_stuff of { + Found loc _ -> found loc mod_name ; + _ -> no_obj mod_name + }} + + found loc mod_name = do { + -- ...and then find the linkable for it + mb_lnk <- findObjectLinkableMaybe mod_name loc ; + case mb_lnk of { + Nothing -> no_obj mod_name ; + Just lnk -> return lnk + }} +\end{code} %************************************************************************ @@ -290,19 +478,16 @@ partitionLinkable li other -> [li] -findModuleLinkable_maybe :: [Linkable] -> ModuleName -> Maybe Linkable +findModuleLinkable_maybe :: [Linkable] -> Module -> Maybe Linkable findModuleLinkable_maybe lis mod = case [LM time nm us | LM time nm us <- lis, nm == mod] of [] -> Nothing [li] -> Just li many -> pprPanic "findModuleLinkable" (ppr mod) -filterModuleLinkables :: (ModuleName -> Bool) -> [Linkable] -> [Linkable] -filterModuleLinkables p ls = filter (p . linkableModName) ls - linkableInSet :: Linkable -> [Linkable] -> Bool linkableInSet l objs_loaded = - case findModuleLinkable_maybe objs_loaded (linkableModName l) of + case findModuleLinkable_maybe objs_loaded (linkableModule l) of Nothing -> False Just m -> linkableTime l == linkableTime m \end{code} @@ -355,66 +540,6 @@ rmDupLinkables already ls | otherwise = go (l:already) (l:extras) ls \end{code} - -\begin{code} -linkLibraries :: DynFlags - -> [String] -- foo.o files specified on command line - -> IO () --- Used just at initialisation time to link in libraries --- specified on the command line. -linkLibraries dflags objs - = do { lib_paths <- readIORef v_Library_paths - ; minus_ls <- readIORef v_Cmdline_libraries - ; let cmdline_lib_specs = map Object objs ++ map DLL minus_ls - - ; if (null cmdline_lib_specs) then return () - else do { - - -- Now link them - ; mapM_ (preloadLib dflags lib_paths) cmdline_lib_specs - - ; maybePutStr dflags "final link ... " - ; ok <- resolveObjs - ; if succeeded ok then maybePutStrLn dflags "done." - else throwDyn (InstallationError "linking extra libraries/objects failed") - }} - where - preloadLib :: DynFlags -> [String] -> LibrarySpec -> IO () - preloadLib dflags lib_paths lib_spec - = do maybePutStr dflags ("Loading object " ++ showLS lib_spec ++ " ... ") - case lib_spec of - Object static_ish - -> do b <- preload_static lib_paths static_ish - maybePutStrLn dflags (if b then "done." - else "not found") - DLL dll_unadorned - -> do maybe_errstr <- loadDynamic lib_paths dll_unadorned - case maybe_errstr of - Nothing -> return () - Just mm -> preloadFailed mm lib_paths lib_spec - maybePutStrLn dflags "done" - - preloadFailed :: String -> [String] -> LibrarySpec -> IO () - preloadFailed sys_errmsg paths spec - = do maybePutStr dflags - ("failed.\nDynamic linker error message was:\n " - ++ sys_errmsg ++ "\nWhilst trying to load: " - ++ showLS spec ++ "\nDirectories to search are:\n" - ++ unlines (map (" "++) paths) ) - give_up - - -- not interested in the paths in the static case. - preload_static paths name - = do b <- doesFileExist name - if not b then return False - else loadObj name >> return True - - give_up - = (throwDyn . CmdLineError) - "user specified .o/.so/.DLL could not be loaded." -\end{code} - - %************************************************************************ %* * \subsection{The byte-code linker} @@ -463,7 +588,7 @@ linkSomeBCOs :: Bool -- False <=> add _all_ BCOs to returned closure env linkSomeBCOs toplevs_only ie ce_in ul_bcos - = do let nms = map nameOfUnlinkedBCO ul_bcos + = do let nms = map unlinkedBCOName ul_bcos hvals <- fixIO ( \ hvs -> let ce_out = extendClosureEnv ce_in (zipLazy nms hvs) in mapM (linkBCO ie ce_out) ul_bcos ) @@ -507,19 +632,17 @@ unload :: DynFlags -> [Linkable] -> IO () unload dflags linkables = block $ do -- block, so we're safe from Ctrl-C in here + + -- Initialise the linker (if it's not been done already) + initDynLinker dflags pls <- readIORef v_PersistentLinkerState new_pls <- unload_wkr dflags linkables pls writeIORef v_PersistentLinkerState new_pls - let verb = verbosity dflags - when (verb >= 3) $ do - hPutStrLn stderr (showSDoc - (text "unload: retaining objs" <+> ppr (objs_loaded new_pls))) - hPutStrLn stderr (showSDoc - (text "unload: retaining bcos" <+> ppr (bcos_loaded new_pls))) - - return () + debugTraceMsg dflags 3 (text "unload: retaining objs" <+> ppr (objs_loaded new_pls)) + debugTraceMsg dflags 3 (text "unload: retaining bcos" <+> ppr (bcos_loaded new_pls)) + return () unload_wkr :: DynFlags -> [Linkable] -- stable linkables @@ -534,8 +657,7 @@ unload_wkr dflags linkables pls objs_loaded' <- filterM (maybeUnload objs_to_keep) (objs_loaded pls) bcos_loaded' <- filterM (maybeUnload bcos_to_keep) (bcos_loaded pls) - let objs_retained = map linkableModName objs_loaded' - bcos_retained = map linkableModName bcos_loaded' + let bcos_retained = map linkableModule bcos_loaded' itbl_env' = filterNameMap bcos_retained (itbl_env pls) closure_env' = filterNameMap bcos_retained (closure_env pls) new_pls = pls { itbl_env = itbl_env', @@ -579,9 +701,11 @@ data LibrarySpec -- On WinDoze "burble" denotes "burble.DLL" -- loadDLL is platform-specific and adds the lib/.so/.DLL -- suffixes platform-dependently -#ifdef darwin_TARGET_OS - | Framework String -#endif + + | DLLPath FilePath -- Absolute or relative pathname to a dynamic library + -- (ends with .dll or .so). + + | Framework String -- Only used for darwin, but does no harm -- If this package is already part of the GHCi binary, we'll already -- have the right DLLs for this package loaded, so don't try to @@ -592,35 +716,41 @@ data LibrarySpec -- of DLL handles that rts/Linker.c maintains, and that in turn is -- used by lookupSymbol. So we must call addDLL for each library -- just to get the DLL handle into the list. -partOfGHCi -# ifndef mingw32_TARGET_OS - = [ "base", "haskell98", "haskell-src", "readline" ] +partOfGHCi +# if defined(mingw32_TARGET_OS) || defined(darwin_TARGET_OS) + = [ ] # else - = [ ] + = [ "base", "haskell98", "template-haskell", "readline" ] # endif -showLS (Object nm) = "(static) " ++ nm -showLS (DLL nm) = "(dynamic) " ++ nm -#ifdef darwin_TARGET_OS +showLS (Object nm) = "(static) " ++ nm +showLS (DLL nm) = "(dynamic) " ++ nm +showLS (DLLPath nm) = "(dynamic) " ++ nm showLS (Framework nm) = "(framework) " ++ nm -#endif -linkPackages :: DynFlags -> [PackageName] -> IO () +linkPackages :: DynFlags -> [PackageId] -> IO () -- Link exactly the specified packages, and their dependents -- (unless of course they are already linked) -- The dependents are linked automatically, and it doesn't matter -- what order you specify the input packages. +-- +-- NOTE: in fact, since each module tracks all the packages it depends on, +-- we don't really need to use the package-config dependencies. +-- However we do need the package-config stuff (to find aux libs etc), +-- and following them lets us load libraries in the right order, which +-- perhaps makes the error message a bit more localised if we get a link +-- failure. So the dependency walking code is still here. linkPackages dflags new_pkgs = do { pls <- readIORef v_PersistentLinkerState - ; pkg_map <- getPackageConfigMap + ; let pkg_map = pkgIdMap (pkgState dflags) ; pkgs' <- link pkg_map (pkgs_loaded pls) new_pkgs ; writeIORef v_PersistentLinkerState (pls { pkgs_loaded = pkgs' }) } where - link :: PackageConfigMap -> [PackageName] -> [PackageName] -> IO [PackageName] + link :: PackageConfigMap -> [PackageId] -> [PackageId] -> IO [PackageId] link pkg_map pkgs new_pkgs = foldM (link_one pkg_map) pkgs new_pkgs @@ -628,64 +758,84 @@ linkPackages dflags new_pkgs | new_pkg `elem` pkgs -- Already linked = return pkgs - | Just pkg_cfg <- lookupPkg pkg_map new_pkg + | Just pkg_cfg <- lookupPackage pkg_map new_pkg = do { -- Link dependents first - pkgs' <- link pkg_map pkgs (packageDependents pkg_cfg) + pkgs' <- link pkg_map pkgs (map mkPackageId (depends pkg_cfg)) -- Now link the package itself ; linkPackage dflags pkg_cfg ; return (new_pkg : pkgs') } | otherwise - = throwDyn (CmdLineError ("unknown package name: " ++ packageNameString new_pkg)) + = throwDyn (CmdLineError ("unknown package: " ++ packageIdString new_pkg)) linkPackage :: DynFlags -> PackageConfig -> IO () linkPackage dflags pkg = do - let dirs = Packages.library_dirs pkg - let libs = Packages.hs_libraries pkg ++ extra_libraries pkg + let dirs = Packages.libraryDirs pkg + + let libs = Packages.hsLibraries pkg + -- Because of slight differences between the GHC dynamic linker and + -- the native system linker some packages have to link with a + -- different list of libraries when using GHCi. Examples include: libs + -- that are actually gnu ld scripts, and the possability that the .a + -- 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. + ++ (if null (Packages.extraGHCiLibraries pkg) + then Packages.extraLibraries pkg + else Packages.extraGHCiLibraries pkg) + ++ [ lib | '-':'l':lib <- Packages.ldOptions pkg ] classifieds <- mapM (locateOneObj dirs) libs -#ifdef darwin_TARGET_OS - let fwDirs = Packages.framework_dirs pkg - let frameworks= Packages.extra_frameworks pkg -#endif -- Complication: all the .so's must be loaded before any of the .o's. let dlls = [ dll | DLL dll <- classifieds ] objs = [ obj | Object obj <- classifieds ] - maybePutStr dflags ("Loading package " ++ Packages.name pkg ++ " ... ") + maybePutStr dflags ("Loading package " ++ showPackageId (package pkg) ++ " ... ") -- See comments with partOfGHCi - when (Packages.name pkg `notElem` partOfGHCi) $ do -#ifdef darwin_TARGET_OS - loadFrameworks fwDirs frameworks -#endif - loadDynamics dirs dlls + when (pkgName (package pkg) `notElem` partOfGHCi) $ do + loadFrameworks pkg + -- When a library A needs symbols from a library B, the order in + -- extra_libraries/extra_ld_opts is "-lA -lB", because that's the + -- way ld expects it for static linking. Dynamic linking is a + -- different story: When A has no dependency information for B, + -- dlopen-ing A with RTLD_NOW (see addDLL in Linker.c) will fail + -- when B has not been loaded before. In a nutshell: Reverse the + -- order of DLLs for dynamic linking. + -- This fixes a problem with the HOpenGL package (see "Compiling + -- HOpenGL under recent versions of GHC" on the HOpenGL list). + mapM_ (load_dyn dirs) (reverse dlls) -- After loading all the DLLs, we can load the static objects. + -- Ordering isn't important here, because we do one final link + -- step to resolve everything. mapM_ loadObj objs maybePutStr dflags "linking ... " ok <- resolveObjs if succeeded ok then maybePutStrLn dflags "done." - else panic ("can't load package `" ++ name pkg ++ "'") - -loadDynamics dirs [] = return () -loadDynamics dirs (dll:dlls) = do - r <- loadDynamic dirs dll - case r of - Nothing -> loadDynamics dirs dlls - Just err -> throwDyn (CmdLineError ("can't load .so/.DLL for: " - ++ dll ++ " (" ++ err ++ ")" )) -#ifdef darwin_TARGET_OS -loadFrameworks dirs [] = return () -loadFrameworks dirs (fw:fws) = do - r <- loadFramework dirs fw - case r of - Nothing -> loadFrameworks dirs fws - Just err -> throwDyn (CmdLineError ("can't load framework: " - ++ fw ++ " (" ++ err ++ ")" )) + else throwDyn (InstallationError ("unable to load package `" ++ showPackageId (package pkg) ++ "'")) + +load_dyn dirs dll = do r <- loadDynamic dirs dll + case r of + Nothing -> return () + Just err -> throwDyn (CmdLineError ("can't load .so/.DLL for: " + ++ dll ++ " (" ++ err ++ ")" )) +#ifndef darwin_TARGET_OS +loadFrameworks pkg = return () +#else +loadFrameworks pkg = mapM_ load frameworks + where + fw_dirs = Packages.frameworkDirs pkg + frameworks = Packages.frameworks pkg + + load fw = do r <- loadFramework fw_dirs fw + case r of + Nothing -> return () + Just err -> throwDyn (CmdLineError ("can't load framework: " + ++ fw ++ " (" ++ err ++ ")" )) #endif -- Try to find an object file for a given library in the given paths. @@ -695,9 +845,14 @@ locateOneObj dirs lib = do { mb_obj_path <- findFile mk_obj_path dirs ; case mb_obj_path of Just obj_path -> return (Object obj_path) - Nothing -> return (DLL lib) } -- we assume + Nothing -> + do { mb_lib_path <- findFile mk_dyn_lib_path dirs + ; case mb_lib_path of + Just lib_path -> return (DLL (lib ++ "_dyn")) + Nothing -> return (DLL lib) }} -- We assume where - mk_obj_path dir = dir ++ '/':lib ++ ".o" + mk_obj_path dir = dir `joinFileName` (lib `joinFileExt` "o") + mk_dyn_lib_path dir = dir `joinFileName` mkSOName (lib ++ "_dyn") -- ---------------------------------------------------------------------------- @@ -712,16 +867,16 @@ loadDynamic paths rootname -- Tried all our known library paths, so let -- dlopen() search its own builtin paths now. where - mk_dll_path dir = dir ++ '/':mkSOName rootname + mk_dll_path dir = dir `joinFileName` mkSOName rootname #if defined(darwin_TARGET_OS) -mkSOName root = "lib" ++ root ++ ".dylib" +mkSOName root = ("lib" ++ root) `joinFileExt` "dylib" #elif defined(mingw32_TARGET_OS) -- Win32 DLLs have no .dll extension here, because addDLL tries -- both foo.dll and foo.drv mkSOName root = root #else -mkSOName root = "lib" ++ root ++ ".so" +mkSOName root = ("lib" ++ root) `joinFileExt` "so" #endif -- Darwin / MacOS X only: load a framework @@ -736,7 +891,7 @@ loadFramework extraPaths rootname -- Tried all our known library paths, but dlopen() -- has no built-in paths for frameworks: give up where - mk_fwk dir = dir ++ '/' : rootname ++ ".framework/" ++ rootname + mk_fwk dir = dir `joinFileName` (rootname ++ ".framework/" ++ rootname) -- sorry for the hardcoded paths, I hope they won't change anytime soon: defaultFrameworkPaths = ["/Library/Frameworks", "/System/Library/Frameworks"] #endif