[project @ 2000-11-14 15:04:15 by sewardj]
[ghc-hetmet.git] / ghc / compiler / compMan / CompManager.lhs
1 %
2 % (c) The University of Glasgow, 2000
3 %
4 \section[CompManager]{The Compilation Manager}
5
6 \begin{code}
7 module CompManager ( cmInit, cmLoadModule, 
8                      cmGetExpr, cmRunExpr,
9                      CmState, emptyCmState  -- abstract
10                    )
11 where
12
13 #include "HsVersions.h"
14
15 import List             ( nub )
16 import Maybe            ( catMaybes, maybeToList, fromMaybe )
17 import Maybes           ( maybeToBool )
18 import Outputable
19 import UniqFM           ( emptyUFM, lookupUFM, addToUFM, delListFromUFM )
20 import Digraph          ( SCC(..), stronglyConnComp, flattenSCC, flattenSCCs )
21 import Panic            ( panic )
22
23 import CmLink           ( PersistentLinkerState, emptyPLS, Linkable(..), 
24                           link, LinkResult(..), 
25                           filterModuleLinkables, modname_of_linkable,
26                           is_package_linkable )
27 import Interpreter      ( HValue )
28 import CmSummarise      ( summarise, ModSummary(..), 
29                           name_of_summary, deps_of_summary,
30                           mimp_name, ms_get_imports )
31 import Module           ( ModuleName, moduleName, packageOfModule, 
32                           isModuleInThisPackage, PackageName, moduleEnvElts )
33 import CmStaticInfo     ( Package(..), PackageConfigInfo )
34 import DriverPipeline   ( compile, preprocess, doLink, CompResult(..) )
35 import HscTypes         ( HomeSymbolTable, HomeIfaceTable, 
36                           PersistentCompilerState, ModDetails(..) )
37 import Name             ( lookupNameEnv )
38 import PrelNames        ( mainName )
39 import HscMain          ( initPersistentCompilerState )
40 import Finder           ( findModule, emptyHomeDirCache )
41 import BasicTypes       ( GhciMode(..) )
42 import Util             ( unJust )
43 import DriverUtil       ( BarfKind(..) )
44 import Exception        ( throwDyn )
45 \end{code}
46
47
48
49 \begin{code}
50 cmInit :: PackageConfigInfo -> IO CmState
51 cmInit raw_package_info
52    = emptyCmState raw_package_info
53
54 cmGetExpr :: CmState
55           -> ModuleName
56           -> String
57           -> IO (CmState, Either [SDoc] HValue)
58 cmGetExpr cmstate modhdl expr
59    = return (panic "cmGetExpr:unimp")
60
61 cmRunExpr :: HValue -> IO ()
62 cmRunExpr hval
63    = return (panic "cmRunExpr:unimp")
64
65
66 -- Persistent state just for CM, excluding link & compile subsystems
67 data PersistentCMState
68    = PersistentCMState {
69         hst :: HomeSymbolTable,    -- home symbol table
70         hit :: HomeIfaceTable,     -- home interface table
71         ui  :: UnlinkedImage,      -- the unlinked images
72         mg  :: ModuleGraph,        -- the module graph
73         pci :: PackageConfigInfo   -- NEVER CHANGES
74      }
75
76 emptyPCMS :: PackageConfigInfo -> PersistentCMState
77 emptyPCMS pci 
78   = PersistentCMState { hst = emptyHST, hit = emptyHIT,
79                         ui  = emptyUI,  mg  = emptyMG, pci = pci }
80
81 emptyHIT :: HomeIfaceTable
82 emptyHIT = emptyUFM
83 emptyHST :: HomeSymbolTable
84 emptyHST = emptyUFM
85
86
87
88 -- Persistent state for the entire system
89 data CmState
90    = CmState {
91         pcms   :: PersistentCMState,       -- CM's persistent state
92         pcs    :: PersistentCompilerState, -- compile's persistent state
93         pls    :: PersistentLinkerState    -- link's persistent state
94      }
95
96 emptyCmState :: PackageConfigInfo -> IO CmState
97 emptyCmState pci
98     = do let pcms = emptyPCMS pci
99          pcs     <- initPersistentCompilerState
100          pls     <- emptyPLS
101          return (CmState { pcms   = pcms,
102                            pcs    = pcs,
103                            pls    = pls })
104
105 -- CM internal types
106 type UnlinkedImage = [Linkable] -- the unlinked images (should be a set, really)
107 emptyUI :: UnlinkedImage
108 emptyUI = []
109
110 type ModuleGraph = [SCC ModSummary]  -- the module graph, topologically sorted
111 emptyMG :: ModuleGraph
112 emptyMG = []
113
114 \end{code}
115
116 The real business of the compilation manager: given a system state and
117 a module name, try and bring the module up to date, probably changing
118 the system state at the same time.
119
120 \begin{code}
121 cmLoadModule :: CmState 
122              -> ModuleName
123              -> IO (CmState, Maybe ModuleName)
124
125 cmLoadModule cmstate1 modname
126    = do -- version 1's are the original, before downsweep
127         let pcms1   = pcms   cmstate1
128         let pls1    = pls    cmstate1
129         let pcs1    = pcs    cmstate1
130         let mg1     = mg     pcms1
131         let hst1    = hst    pcms1
132         let hit1    = hit    pcms1
133         let ui1     = ui     pcms1
134    
135         let pcii    = pci    pcms1      -- this never changes
136
137         -- do the downsweep to reestablish the module graph
138         -- then generate version 2's by removing from HIT,HST,UI any
139         -- modules in the old MG which are not in the new one.
140
141         -- Throw away the old home dir cache
142         emptyHomeDirCache
143
144         putStr "cmLoadModule: downsweep begins\n"
145         mg2unsorted <- downsweep modname
146         putStrLn (showSDoc (vcat (map ppr mg2unsorted)))
147
148         let modnames1   = map name_of_summary (flattenSCCs mg1)
149         let modnames2   = map name_of_summary mg2unsorted
150         let mods_to_zap = filter (`notElem` modnames2) modnames1
151
152         let (hst2, hit2, ui2)
153                = removeFromTopLevelEnvs mods_to_zap (hst1, hit1, ui1)
154
155         let mg2 = topological_sort mg2unsorted
156
157         putStrLn "after tsort:\n"
158         putStrLn (showSDoc (vcat (map ppr (flattenSCCs mg2))))
159
160         -- Now do the upsweep, calling compile for each module in
161         -- turn.  Final result is version 3 of everything.
162
163         let threaded2 = ModThreaded pcs1 hst2 hit2
164
165         (upsweepOK, threaded3, sccOKs, newLis)
166            <- upsweep_sccs threaded2 [] [] mg2
167
168         let ui3 = add_to_ui ui2 newLis
169         let (ModThreaded pcs3 hst3 hit3) = threaded3
170
171         -- Try and do linking in some form, depending on whether the
172         -- upsweep was completely or only partially successful.
173         let ghci_mode = Batch  -- ToDo: fix!
174
175         if upsweepOK
176
177          then 
178            do putStrLn "UPSWEEP COMPLETELY SUCCESSFUL"
179               let someone_exports_main = any exports_main (moduleEnvElts hst3)
180               let mods_to_relink = upwards_closure mg2 
181                                       (map modname_of_linkable newLis)
182               pkg_linkables <- find_pkg_linkables_for pcii
183                                                       mg2 mods_to_relink
184               putStrLn ("needed package modules =\n" 
185                         ++ showSDoc (vcat (map ppr pkg_linkables)))
186               let sccs_to_relink = group_uis ui3 mg2 mods_to_relink
187               let all_to_relink  = map AcyclicSCC pkg_linkables 
188                                    ++ sccs_to_relink
189               linkresult <- link doLink ghci_mode someone_exports_main
190                                  pcii all_to_relink pls1
191               case linkresult of
192                  LinkErrs _ _
193                     -> panic "cmLoadModule: link failed (1)"
194                  LinkOK pls3 
195                     -> do let pcms3 = PersistentCMState { hst=hst3, hit=hit3, 
196                                                           ui=ui3, mg=mg2, pci=pcii }
197                           let cmstate3 
198                                  = CmState { pcms=pcms3, pcs=pcs3, pls=pls3 }
199                           return (cmstate3, Just modname)
200
201          else 
202            do putStrLn "UPSWEEP PARTIALLY SUCCESSFUL"
203               let mods_to_relink = downwards_closure mg2 
204                                       (map name_of_summary (flattenSCCs sccOKs))
205               pkg_linkables <- find_pkg_linkables_for pcii
206                                                       mg2 mods_to_relink
207               let sccs_to_relink = group_uis ui3 mg2 mods_to_relink
208               let all_to_relink  = map AcyclicSCC pkg_linkables 
209                                    ++ sccs_to_relink
210               linkresult <- link doLink ghci_mode False pcii all_to_relink pls1
211               let (hst4, hit4, ui4) 
212                      = removeFromTopLevelEnvs mods_to_relink (hst3,hit3,ui3)
213               case linkresult of
214                  LinkErrs _ _
215                     -> panic "cmLoadModule: link failed (2)"
216                  LinkOK pls4
217                     -> do let pcms4 = PersistentCMState { hst=hst4, hit=hit4, 
218                                                           ui=ui4, mg=mg2, pci=pcii }
219                           let cmstate4 
220                                  = CmState { pcms=pcms4, pcs=pcs3, pls=pls4 }
221                           return (cmstate4, Just modname)
222
223 exports_main :: ModDetails -> Bool
224 exports_main md
225    = maybeToBool (lookupNameEnv (md_types md) mainName)
226
227 -- Given a (home) module graph and a bunch of names of (home) modules
228 -- within that graph, return the names of any packages needed by the
229 -- named modules.  Do this by looking at their imports.  Assumes, and
230 -- checks, that all of "mods" are mentioned in "mg".
231 -- 
232 -- Then, having found the packages directly needed by "mods",
233 -- (1) round up, by looking in "pci", all packages they directly or
234 -- indirectly depend on, and (2) put these packages in topological
235 -- order, since that's important for some linkers.  Since cycles in
236 -- the package dependency graph aren't allowed, we can just return
237 -- the list of (package) linkables, rather than a list of SCCs.
238 find_pkg_linkables_for :: PackageConfigInfo -> [SCC ModSummary] -> [ModuleName]
239                        -> IO [Linkable]
240 find_pkg_linkables_for pcii mg mods
241    = let mg_summaries = flattenSCCs mg
242          mg_names     = map name_of_summary mg_summaries
243      in
244      -- Assert that the modules for which we seek the required packages
245      -- are all in the module graph, i.e. are all home modules.
246      if   not (all (`elem` mg_names) mods)
247      then panic "find_pkg_linkables_for"
248      else 
249      do let all_imports
250                = concat 
251                     [deps_of_summary summ
252                     | summ <- mg_summaries, name_of_summary summ `elem` mods]
253         let imports_not_in_home  -- imports which must be from packages
254                = nub (filter (`notElem` mg_names) all_imports)
255
256         -- Figure out the packages directly imported by the home modules
257         maybe_locs_n_mods <- mapM findModule imports_not_in_home
258         let home_pkgs_needed
259                = nub (concatMap get_pkg maybe_locs_n_mods)
260                  where get_pkg Nothing = []
261                        get_pkg (Just (mod, loc))
262                           = case packageOfModule mod of 
263                                Just p -> [p]; _ -> []
264
265         -- Discover the package dependency graph, and use it to find the
266         -- transitive closure of all the needed packages
267         let pkg_depend_graph :: [(PackageName,[PackageName])]
268             pkg_depend_graph = map (\pkg -> (_PK_ (name pkg), map _PK_ (package_deps pkg))) pcii
269
270         let all_pkgs_needed = simple_transitive_closure 
271                                  pkg_depend_graph home_pkgs_needed
272
273         -- Make a graph, in the style which Digraph.stronglyConnComp expects,
274         -- containing entries only for the needed packages.
275         let needed_graph
276                = concat
277                    [if srcP `elem` all_pkgs_needed
278                      then [(srcP, srcP, dstsP)] 
279                      else []
280                     | (srcP, dstsP) <- pkg_depend_graph]
281             tsorted = flattenSCCs (stronglyConnComp needed_graph)
282         
283         return (map LP tsorted)
284
285
286 simple_transitive_closure :: Eq a => [(a,[a])] -> [a] -> [a]
287 simple_transitive_closure graph set
288    = let set2      = nub (concatMap dsts set ++ set)
289          dsts node = fromMaybe [] (lookup node graph)
290      in
291          if   length set == length set2 
292          then set 
293          else simple_transitive_closure graph set2
294
295
296 -- For each module in mods_to_group, extract the relevant linkable
297 -- out of "ui", and arrange these linkables in SCCs as defined by modGraph.
298 -- All this is so that we can pass SCCified Linkable groups to the
299 -- linker.  A constraint that should be recorded somewhere is that
300 -- all sccs should either be all-interpreted or all-object, not a mixture.
301 group_uis :: UnlinkedImage -> [SCC ModSummary] -> [ModuleName] -> [SCC Linkable]
302 group_uis ui modGraph mods_to_group
303    = map extract (cleanup (fishOut modGraph mods_to_group))
304      where
305         fishOut :: [SCC ModSummary] -> [ModuleName] -> [(Bool,[ModuleName])]
306         fishOut [] unused
307            | null unused = []
308            | otherwise   = panic "group_uis: modnames not in modgraph"
309         fishOut ((AcyclicSCC ms):sccs) unused
310            = case split (== (name_of_summary ms)) unused of
311                 (eq, not_eq) -> (False, eq) : fishOut sccs not_eq
312         fishOut ((CyclicSCC mss):sccs) unused
313            = case split (`elem` (map name_of_summary mss)) unused of
314                 (eq, not_eq) -> (True, eq) : fishOut sccs not_eq
315
316         cleanup :: [(Bool,[ModuleName])] -> [SCC ModuleName]
317         cleanup [] = []
318         cleanup ((isRec,names):rest)
319            | null names = cleanup rest
320            | isRec      = CyclicSCC names : cleanup rest
321            | not isRec  = case names of [name] -> AcyclicSCC name : cleanup rest
322                                         other  -> panic "group_uis(cleanup)"
323
324         extract :: SCC ModuleName -> SCC Linkable
325         extract (AcyclicSCC nm) = AcyclicSCC (getLi nm)
326         extract (CyclicSCC nms) = CyclicSCC (map getLi nms)
327
328         getLi nm = case [li | li <- ui, not (is_package_linkable li),
329                                         nm == modname_of_linkable li] of
330                       [li]  -> li
331                       other -> panic "group_uis:getLi"
332
333         split f xs = (filter f xs, filter (not.f) xs)
334
335
336 -- Add the given (LM-form) Linkables to the UI, overwriting previous
337 -- versions if they exist.
338 add_to_ui :: UnlinkedImage -> [Linkable] -> UnlinkedImage
339 add_to_ui ui lis
340    = foldr add1 ui lis
341      where
342         add1 :: Linkable -> UnlinkedImage -> UnlinkedImage
343         add1 li ui
344            = li : filter (\li2 -> not (for_same_module li li2)) ui
345
346         for_same_module :: Linkable -> Linkable -> Bool
347         for_same_module li1 li2 
348            = not (is_package_linkable li1)
349              && not (is_package_linkable li2)
350              && modname_of_linkable li1 == modname_of_linkable li2
351                                   
352
353 -- Compute upwards and downwards closures in the (home-) module graph.
354 downwards_closure,
355  upwards_closure :: [SCC ModSummary] -> [ModuleName] -> [ModuleName]
356
357 upwards_closure   = up_down_closure True
358 downwards_closure = up_down_closure False
359
360 up_down_closure :: Bool -> [SCC ModSummary] -> [ModuleName] -> [ModuleName]
361 up_down_closure up modGraph roots
362    = let mgFlat = flattenSCCs modGraph
363          nodes  = map name_of_summary mgFlat
364
365          fwdEdges, backEdges  :: [(ModuleName, [ModuleName])] 
366                    -- have an entry for each mod in mgFlat, and do not
367                    -- mention edges leading out of the home package
368          fwdEdges 
369             = map mkEdge mgFlat
370          backEdges -- Only calculated if needed, which is just as well!
371             = [(n, [m | (m, m_imports) <- fwdEdges, n `elem` m_imports])
372                | (n, n_imports) <- fwdEdges]
373
374          mkEdge summ
375             = (name_of_summary summ, 
376                -- ignore imports not from the home package
377                filter (`elem` nodes) (deps_of_summary summ))
378      in
379          simple_transitive_closure
380             (if up then backEdges else fwdEdges) (nub roots)
381
382
383
384 data ModThreaded  -- stuff threaded through individual module compilations
385    = ModThreaded PersistentCompilerState HomeSymbolTable HomeIfaceTable
386
387 -- Compile multiple SCCs, stopping as soon as an error appears
388 upsweep_sccs :: ModThreaded           -- PCS & HST & HIT
389              -> [SCC ModSummary]      -- accum: SCCs which succeeded
390              -> [Linkable]            -- accum: new Linkables
391              -> [SCC ModSummary]      -- SCCs to do (the worklist)
392                                       -- ...... RETURNING ......
393              -> IO (Bool{-success?-},
394                     ModThreaded,
395                     [SCC ModSummary], -- SCCs which succeeded
396                     [Linkable])       -- new linkables
397
398 upsweep_sccs threaded sccOKs newLis []
399    = -- No more SCCs to do.
400      return (True, threaded, sccOKs, newLis)
401
402 upsweep_sccs threaded sccOKs newLis (scc:sccs)
403    = -- Start work on a new SCC.
404      do (sccOK, threaded2, lisSCC) 
405            <- upsweep_scc threaded (flattenSCC scc)
406         if    sccOK
407          then -- all the modules in the scc were ok
408               -- move on to the next SCC
409               upsweep_sccs threaded2 
410                            (scc:sccOKs) (lisSCC++newLis) sccs
411          else -- we got a compilation error; give up now
412               return
413                  (False, threaded2, sccOKs, lisSCC++newLis)
414
415
416 -- Compile multiple modules (one SCC), stopping as soon as an error appears
417 upsweep_scc :: ModThreaded
418              -> [ModSummary]
419              -> IO (Bool{-success?-}, ModThreaded, [Linkable])
420 upsweep_scc threaded []
421    = return (True, threaded, [])
422 upsweep_scc threaded (mod:mods)
423    = do (moduleOK, threaded1, maybe_linkable) 
424            <- upsweep_mod threaded mod
425         if moduleOK
426          then -- No errors; get contribs from the rest
427               do (restOK, threaded2, linkables)
428                     <- upsweep_scc threaded1 mods
429                  return
430                     (restOK, threaded2, maybeToList maybe_linkable ++ linkables)
431          else -- Errors; give up _now_
432               return (False, threaded1, [])
433
434 -- Compile a single module.
435 upsweep_mod :: ModThreaded
436             -> ModSummary
437             -> IO (Bool{-success?-}, ModThreaded, Maybe Linkable)
438
439 upsweep_mod threaded1 summary1
440    = do let mod_name = name_of_summary summary1
441         let (ModThreaded pcs1 hst1 hit1) = threaded1
442         let old_iface = lookupUFM hit1 (name_of_summary summary1)
443         compresult <- compile summary1 old_iface hst1 hit1 pcs1
444
445         case compresult of
446
447            -- Compilation "succeeded", but didn't return a new iface or
448            -- linkable, meaning that compilation wasn't needed, and the
449            -- new details were manufactured from the old iface.
450            CompOK details Nothing pcs2
451               -> let hst2      = addToUFM hst1 mod_name details
452                      hit2      = hit1
453                      threaded2 = ModThreaded pcs2 hst2 hit2
454                  in  return (True, threaded2, Nothing)
455
456            -- Compilation really did happen, and succeeded.  A new
457            -- details, iface and linkable are returned.
458            CompOK details (Just (new_iface, new_linkable)) pcs2
459               -> let hst2      = addToUFM hst1 mod_name details
460                      hit2      = addToUFM hit1 mod_name new_iface
461                      threaded2 = ModThreaded pcs2 hst2 hit2
462                  in  return (True, threaded2, Just new_linkable)
463
464            -- Compilation failed.  compile may still have updated
465            -- the PCS, tho.
466            CompErrs pcs2
467               -> let threaded2 = ModThreaded pcs2 hst1 hit1
468                  in  return (False, threaded2, Nothing)
469
470
471 removeFromTopLevelEnvs :: [ModuleName]
472                        -> (HomeSymbolTable, HomeIfaceTable, UnlinkedImage)
473                        -> (HomeSymbolTable, HomeIfaceTable, UnlinkedImage)
474 removeFromTopLevelEnvs zap_these (hst, hit, ui)
475    = (delListFromUFM hst zap_these,
476       delListFromUFM hit zap_these,
477       filterModuleLinkables (`notElem` zap_these) ui
478      )
479
480 topological_sort :: [ModSummary] -> [SCC ModSummary]
481 topological_sort summaries
482    = let 
483          toEdge :: ModSummary -> (ModSummary,ModuleName,[ModuleName])
484          toEdge summ
485              = (summ, name_of_summary summ, deps_of_summary summ)
486          
487          mash_edge :: (ModSummary,ModuleName,[ModuleName]) -> (ModSummary,Int,[Int])
488          mash_edge (summ, m, m_imports)
489             = case lookup m key_map of
490                  Nothing -> panic "reverse_topological_sort"
491                  Just mk -> (summ, mk, 
492                                 -- ignore imports not from the home package
493                                 catMaybes (map (flip lookup key_map) m_imports))
494
495          edges     = map toEdge summaries
496          key_map   = zip [nm | (s,nm,imps) <- edges] [1 ..] :: [(ModuleName,Int)]
497          scc_input = map mash_edge edges
498          sccs      = stronglyConnComp scc_input
499      in
500          sccs
501
502 downsweep :: ModuleName          -- module to chase from
503           -> IO [ModSummary]
504 downsweep rootNm
505    = do rootLoc <- getSummary rootNm
506         loop [rootLoc]
507      where
508         getSummary :: ModuleName -> IO ModSummary
509         getSummary nm
510            | trace ("getSummary: "++ showSDoc (ppr nm)) True
511            = do found <- findModule nm
512                 case found of
513                    Just (mod, location) -> summarise preprocess mod location
514                    Nothing -> throwDyn (OtherError 
515                                    ("ghc --make: no signs of life for module `" 
516                                      ++ showSDoc (ppr nm) ++ "'"))
517                                  
518
519         -- loop invariant: homeSummaries doesn't contain package modules
520         loop :: [ModSummary] -> IO [ModSummary]
521         loop homeSummaries
522            = do let allImps :: [ModuleName]
523                     allImps   -- all imports
524                        = (nub . map mimp_name . concat . map ms_get_imports)
525                          homeSummaries
526                 let allHome   -- all modules currently in homeSummaries
527                        = map (moduleName.ms_mod) homeSummaries
528                 let neededImps
529                        = filter (`notElem` allHome) allImps
530                 neededSummaries
531                        <- mapM getSummary neededImps
532                 let newHomeSummaries
533                        = filter (isModuleInThisPackage.ms_mod) neededSummaries
534                 if null newHomeSummaries
535                  then return homeSummaries
536                  else loop (newHomeSummaries ++ homeSummaries)
537 \end{code}