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