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