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