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