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