2 % (c) The University of Glasgow 2005
5 -- --------------------------------------
6 -- The dynamic linker for GHCi
7 -- --------------------------------------
9 This module deals with the top-level issues of dynamic linking,
10 calling the object-code linker and the byte-code linker where
16 {-# OPTIONS -optc-DNON_POSIX_SOURCE -#include "Linker.h" #-}
18 module Linker ( HValue, showLinkerState,
19 linkExpr, unload, extendLinkEnv, withExtendedLinkEnv,
21 linkPackages,initDynLinker
24 #include "HsVersions.h"
26 import ObjLink ( loadDLL, loadObj, unloadObj, resolveObjs, initObjLinker )
27 import ByteCodeLink ( HValue, ClosureEnv, extendClosureEnv, linkBCO )
28 import ByteCodeItbls ( ItblEnv )
29 import ByteCodeAsm ( CompiledByteCode(..), bcoFreeNames, UnlinkedBCO(..))
32 import DriverPhases ( isObjectFilename, isDynLibFilename )
33 import Finder ( findModule, findObjectLinkableMaybe, FindResult(..) )
35 import Name ( Name, nameModule, isExternalName, isWiredInName )
37 import NameSet ( nameSetToList )
39 import ListSetOps ( minusList )
40 import DynFlags ( DynFlags(..), getOpts )
41 import BasicTypes ( SuccessFlag(..), succeeded, failed )
43 import Panic ( GhcException(..) )
44 import Util ( zipLazy, global, joinFileExt, joinFileName, suffixOf )
45 import StaticFlags ( v_Ld_inputs )
46 import ErrUtils ( debugTraceMsg )
49 import Control.Monad ( when, filterM, foldM )
51 import Data.IORef ( IORef, readIORef, writeIORef, modifyIORef )
52 import Data.List ( partition, nub )
54 import System.IO ( putStr, putStrLn, hPutStrLn, stderr, fixIO )
55 import System.Directory ( doesFileExist )
57 import Control.Exception ( block, throwDyn, bracket )
58 import Maybe ( isJust, fromJust )
60 #if __GLASGOW_HASKELL__ >= 503
61 import GHC.IOBase ( IO(..) )
63 import PrelIOBase ( IO(..) )
68 %************************************************************************
72 %************************************************************************
74 The persistent linker state *must* match the actual state of the
75 C dynamic linker at all times, so we keep it in a private global variable.
78 The PersistentLinkerState maps Names to actual closures (for
79 interpreted code only), for use during linking.
82 GLOBAL_VAR(v_PersistentLinkerState, panic "Dynamic linker not initialised", PersistentLinkerState)
83 GLOBAL_VAR(v_InitLinkerDone, False, Bool) -- Set True when dynamic linker is initialised
85 data PersistentLinkerState
86 = PersistentLinkerState {
88 -- Current global mapping from Names to their true values
89 closure_env :: ClosureEnv,
91 -- The current global mapping from RdrNames of DataCons to
92 -- info table addresses.
93 -- When a new Unlinked is linked into the running image, or an existing
94 -- module in the image is replaced, the itbl_env must be updated
98 -- The currently loaded interpreted modules (home package)
99 bcos_loaded :: [Linkable],
101 -- And the currently-loaded compiled modules (home package)
102 objs_loaded :: [Linkable],
104 -- The currently-loaded packages; always object code
105 -- Held, as usual, in dependency order; though I am not sure if
106 -- that is really important
107 pkgs_loaded :: [PackageId]
110 emptyPLS :: DynFlags -> PersistentLinkerState
111 emptyPLS dflags = PersistentLinkerState {
112 closure_env = emptyNameEnv,
113 itbl_env = emptyNameEnv,
114 pkgs_loaded = init_pkgs,
117 -- Packages that don't need loading, because the compiler
118 -- shares them with the interpreted program.
120 -- The linker's symbol table is populated with RTS symbols using an
121 -- explicit list. See rts/Linker.c for details.
123 | ExtPackage rts_id <- rtsPackageId (pkgState dflags) = [rts_id]
128 extendLoadedPkgs :: [PackageId] -> IO ()
129 extendLoadedPkgs pkgs
130 = modifyIORef v_PersistentLinkerState (\s -> s{pkgs_loaded = pkgs ++ pkgs_loaded s})
132 extendLinkEnv :: [(Name,HValue)] -> IO ()
133 -- Automatically discards shadowed bindings
134 extendLinkEnv new_bindings
135 = do pls <- readIORef v_PersistentLinkerState
136 let new_closure_env = extendClosureEnv (closure_env pls) new_bindings
137 new_pls = pls { closure_env = new_closure_env }
138 writeIORef v_PersistentLinkerState new_pls
140 withExtendedLinkEnv :: [(Name,HValue)] -> IO a -> IO a
141 withExtendedLinkEnv new_env action
142 = bracket set_new_env
145 where set_new_env = do pls <- readIORef v_PersistentLinkerState
146 let new_closure_env = extendClosureEnv (closure_env pls) new_env
147 new_pls = pls { closure_env = new_closure_env }
148 writeIORef v_PersistentLinkerState new_pls
149 return (closure_env pls)
150 reset_old_env env = modifyIORef v_PersistentLinkerState (\pls -> pls{ closure_env = env })
152 -- filterNameMap removes from the environment all entries except
153 -- those for a given set of modules;
154 -- Note that this removes all *local* (i.e. non-isExternal) names too
155 -- (these are the temporary bindings from the command line).
156 -- Used to filter both the ClosureEnv and ItblEnv
158 filterNameMap :: [Module] -> NameEnv (Name, a) -> NameEnv (Name, a)
159 filterNameMap mods env
160 = filterNameEnv keep_elt env
162 keep_elt (n,_) = isExternalName n
163 && (nameModule n `elem` mods)
168 showLinkerState :: IO ()
169 -- Display the persistent linker state
171 = do pls <- readIORef v_PersistentLinkerState
172 printDump (vcat [text "----- Linker state -----",
173 text "Pkgs:" <+> ppr (pkgs_loaded pls),
174 text "Objs:" <+> ppr (objs_loaded pls),
175 text "BCOs:" <+> ppr (bcos_loaded pls)])
181 %************************************************************************
183 \subsection{Initialisation}
185 %************************************************************************
187 We initialise the dynamic linker by
189 a) calling the C initialisation procedure
191 b) Loading any packages specified on the command line,
192 now held in v_ExplicitPackages
194 c) Loading any packages specified on the command line,
195 now held in the -l options in v_Opt_l
197 d) Loading any .o/.dll files specified on the command line,
198 now held in v_Ld_inputs
200 e) Loading any MacOS frameworks
203 initDynLinker :: DynFlags -> IO ()
204 -- This function is idempotent; if called more than once, it does nothing
205 -- This is useful in Template Haskell, where we call it before trying to link
207 = do { done <- readIORef v_InitLinkerDone
208 ; if done then return ()
209 else do { writeIORef v_InitLinkerDone True
210 ; reallyInitDynLinker dflags }
213 reallyInitDynLinker dflags
214 = do { -- Initialise the linker state
215 ; writeIORef v_PersistentLinkerState (emptyPLS dflags)
217 -- (a) initialise the C dynamic linker
220 -- (b) Load packages from the command-line
221 ; linkPackages dflags (explicitPackages (pkgState dflags))
223 -- (c) Link libraries from the command-line
224 ; let optl = getOpts dflags opt_l
225 ; let minus_ls = [ lib | '-':'l':lib <- optl ]
227 -- (d) Link .o files from the command-line
228 ; let lib_paths = libraryPaths dflags
229 ; cmdline_ld_inputs <- readIORef v_Ld_inputs
231 ; classified_ld_inputs <- mapM classifyLdInput cmdline_ld_inputs
233 -- (e) Link any MacOS frameworks
234 #ifdef darwin_TARGET_OS
235 ; let framework_paths = frameworkPaths dflags
236 ; let frameworks = cmdlineFrameworks dflags
238 ; let frameworks = []
239 ; let framework_paths = []
241 -- Finally do (c),(d),(e)
242 ; let cmdline_lib_specs = [ l | Just l <- classified_ld_inputs ]
244 ++ map Framework frameworks
245 ; if null cmdline_lib_specs then return ()
248 { mapM_ (preloadLib dflags lib_paths framework_paths) cmdline_lib_specs
249 ; maybePutStr dflags "final link ... "
252 ; if succeeded ok then maybePutStrLn dflags "done"
253 else throwDyn (InstallationError "linking extra libraries/objects failed")
256 classifyLdInput :: FilePath -> IO (Maybe LibrarySpec)
258 | isObjectFilename f = return (Just (Object f))
259 | isDynLibFilename f = return (Just (DLLPath f))
261 hPutStrLn stderr ("Warning: ignoring unrecognised input `" ++ f ++ "'")
264 preloadLib :: DynFlags -> [String] -> [String] -> LibrarySpec -> IO ()
265 preloadLib dflags lib_paths framework_paths lib_spec
266 = do maybePutStr dflags ("Loading object " ++ showLS lib_spec ++ " ... ")
269 -> do b <- preload_static lib_paths static_ish
270 maybePutStrLn dflags (if b then "done"
274 -> do maybe_errstr <- loadDynamic lib_paths dll_unadorned
276 Nothing -> maybePutStrLn dflags "done"
277 Just mm -> preloadFailed mm lib_paths lib_spec
280 -> do maybe_errstr <- loadDLL dll_path
282 Nothing -> maybePutStrLn dflags "done"
283 Just mm -> preloadFailed mm lib_paths lib_spec
285 #ifdef darwin_TARGET_OS
287 -> do maybe_errstr <- loadFramework framework_paths framework
289 Nothing -> maybePutStrLn dflags "done"
290 Just mm -> preloadFailed mm framework_paths lib_spec
293 preloadFailed :: String -> [String] -> LibrarySpec -> IO ()
294 preloadFailed sys_errmsg paths spec
295 = do maybePutStr dflags
296 ("failed.\nDynamic linker error message was:\n "
297 ++ sys_errmsg ++ "\nWhilst trying to load: "
298 ++ showLS spec ++ "\nDirectories to search are:\n"
299 ++ unlines (map (" "++) paths) )
302 -- Not interested in the paths in the static case.
303 preload_static paths name
304 = do b <- doesFileExist name
305 if not b then return False
306 else loadObj name >> return True
309 CmdLineError "user specified .o/.so/.DLL could not be loaded."
313 %************************************************************************
315 Link a byte-code expression
317 %************************************************************************
320 linkExpr :: HscEnv -> UnlinkedBCO -> IO HValue
322 -- Link a single expression, *including* first linking packages and
323 -- modules that this expression depends on.
325 -- Raises an IO exception if it can't find a compiled version of the
326 -- dependents to link.
328 linkExpr hsc_env root_ul_bco
330 -- Initialise the linker (if it's not been done already)
331 let dflags = hsc_dflags hsc_env
332 ; initDynLinker dflags
334 -- Find what packages and linkables are required
335 ; eps <- readIORef (hsc_EPS hsc_env)
336 ; (lnks, pkgs) <- getLinkDeps hsc_env hpt (eps_PIT eps) needed_mods
338 -- Link the packages and modules required
339 ; linkPackages dflags pkgs
340 ; ok <- linkModules dflags lnks
345 -- Link the expression itself
346 pls <- readIORef v_PersistentLinkerState
347 ; let ie = itbl_env pls
350 -- Link the necessary packages and linkables
351 ; (_, (root_hval:_)) <- linkSomeBCOs False ie ce [root_ul_bco]
355 hpt = hsc_HPT hsc_env
356 dflags = hsc_dflags hsc_env
357 free_names = nameSetToList (bcoFreeNames root_ul_bco)
359 needed_mods :: [Module]
360 needed_mods = [ nameModule n | n <- free_names,
361 isExternalName n, -- Names from other modules
362 not (isWiredInName n) -- Exclude wired-in names
363 ] -- (see note below)
364 -- Exclude wired-in names because we may not have read
365 -- their interface files, so getLinkDeps will fail
366 -- All wired-in names are in the base package, which we link
367 -- by default, so we can safely ignore them here.
369 dieWith msg = throwDyn (ProgramError (showSDoc msg))
371 getLinkDeps :: HscEnv -> HomePackageTable -> PackageIfaceTable
372 -> [Module] -- If you need these
373 -> IO ([Linkable], [PackageId]) -- ... then link these first
374 -- Fails with an IO exception if it can't find enough files
376 getLinkDeps hsc_env hpt pit mods
377 -- Find all the packages and linkables that a set of modules depends on
378 = do { pls <- readIORef v_PersistentLinkerState ;
380 -- 1. Find the dependent home-pkg-modules/packages from each iface
381 (mods_s, pkgs_s) = unzip (map get_deps mods) ;
383 -- 2. Exclude ones already linked
384 -- Main reason: avoid findModule calls in get_linkable
385 mods_needed = nub (concat mods_s) `minusList` linked_mods ;
386 pkgs_needed = nub (concat pkgs_s) `minusList` pkgs_loaded pls ;
388 linked_mods = map linkableModule (objs_loaded pls ++ bcos_loaded pls)
391 -- 3. For each dependent module, find its linkable
392 -- This will either be in the HPT or (in the case of one-shot
393 -- compilation) we may need to use maybe_getFileLinkable
394 lnks_needed <- mapM get_linkable mods_needed ;
396 return (lnks_needed, pkgs_needed) }
398 get_deps :: Module -> ([Module],[PackageId])
399 -- Get the things needed for the specified module
400 -- This is rather similar to the code in RnNames.importsFromImportDecl
402 | ExtPackage p <- mi_package iface
403 = ([], p : dep_pkgs deps)
405 = (mod : [m | (m,_) <- dep_mods deps], dep_pkgs deps)
407 iface = get_iface mod
410 get_iface mod = case lookupIface hpt pit mod of
412 Nothing -> pprPanic "getLinkDeps" (no_iface mod)
413 no_iface mod = ptext SLIT("No iface for") <+> ppr mod
414 -- This one is a GHC bug
416 no_obj mod = dieWith (ptext SLIT("No compiled code for") <+> ppr mod)
417 -- This one is a build-system bug
419 get_linkable mod_name -- A home-package module
420 | Just mod_info <- lookupModuleEnv hpt mod_name
421 = ASSERT(isJust (hm_linkable mod_info))
422 return (fromJust (hm_linkable mod_info))
424 = -- It's not in the HPT because we are in one shot mode,
425 -- so use the Finder to get a ModLocation...
426 do { mb_stuff <- findModule hsc_env mod_name False ;
428 Found loc _ -> found loc mod_name ;
432 found loc mod_name = do {
433 -- ...and then find the linkable for it
434 mb_lnk <- findObjectLinkableMaybe mod_name loc ;
436 Nothing -> no_obj mod_name ;
437 Just lnk -> return lnk
442 %************************************************************************
445 The linkables may consist of a mixture of
446 byte-code modules and object modules
448 %************************************************************************
451 linkModules :: DynFlags -> [Linkable] -> IO SuccessFlag
452 linkModules dflags linkables
453 = block $ do -- don't want to be interrupted by ^C in here
455 let (objs, bcos) = partition isObjectLinkable
456 (concatMap partitionLinkable linkables)
458 -- Load objects first; they can't depend on BCOs
459 ok_flag <- dynLinkObjs dflags objs
461 if failed ok_flag then
468 -- HACK to support f-x-dynamic in the interpreter; no other purpose
469 partitionLinkable :: Linkable -> [Linkable]
471 = let li_uls = linkableUnlinked li
472 li_uls_obj = filter isObject li_uls
473 li_uls_bco = filter isInterpretable li_uls
475 case (li_uls_obj, li_uls_bco) of
476 (objs@(_:_), bcos@(_:_))
477 -> [li{linkableUnlinked=li_uls_obj}, li{linkableUnlinked=li_uls_bco}]
481 findModuleLinkable_maybe :: [Linkable] -> Module -> Maybe Linkable
482 findModuleLinkable_maybe lis mod
483 = case [LM time nm us | LM time nm us <- lis, nm == mod] of
486 many -> pprPanic "findModuleLinkable" (ppr mod)
488 linkableInSet :: Linkable -> [Linkable] -> Bool
489 linkableInSet l objs_loaded =
490 case findModuleLinkable_maybe objs_loaded (linkableModule l) of
492 Just m -> linkableTime l == linkableTime m
496 %************************************************************************
498 \subsection{The object-code linker}
500 %************************************************************************
503 dynLinkObjs :: DynFlags -> [Linkable] -> IO SuccessFlag
504 -- Side-effects the PersistentLinkerState
506 dynLinkObjs dflags objs
507 = do pls <- readIORef v_PersistentLinkerState
509 -- Load the object files and link them
510 let (objs_loaded', new_objs) = rmDupLinkables (objs_loaded pls) objs
511 pls1 = pls { objs_loaded = objs_loaded' }
512 unlinkeds = concatMap linkableUnlinked new_objs
514 mapM loadObj (map nameOfObject unlinkeds)
516 -- Link the all together
519 -- If resolving failed, unload all our
520 -- object modules and carry on
521 if succeeded ok then do
522 writeIORef v_PersistentLinkerState pls1
525 pls2 <- unload_wkr dflags [] pls1
526 writeIORef v_PersistentLinkerState pls2
530 rmDupLinkables :: [Linkable] -- Already loaded
531 -> [Linkable] -- New linkables
532 -> ([Linkable], -- New loaded set (including new ones)
533 [Linkable]) -- New linkables (excluding dups)
534 rmDupLinkables already ls
537 go already extras [] = (already, extras)
538 go already extras (l:ls)
539 | linkableInSet l already = go already extras ls
540 | otherwise = go (l:already) (l:extras) ls
543 %************************************************************************
545 \subsection{The byte-code linker}
547 %************************************************************************
550 dynLinkBCOs :: [Linkable] -> IO ()
551 -- Side-effects the persistent linker state
553 = do pls <- readIORef v_PersistentLinkerState
555 let (bcos_loaded', new_bcos) = rmDupLinkables (bcos_loaded pls) bcos
556 pls1 = pls { bcos_loaded = bcos_loaded' }
557 unlinkeds :: [Unlinked]
558 unlinkeds = concatMap linkableUnlinked new_bcos
560 cbcs :: [CompiledByteCode]
561 cbcs = map byteCodeOfObject unlinkeds
564 ul_bcos = [b | ByteCode bs _ <- cbcs, b <- bs]
565 ies = [ie | ByteCode _ ie <- cbcs]
566 gce = closure_env pls
567 final_ie = foldr plusNameEnv (itbl_env pls) ies
569 (final_gce, linked_bcos) <- linkSomeBCOs True final_ie gce ul_bcos
570 -- What happens to these linked_bcos?
572 let pls2 = pls1 { closure_env = final_gce,
573 itbl_env = final_ie }
575 writeIORef v_PersistentLinkerState pls2
578 -- Link a bunch of BCOs and return them + updated closure env.
579 linkSomeBCOs :: Bool -- False <=> add _all_ BCOs to returned closure env
580 -- True <=> add only toplevel BCOs to closure env
584 -> IO (ClosureEnv, [HValue])
585 -- The returned HValues are associated 1-1 with
586 -- the incoming unlinked BCOs. Each gives the
587 -- value of the corresponding unlinked BCO
590 linkSomeBCOs toplevs_only ie ce_in ul_bcos
591 = do let nms = map unlinkedBCOName ul_bcos
593 ( \ hvs -> let ce_out = extendClosureEnv ce_in (zipLazy nms hvs)
594 in mapM (linkBCO ie ce_out) ul_bcos )
596 let ce_all_additions = zip nms hvals
597 ce_top_additions = filter (isExternalName.fst) ce_all_additions
598 ce_additions = if toplevs_only then ce_top_additions
599 else ce_all_additions
600 ce_out = -- make sure we're not inserting duplicate names into the
601 -- closure environment, which leads to trouble.
602 ASSERT (all (not . (`elemNameEnv` ce_in)) (map fst ce_additions))
603 extendClosureEnv ce_in ce_additions
604 return (ce_out, hvals)
609 %************************************************************************
611 Unload some object modules
613 %************************************************************************
616 -- ---------------------------------------------------------------------------
617 -- Unloading old objects ready for a new compilation sweep.
619 -- The compilation manager provides us with a list of linkables that it
620 -- considers "stable", i.e. won't be recompiled this time around. For
621 -- each of the modules current linked in memory,
623 -- * if the linkable is stable (and it's the same one - the
624 -- user may have recompiled the module on the side), we keep it,
626 -- * otherwise, we unload it.
628 -- * we also implicitly unload all temporary bindings at this point.
630 unload :: DynFlags -> [Linkable] -> IO ()
631 -- The 'linkables' are the ones to *keep*
633 unload dflags linkables
634 = block $ do -- block, so we're safe from Ctrl-C in here
636 -- Initialise the linker (if it's not been done already)
639 pls <- readIORef v_PersistentLinkerState
640 new_pls <- unload_wkr dflags linkables pls
641 writeIORef v_PersistentLinkerState new_pls
643 debugTraceMsg dflags 3 (text "unload: retaining objs" <+> ppr (objs_loaded new_pls))
644 debugTraceMsg dflags 3 (text "unload: retaining bcos" <+> ppr (bcos_loaded new_pls))
647 unload_wkr :: DynFlags
648 -> [Linkable] -- stable linkables
649 -> PersistentLinkerState
650 -> IO PersistentLinkerState
651 -- Does the core unload business
652 -- (the wrapper blocks exceptions and deals with the PLS get and put)
654 unload_wkr dflags linkables pls
655 = do let (objs_to_keep, bcos_to_keep) = partition isObjectLinkable linkables
657 objs_loaded' <- filterM (maybeUnload objs_to_keep) (objs_loaded pls)
658 bcos_loaded' <- filterM (maybeUnload bcos_to_keep) (bcos_loaded pls)
660 let bcos_retained = map linkableModule bcos_loaded'
661 itbl_env' = filterNameMap bcos_retained (itbl_env pls)
662 closure_env' = filterNameMap bcos_retained (closure_env pls)
663 new_pls = pls { itbl_env = itbl_env',
664 closure_env = closure_env',
665 bcos_loaded = bcos_loaded',
666 objs_loaded = objs_loaded' }
670 maybeUnload :: [Linkable] -> Linkable -> IO Bool
671 maybeUnload keep_linkables lnk
672 | linkableInSet lnk linkables = return True
674 = do mapM_ unloadObj [f | DotO f <- linkableUnlinked lnk]
675 -- The components of a BCO linkable may contain
676 -- dot-o files. Which is very confusing.
678 -- But the BCO parts can be unlinked just by
679 -- letting go of them (plus of course depopulating
680 -- the symbol table which is done in the main body)
685 %************************************************************************
689 %************************************************************************
694 = Object FilePath -- Full path name of a .o file, including trailing .o
695 -- For dynamic objects only, try to find the object
696 -- file in all the directories specified in
697 -- v_Library_paths before giving up.
699 | DLL String -- "Unadorned" name of a .DLL/.so
700 -- e.g. On unix "qt" denotes "libqt.so"
701 -- On WinDoze "burble" denotes "burble.DLL"
702 -- loadDLL is platform-specific and adds the lib/.so/.DLL
703 -- suffixes platform-dependently
705 | DLLPath FilePath -- Absolute or relative pathname to a dynamic library
706 -- (ends with .dll or .so).
708 | Framework String -- Only used for darwin, but does no harm
710 -- If this package is already part of the GHCi binary, we'll already
711 -- have the right DLLs for this package loaded, so don't try to
714 -- But on Win32 we must load them 'again'; doing so is a harmless no-op
715 -- as far as the loader is concerned, but it does initialise the list
716 -- of DLL handles that rts/Linker.c maintains, and that in turn is
717 -- used by lookupSymbol. So we must call addDLL for each library
718 -- just to get the DLL handle into the list.
720 # if defined(mingw32_TARGET_OS) || defined(darwin_TARGET_OS)
723 = [ "base", "haskell98", "template-haskell", "readline" ]
726 showLS (Object nm) = "(static) " ++ nm
727 showLS (DLL nm) = "(dynamic) " ++ nm
728 showLS (DLLPath nm) = "(dynamic) " ++ nm
729 showLS (Framework nm) = "(framework) " ++ nm
731 linkPackages :: DynFlags -> [PackageId] -> IO ()
732 -- Link exactly the specified packages, and their dependents
733 -- (unless of course they are already linked)
734 -- The dependents are linked automatically, and it doesn't matter
735 -- what order you specify the input packages.
737 -- NOTE: in fact, since each module tracks all the packages it depends on,
738 -- we don't really need to use the package-config dependencies.
739 -- However we do need the package-config stuff (to find aux libs etc),
740 -- and following them lets us load libraries in the right order, which
741 -- perhaps makes the error message a bit more localised if we get a link
742 -- failure. So the dependency walking code is still here.
744 linkPackages dflags new_pkgs
745 = do { pls <- readIORef v_PersistentLinkerState
746 ; let pkg_map = pkgIdMap (pkgState dflags)
748 ; pkgs' <- link pkg_map (pkgs_loaded pls) new_pkgs
750 ; writeIORef v_PersistentLinkerState (pls { pkgs_loaded = pkgs' })
753 link :: PackageConfigMap -> [PackageId] -> [PackageId] -> IO [PackageId]
754 link pkg_map pkgs new_pkgs
755 = foldM (link_one pkg_map) pkgs new_pkgs
757 link_one pkg_map pkgs new_pkg
758 | new_pkg `elem` pkgs -- Already linked
761 | Just pkg_cfg <- lookupPackage pkg_map new_pkg
762 = do { -- Link dependents first
763 pkgs' <- link pkg_map pkgs (map mkPackageId (depends pkg_cfg))
764 -- Now link the package itself
765 ; linkPackage dflags pkg_cfg
766 ; return (new_pkg : pkgs') }
769 = throwDyn (CmdLineError ("unknown package: " ++ packageIdString new_pkg))
772 linkPackage :: DynFlags -> PackageConfig -> IO ()
773 linkPackage dflags pkg
775 let dirs = Packages.libraryDirs pkg
777 let libs = Packages.hsLibraries pkg
778 -- Because of slight differences between the GHC dynamic linker and
779 -- the native system linker some packages have to link with a
780 -- different list of libraries when using GHCi. Examples include: libs
781 -- that are actually gnu ld scripts, and the possability that the .a
782 -- libs do not exactly match the .so/.dll equivalents. So if the
783 -- package file provides an "extra-ghci-libraries" field then we use
784 -- that instead of the "extra-libraries" field.
785 ++ (if null (Packages.extraGHCiLibraries pkg)
786 then Packages.extraLibraries pkg
787 else Packages.extraGHCiLibraries pkg)
788 ++ [ lib | '-':'l':lib <- Packages.ldOptions pkg ]
789 classifieds <- mapM (locateOneObj dirs) libs
791 -- Complication: all the .so's must be loaded before any of the .o's.
792 let dlls = [ dll | DLL dll <- classifieds ]
793 objs = [ obj | Object obj <- classifieds ]
795 maybePutStr dflags ("Loading package " ++ showPackageId (package pkg) ++ " ... ")
797 -- See comments with partOfGHCi
798 when (pkgName (package pkg) `notElem` partOfGHCi) $ do
800 -- When a library A needs symbols from a library B, the order in
801 -- extra_libraries/extra_ld_opts is "-lA -lB", because that's the
802 -- way ld expects it for static linking. Dynamic linking is a
803 -- different story: When A has no dependency information for B,
804 -- dlopen-ing A with RTLD_NOW (see addDLL in Linker.c) will fail
805 -- when B has not been loaded before. In a nutshell: Reverse the
806 -- order of DLLs for dynamic linking.
807 -- This fixes a problem with the HOpenGL package (see "Compiling
808 -- HOpenGL under recent versions of GHC" on the HOpenGL list).
809 mapM_ (load_dyn dirs) (reverse dlls)
811 -- After loading all the DLLs, we can load the static objects.
812 -- Ordering isn't important here, because we do one final link
813 -- step to resolve everything.
816 maybePutStr dflags "linking ... "
818 if succeeded ok then maybePutStrLn dflags "done."
819 else throwDyn (InstallationError ("unable to load package `" ++ showPackageId (package pkg) ++ "'"))
821 load_dyn dirs dll = do r <- loadDynamic dirs dll
824 Just err -> throwDyn (CmdLineError ("can't load .so/.DLL for: "
825 ++ dll ++ " (" ++ err ++ ")" ))
826 #ifndef darwin_TARGET_OS
827 loadFrameworks pkg = return ()
829 loadFrameworks pkg = mapM_ load frameworks
831 fw_dirs = Packages.frameworkDirs pkg
832 frameworks = Packages.frameworks pkg
834 load fw = do r <- loadFramework fw_dirs fw
837 Just err -> throwDyn (CmdLineError ("can't load framework: "
838 ++ fw ++ " (" ++ err ++ ")" ))
841 -- Try to find an object file for a given library in the given paths.
842 -- If it isn't present, we assume it's a dynamic library.
843 locateOneObj :: [FilePath] -> String -> IO LibrarySpec
844 locateOneObj dirs lib
845 = do { mb_obj_path <- findFile mk_obj_path dirs
846 ; case mb_obj_path of
847 Just obj_path -> return (Object obj_path)
849 do { mb_lib_path <- findFile mk_dyn_lib_path dirs
850 ; case mb_lib_path of
851 Just lib_path -> return (DLL (lib ++ "_dyn"))
852 Nothing -> return (DLL lib) }} -- We assume
854 mk_obj_path dir = dir `joinFileName` (lib `joinFileExt` "o")
855 mk_dyn_lib_path dir = dir `joinFileName` mkSOName (lib ++ "_dyn")
858 -- ----------------------------------------------------------------------------
859 -- Loading a dyanmic library (dlopen()-ish on Unix, LoadLibrary-ish on Win32)
861 -- return Nothing == success, else Just error message from dlopen
862 loadDynamic paths rootname
863 = do { mb_dll <- findFile mk_dll_path paths
865 Just dll -> loadDLL dll
866 Nothing -> loadDLL (mkSOName rootname) }
867 -- Tried all our known library paths, so let
868 -- dlopen() search its own builtin paths now.
870 mk_dll_path dir = dir `joinFileName` mkSOName rootname
872 #if defined(darwin_TARGET_OS)
873 mkSOName root = ("lib" ++ root) `joinFileExt` "dylib"
874 #elif defined(mingw32_TARGET_OS)
875 -- Win32 DLLs have no .dll extension here, because addDLL tries
876 -- both foo.dll and foo.drv
879 mkSOName root = ("lib" ++ root) `joinFileExt` "so"
882 -- Darwin / MacOS X only: load a framework
883 -- a framework is a dynamic library packaged inside a directory of the same
884 -- name. They are searched for in different paths than normal libraries.
885 #ifdef darwin_TARGET_OS
886 loadFramework extraPaths rootname
887 = do { mb_fwk <- findFile mk_fwk (extraPaths ++ defaultFrameworkPaths)
889 Just fwk_path -> loadDLL fwk_path
890 Nothing -> return (Just "not found") }
891 -- Tried all our known library paths, but dlopen()
892 -- has no built-in paths for frameworks: give up
894 mk_fwk dir = dir `joinFileName` (rootname ++ ".framework/" ++ rootname)
895 -- sorry for the hardcoded paths, I hope they won't change anytime soon:
896 defaultFrameworkPaths = ["/Library/Frameworks", "/System/Library/Frameworks"]
900 %************************************************************************
904 %************************************************************************
907 findFile :: (FilePath -> FilePath) -- Maps a directory path to a file path
908 -> [FilePath] -- Directories to look in
909 -> IO (Maybe FilePath) -- The first file path to match
910 findFile mk_file_path []
912 findFile mk_file_path (dir:dirs)
913 = do { let file_path = mk_file_path dir
914 ; b <- doesFileExist file_path
916 return (Just file_path)
918 findFile mk_file_path dirs }
922 maybePutStr dflags s | verbosity dflags > 0 = putStr s
923 | otherwise = return ()
925 maybePutStrLn dflags s | verbosity dflags > 0 = putStrLn s
926 | otherwise = return ()