8bce437c4bc89e051ec65b14d07d48ded7bb6593
[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                 modname_of_linkable, is_package_linkable,
11                 LinkResult(..),
12                 link, 
13                 unload,
14                 PersistentLinkerState{-abstractly!-}, emptyPLS,
15 #ifdef GHCI
16                 linkExpr
17 #endif
18   ) where
19
20
21 import Interpreter
22 import DriverPipeline
23 import CmTypes
24 import CmStaticInfo     ( GhciMode(..) )
25 import Outputable       ( SDoc )
26 import Digraph          ( SCC(..), flattenSCC )
27 import Module           ( ModuleName )
28 import FiniteMap
29 import Outputable
30 import ErrUtils         ( showPass )
31 import CmdLineOpts      ( DynFlags(..) )
32 import Panic            ( panic, GhcException(..) )
33
34 import Exception
35 import Monad
36 import IO
37
38 #include "HsVersions.h"
39 \end{code}
40
41 \begin{code}
42 data PersistentLinkerState 
43    = PersistentLinkerState {
44
45 #ifdef GHCI
46         -- Current global mapping from RdrNames to closure addresses
47         closure_env :: ClosureEnv,
48
49         -- the current global mapping from RdrNames of DataCons to 
50         -- info table addresses.
51         -- When a new Unlinked is linked into the running image, or an existing
52         -- module in the image is replaced, the itbl_env must be updated
53         -- appropriately.
54         itbl_env    :: ItblEnv
55
56         -- notionally here, but really lives in the C part of the linker:
57         --            object_symtab :: FiniteMap String Addr
58 #else
59         dummy :: ()     --  sigh, can't have an empty record
60 #endif
61
62      }
63
64 data LinkResult 
65    = LinkOK   PersistentLinkerState
66    | LinkErrs PersistentLinkerState [SDoc]
67
68 findModuleLinkable_maybe :: [Linkable] -> ModuleName -> Maybe Linkable
69 findModuleLinkable_maybe lis mod 
70    = case [LM time nm us | LM time nm us <- lis, nm == mod] of
71         []   -> Nothing
72         [li] -> Just li
73         many -> pprPanic "findModuleLinkable" (ppr mod)
74
75
76 emptyPLS :: IO PersistentLinkerState
77 #ifdef GHCI
78 emptyPLS = return (PersistentLinkerState { closure_env = emptyFM, 
79                                            itbl_env    = emptyFM })
80 #else
81 emptyPLS = return (PersistentLinkerState {})
82 #endif
83 \end{code}
84
85 \begin{code}
86 link :: GhciMode                -- interactive or batch
87      -> DynFlags                -- dynamic flags
88      -> Bool                    -- attempt linking in batch mode?
89      -> [Linkable]              -- only contains LMs, not LPs
90      -> PersistentLinkerState 
91      -> IO LinkResult
92
93 -- For the moment, in the batch linker, we don't bother to tell doLink
94 -- which packages to link -- it just tries all that are available.
95 -- batch_attempt_linking should only be *looked at* in batch mode.  It
96 -- should only be True if the upsweep was successful and someone
97 -- exports main, i.e., we have good reason to believe that linking
98 -- will succeed.
99
100 -- There will be (ToDo: are) two lists passed to link.  These
101 -- correspond to
102 --
103 --      1. The list of all linkables in the current home package.  This is
104 --         used by the batch linker to link the program, and by the interactive
105 --         linker to decide which modules from the previous link it can 
106 --         throw away.
107 --      2. The list of modules on which we just called "compile".  This list
108 --         is used by the interactive linker to decide which modules need
109 --         to be actually linked this time around (or unlinked and re-linked 
110 --         if the module was recompiled).
111
112 link mode dflags batch_attempt_linking linkables pls1
113    = do let verb = verbosity dflags
114         when (verb >= 3) $ do
115              hPutStrLn stderr "CmLink.link: linkables are ..."
116              hPutStrLn stderr (showSDoc (vcat (map ppr linkables)))
117         res <- link' mode dflags batch_attempt_linking linkables pls1
118         when (verb >= 3) $ 
119              hPutStrLn stderr "CmLink.link: done"
120         return res
121
122 link' Batch dflags batch_attempt_linking linkables pls1
123    | batch_attempt_linking
124    = do let o_files = concatMap getOfiles linkables
125         when (verb >= 1) $
126              hPutStrLn stderr "ghc: linking ..."
127         -- don't showPass in Batch mode; doLink will do that for us.
128         doLink o_files
129         -- doLink only returns if it succeeds
130         return (LinkOK pls1)
131    | otherwise
132    = do when (verb >= 3) $ do
133             hPutStrLn stderr "CmLink.link(batch): upsweep (partially) failed OR"
134             hPutStrLn stderr "   Main.main not exported; not linking."
135         return (LinkOK pls1)
136    where
137       verb = verbosity dflags
138       getOfiles (LP _)    = panic "CmLink.link(getOfiles): shouldn't get package linkables"
139       getOfiles (LM _ _ us) = map nameOfObject (filter isObject us)
140
141 link' Interactive dflags batch_attempt_linking linkables pls1
142     = do showPass dflags "Linking"
143          pls2 <- unload pls1
144          linkObjs linkables pls2
145
146
147 ppLinkableSCC :: SCC Linkable -> SDoc
148 ppLinkableSCC = ppr . flattenSCC
149
150
151 modname_of_linkable (LM _ nm _) = nm
152 modname_of_linkable (LP _)      = panic "modname_of_linkable: package"
153
154 is_package_linkable (LP _)     = True
155 is_package_linkable (LM _ _ _) = False
156
157 filterModuleLinkables :: (ModuleName -> Bool) 
158                       -> [Linkable] 
159                       -> [Linkable]
160 filterModuleLinkables p [] = []
161 filterModuleLinkables p (li:lis)
162    = case li of
163         LP _         -> retain
164         LM _ modnm _ -> if p modnm then retain else dump
165      where
166         dump   = filterModuleLinkables p lis
167         retain = li : dump
168
169 -----------------------------------------------------------------------------
170 -- Linker for interactive mode
171
172 #ifndef GHCI
173 linkObjs      = panic "CmLink.linkObjs: no interpreter"
174 unload        = panic "CmLink.unload: no interpreter"
175 lookupClosure = panic "CmLink.lookupClosure: no interpreter"
176 #else
177 linkObjs [] pls = linkFinish pls [] []
178 linkObjs (l@(LM _ _ uls) : ls) pls
179    | all isObject uls = do
180         mapM_ loadObj [ file | DotO file <- uls ] 
181         linkObjs ls pls
182    | all isInterpretable uls  = linkInterpretedCode (l:ls) [] [] pls
183    | otherwise                = invalidLinkable
184 linkObjs _ pls = 
185    throwDyn (OtherError "CmLink.linkObjs: found package linkable")
186
187  
188 linkInterpretedCode [] mods ul_trees pls = linkFinish pls mods ul_trees
189 linkInterpretedCode (LM _ m uls : ls) mods ul_trees pls
190    | all isInterpretable uls = 
191         linkInterpretedCode ls (m:mods) (uls++ul_trees) pls
192         
193    | any isObject uls
194         = throwDyn (OtherError "can't link object code that depends on interpreted code")
195    | otherwise = invalidLinkable
196 linkInterpretedCode _ _ _ pls = 
197    throwDyn (OtherError "CmLink.linkInterpretedCode: found package linkable")
198
199 invalidLinkable = throwDyn (OtherError "linkable doesn't contain entirely objects interpreted code")
200
201
202 -- link all the interpreted code in one go.  We first remove from the
203 -- various environments any previous versions of these modules.
204 linkFinish pls mods ul_bcos = do
205    resolveObjs
206    let itbl_env'    = filterNameMap mods (itbl_env pls)
207        closure_env' = filterNameMap mods (closure_env pls)
208        stuff        = [ (bcos,itbls) | BCOs bcos itbls <- ul_bcos ]
209
210    (ibinds, new_itbl_env, new_closure_env) <-
211         linkIModules itbl_env' closure_env' stuff
212
213    let new_pls = PersistentLinkerState {
214                                   closure_env = new_closure_env,
215                                   itbl_env    = new_itbl_env
216                         }
217    return (LinkOK new_pls)
218
219 -- purge the current "linked image"
220 unload :: PersistentLinkerState -> IO PersistentLinkerState
221 unload pls = return pls{ closure_env = emptyFM, itbl_env = emptyFM }
222
223 linkExpr :: PersistentLinkerState -> UnlinkedBCOExpr -> IO HValue
224 linkExpr PersistentLinkerState{ itbl_env = ie, closure_env = ce } bcos
225   = linkIExpr ie ce bcos
226 #endif
227 \end{code}