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