Split main/GHC into GHC and GhcMake
[ghc-hetmet.git] / compiler / main / GhcMake.hs
1 -- -----------------------------------------------------------------------------\r
2 --\r
3 -- (c) The University of Glasgow, 2005\r
4 --\r
5 --       This module deals with --make\r
6 -- -----------------------------------------------------------------------------\r
7 \r
8 module GhcMake( \r
9   depanal, \r
10   load, LoadHowMuch(..),\r
11 \r
12   topSortModuleGraph, \r
13 \r
14   noModError, cyclicModuleErr\r
15   ) where\r
16 \r
17 #include "HsVersions.h"\r
18 \r
19 #ifdef GHCI\r
20 import qualified Linker         ( unload )\r
21 #endif\r
22 \r
23 import DriverPipeline\r
24 import DriverPhases\r
25 import GhcMonad\r
26 import Module\r
27 import HscTypes\r
28 import ErrUtils\r
29 import DynFlags\r
30 import HsSyn hiding ((<.>))\r
31 import Finder\r
32 import HeaderInfo\r
33 import TcIface          ( typecheckIface )\r
34 import TcRnMonad        ( initIfaceCheck )\r
35 import RdrName          ( RdrName )\r
36 \r
37 import Exception        ( evaluate, tryIO )\r
38 import Panic\r
39 import SysTools\r
40 import BasicTypes\r
41 import SrcLoc\r
42 import Util\r
43 import Digraph\r
44 import Bag              ( listToBag )\r
45 import Maybes           ( expectJust, mapCatMaybes )\r
46 import StringBuffer\r
47 import FastString\r
48 import Outputable\r
49 import UniqFM\r
50 \r
51 import qualified Data.Map as Map\r
52 import qualified FiniteMap as Map( insertListWith)\r
53 \r
54 import System.Directory ( doesFileExist, getModificationTime )\r
55 import System.IO        ( fixIO )\r
56 import System.IO.Error  ( isDoesNotExistError )\r
57 import System.Time      ( ClockTime )\r
58 import System.FilePath\r
59 import Control.Monad\r
60 import Data.Maybe\r
61 import Data.List\r
62 import qualified Data.List as List\r
63 \r
64 -- -----------------------------------------------------------------------------\r
65 -- Loading the program\r
66 \r
67 -- | Perform a dependency analysis starting from the current targets\r
68 -- and update the session with the new module graph.\r
69 --\r
70 -- Dependency analysis entails parsing the @import@ directives and may\r
71 -- therefore require running certain preprocessors.\r
72 --\r
73 -- Note that each 'ModSummary' in the module graph caches its 'DynFlags'.\r
74 -- These 'DynFlags' are determined by the /current/ session 'DynFlags' and the\r
75 -- @OPTIONS@ and @LANGUAGE@ pragmas of the parsed module.  Thus if you want to\r
76 -- changes to the 'DynFlags' to take effect you need to call this function\r
77 -- again.\r
78 --\r
79 depanal :: GhcMonad m =>\r
80            [ModuleName]  -- ^ excluded modules\r
81         -> Bool          -- ^ allow duplicate roots\r
82         -> m ModuleGraph\r
83 depanal excluded_mods allow_dup_roots = do\r
84   hsc_env <- getSession\r
85   let\r
86          dflags  = hsc_dflags hsc_env\r
87          targets = hsc_targets hsc_env\r
88          old_graph = hsc_mod_graph hsc_env\r
89         \r
90   liftIO $ showPass dflags "Chasing dependencies"\r
91   liftIO $ debugTraceMsg dflags 2 (hcat [\r
92              text "Chasing modules from: ",\r
93              hcat (punctuate comma (map pprTarget targets))])\r
94 \r
95   mod_graph <- liftIO $ downsweep hsc_env old_graph excluded_mods allow_dup_roots\r
96   modifySession $ \_ -> hsc_env { hsc_mod_graph = mod_graph }\r
97   return mod_graph\r
98 \r
99 -- | Describes which modules of the module graph need to be loaded.\r
100 data LoadHowMuch\r
101    = LoadAllTargets\r
102      -- ^ Load all targets and its dependencies.\r
103    | LoadUpTo ModuleName\r
104      -- ^ Load only the given module and its dependencies.\r
105    | LoadDependenciesOf ModuleName\r
106      -- ^ Load only the dependencies of the given module, but not the module\r
107      -- itself.\r
108 \r
109 -- | Try to load the program.  See 'LoadHowMuch' for the different modes.\r
110 --\r
111 -- This function implements the core of GHC's @--make@ mode.  It preprocesses,\r
112 -- compiles and loads the specified modules, avoiding re-compilation wherever\r
113 -- possible.  Depending on the target (see 'DynFlags.hscTarget') compilating\r
114 -- and loading may result in files being created on disk.\r
115 --\r
116 -- Calls the 'reportModuleCompilationResult' callback after each compiling\r
117 -- each module, whether successful or not.\r
118 --\r
119 -- Throw a 'SourceError' if errors are encountered before the actual\r
120 -- compilation starts (e.g., during dependency analysis).  All other errors\r
121 -- are reported using the callback.\r
122 --\r
123 load :: GhcMonad m => LoadHowMuch -> m SuccessFlag\r
124 load how_much = do\r
125    mod_graph <- depanal [] False\r
126    load2 how_much mod_graph\r
127 \r
128 load2 :: GhcMonad m => LoadHowMuch -> [ModSummary]\r
129       -> m SuccessFlag\r
130 load2 how_much mod_graph = do\r
131         guessOutputFile\r
132         hsc_env <- getSession\r
133 \r
134         let hpt1      = hsc_HPT hsc_env\r
135         let dflags    = hsc_dflags hsc_env\r
136 \r
137         -- The "bad" boot modules are the ones for which we have\r
138         -- B.hs-boot in the module graph, but no B.hs\r
139         -- The downsweep should have ensured this does not happen\r
140         -- (see msDeps)\r
141         let all_home_mods = [ms_mod_name s \r
142                             | s <- mod_graph, not (isBootSummary s)]\r
143             bad_boot_mods = [s        | s <- mod_graph, isBootSummary s,\r
144                                         not (ms_mod_name s `elem` all_home_mods)]\r
145         ASSERT( null bad_boot_mods ) return ()\r
146 \r
147         -- check that the module given in HowMuch actually exists, otherwise\r
148         -- topSortModuleGraph will bomb later.\r
149         let checkHowMuch (LoadUpTo m)           = checkMod m\r
150             checkHowMuch (LoadDependenciesOf m) = checkMod m\r
151             checkHowMuch _ = id\r
152 \r
153             checkMod m and_then\r
154                 | m `elem` all_home_mods = and_then\r
155                 | otherwise = do \r
156                         liftIO $ errorMsg dflags (text "no such module:" <+>\r
157                                          quotes (ppr m))\r
158                         return Failed\r
159 \r
160         checkHowMuch how_much $ do\r
161 \r
162         -- mg2_with_srcimps drops the hi-boot nodes, returning a \r
163         -- graph with cycles.  Among other things, it is used for\r
164         -- backing out partially complete cycles following a failed\r
165         -- upsweep, and for removing from hpt all the modules\r
166         -- not in strict downwards closure, during calls to compile.\r
167         let mg2_with_srcimps :: [SCC ModSummary]\r
168             mg2_with_srcimps = topSortModuleGraph True mod_graph Nothing\r
169 \r
170         -- If we can determine that any of the {-# SOURCE #-} imports\r
171         -- are definitely unnecessary, then emit a warning.\r
172         warnUnnecessarySourceImports mg2_with_srcimps\r
173 \r
174         let\r
175             -- check the stability property for each module.\r
176             stable_mods@(stable_obj,stable_bco)\r
177                 = checkStability hpt1 mg2_with_srcimps all_home_mods\r
178 \r
179             -- prune bits of the HPT which are definitely redundant now,\r
180             -- to save space.\r
181             pruned_hpt = pruneHomePackageTable hpt1 \r
182                                 (flattenSCCs mg2_with_srcimps)\r
183                                 stable_mods\r
184 \r
185         _ <- liftIO $ evaluate pruned_hpt\r
186 \r
187         -- before we unload anything, make sure we don't leave an old\r
188         -- interactive context around pointing to dead bindings.  Also,\r
189         -- write the pruned HPT to allow the old HPT to be GC'd.\r
190         modifySession $ \_ -> hsc_env{ hsc_IC = emptyInteractiveContext,\r
191                                        hsc_HPT = pruned_hpt }\r
192 \r
193         liftIO $ debugTraceMsg dflags 2 (text "Stable obj:" <+> ppr stable_obj $$\r
194                                 text "Stable BCO:" <+> ppr stable_bco)\r
195 \r
196         -- Unload any modules which are going to be re-linked this time around.\r
197         let stable_linkables = [ linkable\r
198                                | m <- stable_obj++stable_bco,\r
199                                  Just hmi <- [lookupUFM pruned_hpt m],\r
200                                  Just linkable <- [hm_linkable hmi] ]\r
201         liftIO $ unload hsc_env stable_linkables\r
202 \r
203         -- We could at this point detect cycles which aren't broken by\r
204         -- a source-import, and complain immediately, but it seems better\r
205         -- to let upsweep_mods do this, so at least some useful work gets\r
206         -- done before the upsweep is abandoned.\r
207         --hPutStrLn stderr "after tsort:\n"\r
208         --hPutStrLn stderr (showSDoc (vcat (map ppr mg2)))\r
209 \r
210         -- Now do the upsweep, calling compile for each module in\r
211         -- turn.  Final result is version 3 of everything.\r
212 \r
213         -- Topologically sort the module graph, this time including hi-boot\r
214         -- nodes, and possibly just including the portion of the graph\r
215         -- reachable from the module specified in the 2nd argument to load.\r
216         -- This graph should be cycle-free.\r
217         -- If we're restricting the upsweep to a portion of the graph, we\r
218         -- also want to retain everything that is still stable.\r
219         let full_mg :: [SCC ModSummary]\r
220             full_mg    = topSortModuleGraph False mod_graph Nothing\r
221 \r
222             maybe_top_mod = case how_much of\r
223                                 LoadUpTo m           -> Just m\r
224                                 LoadDependenciesOf m -> Just m\r
225                                 _                    -> Nothing\r
226 \r
227             partial_mg0 :: [SCC ModSummary]\r
228             partial_mg0 = topSortModuleGraph False mod_graph maybe_top_mod\r
229 \r
230             -- LoadDependenciesOf m: we want the upsweep to stop just\r
231             -- short of the specified module (unless the specified module\r
232             -- is stable).\r
233             partial_mg\r
234                 | LoadDependenciesOf _mod <- how_much\r
235                 = ASSERT( case last partial_mg0 of \r
236                             AcyclicSCC ms -> ms_mod_name ms == _mod; _ -> False )\r
237                   List.init partial_mg0\r
238                 | otherwise\r
239                 = partial_mg0\r
240   \r
241             stable_mg = \r
242                 [ AcyclicSCC ms\r
243                 | AcyclicSCC ms <- full_mg,\r
244                   ms_mod_name ms `elem` stable_obj++stable_bco,\r
245                   ms_mod_name ms `notElem` [ ms_mod_name ms' | \r
246                                                 AcyclicSCC ms' <- partial_mg ] ]\r
247 \r
248             mg = stable_mg ++ partial_mg\r
249 \r
250         -- clean up between compilations\r
251         let cleanup = cleanTempFilesExcept dflags\r
252                           (ppFilesFromSummaries (flattenSCCs mg2_with_srcimps))\r
253 \r
254         liftIO $ debugTraceMsg dflags 2 (hang (text "Ready for upsweep")\r
255                                    2 (ppr mg))\r
256 \r
257         setSession hsc_env{ hsc_HPT = emptyHomePackageTable }\r
258         (upsweep_ok, modsUpswept)\r
259            <- upsweep pruned_hpt stable_mods cleanup mg\r
260 \r
261         -- Make modsDone be the summaries for each home module now\r
262         -- available; this should equal the domain of hpt3.\r
263         -- Get in in a roughly top .. bottom order (hence reverse).\r
264 \r
265         let modsDone = reverse modsUpswept\r
266 \r
267         -- Try and do linking in some form, depending on whether the\r
268         -- upsweep was completely or only partially successful.\r
269 \r
270         if succeeded upsweep_ok\r
271 \r
272          then \r
273            -- Easy; just relink it all.\r
274            do liftIO $ debugTraceMsg dflags 2 (text "Upsweep completely successful.")\r
275 \r
276               -- Clean up after ourselves\r
277               liftIO $ cleanTempFilesExcept dflags (ppFilesFromSummaries modsDone)\r
278 \r
279               -- Issue a warning for the confusing case where the user\r
280               -- said '-o foo' but we're not going to do any linking.\r
281               -- We attempt linking if either (a) one of the modules is\r
282               -- called Main, or (b) the user said -no-hs-main, indicating\r
283               -- that main() is going to come from somewhere else.\r
284               --\r
285               let ofile = outputFile dflags\r
286               let no_hs_main = dopt Opt_NoHsMain dflags\r
287               let \r
288                 main_mod = mainModIs dflags\r
289                 a_root_is_Main = any ((==main_mod).ms_mod) mod_graph\r
290                 do_linking = a_root_is_Main || no_hs_main || ghcLink dflags == LinkDynLib\r
291 \r
292               when (ghcLink dflags == LinkBinary \r
293                     && isJust ofile && not do_linking) $\r
294                 liftIO $ debugTraceMsg dflags 1 $\r
295                     text ("Warning: output was redirected with -o, " ++\r
296                           "but no output will be generated\n" ++\r
297                           "because there is no " ++ \r
298                           moduleNameString (moduleName main_mod) ++ " module.")\r
299 \r
300               -- link everything together\r
301               hsc_env1 <- getSession\r
302               linkresult <- liftIO $ link (ghcLink dflags) dflags do_linking (hsc_HPT hsc_env1)\r
303 \r
304               loadFinish Succeeded linkresult\r
305 \r
306          else \r
307            -- Tricky.  We need to back out the effects of compiling any\r
308            -- half-done cycles, both so as to clean up the top level envs\r
309            -- and to avoid telling the interactive linker to link them.\r
310            do liftIO $ debugTraceMsg dflags 2 (text "Upsweep partially successful.")\r
311 \r
312               let modsDone_names\r
313                      = map ms_mod modsDone\r
314               let mods_to_zap_names \r
315                      = findPartiallyCompletedCycles modsDone_names \r
316                           mg2_with_srcimps\r
317               let mods_to_keep\r
318                      = filter ((`notElem` mods_to_zap_names).ms_mod) \r
319                           modsDone\r
320 \r
321               hsc_env1 <- getSession\r
322               let hpt4 = retainInTopLevelEnvs (map ms_mod_name mods_to_keep) \r
323                                               (hsc_HPT hsc_env1)\r
324 \r
325               -- Clean up after ourselves\r
326               liftIO $ cleanTempFilesExcept dflags (ppFilesFromSummaries mods_to_keep)\r
327 \r
328               -- there should be no Nothings where linkables should be, now\r
329               ASSERT(all (isJust.hm_linkable) \r
330                         (eltsUFM (hsc_HPT hsc_env))) do\r
331         \r
332               -- Link everything together\r
333               linkresult <- liftIO $ link (ghcLink dflags) dflags False hpt4\r
334 \r
335               modifySession $ \hsc_env -> hsc_env{ hsc_HPT = hpt4 }\r
336               loadFinish Failed linkresult\r
337 \r
338 -- Finish up after a load.\r
339 \r
340 -- If the link failed, unload everything and return.\r
341 loadFinish :: GhcMonad m =>\r
342               SuccessFlag -> SuccessFlag\r
343            -> m SuccessFlag\r
344 loadFinish _all_ok Failed\r
345   = do hsc_env <- getSession\r
346        liftIO $ unload hsc_env []\r
347        modifySession discardProg\r
348        return Failed\r
349 \r
350 -- Empty the interactive context and set the module context to the topmost\r
351 -- newly loaded module, or the Prelude if none were loaded.\r
352 loadFinish all_ok Succeeded\r
353   = do modifySession $ \hsc_env -> hsc_env{ hsc_IC = emptyInteractiveContext }\r
354        return all_ok\r
355 \r
356 \r
357 -- Forget the current program, but retain the persistent info in HscEnv\r
358 discardProg :: HscEnv -> HscEnv\r
359 discardProg hsc_env\r
360   = hsc_env { hsc_mod_graph = emptyMG, \r
361               hsc_IC = emptyInteractiveContext,\r
362               hsc_HPT = emptyHomePackageTable }\r
363 \r
364 -- used to fish out the preprocess output files for the purposes of\r
365 -- cleaning up.  The preprocessed file *might* be the same as the\r
366 -- source file, but that doesn't do any harm.\r
367 ppFilesFromSummaries :: [ModSummary] -> [FilePath]\r
368 ppFilesFromSummaries summaries = map ms_hspp_file summaries\r
369 \r
370 -- | If there is no -o option, guess the name of target executable\r
371 -- by using top-level source file name as a base.\r
372 guessOutputFile :: GhcMonad m => m ()\r
373 guessOutputFile = modifySession $ \env ->\r
374     let dflags = hsc_dflags env\r
375         mod_graph = hsc_mod_graph env\r
376         mainModuleSrcPath :: Maybe String\r
377         mainModuleSrcPath = do\r
378             let isMain = (== mainModIs dflags) . ms_mod\r
379             [ms] <- return (filter isMain mod_graph)\r
380             ml_hs_file (ms_location ms)\r
381         name = fmap dropExtension mainModuleSrcPath\r
382 \r
383 #if defined(mingw32_HOST_OS)\r
384         -- we must add the .exe extention unconditionally here, otherwise\r
385         -- when name has an extension of its own, the .exe extension will\r
386         -- not be added by DriverPipeline.exeFileName.  See #2248\r
387         name_exe = fmap (<.> "exe") name\r
388 #else\r
389         name_exe = name\r
390 #endif\r
391     in\r
392     case outputFile dflags of\r
393         Just _ -> env\r
394         Nothing -> env { hsc_dflags = dflags { outputFile = name_exe } }\r
395 \r
396 -- -----------------------------------------------------------------------------\r
397 \r
398 -- | Prune the HomePackageTable\r
399 --\r
400 -- Before doing an upsweep, we can throw away:\r
401 --\r
402 --   - For non-stable modules:\r
403 --      - all ModDetails, all linked code\r
404 --   - all unlinked code that is out of date with respect to\r
405 --     the source file\r
406 --\r
407 -- This is VERY IMPORTANT otherwise we'll end up requiring 2x the\r
408 -- space at the end of the upsweep, because the topmost ModDetails of the\r
409 -- old HPT holds on to the entire type environment from the previous\r
410 -- compilation.\r
411 \r
412 pruneHomePackageTable\r
413    :: HomePackageTable\r
414    -> [ModSummary]\r
415    -> ([ModuleName],[ModuleName])\r
416    -> HomePackageTable\r
417 \r
418 pruneHomePackageTable hpt summ (stable_obj, stable_bco)\r
419   = mapUFM prune hpt\r
420   where prune hmi\r
421           | is_stable modl = hmi'\r
422           | otherwise      = hmi'{ hm_details = emptyModDetails }\r
423           where\r
424            modl = moduleName (mi_module (hm_iface hmi))\r
425            hmi' | Just l <- hm_linkable hmi, linkableTime l < ms_hs_date ms\r
426                 = hmi{ hm_linkable = Nothing }\r
427                 | otherwise\r
428                 = hmi\r
429                 where ms = expectJust "prune" (lookupUFM ms_map modl)\r
430 \r
431         ms_map = listToUFM [(ms_mod_name ms, ms) | ms <- summ]\r
432 \r
433         is_stable m = m `elem` stable_obj || m `elem` stable_bco\r
434 \r
435 -- -----------------------------------------------------------------------------\r
436 \r
437 -- Return (names of) all those in modsDone who are part of a cycle\r
438 -- as defined by theGraph.\r
439 findPartiallyCompletedCycles :: [Module] -> [SCC ModSummary] -> [Module]\r
440 findPartiallyCompletedCycles modsDone theGraph\r
441    = chew theGraph\r
442      where\r
443         chew [] = []\r
444         chew ((AcyclicSCC _):rest) = chew rest    -- acyclic?  not interesting.\r
445         chew ((CyclicSCC vs):rest)\r
446            = let names_in_this_cycle = nub (map ms_mod vs)\r
447                  mods_in_this_cycle  \r
448                     = nub ([done | done <- modsDone, \r
449                                    done `elem` names_in_this_cycle])\r
450                  chewed_rest = chew rest\r
451              in \r
452              if   notNull mods_in_this_cycle\r
453                   && length mods_in_this_cycle < length names_in_this_cycle\r
454              then mods_in_this_cycle ++ chewed_rest\r
455              else chewed_rest\r
456 \r
457 \r
458 -- ---------------------------------------------------------------------------\r
459 -- Unloading\r
460 \r
461 unload :: HscEnv -> [Linkable] -> IO ()\r
462 unload hsc_env stable_linkables -- Unload everthing *except* 'stable_linkables'\r
463   = case ghcLink (hsc_dflags hsc_env) of\r
464 #ifdef GHCI\r
465         LinkInMemory -> Linker.unload (hsc_dflags hsc_env) stable_linkables\r
466 #else\r
467         LinkInMemory -> panic "unload: no interpreter"\r
468                                 -- urgh.  avoid warnings:\r
469                                 hsc_env stable_linkables\r
470 #endif\r
471         _other -> return ()\r
472 \r
473 -- -----------------------------------------------------------------------------\r
474 \r
475 {- |\r
476 \r
477   Stability tells us which modules definitely do not need to be recompiled.\r
478   There are two main reasons for having stability:\r
479   \r
480    - avoid doing a complete upsweep of the module graph in GHCi when\r
481      modules near the bottom of the tree have not changed.\r
482 \r
483    - to tell GHCi when it can load object code: we can only load object code\r
484      for a module when we also load object code fo  all of the imports of the\r
485      module.  So we need to know that we will definitely not be recompiling\r
486      any of these modules, and we can use the object code.\r
487 \r
488   The stability check is as follows.  Both stableObject and\r
489   stableBCO are used during the upsweep phase later.\r
490 \r
491 @\r
492   stable m = stableObject m || stableBCO m\r
493 \r
494   stableObject m = \r
495         all stableObject (imports m)\r
496         && old linkable does not exist, or is == on-disk .o\r
497         && date(on-disk .o) > date(.hs)\r
498 \r
499   stableBCO m =\r
500         all stable (imports m)\r
501         && date(BCO) > date(.hs)\r
502 @\r
503 \r
504   These properties embody the following ideas:\r
505 \r
506     - if a module is stable, then:\r
507 \r
508         - if it has been compiled in a previous pass (present in HPT)\r
509           then it does not need to be compiled or re-linked.\r
510 \r
511         - if it has not been compiled in a previous pass,\r
512           then we only need to read its .hi file from disk and\r
513           link it to produce a 'ModDetails'.\r
514 \r
515     - if a modules is not stable, we will definitely be at least\r
516       re-linking, and possibly re-compiling it during the 'upsweep'.\r
517       All non-stable modules can (and should) therefore be unlinked\r
518       before the 'upsweep'.\r
519 \r
520     - Note that objects are only considered stable if they only depend\r
521       on other objects.  We can't link object code against byte code.\r
522 -}\r
523 \r
524 checkStability\r
525         :: HomePackageTable             -- HPT from last compilation\r
526         -> [SCC ModSummary]             -- current module graph (cyclic)\r
527         -> [ModuleName]                 -- all home modules\r
528         -> ([ModuleName],               -- stableObject\r
529             [ModuleName])               -- stableBCO\r
530 \r
531 checkStability hpt sccs all_home_mods = foldl checkSCC ([],[]) sccs\r
532   where\r
533    checkSCC (stable_obj, stable_bco) scc0\r
534      | stableObjects = (scc_mods ++ stable_obj, stable_bco)\r
535      | stableBCOs    = (stable_obj, scc_mods ++ stable_bco)\r
536      | otherwise     = (stable_obj, stable_bco)\r
537      where\r
538         scc = flattenSCC scc0\r
539         scc_mods = map ms_mod_name scc\r
540         home_module m   = m `elem` all_home_mods && m `notElem` scc_mods\r
541 \r
542         scc_allimps = nub (filter home_module (concatMap ms_home_allimps scc))\r
543             -- all imports outside the current SCC, but in the home pkg\r
544         \r
545         stable_obj_imps = map (`elem` stable_obj) scc_allimps\r
546         stable_bco_imps = map (`elem` stable_bco) scc_allimps\r
547 \r
548         stableObjects = \r
549            and stable_obj_imps\r
550            && all object_ok scc\r
551 \r
552         stableBCOs = \r
553            and (zipWith (||) stable_obj_imps stable_bco_imps)\r
554            && all bco_ok scc\r
555 \r
556         object_ok ms\r
557           | Just t <- ms_obj_date ms  =  t >= ms_hs_date ms \r
558                                          && same_as_prev t\r
559           | otherwise = False\r
560           where\r
561              same_as_prev t = case lookupUFM hpt (ms_mod_name ms) of\r
562                                 Just hmi  | Just l <- hm_linkable hmi\r
563                                  -> isObjectLinkable l && t == linkableTime l\r
564                                 _other  -> True\r
565                 -- why '>=' rather than '>' above?  If the filesystem stores\r
566                 -- times to the nearset second, we may occasionally find that\r
567                 -- the object & source have the same modification time, \r
568                 -- especially if the source was automatically generated\r
569                 -- and compiled.  Using >= is slightly unsafe, but it matches\r
570                 -- make's behaviour.\r
571 \r
572         bco_ok ms\r
573           = case lookupUFM hpt (ms_mod_name ms) of\r
574                 Just hmi  | Just l <- hm_linkable hmi ->\r
575                         not (isObjectLinkable l) && \r
576                         linkableTime l >= ms_hs_date ms\r
577                 _other  -> False\r
578 \r
579 -- -----------------------------------------------------------------------------\r
580 \r
581 -- | The upsweep\r
582 --\r
583 -- This is where we compile each module in the module graph, in a pass\r
584 -- from the bottom to the top of the graph.\r
585 --\r
586 -- There better had not be any cyclic groups here -- we check for them.\r
587 \r
588 upsweep\r
589     :: GhcMonad m\r
590     => HomePackageTable         -- ^ HPT from last time round (pruned)\r
591     -> ([ModuleName],[ModuleName]) -- ^ stable modules (see checkStability)\r
592     -> IO ()                    -- ^ How to clean up unwanted tmp files\r
593     -> [SCC ModSummary]         -- ^ Mods to do (the worklist)\r
594     -> m (SuccessFlag,\r
595           [ModSummary])\r
596        -- ^ Returns:\r
597        --\r
598        --  1. A flag whether the complete upsweep was successful.\r
599        --  2. The 'HscEnv' in the monad has an updated HPT\r
600        --  3. A list of modules which succeeded loading.\r
601 \r
602 upsweep old_hpt stable_mods cleanup sccs = do\r
603    (res, done) <- upsweep' old_hpt [] sccs 1 (length sccs)\r
604    return (res, reverse done)\r
605  where\r
606 \r
607   upsweep' _old_hpt done\r
608      [] _ _\r
609    = return (Succeeded, done)\r
610 \r
611   upsweep' _old_hpt done\r
612      (CyclicSCC ms:_) _ _\r
613    = do dflags <- getSessionDynFlags\r
614         liftIO $ fatalErrorMsg dflags (cyclicModuleErr ms)\r
615         return (Failed, done)\r
616 \r
617   upsweep' old_hpt done\r
618      (AcyclicSCC mod:mods) mod_index nmods\r
619    = do -- putStrLn ("UPSWEEP_MOD: hpt = " ++ \r
620         --           show (map (moduleUserString.moduleName.mi_module.hm_iface) \r
621         --                     (moduleEnvElts (hsc_HPT hsc_env)))\r
622         let logger _mod = defaultWarnErrLogger\r
623 \r
624         hsc_env <- getSession\r
625         mb_mod_info\r
626             <- handleSourceError\r
627                    (\err -> do logger mod (Just err); return Nothing) $ do\r
628                  mod_info <- liftIO $ upsweep_mod hsc_env old_hpt stable_mods\r
629                                                   mod mod_index nmods\r
630                  logger mod Nothing -- log warnings\r
631                  return (Just mod_info)\r
632 \r
633         liftIO cleanup -- Remove unwanted tmp files between compilations\r
634 \r
635         case mb_mod_info of\r
636           Nothing -> return (Failed, done)\r
637           Just mod_info -> do\r
638                 let this_mod = ms_mod_name mod\r
639 \r
640                         -- Add new info to hsc_env\r
641                     hpt1     = addToUFM (hsc_HPT hsc_env) this_mod mod_info\r
642                     hsc_env1 = hsc_env { hsc_HPT = hpt1 }\r
643 \r
644                         -- Space-saving: delete the old HPT entry\r
645                         -- for mod BUT if mod is a hs-boot\r
646                         -- node, don't delete it.  For the\r
647                         -- interface, the HPT entry is probaby for the\r
648                         -- main Haskell source file.  Deleting it\r
649                         -- would force the real module to be recompiled\r
650                         -- every time.\r
651                     old_hpt1 | isBootSummary mod = old_hpt\r
652                              | otherwise = delFromUFM old_hpt this_mod\r
653 \r
654                     done' = mod:done\r
655 \r
656                         -- fixup our HomePackageTable after we've finished compiling\r
657                         -- a mutually-recursive loop.  See reTypecheckLoop, below.\r
658                 hsc_env2 <- liftIO $ reTypecheckLoop hsc_env1 mod done'\r
659                 setSession hsc_env2\r
660 \r
661                 upsweep' old_hpt1 done' mods (mod_index+1) nmods\r
662 \r
663 -- | Compile a single module.  Always produce a Linkable for it if\r
664 -- successful.  If no compilation happened, return the old Linkable.\r
665 upsweep_mod :: HscEnv\r
666             -> HomePackageTable\r
667             -> ([ModuleName],[ModuleName])\r
668             -> ModSummary\r
669             -> Int  -- index of module\r
670             -> Int  -- total number of modules\r
671             -> IO HomeModInfo\r
672 \r
673 upsweep_mod hsc_env old_hpt (stable_obj, stable_bco) summary mod_index nmods\r
674    =    let \r
675             this_mod_name = ms_mod_name summary\r
676             this_mod    = ms_mod summary\r
677             mb_obj_date = ms_obj_date summary\r
678             obj_fn      = ml_obj_file (ms_location summary)\r
679             hs_date     = ms_hs_date summary\r
680 \r
681             is_stable_obj = this_mod_name `elem` stable_obj\r
682             is_stable_bco = this_mod_name `elem` stable_bco\r
683 \r
684             old_hmi = lookupUFM old_hpt this_mod_name\r
685 \r
686             -- We're using the dflags for this module now, obtained by\r
687             -- applying any options in its LANGUAGE & OPTIONS_GHC pragmas.\r
688             dflags = ms_hspp_opts summary\r
689             prevailing_target = hscTarget (hsc_dflags hsc_env)\r
690             local_target      = hscTarget dflags\r
691 \r
692             -- If OPTIONS_GHC contains -fasm or -fvia-C, be careful that\r
693             -- we don't do anything dodgy: these should only work to change\r
694             -- from -fvia-C to -fasm and vice-versa, otherwise we could \r
695             -- end up trying to link object code to byte code.\r
696             target = if prevailing_target /= local_target\r
697                         && (not (isObjectTarget prevailing_target)\r
698                             || not (isObjectTarget local_target))\r
699                         then prevailing_target\r
700                         else local_target \r
701 \r
702             -- store the corrected hscTarget into the summary\r
703             summary' = summary{ ms_hspp_opts = dflags { hscTarget = target } }\r
704 \r
705             -- The old interface is ok if\r
706             --  a) we're compiling a source file, and the old HPT\r
707             --     entry is for a source file\r
708             --  b) we're compiling a hs-boot file\r
709             -- Case (b) allows an hs-boot file to get the interface of its\r
710             -- real source file on the second iteration of the compilation\r
711             -- manager, but that does no harm.  Otherwise the hs-boot file\r
712             -- will always be recompiled\r
713             \r
714             mb_old_iface \r
715                 = case old_hmi of\r
716                      Nothing                              -> Nothing\r
717                      Just hm_info | isBootSummary summary -> Just iface\r
718                                   | not (mi_boot iface)   -> Just iface\r
719                                   | otherwise             -> Nothing\r
720                                    where \r
721                                      iface = hm_iface hm_info\r
722 \r
723             compile_it :: Maybe Linkable -> IO HomeModInfo\r
724             compile_it  mb_linkable = \r
725                   compile hsc_env summary' mod_index nmods \r
726                           mb_old_iface mb_linkable\r
727 \r
728             compile_it_discard_iface :: Maybe Linkable -> IO HomeModInfo\r
729             compile_it_discard_iface mb_linkable =\r
730                   compile hsc_env summary' mod_index nmods\r
731                           Nothing mb_linkable\r
732 \r
733             -- With the HscNothing target we create empty linkables to avoid\r
734             -- recompilation.  We have to detect these to recompile anyway if\r
735             -- the target changed since the last compile.\r
736             is_fake_linkable\r
737                | Just hmi <- old_hmi, Just l <- hm_linkable hmi =\r
738                   null (linkableUnlinked l)\r
739                | otherwise =\r
740                    -- we have no linkable, so it cannot be fake\r
741                    False\r
742 \r
743             implies False _ = True\r
744             implies True x  = x\r
745 \r
746         in\r
747         case () of\r
748          _\r
749                 -- Regardless of whether we're generating object code or\r
750                 -- byte code, we can always use an existing object file\r
751                 -- if it is *stable* (see checkStability).\r
752           | is_stable_obj, Just hmi <- old_hmi -> do\r
753                 liftIO $ debugTraceMsg (hsc_dflags hsc_env) 5\r
754                            (text "skipping stable obj mod:" <+> ppr this_mod_name)\r
755                 return hmi\r
756                 -- object is stable, and we have an entry in the\r
757                 -- old HPT: nothing to do\r
758 \r
759           | is_stable_obj, isNothing old_hmi -> do\r
760                 liftIO $ debugTraceMsg (hsc_dflags hsc_env) 5\r
761                            (text "compiling stable on-disk mod:" <+> ppr this_mod_name)\r
762                 linkable <- liftIO $ findObjectLinkable this_mod obj_fn\r
763                               (expectJust "upsweep1" mb_obj_date)\r
764                 compile_it (Just linkable)\r
765                 -- object is stable, but we need to load the interface\r
766                 -- off disk to make a HMI.\r
767 \r
768           | not (isObjectTarget target), is_stable_bco,\r
769             (target /= HscNothing) `implies` not is_fake_linkable ->\r
770                 ASSERT(isJust old_hmi) -- must be in the old_hpt\r
771                 let Just hmi = old_hmi in do\r
772                 liftIO $ debugTraceMsg (hsc_dflags hsc_env) 5\r
773                            (text "skipping stable BCO mod:" <+> ppr this_mod_name)\r
774                 return hmi\r
775                 -- BCO is stable: nothing to do\r
776 \r
777           | not (isObjectTarget target),\r
778             Just hmi <- old_hmi,\r
779             Just l <- hm_linkable hmi,\r
780             not (isObjectLinkable l),\r
781             (target /= HscNothing) `implies` not is_fake_linkable,\r
782             linkableTime l >= ms_hs_date summary -> do\r
783                 liftIO $ debugTraceMsg (hsc_dflags hsc_env) 5\r
784                            (text "compiling non-stable BCO mod:" <+> ppr this_mod_name)\r
785                 compile_it (Just l)\r
786                 -- we have an old BCO that is up to date with respect\r
787                 -- to the source: do a recompilation check as normal.\r
788 \r
789           -- When generating object code, if there's an up-to-date\r
790           -- object file on the disk, then we can use it.\r
791           -- However, if the object file is new (compared to any\r
792           -- linkable we had from a previous compilation), then we\r
793           -- must discard any in-memory interface, because this\r
794           -- means the user has compiled the source file\r
795           -- separately and generated a new interface, that we must\r
796           -- read from the disk.\r
797           --\r
798           | isObjectTarget target,\r
799             Just obj_date <- mb_obj_date,\r
800             obj_date >= hs_date -> do\r
801                 case old_hmi of\r
802                   Just hmi\r
803                     | Just l <- hm_linkable hmi,\r
804                       isObjectLinkable l && linkableTime l == obj_date -> do\r
805                           liftIO $ debugTraceMsg (hsc_dflags hsc_env) 5\r
806                                      (text "compiling mod with new on-disk obj:" <+> ppr this_mod_name)\r
807                           compile_it (Just l)\r
808                   _otherwise -> do\r
809                           liftIO $ debugTraceMsg (hsc_dflags hsc_env) 5\r
810                                      (text "compiling mod with new on-disk obj2:" <+> ppr this_mod_name)\r
811                           linkable <- liftIO $ findObjectLinkable this_mod obj_fn obj_date\r
812                           compile_it_discard_iface (Just linkable)\r
813 \r
814          _otherwise -> do\r
815                 liftIO $ debugTraceMsg (hsc_dflags hsc_env) 5\r
816                            (text "compiling mod:" <+> ppr this_mod_name)\r
817                 compile_it Nothing\r
818 \r
819 \r
820 \r
821 -- Filter modules in the HPT\r
822 retainInTopLevelEnvs :: [ModuleName] -> HomePackageTable -> HomePackageTable\r
823 retainInTopLevelEnvs keep_these hpt\r
824    = listToUFM   [ (mod, expectJust "retain" mb_mod_info)\r
825                  | mod <- keep_these\r
826                  , let mb_mod_info = lookupUFM hpt mod\r
827                  , isJust mb_mod_info ]\r
828 \r
829 -- ---------------------------------------------------------------------------\r
830 -- Typecheck module loops\r
831 \r
832 {-\r
833 See bug #930.  This code fixes a long-standing bug in --make.  The\r
834 problem is that when compiling the modules *inside* a loop, a data\r
835 type that is only defined at the top of the loop looks opaque; but\r
836 after the loop is done, the structure of the data type becomes\r
837 apparent.\r
838 \r
839 The difficulty is then that two different bits of code have\r
840 different notions of what the data type looks like.\r
841 \r
842 The idea is that after we compile a module which also has an .hs-boot\r
843 file, we re-generate the ModDetails for each of the modules that\r
844 depends on the .hs-boot file, so that everyone points to the proper\r
845 TyCons, Ids etc. defined by the real module, not the boot module.\r
846 Fortunately re-generating a ModDetails from a ModIface is easy: the\r
847 function TcIface.typecheckIface does exactly that.\r
848 \r
849 Picking the modules to re-typecheck is slightly tricky.  Starting from\r
850 the module graph consisting of the modules that have already been\r
851 compiled, we reverse the edges (so they point from the imported module\r
852 to the importing module), and depth-first-search from the .hs-boot\r
853 node.  This gives us all the modules that depend transitively on the\r
854 .hs-boot module, and those are exactly the modules that we need to\r
855 re-typecheck.\r
856 \r
857 Following this fix, GHC can compile itself with --make -O2.\r
858 -}\r
859 \r
860 reTypecheckLoop :: HscEnv -> ModSummary -> ModuleGraph -> IO HscEnv\r
861 reTypecheckLoop hsc_env ms graph\r
862   | not (isBootSummary ms) && \r
863     any (\m -> ms_mod m == this_mod && isBootSummary m) graph\r
864   = do\r
865         let mss = reachableBackwards (ms_mod_name ms) graph\r
866             non_boot = filter (not.isBootSummary) mss\r
867         debugTraceMsg (hsc_dflags hsc_env) 2 $\r
868            text "Re-typechecking loop: " <> ppr (map ms_mod_name non_boot)\r
869         typecheckLoop hsc_env (map ms_mod_name non_boot)\r
870   | otherwise\r
871   = return hsc_env\r
872  where\r
873   this_mod = ms_mod ms\r
874 \r
875 typecheckLoop :: HscEnv -> [ModuleName] -> IO HscEnv\r
876 typecheckLoop hsc_env mods = do\r
877   new_hpt <-\r
878     fixIO $ \new_hpt -> do\r
879       let new_hsc_env = hsc_env{ hsc_HPT = new_hpt }\r
880       mds <- initIfaceCheck new_hsc_env $ \r
881                 mapM (typecheckIface . hm_iface) hmis\r
882       let new_hpt = addListToUFM old_hpt \r
883                         (zip mods [ hmi{ hm_details = details }\r
884                                   | (hmi,details) <- zip hmis mds ])\r
885       return new_hpt\r
886   return hsc_env{ hsc_HPT = new_hpt }\r
887   where\r
888     old_hpt = hsc_HPT hsc_env\r
889     hmis    = map (expectJust "typecheckLoop" . lookupUFM old_hpt) mods\r
890 \r
891 reachableBackwards :: ModuleName -> [ModSummary] -> [ModSummary]\r
892 reachableBackwards mod summaries\r
893   = [ ms | (ms,_,_) <- reachableG (transposeG graph) root ]\r
894   where -- the rest just sets up the graph:\r
895         (graph, lookup_node) = moduleGraphNodes False summaries\r
896         root  = expectJust "reachableBackwards" (lookup_node HsBootFile mod)\r
897 \r
898 -- ---------------------------------------------------------------------------\r
899 -- Topological sort of the module graph\r
900 \r
901 type SummaryNode = (ModSummary, Int, [Int])\r
902 \r
903 topSortModuleGraph\r
904           :: Bool\r
905           -- ^ Drop hi-boot nodes? (see below)\r
906           -> [ModSummary]\r
907           -> Maybe ModuleName\r
908              -- ^ Root module name.  If @Nothing@, use the full graph.\r
909           -> [SCC ModSummary]\r
910 -- ^ Calculate SCCs of the module graph, possibly dropping the hi-boot nodes\r
911 -- The resulting list of strongly-connected-components is in topologically\r
912 -- sorted order, starting with the module(s) at the bottom of the\r
913 -- dependency graph (ie compile them first) and ending with the ones at\r
914 -- the top.\r
915 --\r
916 -- Drop hi-boot nodes (first boolean arg)? \r
917 --\r
918 -- - @False@:   treat the hi-boot summaries as nodes of the graph,\r
919 --              so the graph must be acyclic\r
920 --\r
921 -- - @True@:    eliminate the hi-boot nodes, and instead pretend\r
922 --              the a source-import of Foo is an import of Foo\r
923 --              The resulting graph has no hi-boot nodes, but can be cyclic\r
924 \r
925 topSortModuleGraph drop_hs_boot_nodes summaries mb_root_mod\r
926   = map (fmap summaryNodeSummary) $ stronglyConnCompG initial_graph\r
927   where\r
928     (graph, lookup_node) = moduleGraphNodes drop_hs_boot_nodes summaries\r
929     \r
930     initial_graph = case mb_root_mod of\r
931         Nothing -> graph\r
932         Just root_mod ->\r
933             -- restrict the graph to just those modules reachable from\r
934             -- the specified module.  We do this by building a graph with\r
935             -- the full set of nodes, and determining the reachable set from\r
936             -- the specified node.\r
937             let root | Just node <- lookup_node HsSrcFile root_mod, graph `hasVertexG` node = node\r
938                      | otherwise = ghcError (ProgramError "module does not exist")\r
939             in graphFromEdgedVertices (seq root (reachableG graph root))\r
940 \r
941 summaryNodeKey :: SummaryNode -> Int\r
942 summaryNodeKey (_, k, _) = k\r
943 \r
944 summaryNodeSummary :: SummaryNode -> ModSummary\r
945 summaryNodeSummary (s, _, _) = s\r
946 \r
947 moduleGraphNodes :: Bool -> [ModSummary]\r
948   -> (Graph SummaryNode, HscSource -> ModuleName -> Maybe SummaryNode)\r
949 moduleGraphNodes drop_hs_boot_nodes summaries = (graphFromEdgedVertices nodes, lookup_node)\r
950   where\r
951     numbered_summaries = zip summaries [1..]\r
952 \r
953     lookup_node :: HscSource -> ModuleName -> Maybe SummaryNode\r
954     lookup_node hs_src mod = Map.lookup (mod, hs_src) node_map\r
955 \r
956     lookup_key :: HscSource -> ModuleName -> Maybe Int\r
957     lookup_key hs_src mod = fmap summaryNodeKey (lookup_node hs_src mod)\r
958 \r
959     node_map :: NodeMap SummaryNode\r
960     node_map = Map.fromList [ ((moduleName (ms_mod s), ms_hsc_src s), node)\r
961                             | node@(s, _, _) <- nodes ]\r
962 \r
963     -- We use integers as the keys for the SCC algorithm\r
964     nodes :: [SummaryNode]\r
965     nodes = [ (s, key, out_keys)\r
966             | (s, key) <- numbered_summaries\r
967              -- Drop the hi-boot ones if told to do so\r
968             , not (isBootSummary s && drop_hs_boot_nodes)\r
969             , let out_keys = out_edge_keys hs_boot_key (map unLoc (ms_home_srcimps s)) ++\r
970                              out_edge_keys HsSrcFile   (map unLoc (ms_home_imps s)) ++\r
971                              (-- see [boot-edges] below\r
972                               if drop_hs_boot_nodes || ms_hsc_src s == HsBootFile \r
973                               then [] \r
974                               else case lookup_key HsBootFile (ms_mod_name s) of\r
975                                     Nothing -> []\r
976                                     Just k  -> [k]) ]\r
977 \r
978     -- [boot-edges] if this is a .hs and there is an equivalent\r
979     -- .hs-boot, add a link from the former to the latter.  This\r
980     -- has the effect of detecting bogus cases where the .hs-boot\r
981     -- depends on the .hs, by introducing a cycle.  Additionally,\r
982     -- it ensures that we will always process the .hs-boot before\r
983     -- the .hs, and so the HomePackageTable will always have the\r
984     -- most up to date information.\r
985 \r
986     -- Drop hs-boot nodes by using HsSrcFile as the key\r
987     hs_boot_key | drop_hs_boot_nodes = HsSrcFile\r
988                 | otherwise          = HsBootFile\r
989 \r
990     out_edge_keys :: HscSource -> [ModuleName] -> [Int]\r
991     out_edge_keys hi_boot ms = mapCatMaybes (lookup_key hi_boot) ms\r
992         -- If we want keep_hi_boot_nodes, then we do lookup_key with\r
993         -- the IsBootInterface parameter True; else False\r
994 \r
995 \r
996 type NodeKey   = (ModuleName, HscSource)  -- The nodes of the graph are \r
997 type NodeMap a = Map.Map NodeKey a        -- keyed by (mod, src_file_type) pairs\r
998 \r
999 msKey :: ModSummary -> NodeKey\r
1000 msKey (ModSummary { ms_mod = mod, ms_hsc_src = boot }) = (moduleName mod,boot)\r
1001 \r
1002 mkNodeMap :: [ModSummary] -> NodeMap ModSummary\r
1003 mkNodeMap summaries = Map.fromList [ (msKey s, s) | s <- summaries]\r
1004         \r
1005 nodeMapElts :: NodeMap a -> [a]\r
1006 nodeMapElts = Map.elems\r
1007 \r
1008 -- | If there are {-# SOURCE #-} imports between strongly connected\r
1009 -- components in the topological sort, then those imports can\r
1010 -- definitely be replaced by ordinary non-SOURCE imports: if SOURCE\r
1011 -- were necessary, then the edge would be part of a cycle.\r
1012 warnUnnecessarySourceImports :: GhcMonad m => [SCC ModSummary] -> m ()\r
1013 warnUnnecessarySourceImports sccs = do\r
1014   logWarnings (listToBag (concatMap (check.flattenSCC) sccs))\r
1015   where check ms =\r
1016            let mods_in_this_cycle = map ms_mod_name ms in\r
1017            [ warn i | m <- ms, i <- ms_home_srcimps m,\r
1018                       unLoc i `notElem`  mods_in_this_cycle ]\r
1019 \r
1020         warn :: Located ModuleName -> WarnMsg\r
1021         warn (L loc mod) = \r
1022            mkPlainErrMsg loc\r
1023                 (ptext (sLit "Warning: {-# SOURCE #-} unnecessary in import of ")\r
1024                  <+> quotes (ppr mod))\r
1025 \r
1026 -----------------------------------------------------------------------------\r
1027 -- Downsweep (dependency analysis)\r
1028 \r
1029 -- Chase downwards from the specified root set, returning summaries\r
1030 -- for all home modules encountered.  Only follow source-import\r
1031 -- links.\r
1032 \r
1033 -- We pass in the previous collection of summaries, which is used as a\r
1034 -- cache to avoid recalculating a module summary if the source is\r
1035 -- unchanged.\r
1036 --\r
1037 -- The returned list of [ModSummary] nodes has one node for each home-package\r
1038 -- module, plus one for any hs-boot files.  The imports of these nodes \r
1039 -- are all there, including the imports of non-home-package modules.\r
1040 \r
1041 downsweep :: HscEnv\r
1042           -> [ModSummary]       -- Old summaries\r
1043           -> [ModuleName]       -- Ignore dependencies on these; treat\r
1044                                 -- them as if they were package modules\r
1045           -> Bool               -- True <=> allow multiple targets to have \r
1046                                 --          the same module name; this is \r
1047                                 --          very useful for ghc -M\r
1048           -> IO [ModSummary]\r
1049                 -- The elts of [ModSummary] all have distinct\r
1050                 -- (Modules, IsBoot) identifiers, unless the Bool is true\r
1051                 -- in which case there can be repeats\r
1052 downsweep hsc_env old_summaries excl_mods allow_dup_roots\r
1053    = do\r
1054        rootSummaries <- mapM getRootSummary roots\r
1055        let root_map = mkRootMap rootSummaries\r
1056        checkDuplicates root_map\r
1057        summs <- loop (concatMap msDeps rootSummaries) root_map\r
1058        return summs\r
1059      where\r
1060         roots = hsc_targets hsc_env\r
1061 \r
1062         old_summary_map :: NodeMap ModSummary\r
1063         old_summary_map = mkNodeMap old_summaries\r
1064 \r
1065         getRootSummary :: Target -> IO ModSummary\r
1066         getRootSummary (Target (TargetFile file mb_phase) obj_allowed maybe_buf)\r
1067            = do exists <- liftIO $ doesFileExist file\r
1068                 if exists \r
1069                     then summariseFile hsc_env old_summaries file mb_phase \r
1070                                        obj_allowed maybe_buf\r
1071                     else throwOneError $ mkPlainErrMsg noSrcSpan $\r
1072                            text "can't find file:" <+> text file\r
1073         getRootSummary (Target (TargetModule modl) obj_allowed maybe_buf)\r
1074            = do maybe_summary <- summariseModule hsc_env old_summary_map False \r
1075                                            (L rootLoc modl) obj_allowed \r
1076                                            maybe_buf excl_mods\r
1077                 case maybe_summary of\r
1078                    Nothing -> packageModErr modl\r
1079                    Just s  -> return s\r
1080 \r
1081         rootLoc = mkGeneralSrcSpan (fsLit "<command line>")\r
1082 \r
1083         -- In a root module, the filename is allowed to diverge from the module\r
1084         -- name, so we have to check that there aren't multiple root files\r
1085         -- defining the same module (otherwise the duplicates will be silently\r
1086         -- ignored, leading to confusing behaviour).\r
1087         checkDuplicates :: NodeMap [ModSummary] -> IO ()\r
1088         checkDuplicates root_map \r
1089            | allow_dup_roots = return ()\r
1090            | null dup_roots  = return ()\r
1091            | otherwise       = liftIO $ multiRootsErr (head dup_roots)\r
1092            where\r
1093              dup_roots :: [[ModSummary]]        -- Each at least of length 2\r
1094              dup_roots = filterOut isSingleton (nodeMapElts root_map)\r
1095 \r
1096         loop :: [(Located ModuleName,IsBootInterface)]\r
1097                         -- Work list: process these modules\r
1098              -> NodeMap [ModSummary]\r
1099                         -- Visited set; the range is a list because\r
1100                         -- the roots can have the same module names\r
1101                         -- if allow_dup_roots is True\r
1102              -> IO [ModSummary]\r
1103                         -- The result includes the worklist, except\r
1104                         -- for those mentioned in the visited set\r
1105         loop [] done      = return (concat (nodeMapElts done))\r
1106         loop ((wanted_mod, is_boot) : ss) done \r
1107           | Just summs <- Map.lookup key done\r
1108           = if isSingleton summs then\r
1109                 loop ss done\r
1110             else\r
1111                 do { multiRootsErr summs; return [] }\r
1112           | otherwise\r
1113           = do mb_s <- summariseModule hsc_env old_summary_map \r
1114                                        is_boot wanted_mod True\r
1115                                        Nothing excl_mods\r
1116                case mb_s of\r
1117                    Nothing -> loop ss done\r
1118                    Just s  -> loop (msDeps s ++ ss) (Map.insert key [s] done)\r
1119           where\r
1120             key = (unLoc wanted_mod, if is_boot then HsBootFile else HsSrcFile)\r
1121 \r
1122 -- XXX Does the (++) here need to be flipped?\r
1123 mkRootMap :: [ModSummary] -> NodeMap [ModSummary]\r
1124 mkRootMap summaries = Map.insertListWith (flip (++))\r
1125                                          [ (msKey s, [s]) | s <- summaries ]\r
1126                                          Map.empty\r
1127 \r
1128 msDeps :: ModSummary -> [(Located ModuleName, IsBootInterface)]\r
1129 -- (msDeps s) returns the dependencies of the ModSummary s.\r
1130 -- A wrinkle is that for a {-# SOURCE #-} import we return\r
1131 --      *both* the hs-boot file\r
1132 --      *and* the source file\r
1133 -- as "dependencies".  That ensures that the list of all relevant\r
1134 -- modules always contains B.hs if it contains B.hs-boot.\r
1135 -- Remember, this pass isn't doing the topological sort.  It's\r
1136 -- just gathering the list of all relevant ModSummaries\r
1137 msDeps s = \r
1138     concat [ [(m,True), (m,False)] | m <- ms_home_srcimps s ] \r
1139          ++ [ (m,False) | m <- ms_home_imps s ] \r
1140 \r
1141 home_imps :: [Located (ImportDecl RdrName)] -> [Located ModuleName]\r
1142 home_imps imps = [ ideclName i |  L _ i <- imps, isLocal (ideclPkgQual i) ]\r
1143   where isLocal Nothing = True\r
1144         isLocal (Just pkg) | pkg == fsLit "this" = True -- "this" is special\r
1145         isLocal _ = False\r
1146 \r
1147 ms_home_allimps :: ModSummary -> [ModuleName]\r
1148 ms_home_allimps ms = map unLoc (ms_home_srcimps ms ++ ms_home_imps ms)\r
1149 \r
1150 ms_home_srcimps :: ModSummary -> [Located ModuleName]\r
1151 ms_home_srcimps = home_imps . ms_srcimps\r
1152 \r
1153 ms_home_imps :: ModSummary -> [Located ModuleName]\r
1154 ms_home_imps = home_imps . ms_imps\r
1155 \r
1156 -----------------------------------------------------------------------------\r
1157 -- Summarising modules\r
1158 \r
1159 -- We have two types of summarisation:\r
1160 --\r
1161 --    * Summarise a file.  This is used for the root module(s) passed to\r
1162 --      cmLoadModules.  The file is read, and used to determine the root\r
1163 --      module name.  The module name may differ from the filename.\r
1164 --\r
1165 --    * Summarise a module.  We are given a module name, and must provide\r
1166 --      a summary.  The finder is used to locate the file in which the module\r
1167 --      resides.\r
1168 \r
1169 summariseFile\r
1170         :: HscEnv\r
1171         -> [ModSummary]                 -- old summaries\r
1172         -> FilePath                     -- source file name\r
1173         -> Maybe Phase                  -- start phase\r
1174         -> Bool                         -- object code allowed?\r
1175         -> Maybe (StringBuffer,ClockTime)\r
1176         -> IO ModSummary\r
1177 \r
1178 summariseFile hsc_env old_summaries file mb_phase obj_allowed maybe_buf\r
1179         -- we can use a cached summary if one is available and the\r
1180         -- source file hasn't changed,  But we have to look up the summary\r
1181         -- by source file, rather than module name as we do in summarise.\r
1182    | Just old_summary <- findSummaryBySourceFile old_summaries file\r
1183    = do\r
1184         let location = ms_location old_summary\r
1185 \r
1186                 -- return the cached summary if the source didn't change\r
1187         src_timestamp <- case maybe_buf of\r
1188                            Just (_,t) -> return t\r
1189                            Nothing    -> liftIO $ getModificationTime file\r
1190                 -- The file exists; we checked in getRootSummary above.\r
1191                 -- If it gets removed subsequently, then this \r
1192                 -- getModificationTime may fail, but that's the right\r
1193                 -- behaviour.\r
1194 \r
1195         if ms_hs_date old_summary == src_timestamp \r
1196            then do -- update the object-file timestamp\r
1197                   obj_timestamp <-\r
1198                     if isObjectTarget (hscTarget (hsc_dflags hsc_env)) \r
1199                         || obj_allowed -- bug #1205\r
1200                         then liftIO $ getObjTimestamp location False\r
1201                         else return Nothing\r
1202                   return old_summary{ ms_obj_date = obj_timestamp }\r
1203            else\r
1204                 new_summary\r
1205 \r
1206    | otherwise\r
1207    = new_summary\r
1208   where\r
1209     new_summary = do\r
1210         let dflags = hsc_dflags hsc_env\r
1211 \r
1212         (dflags', hspp_fn, buf)\r
1213             <- preprocessFile hsc_env file mb_phase maybe_buf\r
1214 \r
1215         (srcimps,the_imps, L _ mod_name) <- getImports dflags' buf hspp_fn file\r
1216 \r
1217         -- Make a ModLocation for this file\r
1218         location <- liftIO $ mkHomeModLocation dflags mod_name file\r
1219 \r
1220         -- Tell the Finder cache where it is, so that subsequent calls\r
1221         -- to findModule will find it, even if it's not on any search path\r
1222         mod <- liftIO $ addHomeModuleToFinder hsc_env mod_name location\r
1223 \r
1224         src_timestamp <- case maybe_buf of\r
1225                            Just (_,t) -> return t\r
1226                            Nothing    -> liftIO $ getModificationTime file\r
1227                         -- getMofificationTime may fail\r
1228 \r
1229         -- when the user asks to load a source file by name, we only\r
1230         -- use an object file if -fobject-code is on.  See #1205.\r
1231         obj_timestamp <-\r
1232             if isObjectTarget (hscTarget (hsc_dflags hsc_env)) \r
1233                || obj_allowed -- bug #1205\r
1234                 then liftIO $ modificationTimeIfExists (ml_obj_file location)\r
1235                 else return Nothing\r
1236 \r
1237         return (ModSummary { ms_mod = mod, ms_hsc_src = HsSrcFile,\r
1238                              ms_location = location,\r
1239                              ms_hspp_file = hspp_fn,\r
1240                              ms_hspp_opts = dflags',\r
1241                              ms_hspp_buf  = Just buf,\r
1242                              ms_srcimps = srcimps, ms_imps = the_imps,\r
1243                              ms_hs_date = src_timestamp,\r
1244                              ms_obj_date = obj_timestamp })\r
1245 \r
1246 findSummaryBySourceFile :: [ModSummary] -> FilePath -> Maybe ModSummary\r
1247 findSummaryBySourceFile summaries file\r
1248   = case [ ms | ms <- summaries, HsSrcFile <- [ms_hsc_src ms],\r
1249                                  expectJust "findSummaryBySourceFile" (ml_hs_file (ms_location ms)) == file ] of\r
1250         [] -> Nothing\r
1251         (x:_) -> Just x\r
1252 \r
1253 -- Summarise a module, and pick up source and timestamp.\r
1254 summariseModule\r
1255           :: HscEnv\r
1256           -> NodeMap ModSummary -- Map of old summaries\r
1257           -> IsBootInterface    -- True <=> a {-# SOURCE #-} import\r
1258           -> Located ModuleName -- Imported module to be summarised\r
1259           -> Bool               -- object code allowed?\r
1260           -> Maybe (StringBuffer, ClockTime)\r
1261           -> [ModuleName]               -- Modules to exclude\r
1262           -> IO (Maybe ModSummary)      -- Its new summary\r
1263 \r
1264 summariseModule hsc_env old_summary_map is_boot (L loc wanted_mod) \r
1265                 obj_allowed maybe_buf excl_mods\r
1266   | wanted_mod `elem` excl_mods\r
1267   = return Nothing\r
1268 \r
1269   | Just old_summary <- Map.lookup (wanted_mod, hsc_src) old_summary_map\r
1270   = do          -- Find its new timestamp; all the \r
1271                 -- ModSummaries in the old map have valid ml_hs_files\r
1272         let location = ms_location old_summary\r
1273             src_fn = expectJust "summariseModule" (ml_hs_file location)\r
1274 \r
1275                 -- check the modification time on the source file, and\r
1276                 -- return the cached summary if it hasn't changed.  If the\r
1277                 -- file has disappeared, we need to call the Finder again.\r
1278         case maybe_buf of\r
1279            Just (_,t) -> check_timestamp old_summary location src_fn t\r
1280            Nothing    -> do\r
1281                 m <- tryIO (getModificationTime src_fn)\r
1282                 case m of\r
1283                    Right t -> check_timestamp old_summary location src_fn t\r
1284                    Left e | isDoesNotExistError e -> find_it\r
1285                           | otherwise             -> ioError e\r
1286 \r
1287   | otherwise  = find_it\r
1288   where\r
1289     dflags = hsc_dflags hsc_env\r
1290 \r
1291     hsc_src = if is_boot then HsBootFile else HsSrcFile\r
1292 \r
1293     check_timestamp old_summary location src_fn src_timestamp\r
1294         | ms_hs_date old_summary == src_timestamp = do\r
1295                 -- update the object-file timestamp\r
1296                 obj_timestamp <- \r
1297                     if isObjectTarget (hscTarget (hsc_dflags hsc_env))\r
1298                        || obj_allowed -- bug #1205\r
1299                        then getObjTimestamp location is_boot\r
1300                        else return Nothing\r
1301                 return (Just old_summary{ ms_obj_date = obj_timestamp })\r
1302         | otherwise = \r
1303                 -- source changed: re-summarise.\r
1304                 new_summary location (ms_mod old_summary) src_fn src_timestamp\r
1305 \r
1306     find_it = do\r
1307         -- Don't use the Finder's cache this time.  If the module was\r
1308         -- previously a package module, it may have now appeared on the\r
1309         -- search path, so we want to consider it to be a home module.  If\r
1310         -- the module was previously a home module, it may have moved.\r
1311         uncacheModule hsc_env wanted_mod\r
1312         found <- findImportedModule hsc_env wanted_mod Nothing\r
1313         case found of\r
1314              Found location mod \r
1315                 | isJust (ml_hs_file location) ->\r
1316                         -- Home package\r
1317                          just_found location mod\r
1318                 | otherwise -> \r
1319                         -- Drop external-pkg\r
1320                         ASSERT(modulePackageId mod /= thisPackage dflags)\r
1321                         return Nothing\r
1322                         \r
1323              err -> noModError dflags loc wanted_mod err\r
1324                         -- Not found\r
1325 \r
1326     just_found location mod = do\r
1327                 -- Adjust location to point to the hs-boot source file, \r
1328                 -- hi file, object file, when is_boot says so\r
1329         let location' | is_boot   = addBootSuffixLocn location\r
1330                       | otherwise = location\r
1331             src_fn = expectJust "summarise2" (ml_hs_file location')\r
1332 \r
1333                 -- Check that it exists\r
1334                 -- It might have been deleted since the Finder last found it\r
1335         maybe_t <- modificationTimeIfExists src_fn\r
1336         case maybe_t of\r
1337           Nothing -> noHsFileErr loc src_fn\r
1338           Just t  -> new_summary location' mod src_fn t\r
1339 \r
1340 \r
1341     new_summary location mod src_fn src_timestamp\r
1342       = do\r
1343         -- Preprocess the source file and get its imports\r
1344         -- The dflags' contains the OPTIONS pragmas\r
1345         (dflags', hspp_fn, buf) <- preprocessFile hsc_env src_fn Nothing maybe_buf\r
1346         (srcimps, the_imps, L mod_loc mod_name) <- getImports dflags' buf hspp_fn src_fn\r
1347 \r
1348         when (mod_name /= wanted_mod) $\r
1349                 throwOneError $ mkPlainErrMsg mod_loc $ \r
1350                               text "File name does not match module name:" \r
1351                               $$ text "Saw:" <+> quotes (ppr mod_name)\r
1352                               $$ text "Expected:" <+> quotes (ppr wanted_mod)\r
1353 \r
1354                 -- Find the object timestamp, and return the summary\r
1355         obj_timestamp <-\r
1356            if isObjectTarget (hscTarget (hsc_dflags hsc_env))\r
1357               || obj_allowed -- bug #1205\r
1358               then getObjTimestamp location is_boot\r
1359               else return Nothing\r
1360 \r
1361         return (Just (ModSummary { ms_mod       = mod,\r
1362                               ms_hsc_src   = hsc_src,\r
1363                               ms_location  = location,\r
1364                               ms_hspp_file = hspp_fn,\r
1365                               ms_hspp_opts = dflags',\r
1366                               ms_hspp_buf  = Just buf,\r
1367                               ms_srcimps   = srcimps,\r
1368                               ms_imps      = the_imps,\r
1369                               ms_hs_date   = src_timestamp,\r
1370                               ms_obj_date  = obj_timestamp }))\r
1371 \r
1372 \r
1373 getObjTimestamp :: ModLocation -> Bool -> IO (Maybe ClockTime)\r
1374 getObjTimestamp location is_boot\r
1375   = if is_boot then return Nothing\r
1376                else modificationTimeIfExists (ml_obj_file location)\r
1377 \r
1378 \r
1379 preprocessFile :: HscEnv\r
1380                -> FilePath\r
1381                -> Maybe Phase -- ^ Starting phase\r
1382                -> Maybe (StringBuffer,ClockTime)\r
1383                -> IO (DynFlags, FilePath, StringBuffer)\r
1384 preprocessFile hsc_env src_fn mb_phase Nothing\r
1385   = do\r
1386         (dflags', hspp_fn) <- preprocess hsc_env (src_fn, mb_phase)\r
1387         buf <- hGetStringBuffer hspp_fn\r
1388         return (dflags', hspp_fn, buf)\r
1389 \r
1390 preprocessFile hsc_env src_fn mb_phase (Just (buf, _time))\r
1391   = do\r
1392         let dflags = hsc_dflags hsc_env\r
1393         -- case we bypass the preprocessing stage?\r
1394         let \r
1395             local_opts = getOptions dflags buf src_fn\r
1396         --\r
1397         (dflags', leftovers, warns)\r
1398             <- parseDynamicNoPackageFlags dflags local_opts\r
1399         checkProcessArgsResult leftovers\r
1400         handleFlagWarnings dflags' warns\r
1401 \r
1402         let\r
1403             needs_preprocessing\r
1404                 | Just (Unlit _) <- mb_phase    = True\r
1405                 | Nothing <- mb_phase, Unlit _ <- startPhase src_fn  = True\r
1406                   -- note: local_opts is only required if there's no Unlit phase\r
1407                 | xopt Opt_Cpp dflags'          = True\r
1408                 | dopt Opt_Pp  dflags'          = True\r
1409                 | otherwise                     = False\r
1410 \r
1411         when needs_preprocessing $\r
1412            ghcError (ProgramError "buffer needs preprocesing; interactive check disabled")\r
1413 \r
1414         return (dflags', src_fn, buf)\r
1415 \r
1416 \r
1417 -----------------------------------------------------------------------------\r
1418 --                      Error messages\r
1419 -----------------------------------------------------------------------------\r
1420 \r
1421 noModError :: DynFlags -> SrcSpan -> ModuleName -> FindResult -> IO ab\r
1422 -- ToDo: we don't have a proper line number for this error\r
1423 noModError dflags loc wanted_mod err\r
1424   = throwOneError $ mkPlainErrMsg loc $ cannotFindModule dflags wanted_mod err\r
1425                                 \r
1426 noHsFileErr :: SrcSpan -> String -> IO a\r
1427 noHsFileErr loc path\r
1428   = throwOneError $ mkPlainErrMsg loc $ text "Can't find" <+> text path\r
1429  \r
1430 packageModErr :: ModuleName -> IO a\r
1431 packageModErr mod\r
1432   = throwOneError $ mkPlainErrMsg noSrcSpan $\r
1433         text "module" <+> quotes (ppr mod) <+> text "is a package module"\r
1434 \r
1435 multiRootsErr :: [ModSummary] -> IO ()\r
1436 multiRootsErr [] = panic "multiRootsErr"\r
1437 multiRootsErr summs@(summ1:_)\r
1438   = throwOneError $ mkPlainErrMsg noSrcSpan $\r
1439         text "module" <+> quotes (ppr mod) <+> \r
1440         text "is defined in multiple files:" <+>\r
1441         sep (map text files)\r
1442   where\r
1443     mod = ms_mod summ1\r
1444     files = map (expectJust "checkDup" . ml_hs_file . ms_location) summs\r
1445 \r
1446 cyclicModuleErr :: [ModSummary] -> SDoc\r
1447 cyclicModuleErr ms\r
1448   = hang (ptext (sLit "Module imports form a cycle for modules:"))\r
1449        2 (vcat (map show_one ms))\r
1450   where\r
1451     mods_in_cycle = map ms_mod_name ms\r
1452     imp_modname = unLoc . ideclName . unLoc\r
1453     just_in_cycle = filter ((`elem` mods_in_cycle) . imp_modname)\r
1454 \r
1455     show_one ms = \r
1456            vcat [ show_mod (ms_hsc_src ms) (ms_mod_name ms) <+>\r
1457                   maybe empty (parens . text) (ml_hs_file (ms_location ms)),\r
1458                   nest 2 $ ptext (sLit "imports:") <+> vcat [\r
1459                      pp_imps HsBootFile (just_in_cycle $ ms_srcimps ms),\r
1460                      pp_imps HsSrcFile  (just_in_cycle $ ms_imps ms) ]\r
1461                 ]\r
1462     show_mod hsc_src mod = ppr mod <> text (hscSourceString hsc_src)\r
1463     pp_imps src imps = fsep (map (show_mod src . unLoc . ideclName . unLoc) imps)\r