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