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