e2bac19ba9eddb3df8bc3d9bb75565238f990099
[ghc-hetmet.git] / ghc / compiler / compMan / CmLink.lhs
1 %
2 % (c) The University of Glasgow, 2001
3 %
4 \section[CmLink]{The compilation manager's linker}
5
6 \begin{code}
7 module CmLink (
8         LinkResult(..), link, unload,
9
10         filterModuleLinkables,
11         findModuleLinkable_maybe,
12
13         PersistentLinkerState{-abstractly!-}, emptyPLS,
14
15 #ifdef GHCI
16         delListFromClosureEnv,
17         addListToClosureEnv,
18         linkExpr
19 #endif
20   ) where
21
22
23 #ifdef GHCI
24 import ByteCodeLink     ( linkIModules, linkIExpr )
25 #endif
26
27 import Interpreter
28 import DriverPipeline
29 import CmTypes
30 import HscTypes         ( GhciMode(..) )
31 import Outputable       ( SDoc )
32 import Name             ( Name )
33 import Module           ( ModuleName )
34 import FiniteMap
35 import Outputable
36 import ErrUtils         ( showPass )
37 import CmdLineOpts      ( DynFlags(..) )
38 import Util
39
40 #ifdef GHCI
41 import Exception        ( block )
42 #endif
43
44 import IOExts
45 import List
46 import Monad
47 import IO
48
49 #include "HsVersions.h"
50
51 -- ---------------------------------------------------------------------------
52 -- The Linker's state
53
54 -- The PersistentLinkerState maps Names to actual closures (for
55 -- interpreted code only), for use during linking.
56
57 data PersistentLinkerState
58    = PersistentLinkerState {
59
60 #ifdef GHCI
61         -- Current global mapping from RdrNames to closure addresses
62         closure_env :: ClosureEnv,
63
64         -- the current global mapping from RdrNames of DataCons to
65         -- info table addresses.
66         -- When a new Unlinked is linked into the running image, or an existing
67         -- module in the image is replaced, the itbl_env must be updated
68         -- appropriately.
69         itbl_env    :: ItblEnv,
70
71         -- the currently loaded interpreted modules
72         bcos_loaded :: [Linkable]
73
74 #else
75         dummy :: ()     --  sigh, can't have an empty record
76 #endif
77
78      }
79
80 emptyPLS :: IO PersistentLinkerState
81 #ifdef GHCI
82 emptyPLS = return (PersistentLinkerState { closure_env = emptyFM,
83                                            itbl_env    = emptyFM,
84                                            bcos_loaded = [] })
85 #else
86 emptyPLS = return (PersistentLinkerState {})
87 #endif
88
89 -- We also keep track of which object modules are currently loaded
90 -- into the dynamic linker, so that we can unload them again later.
91 --
92 -- This state *must* match the actual state of the dyanmic linker at
93 -- all times, which is why we keep it private here and don't
94 -- put it in the PersistentLinkerState.
95 --
96 GLOBAL_VAR(v_ObjectsLoaded, [], [Linkable])
97
98
99 -- ---------------------------------------------------------------------------
100 -- Utils
101
102 findModuleLinkable_maybe :: [Linkable] -> ModuleName -> Maybe Linkable
103 findModuleLinkable_maybe lis mod
104    = case [LM time nm us | LM time nm us <- lis, nm == mod] of
105         []   -> Nothing
106         [li] -> Just li
107         many -> pprPanic "findModuleLinkable" (ppr mod)
108
109 filterModuleLinkables :: (ModuleName -> Bool) -> [Linkable] -> [Linkable]
110 filterModuleLinkables p [] = []
111 filterModuleLinkables p (li:lis)
112    = case li of
113         LM _ modnm _ -> if p modnm then retain else dump
114      where
115         dump   = filterModuleLinkables p lis
116         retain = li : dump
117
118 linkableInSet :: Linkable -> [Linkable] -> Bool
119 linkableInSet l objs_loaded =
120   case findModuleLinkable_maybe objs_loaded (linkableModName l) of
121         Nothing -> False
122         Just m  -> linkableTime l == linkableTime m
123
124 -- These two are used to add/remove entries from the closure env for
125 -- new bindings made at the prompt.
126 #ifdef GHCI
127 delListFromClosureEnv :: PersistentLinkerState -> [Name]
128         -> IO PersistentLinkerState
129 delListFromClosureEnv pls names
130   = return pls{ closure_env = delListFromFM (closure_env pls) names }
131
132 addListToClosureEnv :: PersistentLinkerState -> [(Name,HValue)]
133         -> IO PersistentLinkerState
134 addListToClosureEnv pls new_bindings
135   = return pls{ closure_env = addListToFM (closure_env pls) new_bindings }
136 #endif
137
138 -- ---------------------------------------------------------------------------
139 -- Unloading old objects ready for a new compilation sweep.
140 --
141 -- The compilation manager provides us with a list of linkables that it
142 -- considers "stable", i.e. won't be recompiled this time around.  For
143 -- each of the modules current linked in memory,
144 --
145 --      * if the linkable is stable (and it's the same one - the
146 --        user may have recompiled the module on the side), we keep it,
147 --
148 --      * otherwise, we unload it.
149 --
150 --      * we also implicitly unload all temporary bindings at this point.
151
152 unload :: GhciMode
153        -> DynFlags
154        -> [Linkable]            -- stable linkables
155        -> PersistentLinkerState
156        -> IO PersistentLinkerState
157
158 unload Batch dflags linkables pls = return pls
159
160 #ifdef GHCI
161 unload Interactive dflags linkables pls
162   = block $ do -- block, so we're safe from Ctrl-C in here
163         objs_loaded  <- readIORef v_ObjectsLoaded
164         objs_loaded' <- filterM (maybeUnload objs_to_keep) objs_loaded
165         writeIORef v_ObjectsLoaded objs_loaded'
166
167         bcos_loaded' <- filterM (maybeUnload bcos_to_keep) (bcos_loaded pls)
168
169         let objs_retained = map linkableModName objs_loaded'
170             bcos_retained = map linkableModName bcos_loaded'
171             itbl_env'     = filterNameMap bcos_retained (itbl_env pls)
172             closure_env'  = filterNameMap bcos_retained (closure_env pls)
173
174         let verb = verbosity dflags
175         when (verb >= 3) $ do
176             hPutStrLn stderr (showSDoc
177                 (text "CmLink.unload: retaining objs" <+> ppr objs_retained))
178             hPutStrLn stderr (showSDoc
179                 (text "CmLink.unload: retaining bcos" <+> ppr bcos_retained))
180
181         return pls{ itbl_env = itbl_env',
182                     closure_env = closure_env',
183                     bcos_loaded = bcos_loaded' }
184   where
185         (objs_to_keep, bcos_to_keep) = partition isObjectLinkable linkables
186
187         maybeUnload :: [Linkable] -> Linkable -> IO Bool
188         maybeUnload keep_linkables l@(LM time mod objs)
189            | linkableInSet l linkables
190                 = return True
191            | otherwise
192                 = do mapM unloadObj [ f | DotO f <- objs ]
193                      return False
194 #else
195 unload Interactive dflags linkables pls = panic "CmLink.unload: no interpreter"
196 #endif
197
198 -----------------------------------------------------------------------------
199 -- Linking
200
201 data LinkResult
202    = LinkOK   PersistentLinkerState
203    | LinkErrs PersistentLinkerState [SDoc]
204
205 link :: GhciMode                -- interactive or batch
206      -> DynFlags                -- dynamic flags
207      -> Bool                    -- attempt linking in batch mode?
208      -> [Linkable]
209      -> PersistentLinkerState
210      -> IO LinkResult
211
212 -- For the moment, in the batch linker, we don't bother to tell doLink
213 -- which packages to link -- it just tries all that are available.
214 -- batch_attempt_linking should only be *looked at* in batch mode.  It
215 -- should only be True if the upsweep was successful and someone
216 -- exports main, i.e., we have good reason to believe that linking
217 -- will succeed.
218
219 -- There will be (ToDo: are) two lists passed to link.  These
220 -- correspond to
221 --
222 --      1. The list of all linkables in the current home package.  This is
223 --         used by the batch linker to link the program, and by the interactive
224 --         linker to decide which modules from the previous link it can
225 --         throw away.
226 --      2. The list of modules on which we just called "compile".  This list
227 --         is used by the interactive linker to decide which modules need
228 --         to be actually linked this time around (or unlinked and re-linked
229 --         if the module was recompiled).
230
231 link mode dflags batch_attempt_linking linkables pls1
232    = do let verb = verbosity dflags
233         when (verb >= 3) $ do
234              hPutStrLn stderr "CmLink.link: linkables are ..."
235              hPutStrLn stderr (showSDoc (vcat (map ppr linkables)))
236         res <- link' mode dflags batch_attempt_linking linkables pls1
237         when (verb >= 3) $
238              hPutStrLn stderr "CmLink.link: done"
239         return res
240
241 link' Batch dflags batch_attempt_linking linkables pls1
242    | batch_attempt_linking
243    = do let o_files = concatMap getOfiles linkables
244         when (verb >= 1) $
245              hPutStrLn stderr "ghc: linking ..."
246         -- don't showPass in Batch mode; doLink will do that for us.
247         doLink o_files
248         -- doLink only returns if it succeeds
249         return (LinkOK pls1)
250    | otherwise
251    = do when (verb >= 3) $ do
252             hPutStrLn stderr "CmLink.link(batch): upsweep (partially) failed OR"
253             hPutStrLn stderr "   Main.main not exported; not linking."
254         return (LinkOK pls1)
255    where
256       verb = verbosity dflags
257       getOfiles (LM _ _ us) = map nameOfObject (filter isObject us)
258
259 #ifdef GHCI
260 link' Interactive dflags batch_attempt_linking linkables pls
261     = do showPass dflags "Linking"
262          block $ do -- don't want to be interrupted by ^C in here
263
264             -- Always load objects first.  Objects aren't allowed to
265             -- depend on BCOs.
266             let (objs, bcos) = partition isObjectLinkable linkables
267
268             objs_loaded  <- readIORef v_ObjectsLoaded
269             objs_loaded' <- linkObjs objs objs_loaded
270             writeIORef v_ObjectsLoaded objs_loaded'
271
272             -- resolve symbols within the object files
273             resolveObjs
274
275             -- finally link the interpreted linkables
276             linkBCOs bcos [] pls
277 #endif
278
279 -----------------------------------------------------------------------------
280 -- Linker for interactive mode
281
282 #ifdef GHCI
283 linkObjs [] objs_loaded = return objs_loaded
284 linkObjs (l@(LM _ m uls) : ls) objs_loaded
285    | linkableInSet l objs_loaded  = linkObjs ls objs_loaded -- already loaded
286    | otherwise = do mapM_ loadObj [ file | DotO file <- uls ]
287                     linkObjs ls (l:objs_loaded)
288
289 linkBCOs [] ul_trees pls = linkFinish pls ul_trees
290 linkBCOs (l@(LM _ m uls) : ls) ul_trees pls
291    | linkableInSet l (bcos_loaded pls)
292         = linkBCOs ls ul_trees pls
293    | otherwise
294         = linkBCOs ls (uls++ul_trees) pls{bcos_loaded = l : bcos_loaded pls}
295
296 -- link all the interpreted code in one go.
297 linkFinish pls ul_bcos = do
298
299    let stuff = [ (bcos,itbls) | BCOs bcos itbls <- ul_bcos ]
300
301    (ibinds, new_itbl_env, new_closure_env) <-
302         linkIModules (itbl_env pls) (closure_env pls) stuff
303
304    let new_pls = pls { closure_env = new_closure_env,
305                        itbl_env    = new_itbl_env
306                      }
307    return (LinkOK new_pls)
308 #endif
309
310 -- ---------------------------------------------------------------------------
311 -- Link a single expression
312
313 #ifdef GHCI
314 linkExpr :: PersistentLinkerState -> UnlinkedBCOExpr -> IO HValue
315 linkExpr PersistentLinkerState{ itbl_env = ie, closure_env = ce } bcos
316   = linkIExpr ie ce bcos
317 #endif
318 \end{code}