[project @ 2001-02-12 13:33:46 by simonmar]
[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, cmUnload,
8 #ifdef GHCI
9                      cmGetExpr, cmRunExpr,
10 #endif
11                      CmState, emptyCmState  -- abstract
12                    )
13 where
14
15 #include "HsVersions.h"
16
17 import CmLink
18 import CmTypes
19 import HscTypes
20 import Module           ( Module, ModuleName, moduleName, isHomeModule,
21                           mkModuleName, moduleNameUserString )
22 import CmStaticInfo     ( GhciMode(..) )
23 import DriverPipeline
24 import GetImports
25 import HscTypes         ( HomeSymbolTable, HomeIfaceTable, 
26                           PersistentCompilerState, ModDetails(..) )
27 import HscMain          ( initPersistentCompilerState )
28 import Finder
29 import UniqFM           ( emptyUFM, lookupUFM, addToUFM, delListFromUFM,
30                           UniqFM, listToUFM )
31 import Unique           ( Uniquable )
32 import Digraph          ( SCC(..), stronglyConnComp, flattenSCC )
33 import DriverFlags      ( getDynFlags )
34 import DriverPhases
35 import DriverUtil       ( splitFilename3 )
36 import ErrUtils         ( showPass )
37 import Util
38 import DriverUtil
39 import TmpFiles
40 import Outputable
41 import Panic
42 import CmdLineOpts      ( DynFlags(..) )
43 import IOExts
44
45 #ifdef GHCI
46 import Interpreter      ( HValue )
47 import HscMain          ( hscExpr )
48 import Type             ( Type )
49 import PrelGHC          ( unsafeCoerce# )
50 #endif
51
52 -- lang
53 import Exception        ( throwDyn )
54
55 -- std
56 import Time             ( ClockTime )
57 import Directory        ( getModificationTime, doesFileExist )
58 import IO
59 import Monad
60 import List             ( nub )
61 import Maybe            ( catMaybes, fromMaybe, isJust, fromJust )
62 \end{code}
63
64
65 \begin{code}
66 cmInit :: GhciMode -> IO CmState
67 cmInit gmode
68    = emptyCmState gmode
69
70 #ifdef GHCI
71 cmGetExpr :: CmState
72           -> DynFlags
73           -> Bool       -- True <=> wrap in 'print' to get an IO-typed result
74           -> Module
75           -> String
76           -> IO (CmState, Maybe (HValue, PrintUnqualified, Type))
77 cmGetExpr cmstate dflags wrap_io mod expr
78    = do (new_pcs, maybe_stuff) <- 
79            hscExpr dflags wrap_io hst hit pcs mod expr
80         case maybe_stuff of
81            Nothing     -> return (cmstate{ pcs=new_pcs }, Nothing)
82            Just (bcos, print_unqual, ty) -> do
83                 hValue <- linkExpr pls bcos
84                 return (cmstate{ pcs=new_pcs }, 
85                         Just (hValue, print_unqual, ty))
86
87    -- ToDo: check that the module we passed in is sane/exists?
88    where
89        CmState{ hst=hst, hit=hit, pcs=pcs, pls=pls } = cmstate
90
91 -- The HValue should represent a value of type IO () (Perhaps IO a?)
92 cmRunExpr :: HValue -> IO ()
93 cmRunExpr hval
94    = do unsafeCoerce# hval :: IO ()
95         -- putStrLn "done."
96 #endif
97
98 emptyHIT :: HomeIfaceTable
99 emptyHIT = emptyUFM
100 emptyHST :: HomeSymbolTable
101 emptyHST = emptyUFM
102
103 -- Persistent state for the entire system
104 data CmState
105    = CmState {
106         hst   :: HomeSymbolTable,    -- home symbol table
107         hit   :: HomeIfaceTable,     -- home interface table
108         ui    :: UnlinkedImage,      -- the unlinked images
109         mg    :: ModuleGraph,        -- the module graph
110         gmode :: GhciMode,           -- NEVER CHANGES
111
112         pcs    :: PersistentCompilerState, -- compile's persistent state
113         pls    :: PersistentLinkerState    -- link's persistent state
114      }
115
116 emptyCmState :: GhciMode -> IO CmState
117 emptyCmState gmode
118     = do pcs     <- initPersistentCompilerState
119          pls     <- emptyPLS
120          return (CmState { hst = emptyHST,
121                            hit = emptyHIT,
122                            ui  = emptyUI,
123                            mg  = emptyMG, 
124                            gmode = gmode,
125                            pcs    = pcs,
126                            pls    = pls })
127
128 -- CM internal types
129 type UnlinkedImage = [Linkable] -- the unlinked images (should be a set, really)
130 emptyUI :: UnlinkedImage
131 emptyUI = []
132
133 type ModuleGraph = [ModSummary]  -- the module graph, topologically sorted
134 emptyMG :: ModuleGraph
135 emptyMG = []
136
137 \end{code}
138
139 Unload the compilation manager's state: everything it knows about the
140 current collection of modules in the Home package.
141
142 \begin{code}
143 cmUnload :: CmState -> IO CmState
144 cmUnload state 
145  = do -- Throw away the old home dir cache
146       emptyHomeDirCache
147       -- Throw away the HIT and the HST
148       return state{ hst=new_hst, hit=new_hit, ui=emptyUI }
149    where
150      CmState{ hst=hst, hit=hit } = state
151      (new_hst, new_hit) = retainInTopLevelEnvs [] (hst,hit)
152 \end{code}
153
154 The real business of the compilation manager: given a system state and
155 a module name, try and bring the module up to date, probably changing
156 the system state at the same time.
157
158 \begin{code}
159 cmLoadModule :: CmState 
160              -> FilePath
161              -> IO (CmState,            -- new state
162                     Bool,               -- was successful
163                     [Module])           -- list of modules loaded
164
165 cmLoadModule cmstate1 rootname
166    = do -- version 1's are the original, before downsweep
167         let pls1      = pls    cmstate1
168         let pcs1      = pcs    cmstate1
169         let hst1      = hst    cmstate1
170         let hit1      = hit    cmstate1
171         -- similarly, ui1 is the (complete) set of linkables from
172         -- the previous pass, if any.
173         let ui1       = ui     cmstate1
174         let mg1       = mg     cmstate1
175
176         let ghci_mode = gmode cmstate1 -- this never changes
177
178         -- Do the downsweep to reestablish the module graph
179         -- then generate version 2's by retaining in HIT,HST,UI a
180         -- stable set S of modules, as defined below.
181
182         dflags <- getDynFlags
183         let verb = verbosity dflags
184
185         showPass dflags "Chasing dependencies"
186         when (verb >= 1 && ghci_mode == Batch) $
187            hPutStrLn stderr (progName ++ ": chasing modules from: " ++ rootname)
188
189         (mg2unsorted, a_root_is_Main) <- downsweep [rootname] mg1
190         let mg2unsorted_names = map name_of_summary mg2unsorted
191
192         -- reachable_from follows source as well as normal imports
193         let reachable_from :: ModuleName -> [ModuleName]
194             reachable_from = downwards_closure_of_module mg2unsorted
195  
196         -- should be cycle free; ignores 'import source's
197         let mg2 = topological_sort False mg2unsorted
198         -- ... whereas this takes them into account.  Used for
199         -- backing out partially complete cycles following a failed
200         -- upsweep, and for removing from hst/hit all the modules
201         -- not in strict downwards closure, during calls to compile.
202         let mg2_with_srcimps = topological_sort True mg2unsorted
203
204         -- Sort out which linkables we wish to keep in the unlinked image.
205         -- See getValidLinkables below for details.
206         valid_linkables <- getValidLinkables ui1 mg2unsorted_names 
207                                 mg2_with_srcimps
208
209         -- Figure out a stable set of modules which can be retained
210         -- the top level envs, to avoid upsweeping them.  Goes to a
211         -- bit of trouble to avoid upsweeping module cycles.
212         --
213         -- Construct a set S of stable modules like this:
214         -- Travel upwards, over the sccified graph.  For each scc
215         -- of modules ms, add ms to S only if:
216         -- 1.  All home imports of ms are either in ms or S
217         -- 2.  A valid linkable exists for each module in ms
218
219         stable_mods
220            <- preUpsweep valid_linkables ui1 mg2unsorted_names
221                  [] mg2_with_srcimps
222
223         let stable_summaries
224                = concatMap (findInSummaries mg2unsorted) stable_mods
225
226             stable_linkables
227                = filter (\m -> linkableModName m `elem` stable_mods) 
228                     valid_linkables
229
230         when (verb >= 2) $
231            putStrLn (showSDoc (text "STABLE MODULES:" 
232                                <+> sep (map (text.moduleNameUserString) stable_mods)))
233
234         -- unload any modules which aren't going to be re-linked this
235         -- time around.
236         pls2 <- unload ghci_mode dflags stable_linkables pls1
237
238         -- We could at this point detect cycles which aren't broken by
239         -- a source-import, and complain immediately, but it seems better
240         -- to let upsweep_mods do this, so at least some useful work gets
241         -- done before the upsweep is abandoned.
242         let upsweep_these
243                = filter (\scc -> any (`notElem` stable_mods) 
244                                      (map name_of_summary (flattenSCC scc)))
245                         mg2
246
247         --hPutStrLn stderr "after tsort:\n"
248         --hPutStrLn stderr (showSDoc (vcat (map ppr mg2)))
249
250         -- Because we don't take into account source imports when doing
251         -- the topological sort, there shouldn't be any cycles in mg2.
252         -- If there is, we complain and give up -- the user needs to
253         -- break the cycle using a boot file.
254
255         -- Now do the upsweep, calling compile for each module in
256         -- turn.  Final result is version 3 of everything.
257
258         let threaded2 = CmThreaded pcs1 hst1 hit1
259
260         (upsweep_complete_success, threaded3, modsUpswept, newLis)
261            <- upsweep_mods ghci_mode dflags valid_linkables reachable_from 
262                            threaded2 upsweep_these
263
264         let ui3 = add_to_ui valid_linkables newLis
265         let (CmThreaded pcs3 hst3 hit3) = threaded3
266
267         -- At this point, modsUpswept and newLis should have the same
268         -- length, so there is one new (or old) linkable for each 
269         -- mod which was processed (passed to compile).
270
271         -- Make modsDone be the summaries for each home module now
272         -- available; this should equal the domains of hst3 and hit3.
273         -- (NOT STRICTLY TRUE if an interactive session was started
274         --  with some object on disk ???)
275         -- Get in in a roughly top .. bottom order (hence reverse).
276
277         let modsDone = reverse modsUpswept ++ stable_summaries
278
279         -- Try and do linking in some form, depending on whether the
280         -- upsweep was completely or only partially successful.
281
282         if upsweep_complete_success
283
284          then 
285            -- Easy; just relink it all.
286            do when (verb >= 2) $ 
287                  hPutStrLn stderr "Upsweep completely successful."
288
289               -- clean up after ourselves
290               cleanTempFilesExcept verb (ppFilesFromSummaries modsDone)
291
292               linkresult 
293                  <- link ghci_mode dflags a_root_is_Main ui3 pls2
294               case linkresult of
295                  LinkErrs _ _
296                     -> panic "cmLoadModule: link failed (1)"
297                  LinkOK pls3 
298                     -> do let cmstate3 
299                                  = CmState { hst=hst3, hit=hit3, 
300                                              ui=ui3, mg=modsDone, 
301                                              gmode=ghci_mode,
302                                              pcs=pcs3, pls=pls3 }
303                           return (cmstate3, True, 
304                                   map ms_mod modsDone)
305
306          else 
307            -- Tricky.  We need to back out the effects of compiling any
308            -- half-done cycles, both so as to clean up the top level envs
309            -- and to avoid telling the interactive linker to link them.
310            do when (verb >= 2) $
311                 hPutStrLn stderr "Upsweep partially successful."
312
313               let modsDone_names
314                      = map name_of_summary modsDone
315               let mods_to_zap_names 
316                      = findPartiallyCompletedCycles modsDone_names mg2_with_srcimps
317               let (hst4, hit4, ui4) 
318                      = removeFromTopLevelEnvs mods_to_zap_names (hst3,hit3,ui3)
319               let mods_to_keep
320                      = filter ((`notElem` mods_to_zap_names).name_of_summary) modsDone
321               let mods_to_keep_names 
322                      = map name_of_summary mods_to_keep
323               -- we could get the relevant linkables by filtering newLis, but
324               -- it seems easier to drag them out of the updated, cleaned-up UI
325               let linkables_to_link 
326                      = map (unJust "linkables_to_link" . findModuleLinkable_maybe ui4)
327                            mods_to_keep_names
328
329               -- clean up after ourselves
330               cleanTempFilesExcept verb (ppFilesFromSummaries mods_to_keep)
331
332               linkresult <- link ghci_mode dflags False linkables_to_link pls2
333               case linkresult of
334                  LinkErrs _ _
335                     -> panic "cmLoadModule: link failed (2)"
336                  LinkOK pls3
337                     -> do let cmstate4 
338                                  = CmState { hst=hst4, hit=hit4, 
339                                              ui=ui4, mg=mods_to_keep,
340                                              gmode=ghci_mode, pcs=pcs3, pls=pls3 }
341                           return (cmstate4, False, 
342                                   map ms_mod mods_to_keep)
343
344
345 ppFilesFromSummaries summaries
346   = [ fn | Just fn <- map (ml_hspp_file . ms_location) summaries ]
347
348 -----------------------------------------------------------------------------
349 -- getValidLinkables
350
351 -- For each module (or SCC of modules), we take:
352 --
353 --      - the old in-core linkable, if available
354 --      - an on-disk linkable, if available
355 --
356 -- and we take the youngest of these, provided it is younger than the
357 -- source file.  We ignore the on-disk linkables unless all of the
358 -- dependents of this SCC also have on-disk linkables.
359 --
360 -- If a module has a valid linkable, then it may be STABLE (see below),
361 -- and it is classified as SOURCE UNCHANGED for the purposes of calling
362 -- compile.
363 --
364 -- ToDo: this pass could be merged with the preUpsweep.
365
366 getValidLinkables
367         :: [Linkable]           -- old linkables
368         -> [ModuleName]         -- all home modules
369         -> [SCC ModSummary]     -- all modules in the program, dependency order
370         -> IO [Linkable]        -- still-valid linkables 
371
372 getValidLinkables old_linkables all_home_mods module_graph
373   = foldM (getValidLinkablesSCC old_linkables all_home_mods) [] module_graph
374
375 getValidLinkablesSCC old_linkables all_home_mods new_linkables scc0
376    = let 
377           scc             = flattenSCC scc0
378           scc_names       = map name_of_summary scc
379           home_module m   = m `elem` all_home_mods && m `notElem` scc_names
380           scc_allhomeimps = nub (filter home_module (concatMap ms_allimps scc))
381
382           has_object m = case findModuleLinkable_maybe new_linkables m of
383                             Nothing -> False
384                             Just l  -> isObjectLinkable l
385
386           objects_allowed = all has_object scc_allhomeimps
387      in do
388
389      these_linkables 
390         <- foldM (getValidLinkable old_linkables objects_allowed) [] scc
391
392         -- since an scc can contain only all objects or no objects at all,
393         -- we have to check whether we got all objects or not, and re-do
394         -- the linkable check if not.
395      adjusted_linkables 
396         <- if objects_allowed && not (all isObjectLinkable these_linkables)
397               then foldM (getValidLinkable old_linkables False) [] scc
398               else return these_linkables
399
400      return (adjusted_linkables ++ new_linkables)
401
402
403 getValidLinkable :: [Linkable] -> Bool -> [Linkable] -> ModSummary 
404         -> IO [Linkable]
405 getValidLinkable old_linkables objects_allowed new_linkables summary 
406    = do 
407         let mod_name = name_of_summary summary
408
409         maybe_disk_linkable
410            <- if (not objects_allowed)
411                 then return Nothing
412                 else case ml_obj_file (ms_location summary) of
413                         Just obj_fn -> maybe_getFileLinkable mod_name obj_fn
414                         Nothing -> return Nothing
415
416          -- find an old in-core linkable if we have one. (forget about
417          -- on-disk linkables for now, we'll check again whether there's
418          -- one here below, just in case a new one has popped up recently).
419         let old_linkable = findModuleLinkable_maybe old_linkables mod_name
420             maybe_old_linkable =
421                 case old_linkable of
422                     Just (LM _ _ ls) | all isInterpretable ls -> old_linkable
423                     _ -> Nothing
424
425         -- The most recent of the old UI linkable or whatever we could
426         -- find on disk is returned as the linkable if compile
427         -- doesn't think we need to recompile.        
428         let linkable_list
429                = case (maybe_old_linkable, maybe_disk_linkable) of
430                     (Nothing, Nothing) -> []
431                     (Nothing, Just di) -> [di]
432                     (Just ui, Nothing) -> [ui]
433                     (Just ui, Just di)
434                        | linkableTime ui >= linkableTime di -> [ui]
435                        | otherwise                          -> [di]
436
437         -- only linkables newer than the source code are valid
438         let maybe_src_date = ms_hs_date summary
439
440             valid_linkable_list
441               = case maybe_src_date of
442                   Nothing -> panic "valid_linkable_list"
443                   Just src_date 
444                      -> filter (\li -> linkableTime li > src_date) linkable_list
445
446         return (valid_linkable_list ++ new_linkables)
447
448
449 maybe_getFileLinkable :: ModuleName -> FilePath -> IO (Maybe Linkable)
450 maybe_getFileLinkable mod_name obj_fn
451    = do obj_exist <- doesFileExist obj_fn
452         if not obj_exist 
453          then return Nothing 
454          else 
455          do let stub_fn = case splitFilename3 obj_fn of
456                              (dir, base, ext) -> dir ++ "/" ++ base ++ ".stub_o"
457             stub_exist <- doesFileExist stub_fn
458             obj_time <- getModificationTime obj_fn
459             if stub_exist
460              then return (Just (LM obj_time mod_name [DotO obj_fn, DotO stub_fn]))
461              else return (Just (LM obj_time mod_name [DotO obj_fn]))
462
463
464 -----------------------------------------------------------------------------
465 -- Do a pre-upsweep without use of "compile", to establish a 
466 -- (downward-closed) set of stable modules for which we won't call compile.
467
468 preUpsweep :: [Linkable]        -- new valid linkables
469            -> [Linkable]        -- old linkables
470            -> [ModuleName]      -- names of all mods encountered in downsweep
471            -> [ModuleName]      -- accumulating stable modules
472            -> [SCC ModSummary]  -- scc-ified mod graph, including src imps
473            -> IO [ModuleName]   -- stable modules
474
475 preUpsweep valid_lis old_lis all_home_mods stable [] 
476    = return stable
477 preUpsweep valid_lis old_lis all_home_mods stable (scc0:sccs)
478    = do let scc = flattenSCC scc0
479             scc_allhomeimps :: [ModuleName]
480             scc_allhomeimps 
481                = nub (filter (`elem` all_home_mods) (concatMap ms_allimps scc))
482             all_imports_in_scc_or_stable
483                = all in_stable_or_scc scc_allhomeimps
484             scc_names
485                = map name_of_summary scc
486             in_stable_or_scc m
487                = m `elem` scc_names || m `elem` stable
488
489             -- now we check for valid linkables: each module in the SCC must 
490             -- have a valid linkable (see getValidLinkables above), and the
491             -- newest linkable must be the same as the previous linkable for
492             -- this module (if one exists).
493             has_valid_linkable new_summary
494               = case findModuleLinkable_maybe valid_lis modname of
495                    Nothing -> False
496                    Just l  -> case findModuleLinkable_maybe old_lis modname of
497                                 Nothing -> True
498                                 Just m  -> linkableTime l == linkableTime m
499                where modname = name_of_summary new_summary
500
501             scc_is_stable = all_imports_in_scc_or_stable
502                           && all has_valid_linkable scc
503
504         if scc_is_stable
505          then preUpsweep valid_lis old_lis all_home_mods 
506                 (scc_names++stable) sccs
507          else preUpsweep valid_lis old_lis all_home_mods 
508                 stable sccs
509
510    where 
511
512
513 -- Helper for preUpsweep.  Assuming that new_summary's imports are all
514 -- stable (in the sense of preUpsweep), determine if new_summary is itself
515 -- stable, and, if so, in batch mode, return its linkable.
516 findInSummaries :: [ModSummary] -> ModuleName -> [ModSummary]
517 findInSummaries old_summaries mod_name
518    = [s | s <- old_summaries, name_of_summary s == mod_name]
519
520 findModInSummaries :: [ModSummary] -> Module -> Maybe ModSummary
521 findModInSummaries old_summaries mod
522    = case [s | s <- old_summaries, ms_mod s == mod] of
523          [] -> Nothing
524          (s:_) -> Just s
525
526 -- Return (names of) all those in modsDone who are part of a cycle
527 -- as defined by theGraph.
528 findPartiallyCompletedCycles :: [ModuleName] -> [SCC ModSummary] -> [ModuleName]
529 findPartiallyCompletedCycles modsDone theGraph
530    = chew theGraph
531      where
532         chew [] = []
533         chew ((AcyclicSCC v):rest) = chew rest    -- acyclic?  not interesting.
534         chew ((CyclicSCC vs):rest)
535            = let names_in_this_cycle = nub (map name_of_summary vs)
536                  mods_in_this_cycle  
537                     = nub ([done | done <- modsDone, 
538                                    done `elem` names_in_this_cycle])
539                  chewed_rest = chew rest
540              in 
541              if   not (null mods_in_this_cycle) 
542                   && length mods_in_this_cycle < length names_in_this_cycle
543              then mods_in_this_cycle ++ chewed_rest
544              else chewed_rest
545
546
547 -- Add the given (LM-form) Linkables to the UI, overwriting previous
548 -- versions if they exist.
549 add_to_ui :: UnlinkedImage -> [Linkable] -> UnlinkedImage
550 add_to_ui ui lis
551    = filter (not_in lis) ui ++ lis
552      where
553         not_in :: [Linkable] -> Linkable -> Bool
554         not_in lis li
555            = all (\l -> linkableModName l /= mod) lis
556            where mod = linkableModName li
557                                   
558
559 data CmThreaded  -- stuff threaded through individual module compilations
560    = CmThreaded PersistentCompilerState HomeSymbolTable HomeIfaceTable
561
562
563 -- Compile multiple modules, stopping as soon as an error appears.
564 -- There better had not be any cyclic groups here -- we check for them.
565 upsweep_mods :: GhciMode
566              -> DynFlags
567              -> UnlinkedImage         -- valid linkables
568              -> (ModuleName -> [ModuleName])  -- to construct downward closures
569              -> CmThreaded            -- PCS & HST & HIT
570              -> [SCC ModSummary]      -- mods to do (the worklist)
571                                       -- ...... RETURNING ......
572              -> IO (Bool{-complete success?-},
573                     CmThreaded,
574                     [ModSummary],     -- mods which succeeded
575                     [Linkable])       -- new linkables
576
577 upsweep_mods ghci_mode dflags oldUI reachable_from threaded 
578      []
579    = return (True, threaded, [], [])
580
581 upsweep_mods ghci_mode dflags oldUI reachable_from threaded 
582      ((CyclicSCC ms):_)
583    = do hPutStrLn stderr ("Module imports form a cycle for modules:\n\t" ++
584                           unwords (map (moduleNameUserString.name_of_summary) ms))
585         return (False, threaded, [], [])
586
587 upsweep_mods ghci_mode dflags oldUI reachable_from threaded 
588      ((AcyclicSCC mod):mods)
589    = do --case threaded of
590         --   CmThreaded pcsz hstz hitz
591         --      -> putStrLn ("UPSWEEP_MOD: hit = " ++ show (map (moduleNameUserString.moduleName.mi_module) (eltsUFM hitz)))
592
593         (threaded1, maybe_linkable) 
594            <- upsweep_mod ghci_mode dflags oldUI threaded mod 
595                           (reachable_from (name_of_summary mod))
596         case maybe_linkable of
597            Just linkable 
598               -> -- No errors; do the rest
599                  do (restOK, threaded2, modOKs, linkables) 
600                        <- upsweep_mods ghci_mode dflags oldUI reachable_from 
601                                        threaded1 mods
602                     return (restOK, threaded2, mod:modOKs, linkable:linkables)
603            Nothing -- we got a compilation error; give up now
604               -> return (False, threaded1, [], [])
605
606
607 -- Compile a single module.  Always produce a Linkable for it if 
608 -- successful.  If no compilation happened, return the old Linkable.
609 upsweep_mod :: GhciMode 
610             -> DynFlags
611             -> UnlinkedImage
612             -> CmThreaded
613             -> ModSummary
614             -> [ModuleName]
615             -> IO (CmThreaded, Maybe Linkable)
616
617 upsweep_mod ghci_mode dflags oldUI threaded1 summary1 reachable_from_here
618    = do 
619         let mod_name = name_of_summary summary1
620         let verb = verbosity dflags
621
622         when (verb == 1) $
623            if (ghci_mode == Batch)
624                 then hPutStr stderr (progName ++ ": module " 
625                         ++ moduleNameUserString mod_name
626                         ++ ": ")
627                 else hPutStr stderr ("Compiling "
628                         ++ moduleNameUserString mod_name
629                         ++ " ... ")
630
631         let (CmThreaded pcs1 hst1 hit1) = threaded1
632         let old_iface = lookupUFM hit1 mod_name
633
634         let maybe_old_linkable = findModuleLinkable_maybe oldUI mod_name
635
636             source_unchanged = isJust maybe_old_linkable
637
638             (hst1_strictDC, hit1_strictDC)
639                = retainInTopLevelEnvs 
640                     (filter (/= (name_of_summary summary1)) reachable_from_here)
641                     (hst1,hit1)
642
643             old_linkable 
644                = unJust "upsweep_mod:old_linkable" maybe_old_linkable
645
646         compresult <- compile ghci_mode summary1 source_unchanged
647                          old_iface hst1_strictDC hit1_strictDC pcs1
648
649         case compresult of
650
651            -- Compilation "succeeded", but didn't return a new
652            -- linkable, meaning that compilation wasn't needed, and the
653            -- new details were manufactured from the old iface.
654            CompOK pcs2 new_details new_iface Nothing
655               -> do let hst2         = addToUFM hst1 mod_name new_details
656                         hit2         = addToUFM hit1 mod_name new_iface
657                         threaded2    = CmThreaded pcs2 hst2 hit2
658
659                     if ghci_mode == Interactive && verb >= 1 then
660                       -- if we're using an object file, tell the user
661                       case old_linkable of
662                         (LM _ _ objs@(DotO _:_))
663                            -> do hPutStrLn stderr (showSDoc (space <> 
664                                    parens (hsep (text "using": 
665                                         punctuate comma 
666                                           [ text o | DotO o <- objs ]))))
667                         _ -> return ()
668                       else
669                         return ()
670
671                     return (threaded2, Just old_linkable)
672
673            -- Compilation really did happen, and succeeded.  A new
674            -- details, iface and linkable are returned.
675            CompOK pcs2 new_details new_iface (Just new_linkable)
676               -> do let hst2      = addToUFM hst1 mod_name new_details
677                         hit2      = addToUFM hit1 mod_name new_iface
678                         threaded2 = CmThreaded pcs2 hst2 hit2
679
680                     return (threaded2, Just new_linkable)
681
682            -- Compilation failed.  compile may still have updated
683            -- the PCS, tho.
684            CompErrs pcs2
685               -> do let threaded2 = CmThreaded pcs2 hst1 hit1
686                     return (threaded2, Nothing)
687
688 -- Remove unwanted modules from the top level envs (HST, HIT, UI).
689 removeFromTopLevelEnvs :: [ModuleName]
690                        -> (HomeSymbolTable, HomeIfaceTable, UnlinkedImage)
691                        -> (HomeSymbolTable, HomeIfaceTable, UnlinkedImage)
692 removeFromTopLevelEnvs zap_these (hst, hit, ui)
693    = (delListFromUFM hst zap_these,
694       delListFromUFM hit zap_these,
695       filterModuleLinkables (`notElem` zap_these) ui
696      )
697
698 retainInTopLevelEnvs :: [ModuleName]
699                         -> (HomeSymbolTable, HomeIfaceTable)
700                         -> (HomeSymbolTable, HomeIfaceTable)
701 retainInTopLevelEnvs keep_these (hst, hit)
702    = (retainInUFM hst keep_these,
703       retainInUFM hit keep_these
704      )
705      where
706         retainInUFM :: Uniquable key => UniqFM elt -> [key] -> UniqFM elt
707         retainInUFM ufm keys_to_keep
708            = listToUFM (concatMap (maybeLookupUFM ufm) keys_to_keep)
709         maybeLookupUFM ufm u 
710            = case lookupUFM ufm u of Nothing -> []; Just val -> [(u, val)] 
711
712 -- Needed to clean up HIT and HST so that we don't get duplicates in inst env
713 downwards_closure_of_module :: [ModSummary] -> ModuleName -> [ModuleName]
714 downwards_closure_of_module summaries root
715    = let toEdge :: ModSummary -> (ModuleName,[ModuleName])
716          toEdge summ = (name_of_summary summ, ms_allimps summ)
717          res = simple_transitive_closure (map toEdge summaries) [root]             
718      in
719          --trace (showSDoc (text "DC of mod" <+> ppr root
720          --                 <+> text "=" <+> ppr res)) (
721          res
722          --)
723
724 -- Calculate transitive closures from a set of roots given an adjacency list
725 simple_transitive_closure :: Eq a => [(a,[a])] -> [a] -> [a]
726 simple_transitive_closure graph set 
727    = let set2      = nub (concatMap dsts set ++ set)
728          dsts node = fromMaybe [] (lookup node graph)
729      in
730          if   length set == length set2
731          then set
732          else simple_transitive_closure graph set2
733
734
735 -- Calculate SCCs of the module graph, with or without taking into
736 -- account source imports.
737 topological_sort :: Bool -> [ModSummary] -> [SCC ModSummary]
738 topological_sort include_source_imports summaries
739    = let 
740          toEdge :: ModSummary -> (ModSummary,ModuleName,[ModuleName])
741          toEdge summ
742              = (summ, name_of_summary summ, 
743                       (if include_source_imports 
744                        then ms_srcimps summ else []) ++ ms_imps summ)
745         
746          mash_edge :: (ModSummary,ModuleName,[ModuleName]) -> (ModSummary,Int,[Int])
747          mash_edge (summ, m, m_imports)
748             = case lookup m key_map of
749                  Nothing -> panic "reverse_topological_sort"
750                  Just mk -> (summ, mk, 
751                                 -- ignore imports not from the home package
752                                 catMaybes (map (flip lookup key_map) m_imports))
753
754          edges     = map toEdge summaries
755          key_map   = zip [nm | (s,nm,imps) <- edges] [1 ..] :: [(ModuleName,Int)]
756          scc_input = map mash_edge edges
757          sccs      = stronglyConnComp scc_input
758      in
759          sccs
760
761
762 -- Chase downwards from the specified root set, returning summaries
763 -- for all home modules encountered.  Only follow source-import
764 -- links.  Also returns a Bool to indicate whether any of the roots
765 -- are module Main.
766 downsweep :: [FilePath] -> [ModSummary] -> IO ([ModSummary], Bool)
767 downsweep rootNm old_summaries
768    = do rootSummaries <- mapM getRootSummary rootNm
769         let a_root_is_Main 
770                = any ((=="Main").moduleNameUserString.name_of_summary) 
771                      rootSummaries
772         all_summaries
773            <- loop (concat (map ms_imps rootSummaries))
774                 (filter (isHomeModule.ms_mod) rootSummaries)
775         return (all_summaries, a_root_is_Main)
776      where
777         getRootSummary :: FilePath -> IO ModSummary
778         getRootSummary file
779            | haskellish_file file
780            = do exists <- doesFileExist file
781                 if exists then summariseFile file else do
782                 throwDyn (OtherError ("can't find file `" ++ file ++ "'"))      
783            | otherwise
784            = do exists <- doesFileExist hs_file
785                 if exists then summariseFile hs_file else do
786                 exists <- doesFileExist lhs_file
787                 if exists then summariseFile lhs_file else do
788                 getSummary (mkModuleName file)
789            where 
790                  hs_file = file ++ ".hs"
791                  lhs_file = file ++ ".lhs"
792
793         getSummary :: ModuleName -> IO ModSummary
794         getSummary nm
795            = do found <- findModule nm
796                 case found of
797                    Just (mod, location) -> do
798                         let old_summary = findModInSummaries old_summaries mod
799                         new_summary <- summarise mod location old_summary
800                         case new_summary of
801                            Nothing -> return (fromJust old_summary)
802                            Just s  -> return s
803
804                    Nothing -> throwDyn (OtherError 
805                                    ("can't find module `" 
806                                      ++ showSDoc (ppr nm) ++ "'"))
807                                  
808         -- loop invariant: home_summaries doesn't contain package modules
809         loop :: [ModuleName] -> [ModSummary] -> IO [ModSummary]
810         loop [] home_summaries = return home_summaries
811         loop imps home_summaries
812            = do -- all modules currently in homeSummaries
813                 let all_home = map (moduleName.ms_mod) home_summaries
814
815                 -- imports for modules we don't already have
816                 let needed_imps = nub (filter (`notElem` all_home) imps)
817
818                 -- summarise them
819                 needed_summaries <- mapM getSummary needed_imps
820
821                 -- get just the "home" modules
822                 let new_home_summaries
823                        = filter (isHomeModule.ms_mod) needed_summaries
824
825                 -- loop, checking the new imports
826                 let new_imps = concat (map ms_imps new_home_summaries)
827                 loop new_imps (new_home_summaries ++ home_summaries)
828
829 -----------------------------------------------------------------------------
830 -- Summarising modules
831
832 -- We have two types of summarisation:
833 --
834 --    * Summarise a file.  This is used for the root module passed to
835 --      cmLoadModule.  The file is read, and used to determine the root
836 --      module name.  The module name may differ from the filename.
837 --
838 --    * Summarise a module.  We are given a module name, and must provide
839 --      a summary.  The finder is used to locate the file in which the module
840 --      resides.
841
842 summariseFile :: FilePath -> IO ModSummary
843 summariseFile file
844    = do hspp_fn <- preprocess file
845         modsrc <- readFile hspp_fn
846
847         let (srcimps,imps,mod_name) = getImports modsrc
848             (path, basename, ext) = splitFilename3 file
849
850         Just (mod, location)
851            <- mkHomeModuleLocn mod_name (path ++ '/':basename) file
852            
853         maybe_src_timestamp
854            <- case ml_hs_file location of 
855                  Nothing     -> return Nothing
856                  Just src_fn -> maybe_getModificationTime src_fn
857
858         return (ModSummary mod
859                            location{ml_hspp_file=Just hspp_fn}
860                            srcimps imps
861                            maybe_src_timestamp)
862
863 -- Summarise a module, and pick up source and timestamp.
864 summarise :: Module -> ModuleLocation -> Maybe ModSummary 
865     -> IO (Maybe ModSummary)
866 summarise mod location old_summary
867    | isHomeModule mod
868    = do let hs_fn = unJust "summarise" (ml_hs_file location)
869
870         maybe_src_timestamp
871            <- case ml_hs_file location of 
872                  Nothing     -> return Nothing
873                  Just src_fn -> maybe_getModificationTime src_fn
874
875         -- return the cached summary if the source didn't change
876         case old_summary of {
877            Just s | ms_hs_date s == maybe_src_timestamp -> return Nothing;
878            _ -> do
879
880         hspp_fn <- preprocess hs_fn
881         modsrc <- readFile hspp_fn
882         let (srcimps,imps,mod_name) = getImports modsrc
883
884         maybe_src_timestamp
885            <- case ml_hs_file location of 
886                  Nothing     -> return Nothing
887                  Just src_fn -> maybe_getModificationTime src_fn
888
889         when (mod_name /= moduleName mod) $
890                 throwDyn (OtherError 
891                    (showSDoc (text "file name does not match module name: "
892                               <+> ppr (moduleName mod) <+> text "vs" 
893                               <+> ppr mod_name)))
894
895         return (Just (ModSummary mod location{ml_hspp_file=Just hspp_fn} 
896                                  srcimps imps
897                                  maybe_src_timestamp))
898         }
899
900    | otherwise
901    = return (Just (ModSummary mod location [] [] Nothing))
902
903 maybe_getModificationTime :: FilePath -> IO (Maybe ClockTime)
904 maybe_getModificationTime fn
905    = (do time <- getModificationTime fn
906          return (Just time)) 
907      `catch`
908      (\err -> return Nothing)
909 \end{code}