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