[project @ 2003-09-23 16:43:00 by wolfgang]
[ghc-hetmet.git] / ghc / compiler / ghci / Linker.lhs
1 %
2 % (c) The University of Glasgow 2000
3 %
4
5 -- --------------------------------------
6 --      The dynamic linker for GHCi      
7 -- --------------------------------------
8
9 This module deals with the top-level issues of dynamic linking,
10 calling the object-code linker and the byte-code linker where
11 necessary.
12
13
14 \begin{code}
15
16 {-# OPTIONS -optc-DNON_POSIX_SOURCE -#include "Linker.h" #-}
17
18 module Linker ( HValue, initDynLinker, showLinkerState,
19                 linkExpr, unload, extendLinkEnv, 
20                 linkPackages,
21         ) where
22
23 #include "../includes/config.h"
24 #include "HsVersions.h"
25
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(..))
30
31 import Packages
32 import DriverState      ( v_Library_paths, v_Opt_l, v_Ld_inputs, getStaticOpts, v_ExplicitPackages )
33 import DriverUtil       ( getFileSuffix )
34 #ifdef darwin_TARGET_OS
35 import DriverState      ( v_Cmdline_frameworks, v_Framework_paths )
36 #endif
37 import Finder           ( findModule, findLinkable )
38 import HscTypes
39 import Name             ( Name,  nameModule, isExternalName, isWiredInName )
40 import NameEnv
41 import NameSet          ( nameSetToList )
42 import Module
43 import FastString       ( FastString(..), unpackFS )
44 import ListSetOps       ( minusList )
45 import CmdLineOpts      ( DynFlags(verbosity), getDynFlags )
46 import BasicTypes       ( SuccessFlag(..), succeeded, failed )
47 import Outputable
48 import Panic            ( GhcException(..) )
49 import Util             ( zipLazy, global )
50
51 -- Standard libraries
52 import Control.Monad    ( when, filterM, foldM )
53
54 import Data.IORef       ( IORef, readIORef, writeIORef )
55 import Data.List        ( partition, nub )
56
57 import System.IO        ( putStr, putStrLn, hPutStrLn, stderr, fixIO )
58 import System.Directory ( doesFileExist )
59
60 import Control.Exception ( block, throwDyn )
61
62 #if __GLASGOW_HASKELL__ >= 503
63 import GHC.IOBase       ( IO(..) )
64 #else
65 import PrelIOBase       ( IO(..) )
66 #endif
67 \end{code}
68
69
70 %************************************************************************
71 %*                                                                      *
72                         The Linker's state
73 %*                                                                      *
74 %************************************************************************
75
76 The persistent linker state *must* match the actual state of the 
77 C dynamic linker at all times, so we keep it in a private global variable.
78
79
80 The PersistentLinkerState maps Names to actual closures (for
81 interpreted code only), for use during linking.
82
83 \begin{code}
84 GLOBAL_VAR(v_PersistentLinkerState, panic "Dynamic linker not initialised", PersistentLinkerState)
85 GLOBAL_VAR(v_InitLinkerDone, False, Bool)       -- Set True when dynamic linker is initialised
86
87 data PersistentLinkerState
88    = PersistentLinkerState {
89
90         -- Current global mapping from Names to their true values
91         closure_env :: ClosureEnv,
92
93         -- The current global mapping from RdrNames of DataCons to
94         -- info table addresses.
95         -- When a new Unlinked is linked into the running image, or an existing
96         -- module in the image is replaced, the itbl_env must be updated
97         -- appropriately.
98         itbl_env    :: ItblEnv,
99
100         -- The currently loaded interpreted modules (home package)
101         bcos_loaded :: [Linkable],
102
103         -- And the currently-loaded compiled modules (home package)
104         objs_loaded :: [Linkable],
105
106         -- The currently-loaded packages; always object code
107         -- Held, as usual, in dependency order; though I am not sure if
108         -- that is really important
109         pkgs_loaded :: [PackageName]
110      }
111
112 emptyPLS :: PersistentLinkerState
113 emptyPLS = PersistentLinkerState { closure_env = emptyNameEnv,
114                                    itbl_env    = emptyNameEnv,
115                                    pkgs_loaded = init_pkgs_loaded,
116                                    bcos_loaded = [],
117                                    objs_loaded = [] }
118
119 -- Packages that don't need loading, because the compiler 
120 -- shares them with the interpreted program.
121 --
122 -- The linker's symbol table is populated with RTS symbols using an
123 -- explicit list.  See rts/Linker.c for details.
124 init_pkgs_loaded = [ FSLIT("rts") ]
125 \end{code}
126
127 \begin{code}
128 extendLinkEnv :: [(Name,HValue)] -> IO ()
129 -- Automatically discards shadowed bindings
130 extendLinkEnv new_bindings
131   = do  pls <- readIORef v_PersistentLinkerState
132         let new_closure_env = extendClosureEnv (closure_env pls) new_bindings
133             new_pls = pls { closure_env = new_closure_env }
134         writeIORef v_PersistentLinkerState new_pls
135
136 -- filterNameMap removes from the environment all entries except 
137 --      those for a given set of modules;
138 -- Note that this removes all *local* (i.e. non-isExternal) names too 
139 --      (these are the temporary bindings from the command line).
140 -- Used to filter both the ClosureEnv and ItblEnv
141
142 filterNameMap :: [ModuleName] -> NameEnv (Name, a) -> NameEnv (Name, a)
143 filterNameMap mods env 
144    = filterNameEnv keep_elt env
145    where
146      keep_elt (n,_) = isExternalName n 
147                       && (moduleName (nameModule n) `elem` mods)
148 \end{code}
149
150
151 \begin{code}
152 showLinkerState :: IO ()
153 -- Display the persistent linker state
154 showLinkerState
155   = do pls <- readIORef v_PersistentLinkerState
156        printDump (vcat [text "----- Linker state -----",
157                         text "Pkgs:" <+> ppr (pkgs_loaded pls),
158                         text "Objs:" <+> ppr (objs_loaded pls),
159                         text "BCOs:" <+> ppr (bcos_loaded pls)])
160 \end{code}
161                         
162         
163
164
165 %************************************************************************
166 %*                                                                      *
167 \subsection{Initialisation}
168 %*                                                                      *
169 %************************************************************************
170
171 We initialise the dynamic linker by
172
173 a) calling the C initialisation procedure
174
175 b) Loading any packages specified on the command line,
176    now held in v_ExplicitPackages
177
178 c) Loading any packages specified on the command line,
179    now held in the -l options in v_Opt_l
180
181 d) Loading any .o/.dll files specified on the command line,
182    now held in v_Ld_inputs
183
184 e) Loading any MacOS frameworks
185
186 \begin{code}
187 initDynLinker :: IO ()
188 -- This function is idempotent; if called more than once, it does nothing
189 -- This is useful in Template Haskell, where we call it before trying to link
190 initDynLinker 
191   = do  { done <- readIORef v_InitLinkerDone
192         ; if done then return () 
193                   else do { writeIORef v_InitLinkerDone True
194                           ; reallyInitDynLinker }
195         }
196
197 reallyInitDynLinker
198   = do  { dflags <- getDynFlags
199
200                 -- Initialise the linker state
201         ; writeIORef v_PersistentLinkerState emptyPLS
202
203                 -- (a) initialise the C dynamic linker
204         ; initObjLinker 
205
206                 -- (b) Load packages from the command-line
207         ; expl <- readIORef v_ExplicitPackages
208         ; linkPackages dflags expl
209
210                 -- (c) Link libraries from the command-line
211         ; opt_l  <- getStaticOpts v_Opt_l
212         ; let minus_ls = [ lib | '-':'l':lib <- opt_l ]
213
214                 -- (d) Link .o files from the command-line
215         ; lib_paths <- readIORef v_Library_paths
216         ; cmdline_ld_inputs <- readIORef v_Ld_inputs
217
218         ; let (cmdline_libs, cmdline_objs) = partition libish cmdline_ld_inputs
219
220                 -- (e) Link any MacOS frameworks
221 #ifdef darwin_TARGET_OS 
222         ; framework_paths <- readIORef v_Framework_paths
223         ; frameworks      <- readIORef v_Cmdline_frameworks
224 #else
225         ; let frameworks      = []
226         ; let framework_paths = []
227 #endif
228                 -- Finally do (c),(d),(e)       
229         ; let cmdline_lib_specs = map Object    cmdline_objs
230                                ++ map DLLPath   cmdline_libs
231                                ++ map DLL       minus_ls 
232                                ++ map Framework frameworks
233         ; if null cmdline_lib_specs then return ()
234                                     else do
235
236         { mapM_ (preloadLib dflags lib_paths framework_paths) cmdline_lib_specs
237         ; maybePutStr dflags "final link ... "
238         ; ok <- resolveObjs
239
240         ; if succeeded ok then maybePutStrLn dflags "done"
241           else throwDyn (InstallationError "linking extra libraries/objects failed")
242         }}
243
244 libish :: String -> Bool
245 libish f = getFileSuffix f `elem` dynlib_suffixes
246
247 #ifdef mingw32_TARGET_OS
248 dynlib_suffixes = ["dll", "DLL"]
249 #elif defined(darwin_TARGET_OS)
250 dynlib_suffixes = ["dylib"]
251 #else
252 dynlib_suffixes = ["so"]
253 #endif
254
255 preloadLib :: DynFlags -> [String] -> [String] -> LibrarySpec -> IO ()
256 preloadLib dflags lib_paths framework_paths lib_spec
257   = do maybePutStr dflags ("Loading object " ++ showLS lib_spec ++ " ... ")
258        case lib_spec of
259           Object static_ish
260              -> do b <- preload_static lib_paths static_ish
261                    maybePutStrLn dflags (if b  then "done"
262                                                 else "not found")
263          
264           DLL dll_unadorned
265              -> do maybe_errstr <- loadDynamic lib_paths dll_unadorned
266                    case maybe_errstr of
267                       Nothing -> maybePutStrLn dflags "done"
268                       Just mm -> preloadFailed mm lib_paths lib_spec
269
270           DLLPath dll_path
271              -> do maybe_errstr <- loadDLL dll_path
272                    case maybe_errstr of
273                       Nothing -> maybePutStrLn dflags "done"
274                       Just mm -> preloadFailed mm lib_paths lib_spec
275
276 #ifdef darwin_TARGET_OS
277           Framework framework
278              -> do maybe_errstr <- loadFramework framework_paths framework
279                    case maybe_errstr of
280                       Nothing -> maybePutStrLn dflags "done"
281                       Just mm -> preloadFailed mm framework_paths lib_spec
282 #endif
283   where
284     preloadFailed :: String -> [String] -> LibrarySpec -> IO ()
285     preloadFailed sys_errmsg paths spec
286        = do maybePutStr dflags
287                ("failed.\nDynamic linker error message was:\n   " 
288                     ++ sys_errmsg  ++ "\nWhilst trying to load:  " 
289                     ++ showLS spec ++ "\nDirectories to search are:\n"
290                     ++ unlines (map ("   "++) paths) )
291             give_up
292     
293     -- Not interested in the paths in the static case.
294     preload_static paths name
295        = do b <- doesFileExist name
296             if not b then return False
297                      else loadObj name >> return True
298     
299     give_up = throwDyn $ 
300               CmdLineError "user specified .o/.so/.DLL could not be loaded."
301 \end{code}
302
303
304 %************************************************************************
305 %*                                                                      *
306                 Link a byte-code expression
307 %*                                                                      *
308 %************************************************************************
309
310 \begin{code}
311 linkExpr :: HscEnv -> PersistentCompilerState
312          -> UnlinkedBCO -> IO HValue
313
314 -- Link a single expression, *including* first linking packages and 
315 -- modules that this expression depends on.
316 --
317 -- Raises an IO exception if it can't find a compiled version of the
318 -- dependents to link.
319
320 linkExpr hsc_env pcs root_ul_bco
321   = do {  
322         -- Initialise the linker (if it's not been done already)
323      initDynLinker
324
325         -- Find what packages and linkables are required
326    ; (lnks, pkgs) <- getLinkDeps hpt pit needed_mods
327
328         -- Link the packages and modules required
329    ; linkPackages dflags pkgs
330    ; ok <- linkModules dflags lnks
331    ; if failed ok then
332         dieWith empty
333      else do {
334
335         -- Link the expression itself
336      pls <- readIORef v_PersistentLinkerState
337    ; let ie = itbl_env pls
338          ce = closure_env pls
339
340         -- Link the necessary packages and linkables
341    ; (_, (root_hval:_)) <- linkSomeBCOs False ie ce [root_ul_bco]
342    ; return root_hval
343    }}
344    where
345      pit    = eps_PIT (pcs_EPS pcs)
346      hpt    = hsc_HPT hsc_env
347      dflags = hsc_dflags hsc_env
348      free_names = nameSetToList (bcoFreeNames root_ul_bco)
349
350      needed_mods :: [Module]
351      needed_mods = [ nameModule n | n <- free_names, 
352                                     isExternalName n,           -- Names from other modules
353                                     not (isWiredInName n)       -- Exclude wired-in names
354                    ]                                            -- (see note below)
355         -- Exclude wired-in names because we may not have read
356         -- their interface files, so getLinkDeps will fail
357         -- All wired-in names are in the base package, which we link
358         -- by default, so we can safely ignore them here.
359  
360 dieWith msg = throwDyn (ProgramError (showSDoc msg))
361
362 getLinkDeps :: HomePackageTable -> PackageIfaceTable
363             -> [Module]                         -- If you need these
364             -> IO ([Linkable], [PackageName])   -- ... then link these first
365 -- Fails with an IO exception if it can't find enough files
366
367 getLinkDeps hpt pit mods
368 -- Find all the packages and linkables that a set of modules depends on
369  = do { pls <- readIORef v_PersistentLinkerState ;
370         let {
371         -- 1.  Find the dependent home-pkg-modules/packages from each iface
372             (mods_s, pkgs_s) = unzip (map get_deps mods) ;
373
374         -- 2.  Exclude ones already linked
375         --      Main reason: avoid findModule calls in get_linkable
376             mods_needed = nub (concat mods_s) `minusList` linked_mods     ;
377             pkgs_needed = nub (concat pkgs_s) `minusList` pkgs_loaded pls ;
378
379             linked_mods = map linkableModName (objs_loaded pls ++ bcos_loaded pls)
380         } ;
381         
382         -- 3.  For each dependent module, find its linkable
383         --     This will either be in the HPT or (in the case of one-shot
384         --     compilation) we may need to use maybe_getFileLinkable
385         lnks_needed <- mapM get_linkable mods_needed ;
386
387         return (lnks_needed, pkgs_needed) }
388   where
389     get_deps :: Module -> ([ModuleName],[PackageName])
390         -- Get the things needed for the specified module
391         -- This is rather similar to the code in RnNames.importsFromImportDecl
392     get_deps mod
393         | isHomeModule (mi_module iface) 
394         = (moduleName mod : [m | (m,_) <- dep_mods deps], dep_pkgs deps)
395         | otherwise
396         = ([], mi_package iface : dep_pkgs deps)
397         where
398           iface = get_iface mod
399           deps  = mi_deps iface
400
401     get_iface mod = case lookupIface hpt pit mod of
402                             Just iface -> iface
403                             Nothing    -> pprPanic "getLinkDeps" (no_iface mod)
404     no_iface mod = ptext SLIT("No iface for") <+> ppr mod
405         -- This one is a GHC bug
406
407     no_obj mod = dieWith (ptext SLIT("No compiled code for") <+> ppr mod)
408         -- This one is a build-system bug
409
410     get_linkable mod_name       -- A home-package module
411         | Just mod_info <- lookupModuleEnvByName hpt mod_name 
412         = return (hm_linkable mod_info)
413         | otherwise     
414         =       -- It's not in the HPT because we are in one shot mode, 
415                 -- so use the Finder to get a ModLocation...
416           do { mb_stuff <- findModule mod_name ;
417                case mb_stuff of {
418                   Left _ -> no_obj mod_name ;
419                   Right (_, loc) -> do {
420
421                 -- ...and then find the linkable for it
422                mb_lnk <- findLinkable mod_name loc ;
423                case mb_lnk of {
424                   Nothing -> no_obj mod_name ;
425                   Just lnk -> return lnk
426           }}}} 
427 \end{code}
428
429
430 %************************************************************************
431 %*                                                                      *
432                 Link some linkables
433         The linkables may consist of a mixture of 
434         byte-code modules and object modules
435 %*                                                                      *
436 %************************************************************************
437
438 \begin{code}
439 linkModules :: DynFlags -> [Linkable] -> IO SuccessFlag
440 linkModules dflags linkables
441   = block $ do  -- don't want to be interrupted by ^C in here
442         
443         let (objs, bcos) = partition isObjectLinkable 
444                               (concatMap partitionLinkable linkables)
445
446                 -- Load objects first; they can't depend on BCOs
447         ok_flag <- dynLinkObjs dflags objs
448
449         if failed ok_flag then 
450                 return Failed
451           else do
452                 dynLinkBCOs bcos
453                 return Succeeded
454                 
455
456 -- HACK to support f-x-dynamic in the interpreter; no other purpose
457 partitionLinkable :: Linkable -> [Linkable]
458 partitionLinkable li
459    = let li_uls = linkableUnlinked li
460          li_uls_obj = filter isObject li_uls
461          li_uls_bco = filter isInterpretable li_uls
462      in 
463          case (li_uls_obj, li_uls_bco) of
464             (objs@(_:_), bcos@(_:_)) 
465                -> [li{linkableUnlinked=li_uls_obj}, li{linkableUnlinked=li_uls_bco}]
466             other
467                -> [li]
468
469 findModuleLinkable_maybe :: [Linkable] -> ModuleName -> Maybe Linkable
470 findModuleLinkable_maybe lis mod
471    = case [LM time nm us | LM time nm us <- lis, nm == mod] of
472         []   -> Nothing
473         [li] -> Just li
474         many -> pprPanic "findModuleLinkable" (ppr mod)
475
476 filterModuleLinkables :: (ModuleName -> Bool) -> [Linkable] -> [Linkable]
477 filterModuleLinkables p ls = filter (p . linkableModName) ls
478
479 linkableInSet :: Linkable -> [Linkable] -> Bool
480 linkableInSet l objs_loaded =
481   case findModuleLinkable_maybe objs_loaded (linkableModName l) of
482         Nothing -> False
483         Just m  -> linkableTime l == linkableTime m
484 \end{code}
485
486
487 %************************************************************************
488 %*                                                                      *
489 \subsection{The object-code linker}
490 %*                                                                      *
491 %************************************************************************
492
493 \begin{code}
494 dynLinkObjs :: DynFlags -> [Linkable] -> IO SuccessFlag
495         -- Side-effects the PersistentLinkerState
496
497 dynLinkObjs dflags objs
498   = do  pls <- readIORef v_PersistentLinkerState
499
500         -- Load the object files and link them
501         let (objs_loaded', new_objs) = rmDupLinkables (objs_loaded pls) objs
502             pls1                     = pls { objs_loaded = objs_loaded' }
503             unlinkeds                = concatMap linkableUnlinked new_objs
504
505         mapM loadObj (map nameOfObject unlinkeds)
506
507         -- Link the all together
508         ok <- resolveObjs
509
510         -- If resolving failed, unload all our 
511         -- object modules and carry on
512         if succeeded ok then do
513                 writeIORef v_PersistentLinkerState pls1
514                 return Succeeded
515           else do
516                 pls2 <- unload_wkr dflags [] pls1
517                 writeIORef v_PersistentLinkerState pls2
518                 return Failed
519
520
521 rmDupLinkables :: [Linkable]    -- Already loaded
522                -> [Linkable]    -- New linkables
523                -> ([Linkable],  -- New loaded set (including new ones)
524                    [Linkable])  -- New linkables (excluding dups)
525 rmDupLinkables already ls
526   = go already [] ls
527   where
528     go already extras [] = (already, extras)
529     go already extras (l:ls)
530         | linkableInSet l already = go already     extras     ls
531         | otherwise               = go (l:already) (l:extras) ls
532 \end{code}
533
534 %************************************************************************
535 %*                                                                      *
536 \subsection{The byte-code linker}
537 %*                                                                      *
538 %************************************************************************
539
540 \begin{code}
541 dynLinkBCOs :: [Linkable] -> IO ()
542         -- Side-effects the persistent linker state
543 dynLinkBCOs bcos
544   = do  pls <- readIORef v_PersistentLinkerState
545
546         let (bcos_loaded', new_bcos) = rmDupLinkables (bcos_loaded pls) bcos
547             pls1                     = pls { bcos_loaded = bcos_loaded' }
548             unlinkeds :: [Unlinked]
549             unlinkeds                = concatMap linkableUnlinked new_bcos
550
551             cbcs :: [CompiledByteCode]
552             cbcs      = map byteCodeOfObject unlinkeds
553                       
554                       
555             ul_bcos    = [b | ByteCode bs _  <- cbcs, b <- bs]
556             ies        = [ie | ByteCode _ ie <- cbcs]
557             gce       = closure_env pls
558             final_ie  = foldr plusNameEnv (itbl_env pls) ies
559
560         (final_gce, linked_bcos) <- linkSomeBCOs True final_ie gce ul_bcos
561                 -- What happens to these linked_bcos?
562
563         let pls2 = pls1 { closure_env = final_gce,
564                           itbl_env    = final_ie }
565
566         writeIORef v_PersistentLinkerState pls2
567         return ()
568
569 -- Link a bunch of BCOs and return them + updated closure env.
570 linkSomeBCOs :: Bool    -- False <=> add _all_ BCOs to returned closure env
571                         -- True  <=> add only toplevel BCOs to closure env
572              -> ItblEnv 
573              -> ClosureEnv 
574              -> [UnlinkedBCO]
575              -> IO (ClosureEnv, [HValue])
576                         -- The returned HValues are associated 1-1 with
577                         -- the incoming unlinked BCOs.  Each gives the
578                         -- value of the corresponding unlinked BCO
579                                         
580
581 linkSomeBCOs toplevs_only ie ce_in ul_bcos
582    = do let nms = map unlinkedBCOName ul_bcos
583         hvals <- fixIO 
584                     ( \ hvs -> let ce_out = extendClosureEnv ce_in (zipLazy nms hvs)
585                                in  mapM (linkBCO ie ce_out) ul_bcos )
586
587         let ce_all_additions = zip nms hvals
588             ce_top_additions = filter (isExternalName.fst) ce_all_additions
589             ce_additions     = if toplevs_only then ce_top_additions 
590                                                else ce_all_additions
591             ce_out = -- make sure we're not inserting duplicate names into the 
592                      -- closure environment, which leads to trouble.
593                      ASSERT (all (not . (`elemNameEnv` ce_in)) (map fst ce_additions))
594                      extendClosureEnv ce_in ce_additions
595         return (ce_out, hvals)
596
597 \end{code}
598
599
600 %************************************************************************
601 %*                                                                      *
602                 Unload some object modules
603 %*                                                                      *
604 %************************************************************************
605
606 \begin{code}
607 -- ---------------------------------------------------------------------------
608 -- Unloading old objects ready for a new compilation sweep.
609 --
610 -- The compilation manager provides us with a list of linkables that it
611 -- considers "stable", i.e. won't be recompiled this time around.  For
612 -- each of the modules current linked in memory,
613 --
614 --      * if the linkable is stable (and it's the same one - the
615 --        user may have recompiled the module on the side), we keep it,
616 --
617 --      * otherwise, we unload it.
618 --
619 --      * we also implicitly unload all temporary bindings at this point.
620
621 unload :: DynFlags -> [Linkable] -> IO ()
622 -- The 'linkables' are the ones to *keep*
623
624 unload dflags linkables
625   = block $ do -- block, so we're safe from Ctrl-C in here
626
627         pls     <- readIORef v_PersistentLinkerState
628         new_pls <- unload_wkr dflags linkables pls
629         writeIORef v_PersistentLinkerState new_pls
630
631         let verb = verbosity dflags
632         when (verb >= 3) $ do
633             hPutStrLn stderr (showSDoc
634                 (text "unload: retaining objs" <+> ppr (objs_loaded new_pls)))
635             hPutStrLn stderr (showSDoc
636                 (text "unload: retaining bcos" <+> ppr (bcos_loaded new_pls)))
637
638         return ()
639
640 unload_wkr :: DynFlags
641            -> [Linkable]                -- stable linkables
642            -> PersistentLinkerState
643            -> IO PersistentLinkerState
644 -- Does the core unload business
645 -- (the wrapper blocks exceptions and deals with the PLS get and put)
646
647 unload_wkr dflags linkables pls
648   = do  let (objs_to_keep, bcos_to_keep) = partition isObjectLinkable linkables
649
650         objs_loaded' <- filterM (maybeUnload objs_to_keep) (objs_loaded pls)
651         bcos_loaded' <- filterM (maybeUnload bcos_to_keep) (bcos_loaded pls)
652
653         let objs_retained = map linkableModName objs_loaded'
654             bcos_retained = map linkableModName bcos_loaded'
655             itbl_env'     = filterNameMap bcos_retained (itbl_env pls)
656             closure_env'  = filterNameMap bcos_retained (closure_env pls)
657             new_pls = pls { itbl_env = itbl_env',
658                             closure_env = closure_env',
659                             bcos_loaded = bcos_loaded',
660                             objs_loaded = objs_loaded' }
661
662         return new_pls
663   where
664     maybeUnload :: [Linkable] -> Linkable -> IO Bool
665     maybeUnload keep_linkables lnk
666       | linkableInSet lnk linkables = return True
667       | otherwise                   
668       = do mapM_ unloadObj [f | DotO f <- linkableUnlinked lnk]
669                 -- The components of a BCO linkable may contain
670                 -- dot-o files.  Which is very confusing.
671                 --
672                 -- But the BCO parts can be unlinked just by 
673                 -- letting go of them (plus of course depopulating
674                 -- the symbol table which is done in the main body)
675            return False
676 \end{code}
677
678
679 %************************************************************************
680 %*                                                                      *
681                 Loading packages
682 %*                                                                      *
683 %************************************************************************
684
685
686 \begin{code}
687 data LibrarySpec 
688    = Object FilePath    -- Full path name of a .o file, including trailing .o
689                         -- For dynamic objects only, try to find the object 
690                         -- file in all the directories specified in 
691                         -- v_Library_paths before giving up.
692
693    | DLL String         -- "Unadorned" name of a .DLL/.so
694                         --  e.g.    On unix     "qt"  denotes "libqt.so"
695                         --          On WinDoze  "burble"  denotes "burble.DLL"
696                         --  loadDLL is platform-specific and adds the lib/.so/.DLL
697                         --  suffixes platform-dependently
698
699    | DLLPath FilePath   -- Absolute or relative pathname to a dynamic library
700                         -- (ends with .dll or .so).
701
702    | Framework String   -- Only used for darwin, but does no harm
703
704 -- If this package is already part of the GHCi binary, we'll already
705 -- have the right DLLs for this package loaded, so don't try to
706 -- load them again.
707 -- 
708 -- But on Win32 we must load them 'again'; doing so is a harmless no-op
709 -- as far as the loader is concerned, but it does initialise the list
710 -- of DLL handles that rts/Linker.c maintains, and that in turn is 
711 -- used by lookupSymbol.  So we must call addDLL for each library 
712 -- just to get the DLL handle into the list.
713 partOfGHCi
714 #          if defined(mingw32_TARGET_OS) || defined(darwin_TARGET_OS)
715            = [ ]
716 #          else
717            = [ "base", "haskell98", "haskell-src", "readline" ]
718 #          endif
719
720 showLS (Object nm)    = "(static) " ++ nm
721 showLS (DLL nm)       = "(dynamic) " ++ nm
722 showLS (DLLPath nm)   = "(dynamic) " ++ nm
723 showLS (Framework nm) = "(framework) " ++ nm
724
725 linkPackages :: DynFlags -> [PackageName] -> IO ()
726 -- Link exactly the specified packages, and their dependents
727 -- (unless of course they are already linked)
728 -- The dependents are linked automatically, and it doesn't matter
729 -- what order you specify the input packages.
730 --
731 -- NOTE: in fact, since each module tracks all the packages it depends on,
732 --       we don't really need to use the package-config dependencies.
733 -- However we do need the package-config stuff (to find aux libs etc),
734 -- and following them lets us load libraries in the right order, which 
735 -- perhaps makes the error message a bit more localised if we get a link
736 -- failure.  So the dependency walking code is still here.
737
738 linkPackages dflags new_pkgs
739    = do { pls     <- readIORef v_PersistentLinkerState
740         ; pkg_map <- getPackageConfigMap
741
742         ; pkgs' <- link pkg_map (pkgs_loaded pls) new_pkgs
743
744         ; writeIORef v_PersistentLinkerState (pls { pkgs_loaded = pkgs' })
745         }
746    where
747      link :: PackageConfigMap -> [PackageName] -> [PackageName] -> IO [PackageName]
748      link pkg_map pkgs new_pkgs 
749         = foldM (link_one pkg_map) pkgs new_pkgs
750
751      link_one pkg_map pkgs new_pkg
752         | new_pkg `elem` pkgs   -- Already linked
753         = return pkgs
754
755         | Just pkg_cfg <- lookupPkg pkg_map new_pkg
756         = do {  -- Link dependents first
757                pkgs' <- link pkg_map pkgs (packageDependents pkg_cfg)
758                 -- Now link the package itself
759              ; linkPackage dflags pkg_cfg
760              ; return (new_pkg : pkgs') }
761
762         | otherwise
763         = throwDyn (CmdLineError ("unknown package name: " ++ packageNameString new_pkg))
764
765
766 linkPackage :: DynFlags -> PackageConfig -> IO ()
767 linkPackage dflags pkg
768    = do 
769         let dirs      =  Packages.library_dirs pkg
770         let libs      =  Packages.hs_libraries pkg ++ extra_libraries pkg
771                                 ++ [ lib | '-':'l':lib <- extra_ld_opts pkg ]
772         classifieds   <- mapM (locateOneObj dirs) libs
773
774         -- Complication: all the .so's must be loaded before any of the .o's.  
775         let dlls = [ dll | DLL dll    <- classifieds ]
776             objs = [ obj | Object obj <- classifieds ]
777
778         maybePutStr dflags ("Loading package " ++ Packages.name pkg ++ " ... ")
779
780         -- See comments with partOfGHCi
781         when (Packages.name pkg `notElem` partOfGHCi) $ do
782             loadFrameworks pkg
783             mapM_ (load_dyn dirs) dlls
784         
785         -- After loading all the DLLs, we can load the static objects.
786         mapM_ loadObj objs
787
788         maybePutStr dflags "linking ... "
789         ok <- resolveObjs
790         if succeeded ok then maybePutStrLn dflags "done."
791               else panic ("can't load package `" ++ name pkg ++ "'")
792
793 load_dyn dirs dll = do r <- loadDynamic dirs dll
794                        case r of
795                          Nothing  -> return ()
796                          Just err -> throwDyn (CmdLineError ("can't load .so/.DLL for: " 
797                                                               ++ dll ++ " (" ++ err ++ ")" ))
798 #ifndef darwin_TARGET_OS
799 loadFrameworks pkg = return ()
800 #else
801 loadFrameworks pkg = mapM_ load frameworks
802   where
803     fw_dirs    = Packages.framework_dirs pkg
804     frameworks = Packages.extra_frameworks pkg
805
806     load fw = do  r <- loadFramework fw_dirs fw
807                   case r of
808                     Nothing  -> return ()
809                     Just err -> throwDyn (CmdLineError ("can't load framework: " 
810                                                         ++ fw ++ " (" ++ err ++ ")" ))
811 #endif
812
813 -- Try to find an object file for a given library in the given paths.
814 -- If it isn't present, we assume it's a dynamic library.
815 locateOneObj :: [FilePath] -> String -> IO LibrarySpec
816 locateOneObj dirs lib
817   = do  { mb_obj_path <- findFile mk_obj_path dirs 
818         ; case mb_obj_path of
819             Just obj_path -> return (Object obj_path)
820             Nothing       -> return (DLL lib) }         -- We assume
821    where
822      mk_obj_path dir = dir ++ '/':lib ++ ".o"
823
824
825 -- ----------------------------------------------------------------------------
826 -- Loading a dyanmic library (dlopen()-ish on Unix, LoadLibrary-ish on Win32)
827
828 -- return Nothing == success, else Just error message from dlopen
829 loadDynamic paths rootname
830   = do  { mb_dll <- findFile mk_dll_path paths
831         ; case mb_dll of
832             Just dll -> loadDLL dll
833             Nothing  -> loadDLL (mkSOName rootname) }
834                         -- Tried all our known library paths, so let 
835                         -- dlopen() search its own builtin paths now.
836   where
837     mk_dll_path dir = dir ++ '/':mkSOName rootname
838
839 #if defined(darwin_TARGET_OS)
840 mkSOName root = "lib" ++ root ++ ".dylib"
841 #elif defined(mingw32_TARGET_OS)
842 -- Win32 DLLs have no .dll extension here, because addDLL tries
843 -- both foo.dll and foo.drv
844 mkSOName root = root
845 #else
846 mkSOName root = "lib" ++ root ++ ".so"
847 #endif
848
849 -- Darwin / MacOS X only: load a framework
850 -- a framework is a dynamic library packaged inside a directory of the same
851 -- name. They are searched for in different paths than normal libraries.
852 #ifdef darwin_TARGET_OS
853 loadFramework extraPaths rootname
854    = do { mb_fwk <- findFile mk_fwk (extraPaths ++ defaultFrameworkPaths)
855         ; case mb_fwk of
856             Just fwk_path -> loadDLL fwk_path
857             Nothing       -> return (Just "not found") }
858                 -- Tried all our known library paths, but dlopen()
859                 -- has no built-in paths for frameworks: give up
860    where
861      mk_fwk dir = dir ++ '/' : rootname ++ ".framework/" ++ rootname
862         -- sorry for the hardcoded paths, I hope they won't change anytime soon:
863      defaultFrameworkPaths = ["/Library/Frameworks", "/System/Library/Frameworks"]
864 #endif
865 \end{code}
866
867 %************************************************************************
868 %*                                                                      *
869                 Helper functions
870 %*                                                                      *
871 %************************************************************************
872
873 \begin{code}
874 findFile :: (FilePath -> FilePath)      -- Maps a directory path to a file path
875          -> [FilePath]                  -- Directories to look in
876          -> IO (Maybe FilePath)         -- The first file path to match
877 findFile mk_file_path [] 
878   = return Nothing
879 findFile mk_file_path (dir:dirs)
880   = do  { let file_path = mk_file_path dir
881         ; b <- doesFileExist file_path
882         ; if b then 
883              return (Just file_path)
884           else
885              findFile mk_file_path dirs }
886 \end{code}
887
888 \begin{code}
889 maybePutStr dflags s | verbosity dflags > 0 = putStr s
890                      | otherwise            = return ()
891
892 maybePutStrLn dflags s | verbosity dflags > 0 = putStrLn s
893                        | otherwise            = return ()
894 \end{code}