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