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