2 % (c) The University of Glasgow 2000
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,
23 #include "HsVersions.h"
25 import ObjLink ( loadDLL, loadObj, unloadObj, resolveObjs, initObjLinker )
26 import ByteCodeLink ( HValue, ClosureEnv, extendClosureEnv, linkBCO )
27 import ByteCodeItbls ( ItblEnv )
28 import ByteCodeAsm ( CompiledByteCode(..), bcoFreeNames, UnlinkedBCO(..))
31 import DriverState ( v_Library_paths, v_Opt_l, v_Ld_inputs, getStaticOpts )
32 import DriverPhases ( isObjectFilename, isDynLibFilename )
33 import DriverUtil ( getFileSuffix )
34 #ifdef darwin_TARGET_OS
35 import DriverState ( v_Cmdline_frameworks, v_Framework_paths )
37 import Finder ( findModule, findLinkable, FindResult(..) )
39 import Name ( Name, nameModule, isExternalName, isWiredInName )
41 import NameSet ( nameSetToList )
43 import ListSetOps ( minusList )
44 import CmdLineOpts ( DynFlags(..) )
45 import BasicTypes ( SuccessFlag(..), succeeded, failed )
47 import Panic ( GhcException(..) )
48 import Util ( zipLazy, global )
51 import Control.Monad ( when, filterM, foldM )
53 import Data.IORef ( IORef, readIORef, writeIORef )
54 import Data.List ( partition, nub )
56 import System.IO ( putStr, putStrLn, hPutStrLn, stderr, fixIO )
57 import System.Directory ( doesFileExist )
59 import Control.Exception ( block, throwDyn )
61 #if __GLASGOW_HASKELL__ >= 503
62 import GHC.IOBase ( IO(..) )
64 import PrelIOBase ( IO(..) )
69 %************************************************************************
73 %************************************************************************
75 The persistent linker state *must* match the actual state of the
76 C dynamic linker at all times, so we keep it in a private global variable.
79 The PersistentLinkerState maps Names to actual closures (for
80 interpreted code only), for use during linking.
83 GLOBAL_VAR(v_PersistentLinkerState, panic "Dynamic linker not initialised", PersistentLinkerState)
84 GLOBAL_VAR(v_InitLinkerDone, False, Bool) -- Set True when dynamic linker is initialised
86 data PersistentLinkerState
87 = PersistentLinkerState {
89 -- Current global mapping from Names to their true values
90 closure_env :: ClosureEnv,
92 -- The current global mapping from RdrNames of DataCons to
93 -- info table addresses.
94 -- When a new Unlinked is linked into the running image, or an existing
95 -- module in the image is replaced, the itbl_env must be updated
99 -- The currently loaded interpreted modules (home package)
100 bcos_loaded :: [Linkable],
102 -- And the currently-loaded compiled modules (home package)
103 objs_loaded :: [Linkable],
105 -- The currently-loaded packages; always object code
106 -- Held, as usual, in dependency order; though I am not sure if
107 -- that is really important
108 pkgs_loaded :: [PackageId]
111 emptyPLS :: DynFlags -> PersistentLinkerState
112 emptyPLS dflags = PersistentLinkerState {
113 closure_env = emptyNameEnv,
114 itbl_env = emptyNameEnv,
115 pkgs_loaded = init_pkgs,
118 -- Packages that don't need loading, because the compiler
119 -- shares them with the interpreted program.
121 -- The linker's symbol table is populated with RTS symbols using an
122 -- explicit list. See rts/Linker.c for details.
124 | ExtPackage rts_id <- rtsPackageId (pkgState dflags) = [rts_id]
129 extendLinkEnv :: [(Name,HValue)] -> IO ()
130 -- Automatically discards shadowed bindings
131 extendLinkEnv new_bindings
132 = do pls <- readIORef v_PersistentLinkerState
133 let new_closure_env = extendClosureEnv (closure_env pls) new_bindings
134 new_pls = pls { closure_env = new_closure_env }
135 writeIORef v_PersistentLinkerState new_pls
137 -- filterNameMap removes from the environment all entries except
138 -- those for a given set of modules;
139 -- Note that this removes all *local* (i.e. non-isExternal) names too
140 -- (these are the temporary bindings from the command line).
141 -- Used to filter both the ClosureEnv and ItblEnv
143 filterNameMap :: [Module] -> NameEnv (Name, a) -> NameEnv (Name, a)
144 filterNameMap mods env
145 = filterNameEnv keep_elt env
147 keep_elt (n,_) = isExternalName n
148 && (nameModule n `elem` mods)
153 showLinkerState :: IO ()
154 -- Display the persistent linker state
156 = do pls <- readIORef v_PersistentLinkerState
157 printDump (vcat [text "----- Linker state -----",
158 text "Pkgs:" <+> ppr (pkgs_loaded pls),
159 text "Objs:" <+> ppr (objs_loaded pls),
160 text "BCOs:" <+> ppr (bcos_loaded pls)])
166 %************************************************************************
168 \subsection{Initialisation}
170 %************************************************************************
172 We initialise the dynamic linker by
174 a) calling the C initialisation procedure
176 b) Loading any packages specified on the command line,
177 now held in v_ExplicitPackages
179 c) Loading any packages specified on the command line,
180 now held in the -l options in v_Opt_l
182 d) Loading any .o/.dll files specified on the command line,
183 now held in v_Ld_inputs
185 e) Loading any MacOS frameworks
188 initDynLinker :: DynFlags -> IO ()
189 -- This function is idempotent; if called more than once, it does nothing
190 -- This is useful in Template Haskell, where we call it before trying to link
192 = do { done <- readIORef v_InitLinkerDone
193 ; if done then return ()
194 else do { writeIORef v_InitLinkerDone True
195 ; reallyInitDynLinker dflags }
198 reallyInitDynLinker dflags
199 = do { -- Initialise the linker state
200 ; writeIORef v_PersistentLinkerState (emptyPLS dflags)
202 -- (a) initialise the C dynamic linker
205 -- (b) Load packages from the command-line
206 ; linkPackages dflags (explicitPackages (pkgState dflags))
208 -- (c) Link libraries from the command-line
209 ; opt_l <- getStaticOpts v_Opt_l
210 ; let minus_ls = [ lib | '-':'l':lib <- opt_l ]
212 -- (d) Link .o files from the command-line
213 ; lib_paths <- readIORef v_Library_paths
214 ; cmdline_ld_inputs <- readIORef v_Ld_inputs
216 ; classified_ld_inputs <- mapM classifyLdInput cmdline_ld_inputs
218 -- (e) Link any MacOS frameworks
219 #ifdef darwin_TARGET_OS
220 ; framework_paths <- readIORef v_Framework_paths
221 ; frameworks <- readIORef v_Cmdline_frameworks
223 ; let frameworks = []
224 ; let framework_paths = []
226 -- Finally do (c),(d),(e)
227 ; let cmdline_lib_specs = [ l | Just l <- classified_ld_inputs ]
229 ++ map Framework frameworks
230 ; if null cmdline_lib_specs then return ()
233 { mapM_ (preloadLib dflags lib_paths framework_paths) cmdline_lib_specs
234 ; maybePutStr dflags "final link ... "
237 ; if succeeded ok then maybePutStrLn dflags "done"
238 else throwDyn (InstallationError "linking extra libraries/objects failed")
241 classifyLdInput :: FilePath -> IO (Maybe LibrarySpec)
243 | isObjectFilename f = return (Just (Object f))
244 | isDynLibFilename f = return (Just (DLLPath f))
246 hPutStrLn stderr ("Warning: ignoring unrecognised input `" ++ f ++ "'")
249 preloadLib :: DynFlags -> [String] -> [String] -> LibrarySpec -> IO ()
250 preloadLib dflags lib_paths framework_paths lib_spec
251 = do maybePutStr dflags ("Loading object " ++ showLS lib_spec ++ " ... ")
254 -> do b <- preload_static lib_paths static_ish
255 maybePutStrLn dflags (if b then "done"
259 -> do maybe_errstr <- loadDynamic lib_paths dll_unadorned
261 Nothing -> maybePutStrLn dflags "done"
262 Just mm -> preloadFailed mm lib_paths lib_spec
265 -> do maybe_errstr <- loadDLL dll_path
267 Nothing -> maybePutStrLn dflags "done"
268 Just mm -> preloadFailed mm lib_paths lib_spec
270 #ifdef darwin_TARGET_OS
272 -> do maybe_errstr <- loadFramework framework_paths framework
274 Nothing -> maybePutStrLn dflags "done"
275 Just mm -> preloadFailed mm framework_paths lib_spec
278 preloadFailed :: String -> [String] -> LibrarySpec -> IO ()
279 preloadFailed sys_errmsg paths spec
280 = do maybePutStr dflags
281 ("failed.\nDynamic linker error message was:\n "
282 ++ sys_errmsg ++ "\nWhilst trying to load: "
283 ++ showLS spec ++ "\nDirectories to search are:\n"
284 ++ unlines (map (" "++) paths) )
287 -- Not interested in the paths in the static case.
288 preload_static paths name
289 = do b <- doesFileExist name
290 if not b then return False
291 else loadObj name >> return True
294 CmdLineError "user specified .o/.so/.DLL could not be loaded."
298 %************************************************************************
300 Link a byte-code expression
302 %************************************************************************
305 linkExpr :: HscEnv -> UnlinkedBCO -> IO HValue
307 -- Link a single expression, *including* first linking packages and
308 -- modules that this expression depends on.
310 -- Raises an IO exception if it can't find a compiled version of the
311 -- dependents to link.
313 linkExpr hsc_env root_ul_bco
315 -- Initialise the linker (if it's not been done already)
316 let dflags = hsc_dflags hsc_env
317 ; initDynLinker dflags
319 -- Find what packages and linkables are required
320 ; eps <- readIORef (hsc_EPS hsc_env)
321 ; (lnks, pkgs) <- getLinkDeps dflags hpt (eps_PIT eps) needed_mods
323 -- Link the packages and modules required
324 ; linkPackages dflags pkgs
325 ; ok <- linkModules dflags lnks
330 -- Link the expression itself
331 pls <- readIORef v_PersistentLinkerState
332 ; let ie = itbl_env pls
335 -- Link the necessary packages and linkables
336 ; (_, (root_hval:_)) <- linkSomeBCOs False ie ce [root_ul_bco]
340 hpt = hsc_HPT hsc_env
341 dflags = hsc_dflags hsc_env
342 free_names = nameSetToList (bcoFreeNames root_ul_bco)
344 needed_mods :: [Module]
345 needed_mods = [ nameModule n | n <- free_names,
346 isExternalName n, -- Names from other modules
347 not (isWiredInName n) -- Exclude wired-in names
348 ] -- (see note below)
349 -- Exclude wired-in names because we may not have read
350 -- their interface files, so getLinkDeps will fail
351 -- All wired-in names are in the base package, which we link
352 -- by default, so we can safely ignore them here.
354 dieWith msg = throwDyn (ProgramError (showSDoc msg))
356 getLinkDeps :: DynFlags -> HomePackageTable -> PackageIfaceTable
357 -> [Module] -- If you need these
358 -> IO ([Linkable], [PackageId]) -- ... then link these first
359 -- Fails with an IO exception if it can't find enough files
361 getLinkDeps dflags hpt pit mods
362 -- Find all the packages and linkables that a set of modules depends on
363 = do { pls <- readIORef v_PersistentLinkerState ;
365 -- 1. Find the dependent home-pkg-modules/packages from each iface
366 (mods_s, pkgs_s) = unzip (map get_deps mods) ;
368 -- 2. Exclude ones already linked
369 -- Main reason: avoid findModule calls in get_linkable
370 mods_needed = nub (concat mods_s) `minusList` linked_mods ;
371 pkgs_needed = nub (concat pkgs_s) `minusList` pkgs_loaded pls ;
373 linked_mods = map linkableModule (objs_loaded pls ++ bcos_loaded pls)
376 -- 3. For each dependent module, find its linkable
377 -- This will either be in the HPT or (in the case of one-shot
378 -- compilation) we may need to use maybe_getFileLinkable
379 lnks_needed <- mapM get_linkable mods_needed ;
381 return (lnks_needed, pkgs_needed) }
383 get_deps :: Module -> ([Module],[PackageId])
384 -- Get the things needed for the specified module
385 -- This is rather similar to the code in RnNames.importsFromImportDecl
387 | ExtPackage p <- mi_package iface
388 = ([], p : dep_pkgs deps)
390 = (mod : [m | (m,_) <- dep_mods deps], dep_pkgs deps)
392 iface = get_iface mod
395 get_iface mod = case lookupIface hpt pit mod of
397 Nothing -> pprPanic "getLinkDeps" (no_iface mod)
398 no_iface mod = ptext SLIT("No iface for") <+> ppr mod
399 -- This one is a GHC bug
401 no_obj mod = dieWith (ptext SLIT("No compiled code for") <+> ppr mod)
402 -- This one is a build-system bug
404 get_linkable mod_name -- A home-package module
405 | Just mod_info <- lookupModuleEnv hpt mod_name
406 = return (hm_linkable mod_info)
408 = -- It's not in the HPT because we are in one shot mode,
409 -- so use the Finder to get a ModLocation...
410 do { mb_stuff <- findModule dflags mod_name False ;
412 Found loc _ -> found loc mod_name ;
416 found loc mod_name = do {
417 -- ...and then find the linkable for it
418 mb_lnk <- findLinkable mod_name loc ;
420 Nothing -> no_obj mod_name ;
421 Just lnk -> return lnk
426 %************************************************************************
429 The linkables may consist of a mixture of
430 byte-code modules and object modules
432 %************************************************************************
435 linkModules :: DynFlags -> [Linkable] -> IO SuccessFlag
436 linkModules dflags linkables
437 = block $ do -- don't want to be interrupted by ^C in here
439 let (objs, bcos) = partition isObjectLinkable
440 (concatMap partitionLinkable linkables)
442 -- Load objects first; they can't depend on BCOs
443 ok_flag <- dynLinkObjs dflags objs
445 if failed ok_flag then
452 -- HACK to support f-x-dynamic in the interpreter; no other purpose
453 partitionLinkable :: Linkable -> [Linkable]
455 = let li_uls = linkableUnlinked li
456 li_uls_obj = filter isObject li_uls
457 li_uls_bco = filter isInterpretable li_uls
459 case (li_uls_obj, li_uls_bco) of
460 (objs@(_:_), bcos@(_:_))
461 -> [li{linkableUnlinked=li_uls_obj}, li{linkableUnlinked=li_uls_bco}]
465 findModuleLinkable_maybe :: [Linkable] -> Module -> Maybe Linkable
466 findModuleLinkable_maybe lis mod
467 = case [LM time nm us | LM time nm us <- lis, nm == mod] of
470 many -> pprPanic "findModuleLinkable" (ppr mod)
472 linkableInSet :: Linkable -> [Linkable] -> Bool
473 linkableInSet l objs_loaded =
474 case findModuleLinkable_maybe objs_loaded (linkableModule l) of
476 Just m -> linkableTime l == linkableTime m
480 %************************************************************************
482 \subsection{The object-code linker}
484 %************************************************************************
487 dynLinkObjs :: DynFlags -> [Linkable] -> IO SuccessFlag
488 -- Side-effects the PersistentLinkerState
490 dynLinkObjs dflags objs
491 = do pls <- readIORef v_PersistentLinkerState
493 -- Load the object files and link them
494 let (objs_loaded', new_objs) = rmDupLinkables (objs_loaded pls) objs
495 pls1 = pls { objs_loaded = objs_loaded' }
496 unlinkeds = concatMap linkableUnlinked new_objs
498 mapM loadObj (map nameOfObject unlinkeds)
500 -- Link the all together
503 -- If resolving failed, unload all our
504 -- object modules and carry on
505 if succeeded ok then do
506 writeIORef v_PersistentLinkerState pls1
509 pls2 <- unload_wkr dflags [] pls1
510 writeIORef v_PersistentLinkerState pls2
514 rmDupLinkables :: [Linkable] -- Already loaded
515 -> [Linkable] -- New linkables
516 -> ([Linkable], -- New loaded set (including new ones)
517 [Linkable]) -- New linkables (excluding dups)
518 rmDupLinkables already ls
521 go already extras [] = (already, extras)
522 go already extras (l:ls)
523 | linkableInSet l already = go already extras ls
524 | otherwise = go (l:already) (l:extras) ls
527 %************************************************************************
529 \subsection{The byte-code linker}
531 %************************************************************************
534 dynLinkBCOs :: [Linkable] -> IO ()
535 -- Side-effects the persistent linker state
537 = do pls <- readIORef v_PersistentLinkerState
539 let (bcos_loaded', new_bcos) = rmDupLinkables (bcos_loaded pls) bcos
540 pls1 = pls { bcos_loaded = bcos_loaded' }
541 unlinkeds :: [Unlinked]
542 unlinkeds = concatMap linkableUnlinked new_bcos
544 cbcs :: [CompiledByteCode]
545 cbcs = map byteCodeOfObject unlinkeds
548 ul_bcos = [b | ByteCode bs _ <- cbcs, b <- bs]
549 ies = [ie | ByteCode _ ie <- cbcs]
550 gce = closure_env pls
551 final_ie = foldr plusNameEnv (itbl_env pls) ies
553 (final_gce, linked_bcos) <- linkSomeBCOs True final_ie gce ul_bcos
554 -- What happens to these linked_bcos?
556 let pls2 = pls1 { closure_env = final_gce,
557 itbl_env = final_ie }
559 writeIORef v_PersistentLinkerState pls2
562 -- Link a bunch of BCOs and return them + updated closure env.
563 linkSomeBCOs :: Bool -- False <=> add _all_ BCOs to returned closure env
564 -- True <=> add only toplevel BCOs to closure env
568 -> IO (ClosureEnv, [HValue])
569 -- The returned HValues are associated 1-1 with
570 -- the incoming unlinked BCOs. Each gives the
571 -- value of the corresponding unlinked BCO
574 linkSomeBCOs toplevs_only ie ce_in ul_bcos
575 = do let nms = map unlinkedBCOName ul_bcos
577 ( \ hvs -> let ce_out = extendClosureEnv ce_in (zipLazy nms hvs)
578 in mapM (linkBCO ie ce_out) ul_bcos )
580 let ce_all_additions = zip nms hvals
581 ce_top_additions = filter (isExternalName.fst) ce_all_additions
582 ce_additions = if toplevs_only then ce_top_additions
583 else ce_all_additions
584 ce_out = -- make sure we're not inserting duplicate names into the
585 -- closure environment, which leads to trouble.
586 ASSERT (all (not . (`elemNameEnv` ce_in)) (map fst ce_additions))
587 extendClosureEnv ce_in ce_additions
588 return (ce_out, hvals)
593 %************************************************************************
595 Unload some object modules
597 %************************************************************************
600 -- ---------------------------------------------------------------------------
601 -- Unloading old objects ready for a new compilation sweep.
603 -- The compilation manager provides us with a list of linkables that it
604 -- considers "stable", i.e. won't be recompiled this time around. For
605 -- each of the modules current linked in memory,
607 -- * if the linkable is stable (and it's the same one - the
608 -- user may have recompiled the module on the side), we keep it,
610 -- * otherwise, we unload it.
612 -- * we also implicitly unload all temporary bindings at this point.
614 unload :: DynFlags -> [Linkable] -> IO ()
615 -- The 'linkables' are the ones to *keep*
617 unload dflags linkables
618 = block $ do -- block, so we're safe from Ctrl-C in here
620 pls <- readIORef v_PersistentLinkerState
621 new_pls <- unload_wkr dflags linkables pls
622 writeIORef v_PersistentLinkerState new_pls
624 let verb = verbosity dflags
625 when (verb >= 3) $ do
626 hPutStrLn stderr (showSDoc
627 (text "unload: retaining objs" <+> ppr (objs_loaded new_pls)))
628 hPutStrLn stderr (showSDoc
629 (text "unload: retaining bcos" <+> ppr (bcos_loaded new_pls)))
633 unload_wkr :: DynFlags
634 -> [Linkable] -- stable linkables
635 -> PersistentLinkerState
636 -> IO PersistentLinkerState
637 -- Does the core unload business
638 -- (the wrapper blocks exceptions and deals with the PLS get and put)
640 unload_wkr dflags linkables pls
641 = do let (objs_to_keep, bcos_to_keep) = partition isObjectLinkable linkables
643 objs_loaded' <- filterM (maybeUnload objs_to_keep) (objs_loaded pls)
644 bcos_loaded' <- filterM (maybeUnload bcos_to_keep) (bcos_loaded pls)
646 let bcos_retained = map linkableModule bcos_loaded'
647 itbl_env' = filterNameMap bcos_retained (itbl_env pls)
648 closure_env' = filterNameMap bcos_retained (closure_env pls)
649 new_pls = pls { itbl_env = itbl_env',
650 closure_env = closure_env',
651 bcos_loaded = bcos_loaded',
652 objs_loaded = objs_loaded' }
656 maybeUnload :: [Linkable] -> Linkable -> IO Bool
657 maybeUnload keep_linkables lnk
658 | linkableInSet lnk linkables = return True
660 = do mapM_ unloadObj [f | DotO f <- linkableUnlinked lnk]
661 -- The components of a BCO linkable may contain
662 -- dot-o files. Which is very confusing.
664 -- But the BCO parts can be unlinked just by
665 -- letting go of them (plus of course depopulating
666 -- the symbol table which is done in the main body)
671 %************************************************************************
675 %************************************************************************
680 = Object FilePath -- Full path name of a .o file, including trailing .o
681 -- For dynamic objects only, try to find the object
682 -- file in all the directories specified in
683 -- v_Library_paths before giving up.
685 | DLL String -- "Unadorned" name of a .DLL/.so
686 -- e.g. On unix "qt" denotes "libqt.so"
687 -- On WinDoze "burble" denotes "burble.DLL"
688 -- loadDLL is platform-specific and adds the lib/.so/.DLL
689 -- suffixes platform-dependently
691 | DLLPath FilePath -- Absolute or relative pathname to a dynamic library
692 -- (ends with .dll or .so).
694 | Framework String -- Only used for darwin, but does no harm
696 -- If this package is already part of the GHCi binary, we'll already
697 -- have the right DLLs for this package loaded, so don't try to
700 -- But on Win32 we must load them 'again'; doing so is a harmless no-op
701 -- as far as the loader is concerned, but it does initialise the list
702 -- of DLL handles that rts/Linker.c maintains, and that in turn is
703 -- used by lookupSymbol. So we must call addDLL for each library
704 -- just to get the DLL handle into the list.
706 # if defined(mingw32_TARGET_OS) || defined(darwin_TARGET_OS)
709 = [ "base", "haskell98", "template-haskell", "readline" ]
712 showLS (Object nm) = "(static) " ++ nm
713 showLS (DLL nm) = "(dynamic) " ++ nm
714 showLS (DLLPath nm) = "(dynamic) " ++ nm
715 showLS (Framework nm) = "(framework) " ++ nm
717 linkPackages :: DynFlags -> [PackageId] -> IO ()
718 -- Link exactly the specified packages, and their dependents
719 -- (unless of course they are already linked)
720 -- The dependents are linked automatically, and it doesn't matter
721 -- what order you specify the input packages.
723 -- NOTE: in fact, since each module tracks all the packages it depends on,
724 -- we don't really need to use the package-config dependencies.
725 -- However we do need the package-config stuff (to find aux libs etc),
726 -- and following them lets us load libraries in the right order, which
727 -- perhaps makes the error message a bit more localised if we get a link
728 -- failure. So the dependency walking code is still here.
730 linkPackages dflags new_pkgs
731 = do { pls <- readIORef v_PersistentLinkerState
732 ; let pkg_map = pkgIdMap (pkgState dflags)
734 ; pkgs' <- link pkg_map (pkgs_loaded pls) new_pkgs
736 ; writeIORef v_PersistentLinkerState (pls { pkgs_loaded = pkgs' })
739 link :: PackageConfigMap -> [PackageId] -> [PackageId] -> IO [PackageId]
740 link pkg_map pkgs new_pkgs
741 = foldM (link_one pkg_map) pkgs new_pkgs
743 link_one pkg_map pkgs new_pkg
744 | new_pkg `elem` pkgs -- Already linked
747 | Just pkg_cfg <- lookupPackage pkg_map new_pkg
748 = do { -- Link dependents first
749 pkgs' <- link pkg_map pkgs (map mkPackageId (depends pkg_cfg))
750 -- Now link the package itself
751 ; linkPackage dflags pkg_cfg
752 ; return (new_pkg : pkgs') }
755 = throwDyn (CmdLineError ("unknown package: " ++ packageIdString new_pkg))
758 linkPackage :: DynFlags -> PackageConfig -> IO ()
759 linkPackage dflags pkg
761 let dirs = Packages.libraryDirs pkg
762 let libs = Packages.hsLibraries pkg ++ Packages.extraLibraries pkg
763 ++ [ lib | '-':'l':lib <- Packages.extraLdOpts pkg ]
764 classifieds <- mapM (locateOneObj dirs) libs
766 -- Complication: all the .so's must be loaded before any of the .o's.
767 let dlls = [ dll | DLL dll <- classifieds ]
768 objs = [ obj | Object obj <- classifieds ]
770 maybePutStr dflags ("Loading package " ++ showPackageId (package pkg) ++ " ... ")
772 -- See comments with partOfGHCi
773 when (pkgName (package pkg) `notElem` partOfGHCi) $ do
775 -- When a library A needs symbols from a library B, the order in
776 -- extra_libraries/extra_ld_opts is "-lA -lB", because that's the
777 -- way ld expects it for static linking. Dynamic linking is a
778 -- different story: When A has no dependency information for B,
779 -- dlopen-ing A with RTLD_NOW (see addDLL in Linker.c) will fail
780 -- when B has not been loaded before. In a nutshell: Reverse the
781 -- order of DLLs for dynamic linking.
782 -- This fixes a problem with the HOpenGL package (see "Compiling
783 -- HOpenGL under recent versions of GHC" on the HOpenGL list).
784 mapM_ (load_dyn dirs) (reverse dlls)
786 -- After loading all the DLLs, we can load the static objects.
787 -- Ordering isn't important here, because we do one final link
788 -- step to resolve everything.
791 maybePutStr dflags "linking ... "
793 if succeeded ok then maybePutStrLn dflags "done."
794 else throwDyn (InstallationError ("unable to load package `" ++ showPackageId (package pkg) ++ "'"))
796 load_dyn dirs dll = do r <- loadDynamic dirs dll
799 Just err -> throwDyn (CmdLineError ("can't load .so/.DLL for: "
800 ++ dll ++ " (" ++ err ++ ")" ))
801 #ifndef darwin_TARGET_OS
802 loadFrameworks pkg = return ()
804 loadFrameworks pkg = mapM_ load frameworks
806 fw_dirs = Packages.frameworkDirs pkg
807 frameworks = Packages.extraFrameworks pkg
809 load fw = do r <- loadFramework fw_dirs fw
812 Just err -> throwDyn (CmdLineError ("can't load framework: "
813 ++ fw ++ " (" ++ err ++ ")" ))
816 -- Try to find an object file for a given library in the given paths.
817 -- If it isn't present, we assume it's a dynamic library.
818 locateOneObj :: [FilePath] -> String -> IO LibrarySpec
819 locateOneObj dirs lib
820 = do { mb_obj_path <- findFile mk_obj_path dirs
821 ; case mb_obj_path of
822 Just obj_path -> return (Object obj_path)
824 do { mb_lib_path <- findFile mk_dyn_lib_path dirs
825 ; case mb_lib_path of
826 Just lib_path -> return (DLL (lib ++ "_dyn"))
827 Nothing -> return (DLL lib) }} -- We assume
829 mk_obj_path dir = dir ++ '/':lib ++ ".o"
830 mk_dyn_lib_path dir = dir ++ '/':mkSOName (lib ++ "_dyn")
833 -- ----------------------------------------------------------------------------
834 -- Loading a dyanmic library (dlopen()-ish on Unix, LoadLibrary-ish on Win32)
836 -- return Nothing == success, else Just error message from dlopen
837 loadDynamic paths rootname
838 = do { mb_dll <- findFile mk_dll_path paths
840 Just dll -> loadDLL dll
841 Nothing -> loadDLL (mkSOName rootname) }
842 -- Tried all our known library paths, so let
843 -- dlopen() search its own builtin paths now.
845 mk_dll_path dir = dir ++ '/':mkSOName rootname
847 #if defined(darwin_TARGET_OS)
848 mkSOName root = "lib" ++ root ++ ".dylib"
849 #elif defined(mingw32_TARGET_OS)
850 -- Win32 DLLs have no .dll extension here, because addDLL tries
851 -- both foo.dll and foo.drv
854 mkSOName root = "lib" ++ root ++ ".so"
857 -- Darwin / MacOS X only: load a framework
858 -- a framework is a dynamic library packaged inside a directory of the same
859 -- name. They are searched for in different paths than normal libraries.
860 #ifdef darwin_TARGET_OS
861 loadFramework extraPaths rootname
862 = do { mb_fwk <- findFile mk_fwk (extraPaths ++ defaultFrameworkPaths)
864 Just fwk_path -> loadDLL fwk_path
865 Nothing -> return (Just "not found") }
866 -- Tried all our known library paths, but dlopen()
867 -- has no built-in paths for frameworks: give up
869 mk_fwk dir = dir ++ '/' : rootname ++ ".framework/" ++ rootname
870 -- sorry for the hardcoded paths, I hope they won't change anytime soon:
871 defaultFrameworkPaths = ["/Library/Frameworks", "/System/Library/Frameworks"]
875 %************************************************************************
879 %************************************************************************
882 findFile :: (FilePath -> FilePath) -- Maps a directory path to a file path
883 -> [FilePath] -- Directories to look in
884 -> IO (Maybe FilePath) -- The first file path to match
885 findFile mk_file_path []
887 findFile mk_file_path (dir:dirs)
888 = do { let file_path = mk_file_path dir
889 ; b <- doesFileExist file_path
891 return (Just file_path)
893 findFile mk_file_path dirs }
897 maybePutStr dflags s | verbosity dflags > 0 = putStr s
898 | otherwise = return ()
900 maybePutStrLn dflags s | verbosity dflags > 0 = putStrLn s
901 | otherwise = return ()