[project @ 2001-02-28 17:57:52 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
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 mg2unsorted_names [] mg2_with_srcimps
392
393         let stable_summaries
394                = concatMap (findInSummaries mg2unsorted) stable_mods
395
396             stable_linkables
397                = filter (\m -> linkableModName m `elem` stable_mods) 
398                     valid_linkables
399
400         when (verb >= 2) $
401            putStrLn (showSDoc (text "Stable modules:" 
402                                <+> sep (map (text.moduleNameUserString) stable_mods)))
403
404         -- unload any modules which aren't going to be re-linked this
405         -- time around.
406         pls2 <- unload ghci_mode dflags stable_linkables pls1
407
408         -- We could at this point detect cycles which aren't broken by
409         -- a source-import, and complain immediately, but it seems better
410         -- to let upsweep_mods do this, so at least some useful work gets
411         -- done before the upsweep is abandoned.
412         let upsweep_these
413                = filter (\scc -> any (`notElem` stable_mods) 
414                                      (map name_of_summary (flattenSCC scc)))
415                         mg2
416
417         --hPutStrLn stderr "after tsort:\n"
418         --hPutStrLn stderr (showSDoc (vcat (map ppr mg2)))
419
420         -- Because we don't take into account source imports when doing
421         -- the topological sort, there shouldn't be any cycles in mg2.
422         -- If there is, we complain and give up -- the user needs to
423         -- break the cycle using a boot file.
424
425         -- Now do the upsweep, calling compile for each module in
426         -- turn.  Final result is version 3 of everything.
427
428         let threaded2 = CmThreaded pcs1 hst1 hit1
429
430         (upsweep_complete_success, threaded3, modsUpswept, newLis)
431            <- upsweep_mods ghci_mode dflags valid_linkables reachable_from 
432                            threaded2 upsweep_these
433
434         let ui3 = add_to_ui valid_linkables newLis
435         let (CmThreaded pcs3 hst3 hit3) = threaded3
436
437         -- At this point, modsUpswept and newLis should have the same
438         -- length, so there is one new (or old) linkable for each 
439         -- mod which was processed (passed to compile).
440
441         -- Make modsDone be the summaries for each home module now
442         -- available; this should equal the domains of hst3 and hit3.
443         -- (NOT STRICTLY TRUE if an interactive session was started
444         --  with some object on disk ???)
445         -- Get in in a roughly top .. bottom order (hence reverse).
446
447         let modsDone = reverse modsUpswept ++ stable_summaries
448
449         -- Try and do linking in some form, depending on whether the
450         -- upsweep was completely or only partially successful.
451
452         if upsweep_complete_success
453
454          then 
455            -- Easy; just relink it all.
456            do when (verb >= 2) $ 
457                  hPutStrLn stderr "Upsweep completely successful."
458
459               -- clean up after ourselves
460               cleanTempFilesExcept verb (ppFilesFromSummaries modsDone)
461
462               -- link everything together
463               linkresult <- link ghci_mode dflags a_root_is_Main ui3 pls2
464
465               cmLoadFinish True linkresult 
466                         hst3 hit3 ui3 modsDone ghci_mode pcs3
467
468          else 
469            -- Tricky.  We need to back out the effects of compiling any
470            -- half-done cycles, both so as to clean up the top level envs
471            -- and to avoid telling the interactive linker to link them.
472            do when (verb >= 2) $
473                 hPutStrLn stderr "Upsweep partially successful."
474
475               let modsDone_names
476                      = map name_of_summary modsDone
477               let mods_to_zap_names 
478                      = findPartiallyCompletedCycles modsDone_names 
479                           mg2_with_srcimps
480               let (hst4, hit4, ui4)
481                      = removeFromTopLevelEnvs mods_to_zap_names (hst3,hit3,ui3)
482
483               let mods_to_keep
484                      = filter ((`notElem` mods_to_zap_names).name_of_summary) 
485                           modsDone
486
487               -- clean up after ourselves
488               cleanTempFilesExcept verb (ppFilesFromSummaries mods_to_keep)
489
490               -- link everything together
491               linkresult <- link ghci_mode dflags False ui4 pls2
492
493               cmLoadFinish False linkresult 
494                     hst4 hit4 ui4 mods_to_keep ghci_mode pcs3
495
496
497 -- Finish up after a cmLoad.
498 --
499 -- Empty the interactive context and set the module context to the topmost
500 -- newly loaded module, or the Prelude if none were loaded.
501 cmLoadFinish ok linkresult hst hit ui mods ghci_mode pcs
502   = do case linkresult of {
503           LinkErrs _ _ -> panic "cmLoadModule: link failed (2)";
504           LinkOK pls   -> do
505
506        def_mod <- readIORef defaultCurrentModule
507        let current_mod = case mods of 
508                                 []    -> def_mod
509                                 (x:_) -> ms_mod x
510
511            new_ic = emptyInteractiveContext current_mod
512
513            new_cmstate = CmState{ hst=hst, hit=hit, 
514                                   ui=ui, mg=mods,
515                                   gmode=ghci_mode, pcs=pcs, 
516                                   pls=pls,
517                                   ic = new_ic }
518            mods_loaded = map (moduleNameUserString.name_of_summary) mods
519
520        return (new_cmstate, ok, mods_loaded)
521     }
522
523 ppFilesFromSummaries summaries
524   = [ fn | Just fn <- map (ml_hspp_file . ms_location) summaries ]
525
526 -----------------------------------------------------------------------------
527 -- getValidLinkables
528
529 -- For each module (or SCC of modules), we take:
530 --
531 --      - an on-disk linkable, if this is the first time around and one
532 --        is available.
533 --
534 --      - the old linkable, otherwise (and if one is available).
535 --
536 -- and we throw away the linkable if it is older than the source
537 -- file.  We ignore the on-disk linkables unless all of the dependents
538 -- of this SCC also have on-disk linkables.
539 --
540 -- If a module has a valid linkable, then it may be STABLE (see below),
541 -- and it is classified as SOURCE UNCHANGED for the purposes of calling
542 -- compile.
543 --
544 -- ToDo: this pass could be merged with the preUpsweep.
545
546 getValidLinkables
547         :: [Linkable]           -- old linkables
548         -> [ModuleName]         -- all home modules
549         -> [SCC ModSummary]     -- all modules in the program, dependency order
550         -> IO [Linkable]        -- still-valid linkables 
551
552 getValidLinkables old_linkables all_home_mods module_graph
553   = foldM (getValidLinkablesSCC old_linkables all_home_mods) [] module_graph
554
555 getValidLinkablesSCC old_linkables all_home_mods new_linkables scc0
556    = let 
557           scc             = flattenSCC scc0
558           scc_names       = map name_of_summary scc
559           home_module m   = m `elem` all_home_mods && m `notElem` scc_names
560           scc_allhomeimps = nub (filter home_module (concatMap ms_allimps scc))
561
562           has_object m = case findModuleLinkable_maybe new_linkables m of
563                             Nothing -> False
564                             Just l  -> isObjectLinkable l
565
566           objects_allowed = all has_object scc_allhomeimps
567      in do
568
569      these_linkables 
570         <- foldM (getValidLinkable old_linkables objects_allowed) [] scc
571
572         -- since an scc can contain only all objects or no objects at all,
573         -- we have to check whether we got all objects or not, and re-do
574         -- the linkable check if not.
575      adjusted_linkables 
576         <- if objects_allowed && not (all isObjectLinkable these_linkables)
577               then foldM (getValidLinkable old_linkables False) [] scc
578               else return these_linkables
579
580      return (adjusted_linkables ++ new_linkables)
581
582
583 getValidLinkable :: [Linkable] -> Bool -> [Linkable] -> ModSummary 
584         -> IO [Linkable]
585 getValidLinkable old_linkables objects_allowed new_linkables summary 
586   = do let mod_name = name_of_summary summary
587
588        -- we only look for objects on disk the first time around;
589        -- if the user compiles a module on the side during a GHCi session,
590        -- it won't be picked up until the next ":load".  This is what the
591        -- "null old_linkables" test below is.
592        maybe_disk_linkable
593           <- if (not objects_allowed)
594                 then return Nothing
595                 else case ml_obj_file (ms_location summary) of
596                         Just obj_fn -> maybe_getFileLinkable mod_name obj_fn
597                         Nothing -> return Nothing
598
599        let old_linkable = findModuleLinkable_maybe old_linkables mod_name
600            maybe_old_linkable =
601                 case old_linkable of
602                     Just l | not (isObjectLinkable l) || stillThere l 
603                                 -> old_linkable
604                                 -- ToDo: emit a warning if not (stillThere l)
605                            | otherwise
606                                 -> Nothing
607
608            -- make sure that if we had an old disk linkable around, that it's
609            -- still there on the disk (in case we need to re-link it).
610            stillThere l = 
611                 case maybe_disk_linkable of
612                    Nothing    -> False
613                    Just l_disk -> linkableTime l == linkableTime l_disk
614
615            linkable | null old_linkables = maybeToList maybe_disk_linkable
616                     | otherwise          = maybeToList maybe_old_linkable
617
618            -- only linkables newer than the source code are valid
619            maybe_src_date = ms_hs_date summary
620
621            valid_linkable
622               = case maybe_src_date of
623                   Nothing -> panic "valid_linkable_list"
624                   Just src_date 
625                      -> filter (\l -> linkableTime l > src_date) linkable
626
627        return (valid_linkable ++ new_linkables)
628
629
630
631 maybe_getFileLinkable :: ModuleName -> FilePath -> IO (Maybe Linkable)
632 maybe_getFileLinkable mod_name obj_fn
633    = do obj_exist <- doesFileExist obj_fn
634         if not obj_exist 
635          then return Nothing 
636          else 
637          do let stub_fn = case splitFilename3 obj_fn of
638                              (dir, base, ext) -> dir ++ "/" ++ base ++ ".stub_o"
639             stub_exist <- doesFileExist stub_fn
640             obj_time <- getModificationTime obj_fn
641             if stub_exist
642              then return (Just (LM obj_time mod_name [DotO obj_fn, DotO stub_fn]))
643              else return (Just (LM obj_time mod_name [DotO obj_fn]))
644
645
646 -----------------------------------------------------------------------------
647 -- Do a pre-upsweep without use of "compile", to establish a 
648 -- (downward-closed) set of stable modules for which we won't call compile.
649
650 preUpsweep :: [Linkable]        -- new valid linkables
651            -> [ModuleName]      -- names of all mods encountered in downsweep
652            -> [ModuleName]      -- accumulating stable modules
653            -> [SCC ModSummary]  -- scc-ified mod graph, including src imps
654            -> IO [ModuleName]   -- stable modules
655
656 preUpsweep valid_lis all_home_mods stable []  = return stable
657 preUpsweep valid_lis all_home_mods stable (scc0:sccs)
658    = do let scc = flattenSCC scc0
659             scc_allhomeimps :: [ModuleName]
660             scc_allhomeimps 
661                = nub (filter (`elem` all_home_mods) (concatMap ms_allimps scc))
662             all_imports_in_scc_or_stable
663                = all in_stable_or_scc scc_allhomeimps
664             scc_names
665                = map name_of_summary scc
666             in_stable_or_scc m
667                = m `elem` scc_names || m `elem` stable
668
669             -- now we check for valid linkables: each module in the SCC must 
670             -- have a valid linkable (see getValidLinkables above).
671             has_valid_linkable new_summary
672               = isJust (findModuleLinkable_maybe valid_lis modname)
673                where modname = name_of_summary new_summary
674
675             scc_is_stable = all_imports_in_scc_or_stable
676                           && all has_valid_linkable scc
677
678         if scc_is_stable
679          then preUpsweep valid_lis all_home_mods (scc_names++stable) sccs
680          else preUpsweep valid_lis all_home_mods stable sccs
681
682    where 
683
684
685 -- Helper for preUpsweep.  Assuming that new_summary's imports are all
686 -- stable (in the sense of preUpsweep), determine if new_summary is itself
687 -- stable, and, if so, in batch mode, return its linkable.
688 findInSummaries :: [ModSummary] -> ModuleName -> [ModSummary]
689 findInSummaries old_summaries mod_name
690    = [s | s <- old_summaries, name_of_summary s == mod_name]
691
692 findModInSummaries :: [ModSummary] -> Module -> Maybe ModSummary
693 findModInSummaries old_summaries mod
694    = case [s | s <- old_summaries, ms_mod s == mod] of
695          [] -> Nothing
696          (s:_) -> Just s
697
698 -- Return (names of) all those in modsDone who are part of a cycle
699 -- as defined by theGraph.
700 findPartiallyCompletedCycles :: [ModuleName] -> [SCC ModSummary] -> [ModuleName]
701 findPartiallyCompletedCycles modsDone theGraph
702    = chew theGraph
703      where
704         chew [] = []
705         chew ((AcyclicSCC v):rest) = chew rest    -- acyclic?  not interesting.
706         chew ((CyclicSCC vs):rest)
707            = let names_in_this_cycle = nub (map name_of_summary vs)
708                  mods_in_this_cycle  
709                     = nub ([done | done <- modsDone, 
710                                    done `elem` names_in_this_cycle])
711                  chewed_rest = chew rest
712              in 
713              if   not (null mods_in_this_cycle) 
714                   && length mods_in_this_cycle < length names_in_this_cycle
715              then mods_in_this_cycle ++ chewed_rest
716              else chewed_rest
717
718
719 -- Add the given (LM-form) Linkables to the UI, overwriting previous
720 -- versions if they exist.
721 add_to_ui :: UnlinkedImage -> [Linkable] -> UnlinkedImage
722 add_to_ui ui lis
723    = filter (not_in lis) ui ++ lis
724      where
725         not_in :: [Linkable] -> Linkable -> Bool
726         not_in lis li
727            = all (\l -> linkableModName l /= mod) lis
728            where mod = linkableModName li
729                                   
730
731 data CmThreaded  -- stuff threaded through individual module compilations
732    = CmThreaded PersistentCompilerState HomeSymbolTable HomeIfaceTable
733
734
735 -- Compile multiple modules, stopping as soon as an error appears.
736 -- There better had not be any cyclic groups here -- we check for them.
737 upsweep_mods :: GhciMode
738              -> DynFlags
739              -> UnlinkedImage         -- valid linkables
740              -> (ModuleName -> [ModuleName])  -- to construct downward closures
741              -> CmThreaded            -- PCS & HST & HIT
742              -> [SCC ModSummary]      -- mods to do (the worklist)
743                                       -- ...... RETURNING ......
744              -> IO (Bool{-complete success?-},
745                     CmThreaded,
746                     [ModSummary],     -- mods which succeeded
747                     [Linkable])       -- new linkables
748
749 upsweep_mods ghci_mode dflags oldUI reachable_from threaded 
750      []
751    = return (True, threaded, [], [])
752
753 upsweep_mods ghci_mode dflags oldUI reachable_from threaded 
754      ((CyclicSCC ms):_)
755    = do hPutStrLn stderr ("Module imports form a cycle for modules:\n\t" ++
756                           unwords (map (moduleNameUserString.name_of_summary) ms))
757         return (False, threaded, [], [])
758
759 upsweep_mods ghci_mode dflags oldUI reachable_from threaded 
760      ((AcyclicSCC mod):mods)
761    = do --case threaded of
762         --   CmThreaded pcsz hstz hitz
763         --      -> putStrLn ("UPSWEEP_MOD: hit = " ++ show (map (moduleNameUserString.moduleName.mi_module) (eltsUFM hitz)))
764
765         (threaded1, maybe_linkable) 
766            <- upsweep_mod ghci_mode dflags oldUI threaded mod 
767                           (reachable_from (name_of_summary mod))
768         case maybe_linkable of
769            Just linkable 
770               -> -- No errors; do the rest
771                  do (restOK, threaded2, modOKs, linkables) 
772                        <- upsweep_mods ghci_mode dflags oldUI reachable_from 
773                                        threaded1 mods
774                     return (restOK, threaded2, mod:modOKs, linkable:linkables)
775            Nothing -- we got a compilation error; give up now
776               -> return (False, threaded1, [], [])
777
778
779 -- Compile a single module.  Always produce a Linkable for it if 
780 -- successful.  If no compilation happened, return the old Linkable.
781 upsweep_mod :: GhciMode 
782             -> DynFlags
783             -> UnlinkedImage
784             -> CmThreaded
785             -> ModSummary
786             -> [ModuleName]
787             -> IO (CmThreaded, Maybe Linkable)
788
789 upsweep_mod ghci_mode dflags oldUI threaded1 summary1 reachable_from_here
790    = do 
791         let mod_name = name_of_summary summary1
792         let verb = verbosity dflags
793
794         let (CmThreaded pcs1 hst1 hit1) = threaded1
795         let old_iface = lookupUFM hit1 mod_name
796
797         let maybe_old_linkable = findModuleLinkable_maybe oldUI mod_name
798
799             source_unchanged = isJust maybe_old_linkable
800
801             (hst1_strictDC, hit1_strictDC)
802                = retainInTopLevelEnvs 
803                     (filter (/= (name_of_summary summary1)) reachable_from_here)
804                     (hst1,hit1)
805
806             old_linkable 
807                = unJust "upsweep_mod:old_linkable" maybe_old_linkable
808
809         compresult <- compile ghci_mode summary1 source_unchanged
810                          old_iface hst1_strictDC hit1_strictDC pcs1
811
812         case compresult of
813
814            -- Compilation "succeeded", but didn't return a new
815            -- linkable, meaning that compilation wasn't needed, and the
816            -- new details were manufactured from the old iface.
817            CompOK pcs2 new_details new_iface Nothing
818               -> do let hst2         = addToUFM hst1 mod_name new_details
819                         hit2         = addToUFM hit1 mod_name new_iface
820                         threaded2    = CmThreaded pcs2 hst2 hit2
821
822                     if ghci_mode == Interactive && verb >= 1 then
823                       -- if we're using an object file, tell the user
824                       case old_linkable of
825                         (LM _ _ objs@(DotO _:_))
826                            -> do hPutStrLn stderr (showSDoc (space <> 
827                                    parens (hsep (text "using": 
828                                         punctuate comma 
829                                           [ text o | DotO o <- objs ]))))
830                         _ -> return ()
831                       else
832                         return ()
833
834                     return (threaded2, Just old_linkable)
835
836            -- Compilation really did happen, and succeeded.  A new
837            -- details, iface and linkable are returned.
838            CompOK pcs2 new_details new_iface (Just new_linkable)
839               -> do let hst2      = addToUFM hst1 mod_name new_details
840                         hit2      = addToUFM hit1 mod_name new_iface
841                         threaded2 = CmThreaded pcs2 hst2 hit2
842
843                     return (threaded2, Just new_linkable)
844
845            -- Compilation failed.  compile may still have updated
846            -- the PCS, tho.
847            CompErrs pcs2
848               -> do let threaded2 = CmThreaded pcs2 hst1 hit1
849                     return (threaded2, Nothing)
850
851 -- Remove unwanted modules from the top level envs (HST, HIT, UI).
852 removeFromTopLevelEnvs :: [ModuleName]
853                        -> (HomeSymbolTable, HomeIfaceTable, UnlinkedImage)
854                        -> (HomeSymbolTable, HomeIfaceTable, UnlinkedImage)
855 removeFromTopLevelEnvs zap_these (hst, hit, ui)
856    = (delListFromUFM hst zap_these,
857       delListFromUFM hit zap_these,
858       filterModuleLinkables (`notElem` zap_these) ui
859      )
860
861 retainInTopLevelEnvs :: [ModuleName]
862                         -> (HomeSymbolTable, HomeIfaceTable)
863                         -> (HomeSymbolTable, HomeIfaceTable)
864 retainInTopLevelEnvs keep_these (hst, hit)
865    = (retainInUFM hst keep_these,
866       retainInUFM hit keep_these
867      )
868      where
869         retainInUFM :: Uniquable key => UniqFM elt -> [key] -> UniqFM elt
870         retainInUFM ufm keys_to_keep
871            = listToUFM (concatMap (maybeLookupUFM ufm) keys_to_keep)
872         maybeLookupUFM ufm u 
873            = case lookupUFM ufm u of Nothing -> []; Just val -> [(u, val)] 
874
875 -- Needed to clean up HIT and HST so that we don't get duplicates in inst env
876 downwards_closure_of_module :: [ModSummary] -> ModuleName -> [ModuleName]
877 downwards_closure_of_module summaries root
878    = let toEdge :: ModSummary -> (ModuleName,[ModuleName])
879          toEdge summ = (name_of_summary summ, ms_allimps summ)
880          res = simple_transitive_closure (map toEdge summaries) [root]             
881      in
882          --trace (showSDoc (text "DC of mod" <+> ppr root
883          --                 <+> text "=" <+> ppr res)) (
884          res
885          --)
886
887 -- Calculate transitive closures from a set of roots given an adjacency list
888 simple_transitive_closure :: Eq a => [(a,[a])] -> [a] -> [a]
889 simple_transitive_closure graph set 
890    = let set2      = nub (concatMap dsts set ++ set)
891          dsts node = fromMaybe [] (lookup node graph)
892      in
893          if   length set == length set2
894          then set
895          else simple_transitive_closure graph set2
896
897
898 -- Calculate SCCs of the module graph, with or without taking into
899 -- account source imports.
900 topological_sort :: Bool -> [ModSummary] -> [SCC ModSummary]
901 topological_sort include_source_imports summaries
902    = let 
903          toEdge :: ModSummary -> (ModSummary,ModuleName,[ModuleName])
904          toEdge summ
905              = (summ, name_of_summary summ, 
906                       (if include_source_imports 
907                        then ms_srcimps summ else []) ++ ms_imps summ)
908         
909          mash_edge :: (ModSummary,ModuleName,[ModuleName]) -> (ModSummary,Int,[Int])
910          mash_edge (summ, m, m_imports)
911             = case lookup m key_map of
912                  Nothing -> panic "reverse_topological_sort"
913                  Just mk -> (summ, mk, 
914                                 -- ignore imports not from the home package
915                                 catMaybes (map (flip lookup key_map) m_imports))
916
917          edges     = map toEdge summaries
918          key_map   = zip [nm | (s,nm,imps) <- edges] [1 ..] :: [(ModuleName,Int)]
919          scc_input = map mash_edge edges
920          sccs      = stronglyConnComp scc_input
921      in
922          sccs
923
924
925 -- Chase downwards from the specified root set, returning summaries
926 -- for all home modules encountered.  Only follow source-import
927 -- links.  Also returns a Bool to indicate whether any of the roots
928 -- are module Main.
929 downsweep :: [FilePath] -> [ModSummary] -> IO ([ModSummary], Bool)
930 downsweep rootNm old_summaries
931    = do rootSummaries <- mapM getRootSummary rootNm
932         let a_root_is_Main 
933                = any ((=="Main").moduleNameUserString.name_of_summary) 
934                      rootSummaries
935         all_summaries
936            <- loop (concat (map ms_imps rootSummaries))
937                 (filter (isHomeModule.ms_mod) rootSummaries)
938         return (all_summaries, a_root_is_Main)
939      where
940         getRootSummary :: FilePath -> IO ModSummary
941         getRootSummary file
942            | haskellish_file file
943            = do exists <- doesFileExist file
944                 if exists then summariseFile file else do
945                 throwDyn (OtherError ("can't find file `" ++ file ++ "'"))      
946            | otherwise
947            = do exists <- doesFileExist hs_file
948                 if exists then summariseFile hs_file else do
949                 exists <- doesFileExist lhs_file
950                 if exists then summariseFile lhs_file else do
951                 getSummary (mkModuleName file)
952            where 
953                  hs_file = file ++ ".hs"
954                  lhs_file = file ++ ".lhs"
955
956         getSummary :: ModuleName -> IO ModSummary
957         getSummary nm
958            = do found <- findModule nm
959                 case found of
960                    Just (mod, location) -> do
961                         let old_summary = findModInSummaries old_summaries mod
962                         new_summary <- summarise mod location old_summary
963                         case new_summary of
964                            Nothing -> return (fromJust old_summary)
965                            Just s  -> return s
966
967                    Nothing -> throwDyn (OtherError 
968                                    ("can't find module `" 
969                                      ++ showSDoc (ppr nm) ++ "'"))
970                                  
971         -- loop invariant: home_summaries doesn't contain package modules
972         loop :: [ModuleName] -> [ModSummary] -> IO [ModSummary]
973         loop [] home_summaries = return home_summaries
974         loop imps home_summaries
975            = do -- all modules currently in homeSummaries
976                 let all_home = map (moduleName.ms_mod) home_summaries
977
978                 -- imports for modules we don't already have
979                 let needed_imps = nub (filter (`notElem` all_home) imps)
980
981                 -- summarise them
982                 needed_summaries <- mapM getSummary needed_imps
983
984                 -- get just the "home" modules
985                 let new_home_summaries
986                        = filter (isHomeModule.ms_mod) needed_summaries
987
988                 -- loop, checking the new imports
989                 let new_imps = concat (map ms_imps new_home_summaries)
990                 loop new_imps (new_home_summaries ++ home_summaries)
991
992 -----------------------------------------------------------------------------
993 -- Summarising modules
994
995 -- We have two types of summarisation:
996 --
997 --    * Summarise a file.  This is used for the root module passed to
998 --      cmLoadModule.  The file is read, and used to determine the root
999 --      module name.  The module name may differ from the filename.
1000 --
1001 --    * Summarise a module.  We are given a module name, and must provide
1002 --      a summary.  The finder is used to locate the file in which the module
1003 --      resides.
1004
1005 summariseFile :: FilePath -> IO ModSummary
1006 summariseFile file
1007    = do hspp_fn <- preprocess file
1008         modsrc <- readFile hspp_fn
1009
1010         let (srcimps,imps,mod_name) = getImports modsrc
1011             (path, basename, ext) = splitFilename3 file
1012
1013         Just (mod, location)
1014            <- mkHomeModuleLocn mod_name (path ++ '/':basename) file
1015            
1016         maybe_src_timestamp
1017            <- case ml_hs_file location of 
1018                  Nothing     -> return Nothing
1019                  Just src_fn -> maybe_getModificationTime src_fn
1020
1021         return (ModSummary mod
1022                            location{ml_hspp_file=Just hspp_fn}
1023                            srcimps imps
1024                            maybe_src_timestamp)
1025
1026 -- Summarise a module, and pick up source and timestamp.
1027 summarise :: Module -> ModuleLocation -> Maybe ModSummary 
1028     -> IO (Maybe ModSummary)
1029 summarise mod location old_summary
1030    | isHomeModule mod
1031    = do let hs_fn = unJust "summarise" (ml_hs_file location)
1032
1033         maybe_src_timestamp
1034            <- case ml_hs_file location of 
1035                  Nothing     -> return Nothing
1036                  Just src_fn -> maybe_getModificationTime src_fn
1037
1038         -- return the cached summary if the source didn't change
1039         case old_summary of {
1040            Just s | ms_hs_date s == maybe_src_timestamp -> return Nothing;
1041            _ -> do
1042
1043         hspp_fn <- preprocess hs_fn
1044         modsrc <- readFile hspp_fn
1045         let (srcimps,imps,mod_name) = getImports modsrc
1046
1047         maybe_src_timestamp
1048            <- case ml_hs_file location of 
1049                  Nothing     -> return Nothing
1050                  Just src_fn -> maybe_getModificationTime src_fn
1051
1052         when (mod_name /= moduleName mod) $
1053                 throwDyn (OtherError 
1054                    (showSDoc (text "file name does not match module name: "
1055                               <+> ppr (moduleName mod) <+> text "vs" 
1056                               <+> ppr mod_name)))
1057
1058         return (Just (ModSummary mod location{ml_hspp_file=Just hspp_fn} 
1059                                  srcimps imps
1060                                  maybe_src_timestamp))
1061         }
1062
1063    | otherwise
1064    = return (Just (ModSummary mod location [] [] Nothing))
1065
1066 maybe_getModificationTime :: FilePath -> IO (Maybe ClockTime)
1067 maybe_getModificationTime fn
1068    = (do time <- getModificationTime fn
1069          return (Just time)) 
1070      `catch`
1071      (\err -> return Nothing)
1072 \end{code}