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