The default cleanup handler should /always/ delete the temp files
[ghc-hetmet.git] / compiler / main / GHC.hs
1 -- -----------------------------------------------------------------------------
2 --
3 -- (c) The University of Glasgow, 2005
4 --
5 -- The GHC API
6 --
7 -- -----------------------------------------------------------------------------
8
9 module GHC (
10         -- * Initialisation
11         defaultErrorHandler,
12         defaultCleanupHandler,
13
14         -- * GHC Monad
15         Ghc, GhcT, GhcMonad(..),
16         runGhc, runGhcT, initGhcMonad,
17         gcatch, gbracket, gfinally,
18         clearWarnings, getWarnings, hasWarnings,
19         printExceptionAndWarnings, printWarnings,
20         handleSourceError, defaultCallbacks, GhcApiCallbacks(..),
21         needsTemplateHaskell,
22
23         -- * Flags and settings
24         DynFlags(..), DynFlag(..), Severity(..), HscTarget(..), dopt,
25         GhcMode(..), GhcLink(..), defaultObjectTarget,
26         parseDynamicFlags,
27         getSessionDynFlags,
28         setSessionDynFlags,
29         parseStaticFlags,
30
31         -- * Targets
32         Target(..), TargetId(..), Phase,
33         setTargets,
34         getTargets,
35         addTarget,
36         removeTarget,
37         guessTarget,
38         
39         -- * Extending the program scope 
40         extendGlobalRdrScope,
41         setGlobalRdrScope,
42         extendGlobalTypeScope,
43         setGlobalTypeScope,
44
45         -- * Loading\/compiling the program
46         depanal,
47         load, loadWithLogger, LoadHowMuch(..),
48         SuccessFlag(..), succeeded, failed,
49         defaultWarnErrLogger, WarnErrLogger,
50         workingDirectoryChanged,
51         parseModule, typecheckModule, desugarModule, loadModule,
52         ParsedModule(..), TypecheckedModule(..), DesugaredModule(..),
53         TypecheckedSource, ParsedSource, RenamedSource,   -- ditto
54         TypecheckedMod, ParsedMod,
55         moduleInfo, renamedSource, typecheckedSource,
56         parsedSource, coreModule,
57         compileToCoreModule, compileToCoreSimplified,
58         compileCoreToObj,
59         getModSummary,
60
61         -- * Parsing Haddock comments
62         parseHaddockComment,
63
64         -- * Inspecting the module structure of the program
65         ModuleGraph, ModSummary(..), ms_mod_name, ModLocation(..),
66         getModuleGraph,
67         isLoaded,
68         topSortModuleGraph,
69
70         -- * Inspecting modules
71         ModuleInfo,
72         getModuleInfo,
73         modInfoTyThings,
74         modInfoTopLevelScope,
75         modInfoExports,
76         modInfoInstances,
77         modInfoIsExportedName,
78         modInfoLookupName,
79         lookupGlobalName,
80         findGlobalAnns,
81         mkPrintUnqualifiedForModule,
82
83         -- * Querying the environment
84         packageDbModules,
85
86         -- * Printing
87         PrintUnqualified, alwaysQualify,
88
89         -- * Interactive evaluation
90         getBindings, getPrintUnqual,
91         findModule,
92 #ifdef GHCI
93         setContext, getContext, 
94         getNamesInScope,
95         getRdrNamesInScope,
96         getGRE,
97         moduleIsInterpreted,
98         getInfo,
99         exprType,
100         typeKind,
101         parseName,
102         RunResult(..),  
103         runStmt, SingleStep(..),
104         resume,
105         Resume(resumeStmt, resumeThreadId, resumeBreakInfo, resumeSpan,
106                resumeHistory, resumeHistoryIx),
107         History(historyBreakInfo, historyEnclosingDecl), 
108         GHC.getHistorySpan, getHistoryModule,
109         getResumeContext,
110         abandon, abandonAll,
111         InteractiveEval.back,
112         InteractiveEval.forward,
113         showModule,
114         isModuleInterpreted,
115         InteractiveEval.compileExpr, HValue, dynCompileExpr,
116         lookupName,
117         GHC.obtainTermFromId, GHC.obtainTermFromVal, reconstructType,
118         modInfoModBreaks,
119         ModBreaks(..), BreakIndex,
120         BreakInfo(breakInfo_number, breakInfo_module),
121         BreakArray, setBreakOn, setBreakOff, getBreak,
122 #endif
123
124         -- * Abstract syntax elements
125
126         -- ** Packages
127         PackageId,
128
129         -- ** Modules
130         Module, mkModule, pprModule, moduleName, modulePackageId,
131         ModuleName, mkModuleName, moduleNameString,
132
133         -- ** Names
134         Name, 
135         isExternalName, nameModule, pprParenSymName, nameSrcSpan,
136         NamedThing(..),
137         RdrName(Qual,Unqual),
138         
139         -- ** Identifiers
140         Id, idType,
141         isImplicitId, isDeadBinder,
142         isExportedId, isLocalId, isGlobalId,
143         isRecordSelector,
144         isPrimOpId, isFCallId, isClassOpId_maybe,
145         isDataConWorkId, idDataCon,
146         isBottomingId, isDictonaryId,
147         recordSelectorFieldLabel,
148
149         -- ** Type constructors
150         TyCon, 
151         tyConTyVars, tyConDataCons, tyConArity,
152         isClassTyCon, isSynTyCon, isNewTyCon, isPrimTyCon, isFunTyCon,
153         isOpenTyCon,
154         synTyConDefn, synTyConType, synTyConResKind,
155
156         -- ** Type variables
157         TyVar,
158         alphaTyVars,
159
160         -- ** Data constructors
161         DataCon,
162         dataConSig, dataConType, dataConTyCon, dataConFieldLabels,
163         dataConIsInfix, isVanillaDataCon,
164         dataConStrictMarks,  
165         StrictnessMark(..), isMarkedStrict,
166
167         -- ** Classes
168         Class, 
169         classMethods, classSCTheta, classTvsFds,
170         pprFundeps,
171
172         -- ** Instances
173         Instance, 
174         instanceDFunId, pprInstance, pprInstanceHdr,
175
176         -- ** Types and Kinds
177         Type, splitForAllTys, funResultTy, 
178         pprParendType, pprTypeApp, 
179         Kind,
180         PredType,
181         ThetaType, pprThetaArrow,
182
183         -- ** Entities
184         TyThing(..), 
185
186         -- ** Syntax
187         module HsSyn, -- ToDo: remove extraneous bits
188
189         -- ** Fixities
190         FixityDirection(..), 
191         defaultFixity, maxPrecedence, 
192         negateFixity,
193         compareFixity,
194
195         -- ** Source locations
196         SrcLoc, pprDefnLoc,
197         mkSrcLoc, isGoodSrcLoc, noSrcLoc,
198         srcLocFile, srcLocLine, srcLocCol,
199         SrcSpan,
200         mkSrcSpan, srcLocSpan, isGoodSrcSpan, noSrcSpan,
201         srcSpanStart, srcSpanEnd,
202         srcSpanFile, 
203         srcSpanStartLine, srcSpanEndLine, 
204         srcSpanStartCol, srcSpanEndCol,
205
206         -- ** Located
207         Located(..),
208
209         -- *** Constructing Located
210         noLoc, mkGeneralLocated,
211
212         -- *** Deconstructing Located
213         getLoc, unLoc,
214
215         -- *** Combining and comparing Located values
216         eqLocated, cmpLocated, combineLocs, addCLoc,
217         leftmost_smallest, leftmost_largest, rightmost,
218         spans, isSubspanOf,
219
220         -- * Exceptions
221         GhcException(..), showGhcException,
222
223         -- * Token stream manipulations
224         Token,
225         getTokenStream, getRichTokenStream,
226         showRichTokenStream, addSourceToTokens,
227
228         -- * Miscellaneous
229         --sessionHscEnv,
230         cyclicModuleErr,
231   ) where
232
233 {-
234  ToDo:
235
236   * inline bits of HscMain here to simplify layering: hscTcExpr, hscStmt.
237   * what StaticFlags should we expose, if any?
238 -}
239
240 #include "HsVersions.h"
241
242 #ifdef GHCI
243 import qualified Linker
244 import Linker           ( HValue )
245 import ByteCodeInstr
246 import BreakArray
247 import NameSet
248 import InteractiveEval
249 import TcRnDriver
250 #endif
251
252 import TcIface
253 import TcRnTypes        hiding (LIE)
254 import TcRnMonad        ( initIfaceCheck )
255 import Packages
256 import NameSet
257 import RdrName
258 import qualified HsSyn -- hack as we want to reexport the whole module
259 import HsSyn hiding ((<.>))
260 import Type             hiding (typeKind)
261 import TcType           hiding (typeKind)
262 import Id
263 import Var
264 import TysPrim          ( alphaTyVars )
265 import TyCon
266 import Class
267 import FunDeps
268 import DataCon
269 import Name             hiding ( varName )
270 import OccName          ( parenSymOcc )
271 import InstEnv          ( Instance, instanceDFunId, pprInstance, pprInstanceHdr,
272                           emptyInstEnv )
273 import FamInstEnv       ( emptyFamInstEnv )
274 import SrcLoc
275 --import CoreSyn
276 import TidyPgm
277 import DriverPipeline
278 import DriverPhases     ( HscSource(..), Phase(..), isHaskellSrcFilename, startPhase )
279 import HeaderInfo
280 import Finder
281 import HscMain
282 import HscTypes
283 import DynFlags
284 import StaticFlagParser
285 import qualified StaticFlags
286 import SysTools     ( initSysTools, cleanTempFiles, cleanTempFilesExcept,
287                       cleanTempDirs )
288 import Annotations
289 import Module
290 import LazyUniqFM
291 import qualified UniqFM as UFM
292 import UniqSet
293 import Unique
294 import FiniteMap
295 import Panic
296 import Digraph
297 import Bag              ( unitBag, listToBag, emptyBag, isEmptyBag )
298 import ErrUtils
299 import MonadUtils
300 import Util
301 import StringBuffer     ( StringBuffer, hGetStringBuffer, nextChar )
302 import Outputable
303 import BasicTypes
304 import Maybes           ( expectJust, mapCatMaybes )
305 import HaddockParse
306 import HaddockLex       ( tokenise )
307 import FastString
308 import Lexer
309
310 import Control.Concurrent
311 import System.Directory ( getModificationTime, doesFileExist,
312                           getCurrentDirectory )
313 import Data.Maybe
314 import Data.List
315 import qualified Data.List as List
316 import Data.Typeable    ( Typeable )
317 import Data.Word        ( Word8 )
318 import Control.Monad
319 import System.Exit      ( exitWith, ExitCode(..) )
320 import System.Time      ( ClockTime, getClockTime )
321 import Exception
322 import Data.IORef
323 import System.FilePath
324 import System.IO
325 import System.IO.Error  ( try, isDoesNotExistError )
326 import Prelude hiding (init)
327
328
329 -- -----------------------------------------------------------------------------
330 -- Exception handlers
331
332 -- | Install some default exception handlers and run the inner computation.
333 -- Unless you want to handle exceptions yourself, you should wrap this around
334 -- the top level of your program.  The default handlers output the error
335 -- message(s) to stderr and exit cleanly.
336 defaultErrorHandler :: (ExceptionMonad m, MonadIO m) => DynFlags -> m a -> m a
337 defaultErrorHandler dflags inner =
338   -- top-level exception handler: any unrecognised exception is a compiler bug.
339   ghandle (\exception -> liftIO $ do
340            hFlush stdout
341            case fromException exception of
342                 -- an IO exception probably isn't our fault, so don't panic
343                 Just (ioe :: IOException) ->
344                   fatalErrorMsg dflags (text (show ioe))
345                 _ -> case fromException exception of
346                      Just StackOverflow ->
347                          fatalErrorMsg dflags (text "stack overflow: use +RTS -K<size> to increase it")
348                      _ -> case fromException exception of
349                           Just (ex :: ExitCode) -> throw ex
350                           _ ->
351                               fatalErrorMsg dflags
352                                   (text (show (Panic (show exception))))
353            exitWith (ExitFailure 1)
354          ) $
355
356   -- error messages propagated as exceptions
357   handleGhcException
358             (\ge -> liftIO $ do
359                 hFlush stdout
360                 case ge of
361                      PhaseFailed _ code -> exitWith code
362                      Interrupted -> exitWith (ExitFailure 1)
363                      _ -> do fatalErrorMsg dflags (text (show ge))
364                              exitWith (ExitFailure 1)
365             ) $
366   inner
367
368 -- | Install a default cleanup handler to remove temporary files deposited by
369 -- a GHC run.  This is seperate from 'defaultErrorHandler', because you might
370 -- want to override the error handling, but still get the ordinary cleanup
371 -- behaviour.
372 defaultCleanupHandler :: (ExceptionMonad m, MonadIO m) =>
373                          DynFlags -> m a -> m a
374 defaultCleanupHandler dflags inner =
375     -- make sure we clean up after ourselves
376     inner `gfinally`
377           (liftIO $ do
378               cleanTempFiles dflags
379               cleanTempDirs dflags
380           )
381           --  exceptions will be blocked while we clean the temporary files,
382           -- so there shouldn't be any difficulty if we receive further
383           -- signals.
384
385 -- | Print the error message and all warnings.  Useful inside exception
386 --   handlers.  Clears warnings after printing.
387 printExceptionAndWarnings :: GhcMonad m => SourceError -> m ()
388 printExceptionAndWarnings err = do
389     let errs = srcErrorMessages err
390     warns <- getWarnings
391     dflags <- getSessionDynFlags
392     if isEmptyBag errs
393        -- Empty errors means we failed due to -Werror.  (Since this function
394        -- takes a source error as argument, we know for sure _some_ error
395        -- did indeed happen.)
396        then liftIO $ do
397               printBagOfWarnings dflags warns
398               printBagOfErrors dflags (unitBag warnIsErrorMsg)
399        else liftIO $ printBagOfErrors dflags errs
400     clearWarnings
401
402 -- | Print all accumulated warnings using 'log_action'.
403 printWarnings :: GhcMonad m => m ()
404 printWarnings = do
405     dflags <- getSessionDynFlags
406     warns <- getWarnings
407     liftIO $ printBagOfWarnings dflags warns
408     clearWarnings
409
410 -- | Run function for the 'Ghc' monad.
411 --
412 -- It initialises the GHC session and warnings via 'initGhcMonad'.  Each call
413 -- to this function will create a new session which should not be shared among
414 -- several threads.
415 --
416 -- Any errors not handled inside the 'Ghc' action are propagated as IO
417 -- exceptions.
418
419 runGhc :: Maybe FilePath  -- ^ See argument to 'initGhcMonad'.
420        -> Ghc a           -- ^ The action to perform.
421        -> IO a
422 runGhc mb_top_dir ghc = do
423   wref <- newIORef emptyBag
424   ref <- newIORef undefined
425   let session = Session ref wref
426   flip unGhc session $ do
427     initGhcMonad mb_top_dir
428     ghc
429   -- XXX: unregister interrupt handlers here?
430
431 -- | Run function for 'GhcT' monad transformer.
432 --
433 -- It initialises the GHC session and warnings via 'initGhcMonad'.  Each call
434 -- to this function will create a new session which should not be shared among
435 -- several threads.
436
437 runGhcT :: (ExceptionMonad m, Functor m, MonadIO m) =>
438            Maybe FilePath  -- ^ See argument to 'initGhcMonad'.
439         -> GhcT m a        -- ^ The action to perform.
440         -> m a
441 runGhcT mb_top_dir ghct = do
442   wref <- liftIO $ newIORef emptyBag
443   ref <- liftIO $ newIORef undefined
444   let session = Session ref wref
445   flip unGhcT session $ do
446     initGhcMonad mb_top_dir
447     ghct
448
449 -- | Initialise a GHC session.
450 --
451 -- If you implement a custom 'GhcMonad' you must call this function in the
452 -- monad run function.  It will initialise the session variable and clear all
453 -- warnings.
454 --
455 -- The first argument should point to the directory where GHC's library files
456 -- reside.  More precisely, this should be the output of @ghc --print-libdir@
457 -- of the version of GHC the module using this API is compiled with.  For
458 -- portability, you should use the @ghc-paths@ package, available at
459 -- <http://hackage.haskell.org/cgi-bin/hackage-scripts/package/ghc-paths>.
460
461 initGhcMonad :: GhcMonad m => Maybe FilePath -> m ()
462 initGhcMonad mb_top_dir = do
463   -- catch ^C
464   main_thread <- liftIO $ myThreadId
465   liftIO $ modifyMVar_ interruptTargetThread (return . (main_thread :))
466   liftIO $ installSignalHandlers
467
468   liftIO $ StaticFlags.initStaticOpts
469
470   dflags0 <- liftIO $ initDynFlags defaultDynFlags
471   dflags <- liftIO $ initSysTools mb_top_dir dflags0
472   env <- liftIO $ newHscEnv defaultCallbacks dflags
473   setSession env
474   clearWarnings
475
476 defaultCallbacks :: GhcApiCallbacks
477 defaultCallbacks =
478   GhcApiCallbacks {
479     reportModuleCompilationResult =
480         \_ mb_err -> defaultWarnErrLogger mb_err
481   }
482
483 -- -----------------------------------------------------------------------------
484 -- Flags & settings
485
486 -- | Grabs the DynFlags from the Session
487 getSessionDynFlags :: GhcMonad m => m DynFlags
488 getSessionDynFlags = withSession (return . hsc_dflags)
489
490 -- | Updates the DynFlags in a Session.  This also reads
491 -- the package database (unless it has already been read),
492 -- and prepares the compilers knowledge about packages.  It
493 -- can be called again to load new packages: just add new
494 -- package flags to (packageFlags dflags).
495 --
496 -- Returns a list of new packages that may need to be linked in using
497 -- the dynamic linker (see 'linkPackages') as a result of new package
498 -- flags.  If you are not doing linking or doing static linking, you
499 -- can ignore the list of packages returned.
500 --
501 setSessionDynFlags :: GhcMonad m => DynFlags -> m [PackageId]
502 setSessionDynFlags dflags = do
503   (dflags', preload) <- liftIO $ initPackages dflags
504   modifySession (\h -> h{ hsc_dflags = dflags' })
505   return preload
506
507 -- | If there is no -o option, guess the name of target executable
508 -- by using top-level source file name as a base.
509 guessOutputFile :: GhcMonad m => m ()
510 guessOutputFile = modifySession $ \env ->
511     let dflags = hsc_dflags env
512         mod_graph = hsc_mod_graph env
513         mainModuleSrcPath :: Maybe String
514         mainModuleSrcPath = do
515             let isMain = (== mainModIs dflags) . ms_mod
516             [ms] <- return (filter isMain mod_graph)
517             ml_hs_file (ms_location ms)
518         name = fmap dropExtension mainModuleSrcPath
519
520 #if defined(mingw32_HOST_OS)
521         -- we must add the .exe extention unconditionally here, otherwise
522         -- when name has an extension of its own, the .exe extension will
523         -- not be added by DriverPipeline.exeFileName.  See #2248
524         name_exe = fmap (<.> "exe") name
525 #else
526         name_exe = name
527 #endif
528     in
529     case outputFile dflags of
530         Just _ -> env
531         Nothing -> env { hsc_dflags = dflags { outputFile = name_exe } }
532
533 -- -----------------------------------------------------------------------------
534 -- Targets
535
536 -- ToDo: think about relative vs. absolute file paths. And what
537 -- happens when the current directory changes.
538
539 -- | Sets the targets for this session.  Each target may be a module name
540 -- or a filename.  The targets correspond to the set of root modules for
541 -- the program\/library.  Unloading the current program is achieved by
542 -- setting the current set of targets to be empty, followed by 'load'.
543 setTargets :: GhcMonad m => [Target] -> m ()
544 setTargets targets = modifySession (\h -> h{ hsc_targets = targets })
545
546 -- | Returns the current set of targets
547 getTargets :: GhcMonad m => m [Target]
548 getTargets = withSession (return . hsc_targets)
549
550 -- | Add another target.
551 addTarget :: GhcMonad m => Target -> m ()
552 addTarget target
553   = modifySession (\h -> h{ hsc_targets = target : hsc_targets h })
554
555 -- | Remove a target
556 removeTarget :: GhcMonad m => TargetId -> m ()
557 removeTarget target_id
558   = modifySession (\h -> h{ hsc_targets = filter (hsc_targets h) })
559   where
560    filter targets = [ t | t@(Target id _ _) <- targets, id /= target_id ]
561
562 -- | Attempts to guess what Target a string refers to.  This function
563 -- implements the @--make@/GHCi command-line syntax for filenames:
564 --
565 --   - if the string looks like a Haskell source filename, then interpret it
566 --     as such
567 --
568 --   - if adding a .hs or .lhs suffix yields the name of an existing file,
569 --     then use that
570 --
571 --   - otherwise interpret the string as a module name
572 --
573 guessTarget :: GhcMonad m => String -> Maybe Phase -> m Target
574 guessTarget str (Just phase)
575    = return (Target (TargetFile str (Just phase)) True Nothing)
576 guessTarget str Nothing
577    | isHaskellSrcFilename file
578    = return (target (TargetFile file Nothing))
579    | otherwise
580    = do exists <- liftIO $ doesFileExist hs_file
581         if exists
582            then return (target (TargetFile hs_file Nothing))
583            else do
584         exists <- liftIO $ doesFileExist lhs_file
585         if exists
586            then return (target (TargetFile lhs_file Nothing))
587            else do
588         if looksLikeModuleName file
589            then return (target (TargetModule (mkModuleName file)))
590            else do
591         throwGhcException
592                  (ProgramError (showSDoc $
593                  text "target" <+> quotes (text file) <+> 
594                  text "is not a module name or a source file"))
595      where 
596          (file,obj_allowed)
597                 | '*':rest <- str = (rest, False)
598                 | otherwise       = (str,  True)
599
600          hs_file  = file <.> "hs"
601          lhs_file = file <.> "lhs"
602
603          target tid = Target tid obj_allowed Nothing
604
605 -- -----------------------------------------------------------------------------
606 -- Extending the program scope
607
608 extendGlobalRdrScope :: GhcMonad m => [GlobalRdrElt] -> m ()
609 extendGlobalRdrScope rdrElts
610     = modifySession $ \hscEnv ->
611       let global_rdr = hsc_global_rdr_env hscEnv
612       in hscEnv{ hsc_global_rdr_env = foldl extendGlobalRdrEnv global_rdr rdrElts }
613
614 setGlobalRdrScope :: GhcMonad m => [GlobalRdrElt] -> m ()
615 setGlobalRdrScope rdrElts
616     = modifySession $ \hscEnv ->
617       hscEnv{ hsc_global_rdr_env = foldl extendGlobalRdrEnv emptyGlobalRdrEnv rdrElts }
618
619 extendGlobalTypeScope :: GhcMonad m => [Id] -> m ()
620 extendGlobalTypeScope ids
621     = modifySession $ \hscEnv ->
622       let global_type = hsc_global_type_env hscEnv
623       in hscEnv{ hsc_global_type_env = extendTypeEnvWithIds global_type ids }
624
625 setGlobalTypeScope :: GhcMonad m => [Id] -> m ()
626 setGlobalTypeScope ids
627     = modifySession $ \hscEnv ->
628       hscEnv{ hsc_global_type_env = extendTypeEnvWithIds emptyTypeEnv ids }
629
630 -- -----------------------------------------------------------------------------
631 -- Parsing Haddock comments
632
633 parseHaddockComment :: String -> Either String (HsDoc RdrName)
634 parseHaddockComment string = 
635   case parseHaddockParagraphs (tokenise string) of
636     MyLeft x  -> Left x
637     MyRight x -> Right x
638
639 -- -----------------------------------------------------------------------------
640 -- Loading the program
641
642 -- | Perform a dependency analysis starting from the current targets
643 -- and update the session with the new module graph.
644 --
645 -- Dependency analysis entails parsing the @import@ directives and may
646 -- therefore require running certain preprocessors.
647 --
648 -- Note that each 'ModSummary' in the module graph caches its 'DynFlags'.
649 -- These 'DynFlags' are determined by the /current/ session 'DynFlags' and the
650 -- @OPTIONS@ and @LANGUAGE@ pragmas of the parsed module.  Thus if you want to
651 -- changes to the 'DynFlags' to take effect you need to call this function
652 -- again.
653 --
654 depanal :: GhcMonad m =>
655            [ModuleName]  -- ^ excluded modules
656         -> Bool          -- ^ allow duplicate roots
657         -> m ModuleGraph
658 depanal excluded_mods allow_dup_roots = do
659   hsc_env <- getSession
660   let
661          dflags  = hsc_dflags hsc_env
662          targets = hsc_targets hsc_env
663          old_graph = hsc_mod_graph hsc_env
664         
665   liftIO $ showPass dflags "Chasing dependencies"
666   liftIO $ debugTraceMsg dflags 2 (hcat [
667              text "Chasing modules from: ",
668              hcat (punctuate comma (map pprTarget targets))])
669
670   mod_graph <- downsweep hsc_env old_graph excluded_mods allow_dup_roots
671   modifySession $ \_ -> hsc_env { hsc_mod_graph = mod_graph }
672   return mod_graph
673
674 -- | Describes which modules of the module graph need to be loaded.
675 data LoadHowMuch
676    = LoadAllTargets
677      -- ^ Load all targets and its dependencies.
678    | LoadUpTo ModuleName
679      -- ^ Load only the given module and its dependencies.
680    | LoadDependenciesOf ModuleName
681      -- ^ Load only the dependencies of the given module, but not the module
682      -- itself.
683
684 -- | Try to load the program.  See 'LoadHowMuch' for the different modes.
685 --
686 -- This function implements the core of GHC's @--make@ mode.  It preprocesses,
687 -- compiles and loads the specified modules, avoiding re-compilation wherever
688 -- possible.  Depending on the target (see 'DynFlags.hscTarget') compilating
689 -- and loading may result in files being created on disk.
690 --
691 -- Calls the 'reportModuleCompilationResult' callback after each compiling
692 -- each module, whether successful or not.
693 --
694 -- Throw a 'SourceError' if errors are encountered before the actual
695 -- compilation starts (e.g., during dependency analysis).  All other errors
696 -- are reported using the callback.
697 --
698 load :: GhcMonad m => LoadHowMuch -> m SuccessFlag
699 load how_much = do
700    mod_graph <- depanal [] False
701    load2 how_much mod_graph
702
703 -- | A function called to log warnings and errors.
704 type WarnErrLogger = GhcMonad m => Maybe SourceError -> m ()
705
706 defaultWarnErrLogger :: WarnErrLogger
707 defaultWarnErrLogger Nothing = printWarnings
708 defaultWarnErrLogger (Just e) = printExceptionAndWarnings e
709
710 -- | Try to load the program.  If a Module is supplied, then just
711 -- attempt to load up to this target.  If no Module is supplied,
712 -- then try to load all targets.
713 --
714 -- The first argument is a function that is called after compiling each
715 -- module to print wanrings and errors.
716 --
717 -- While compiling a module, all 'SourceError's are caught and passed to the
718 -- logger, however, this function may still throw a 'SourceError' if
719 -- dependency analysis failed (e.g., due to a parse error).
720 --
721 loadWithLogger :: GhcMonad m => WarnErrLogger -> LoadHowMuch -> m SuccessFlag
722 loadWithLogger logger how_much = do
723     -- Dependency analysis first.  Note that this fixes the module graph:
724     -- even if we don't get a fully successful upsweep, the full module
725     -- graph is still retained in the Session.  We can tell which modules
726     -- were successfully loaded by inspecting the Session's HPT.
727     withLocalCallbacks (\cbs -> cbs { reportModuleCompilationResult =
728                                           \_ -> logger }) $
729       load how_much
730
731 load2 :: GhcMonad m => LoadHowMuch -> [ModSummary]
732       -> m SuccessFlag
733 load2 how_much mod_graph = do
734         guessOutputFile
735         hsc_env <- getSession
736
737         let hpt1      = hsc_HPT hsc_env
738         let dflags    = hsc_dflags hsc_env
739
740         -- The "bad" boot modules are the ones for which we have
741         -- B.hs-boot in the module graph, but no B.hs
742         -- The downsweep should have ensured this does not happen
743         -- (see msDeps)
744         let all_home_mods = [ms_mod_name s 
745                             | s <- mod_graph, not (isBootSummary s)]
746             bad_boot_mods = [s        | s <- mod_graph, isBootSummary s,
747                                         not (ms_mod_name s `elem` all_home_mods)]
748         ASSERT( null bad_boot_mods ) return ()
749
750         -- check that the module given in HowMuch actually exists, otherwise
751         -- topSortModuleGraph will bomb later.
752         let checkHowMuch (LoadUpTo m)           = checkMod m
753             checkHowMuch (LoadDependenciesOf m) = checkMod m
754             checkHowMuch _ = id
755
756             checkMod m and_then
757                 | m `elem` all_home_mods = and_then
758                 | otherwise = do 
759                         liftIO $ errorMsg dflags (text "no such module:" <+>
760                                          quotes (ppr m))
761                         return Failed
762
763         checkHowMuch how_much $ do
764
765         -- mg2_with_srcimps drops the hi-boot nodes, returning a 
766         -- graph with cycles.  Among other things, it is used for
767         -- backing out partially complete cycles following a failed
768         -- upsweep, and for removing from hpt all the modules
769         -- not in strict downwards closure, during calls to compile.
770         let mg2_with_srcimps :: [SCC ModSummary]
771             mg2_with_srcimps = topSortModuleGraph True mod_graph Nothing
772
773         -- If we can determine that any of the {-# SOURCE #-} imports
774         -- are definitely unnecessary, then emit a warning.
775         warnUnnecessarySourceImports mg2_with_srcimps
776
777         let
778             -- check the stability property for each module.
779             stable_mods@(stable_obj,stable_bco)
780                 = checkStability hpt1 mg2_with_srcimps all_home_mods
781
782             -- prune bits of the HPT which are definitely redundant now,
783             -- to save space.
784             pruned_hpt = pruneHomePackageTable hpt1 
785                                 (flattenSCCs mg2_with_srcimps)
786                                 stable_mods
787
788         liftIO $ evaluate pruned_hpt
789
790         -- before we unload anything, make sure we don't leave an old
791         -- interactive context around pointing to dead bindings.  Also,
792         -- write the pruned HPT to allow the old HPT to be GC'd.
793         modifySession $ \_ -> hsc_env{ hsc_IC = emptyInteractiveContext,
794                                        hsc_HPT = pruned_hpt }
795
796         liftIO $ debugTraceMsg dflags 2 (text "Stable obj:" <+> ppr stable_obj $$
797                                 text "Stable BCO:" <+> ppr stable_bco)
798
799         -- Unload any modules which are going to be re-linked this time around.
800         let stable_linkables = [ linkable
801                                | m <- stable_obj++stable_bco,
802                                  Just hmi <- [lookupUFM pruned_hpt m],
803                                  Just linkable <- [hm_linkable hmi] ]
804         liftIO $ unload hsc_env stable_linkables
805
806         -- We could at this point detect cycles which aren't broken by
807         -- a source-import, and complain immediately, but it seems better
808         -- to let upsweep_mods do this, so at least some useful work gets
809         -- done before the upsweep is abandoned.
810         --hPutStrLn stderr "after tsort:\n"
811         --hPutStrLn stderr (showSDoc (vcat (map ppr mg2)))
812
813         -- Now do the upsweep, calling compile for each module in
814         -- turn.  Final result is version 3 of everything.
815
816         -- Topologically sort the module graph, this time including hi-boot
817         -- nodes, and possibly just including the portion of the graph
818         -- reachable from the module specified in the 2nd argument to load.
819         -- This graph should be cycle-free.
820         -- If we're restricting the upsweep to a portion of the graph, we
821         -- also want to retain everything that is still stable.
822         let full_mg :: [SCC ModSummary]
823             full_mg    = topSortModuleGraph False mod_graph Nothing
824
825             maybe_top_mod = case how_much of
826                                 LoadUpTo m           -> Just m
827                                 LoadDependenciesOf m -> Just m
828                                 _                    -> Nothing
829
830             partial_mg0 :: [SCC ModSummary]
831             partial_mg0 = topSortModuleGraph False mod_graph maybe_top_mod
832
833             -- LoadDependenciesOf m: we want the upsweep to stop just
834             -- short of the specified module (unless the specified module
835             -- is stable).
836             partial_mg
837                 | LoadDependenciesOf _mod <- how_much
838                 = ASSERT( case last partial_mg0 of 
839                             AcyclicSCC ms -> ms_mod_name ms == _mod; _ -> False )
840                   List.init partial_mg0
841                 | otherwise
842                 = partial_mg0
843   
844             stable_mg = 
845                 [ AcyclicSCC ms
846                 | AcyclicSCC ms <- full_mg,
847                   ms_mod_name ms `elem` stable_obj++stable_bco,
848                   ms_mod_name ms `notElem` [ ms_mod_name ms' | 
849                                                 AcyclicSCC ms' <- partial_mg ] ]
850
851             mg = stable_mg ++ partial_mg
852
853         -- clean up between compilations
854         let cleanup = cleanTempFilesExcept dflags
855                           (ppFilesFromSummaries (flattenSCCs mg2_with_srcimps))
856
857         liftIO $ debugTraceMsg dflags 2 (hang (text "Ready for upsweep")
858                                    2 (ppr mg))
859         (upsweep_ok, hsc_env1, modsUpswept)
860            <- upsweep (hsc_env { hsc_HPT = emptyHomePackageTable })
861                       pruned_hpt stable_mods cleanup mg
862
863         -- Make modsDone be the summaries for each home module now
864         -- available; this should equal the domain of hpt3.
865         -- Get in in a roughly top .. bottom order (hence reverse).
866
867         let modsDone = reverse modsUpswept
868
869         -- Try and do linking in some form, depending on whether the
870         -- upsweep was completely or only partially successful.
871
872         if succeeded upsweep_ok
873
874          then 
875            -- Easy; just relink it all.
876            do liftIO $ debugTraceMsg dflags 2 (text "Upsweep completely successful.")
877
878               -- Clean up after ourselves
879               liftIO $ cleanTempFilesExcept dflags (ppFilesFromSummaries modsDone)
880
881               -- Issue a warning for the confusing case where the user
882               -- said '-o foo' but we're not going to do any linking.
883               -- We attempt linking if either (a) one of the modules is
884               -- called Main, or (b) the user said -no-hs-main, indicating
885               -- that main() is going to come from somewhere else.
886               --
887               let ofile = outputFile dflags
888               let no_hs_main = dopt Opt_NoHsMain dflags
889               let 
890                 main_mod = mainModIs dflags
891                 a_root_is_Main = any ((==main_mod).ms_mod) mod_graph
892                 do_linking = a_root_is_Main || no_hs_main
893
894               when (ghcLink dflags == LinkBinary 
895                     && isJust ofile && not do_linking) $
896                 liftIO $ debugTraceMsg dflags 1 $
897                     text ("Warning: output was redirected with -o, " ++
898                           "but no output will be generated\n" ++
899                           "because there is no " ++ 
900                           moduleNameString (moduleName main_mod) ++ " module.")
901
902               -- link everything together
903               linkresult <- liftIO $ link (ghcLink dflags) dflags do_linking (hsc_HPT hsc_env1)
904
905               loadFinish Succeeded linkresult hsc_env1
906
907          else 
908            -- Tricky.  We need to back out the effects of compiling any
909            -- half-done cycles, both so as to clean up the top level envs
910            -- and to avoid telling the interactive linker to link them.
911            do liftIO $ debugTraceMsg dflags 2 (text "Upsweep partially successful.")
912
913               let modsDone_names
914                      = map ms_mod modsDone
915               let mods_to_zap_names 
916                      = findPartiallyCompletedCycles modsDone_names 
917                           mg2_with_srcimps
918               let mods_to_keep
919                      = filter ((`notElem` mods_to_zap_names).ms_mod) 
920                           modsDone
921
922               let hpt4 = retainInTopLevelEnvs (map ms_mod_name mods_to_keep) 
923                                               (hsc_HPT hsc_env1)
924
925               -- Clean up after ourselves
926               liftIO $ cleanTempFilesExcept dflags (ppFilesFromSummaries mods_to_keep)
927
928               -- there should be no Nothings where linkables should be, now
929               ASSERT(all (isJust.hm_linkable) 
930                         (eltsUFM (hsc_HPT hsc_env))) do
931         
932               -- Link everything together
933               linkresult <- liftIO $ link (ghcLink dflags) dflags False hpt4
934
935               let hsc_env4 = hsc_env1{ hsc_HPT = hpt4 }
936               loadFinish Failed linkresult hsc_env4
937
938 -- Finish up after a load.
939
940 -- If the link failed, unload everything and return.
941 loadFinish :: GhcMonad m =>
942               SuccessFlag -> SuccessFlag -> HscEnv
943            -> m SuccessFlag
944 loadFinish _all_ok Failed hsc_env
945   = do liftIO $ unload hsc_env []
946        modifySession $ \_ -> discardProg hsc_env
947        return Failed
948
949 -- Empty the interactive context and set the module context to the topmost
950 -- newly loaded module, or the Prelude if none were loaded.
951 loadFinish all_ok Succeeded hsc_env
952   = do modifySession $ \_ -> hsc_env{ hsc_IC = emptyInteractiveContext }
953        return all_ok
954
955
956 -- Forget the current program, but retain the persistent info in HscEnv
957 discardProg :: HscEnv -> HscEnv
958 discardProg hsc_env
959   = hsc_env { hsc_mod_graph = emptyMG, 
960               hsc_IC = emptyInteractiveContext,
961               hsc_HPT = emptyHomePackageTable }
962
963 -- used to fish out the preprocess output files for the purposes of
964 -- cleaning up.  The preprocessed file *might* be the same as the
965 -- source file, but that doesn't do any harm.
966 ppFilesFromSummaries :: [ModSummary] -> [FilePath]
967 ppFilesFromSummaries summaries = map ms_hspp_file summaries
968
969 -- -----------------------------------------------------------------------------
970
971 class ParsedMod m where
972   modSummary   :: m -> ModSummary
973   parsedSource :: m -> ParsedSource
974
975 class ParsedMod m => TypecheckedMod m where
976   renamedSource     :: m -> Maybe RenamedSource
977   typecheckedSource :: m -> TypecheckedSource
978   moduleInfo        :: m -> ModuleInfo
979   tm_internals      :: m -> (TcGblEnv, ModDetails)
980         -- ToDo: improvements that could be made here:
981         --  if the module succeeded renaming but not typechecking,
982         --  we can still get back the GlobalRdrEnv and exports, so
983         --  perhaps the ModuleInfo should be split up into separate
984         --  fields.
985
986 class TypecheckedMod m => DesugaredMod m where
987   coreModule :: m -> ModGuts
988
989 -- | The result of successful parsing.
990 data ParsedModule =
991   ParsedModule { pm_mod_summary   :: ModSummary
992                , pm_parsed_source :: ParsedSource }
993
994 instance ParsedMod ParsedModule where
995   modSummary m    = pm_mod_summary m
996   parsedSource m = pm_parsed_source m
997
998 -- | The result of successful typechecking.  It also contains the parser
999 --   result.
1000 data TypecheckedModule =
1001   TypecheckedModule { tm_parsed_module       :: ParsedModule
1002                     , tm_renamed_source      :: Maybe RenamedSource
1003                     , tm_typechecked_source  :: TypecheckedSource
1004                     , tm_checked_module_info :: ModuleInfo
1005                     , tm_internals_          :: (TcGblEnv, ModDetails)
1006                     }
1007
1008 instance ParsedMod TypecheckedModule where
1009   modSummary m   = modSummary (tm_parsed_module m)
1010   parsedSource m = parsedSource (tm_parsed_module m)
1011
1012 instance TypecheckedMod TypecheckedModule where
1013   renamedSource m     = tm_renamed_source m
1014   typecheckedSource m = tm_typechecked_source m
1015   moduleInfo m = tm_checked_module_info m
1016   tm_internals m      = tm_internals_ m
1017
1018 -- | The result of successful desugaring (i.e., translation to core).  Also
1019 --  contains all the information of a typechecked module.
1020 data DesugaredModule =
1021   DesugaredModule { dm_typechecked_module :: TypecheckedModule
1022                   , dm_core_module        :: ModGuts
1023              }
1024
1025 instance ParsedMod DesugaredModule where
1026   modSummary m   = modSummary (dm_typechecked_module m)
1027   parsedSource m = parsedSource (dm_typechecked_module m)
1028
1029 instance TypecheckedMod DesugaredModule where
1030   renamedSource m     = renamedSource (dm_typechecked_module m)
1031   typecheckedSource m = typecheckedSource (dm_typechecked_module m)
1032   moduleInfo m        = moduleInfo (dm_typechecked_module m)
1033   tm_internals m      = tm_internals_ (dm_typechecked_module m)
1034
1035 instance DesugaredMod DesugaredModule where
1036   coreModule m = dm_core_module m
1037
1038 type ParsedSource      = Located (HsModule RdrName)
1039 type RenamedSource     = (HsGroup Name, [LImportDecl Name], Maybe [LIE Name],
1040                           Maybe (HsDoc Name), HaddockModInfo Name)
1041 type TypecheckedSource = LHsBinds Id
1042
1043 -- NOTE:
1044 --   - things that aren't in the output of the typechecker right now:
1045 --     - the export list
1046 --     - the imports
1047 --     - type signatures
1048 --     - type/data/newtype declarations
1049 --     - class declarations
1050 --     - instances
1051 --   - extra things in the typechecker's output:
1052 --     - default methods are turned into top-level decls.
1053 --     - dictionary bindings
1054
1055 -- | Return the 'ModSummary' of a module with the given name.
1056 --
1057 -- The module must be part of the module graph (see 'hsc_mod_graph' and
1058 -- 'ModuleGraph').  If this is not the case, this function will throw a
1059 -- 'GhcApiError'.
1060 --
1061 -- This function ignores boot modules and requires that there is only one
1062 -- non-boot module with the given name.
1063 getModSummary :: GhcMonad m => ModuleName -> m ModSummary
1064 getModSummary mod = do
1065    mg <- liftM hsc_mod_graph getSession
1066    case [ ms | ms <- mg, ms_mod_name ms == mod, not (isBootSummary ms) ] of
1067      [] -> throw $ mkApiErr (text "Module not part of module graph")
1068      [ms] -> return ms
1069      multiple -> throw $ mkApiErr (text "getModSummary is ambiguous: " <+> ppr multiple)
1070
1071 -- | Parse a module.
1072 --
1073 -- Throws a 'SourceError' on parse error.
1074 parseModule :: GhcMonad m => ModSummary -> m ParsedModule
1075 parseModule ms = do
1076    rdr_module <- withTempSession
1077                      (\e -> e { hsc_dflags = ms_hspp_opts ms }) $
1078                    hscParse ms
1079    return (ParsedModule ms rdr_module)
1080
1081 -- | Typecheck and rename a parsed module.
1082 --
1083 -- Throws a 'SourceError' if either fails.
1084 typecheckModule :: GhcMonad m => ParsedModule -> m TypecheckedModule
1085 typecheckModule pmod = do
1086  let ms = modSummary pmod
1087  withTempSession (\e -> e { hsc_dflags = ms_hspp_opts ms }) $ do
1088    (tc_gbl_env, rn_info)
1089        <- hscTypecheckRename ms (parsedSource pmod)
1090    details <- makeSimpleDetails tc_gbl_env
1091    return $
1092      TypecheckedModule {
1093        tm_internals_          = (tc_gbl_env, details),
1094        tm_parsed_module       = pmod,
1095        tm_renamed_source      = rn_info,
1096        tm_typechecked_source  = tcg_binds tc_gbl_env,
1097        tm_checked_module_info =
1098          ModuleInfo {
1099            minf_type_env  = md_types details,
1100            minf_exports   = availsToNameSet $ md_exports details,
1101            minf_rdr_env   = Just (tcg_rdr_env tc_gbl_env),
1102            minf_instances = md_insts details
1103 #ifdef GHCI
1104            ,minf_modBreaks = emptyModBreaks
1105 #endif
1106          }}
1107
1108 -- | Desugar a typechecked module.
1109 desugarModule :: GhcMonad m => TypecheckedModule -> m DesugaredModule
1110 desugarModule tcm = do
1111  let ms = modSummary tcm
1112  withTempSession (\e -> e { hsc_dflags = ms_hspp_opts ms }) $ do
1113    let (tcg, _) = tm_internals tcm
1114    guts <- hscDesugar ms tcg
1115    return $
1116      DesugaredModule {
1117        dm_typechecked_module = tcm,
1118        dm_core_module        = guts
1119      }
1120
1121 -- | Load a module.  Input doesn't need to be desugared.
1122 --
1123 -- A module must be loaded before dependent modules can be typechecked.  This
1124 -- always includes generating a 'ModIface' and, depending on the
1125 -- 'DynFlags.hscTarget', may also include code generation.
1126 --
1127 -- This function will always cause recompilation and will always overwrite
1128 -- previous compilation results (potentially files on disk).
1129 --
1130 loadModule :: (TypecheckedMod mod, GhcMonad m) => mod -> m mod
1131 loadModule tcm = do
1132    let ms = modSummary tcm
1133    let mod = ms_mod_name ms
1134    let (tcg, _details) = tm_internals tcm
1135    hpt_new <-
1136        withTempSession (\e -> e { hsc_dflags = ms_hspp_opts ms }) $ do
1137
1138          let compilerBackend comp env ms' _ _mb_old_iface _ =
1139                withTempSession (\_ -> env) $
1140                  hscBackend comp tcg ms'
1141                             Nothing
1142          hsc_env <- getSession
1143          mod_info
1144              <- compile' (compilerBackend hscNothingCompiler
1145                          ,compilerBackend hscInteractiveCompiler
1146                          ,compilerBackend hscBatchCompiler)
1147                          hsc_env ms 1 1 Nothing Nothing
1148          -- compile' shouldn't change the environment
1149          return $ addToUFM (hsc_HPT hsc_env) mod mod_info
1150    modifySession $ \e -> e{ hsc_HPT = hpt_new }
1151    return tcm
1152
1153 -- | This is the way to get access to the Core bindings corresponding
1154 -- to a module. 'compileToCore' parses, typechecks, and
1155 -- desugars the module, then returns the resulting Core module (consisting of
1156 -- the module name, type declarations, and function declarations) if
1157 -- successful.
1158 compileToCoreModule :: GhcMonad m => FilePath -> m CoreModule
1159 compileToCoreModule = compileCore False
1160
1161 -- | Like compileToCoreModule, but invokes the simplifier, so
1162 -- as to return simplified and tidied Core.
1163 compileToCoreSimplified :: GhcMonad m => FilePath -> m CoreModule
1164 compileToCoreSimplified = compileCore True
1165 {-
1166 -- | Provided for backwards-compatibility: compileToCore returns just the Core
1167 -- bindings, but for most purposes, you probably want to call
1168 -- compileToCoreModule.
1169 compileToCore :: GhcMonad m => FilePath -> m [CoreBind]
1170 compileToCore fn = do
1171    mod <- compileToCoreModule session fn
1172    return $ cm_binds mod
1173 -}
1174 -- | Takes a CoreModule and compiles the bindings therein
1175 -- to object code. The first argument is a bool flag indicating
1176 -- whether to run the simplifier.
1177 -- The resulting .o, .hi, and executable files, if any, are stored in the
1178 -- current directory, and named according to the module name.
1179 -- This has only so far been tested with a single self-contained module.
1180 compileCoreToObj :: GhcMonad m => Bool -> CoreModule -> m ()
1181 compileCoreToObj simplify cm@(CoreModule{ cm_module = mName }) = do
1182   dflags      <- getSessionDynFlags
1183   currentTime <- liftIO $ getClockTime
1184   cwd         <- liftIO $ getCurrentDirectory
1185   modLocation <- liftIO $ mkHiOnlyModLocation dflags (hiSuf dflags) cwd
1186                    ((moduleNameSlashes . moduleName) mName)
1187
1188   let modSummary = ModSummary { ms_mod = mName,
1189          ms_hsc_src = ExtCoreFile,
1190          ms_location = modLocation,
1191          -- By setting the object file timestamp to Nothing,
1192          -- we always force recompilation, which is what we
1193          -- want. (Thus it doesn't matter what the timestamp
1194          -- for the (nonexistent) source file is.)
1195          ms_hs_date = currentTime,
1196          ms_obj_date = Nothing,
1197          -- Only handling the single-module case for now, so no imports.
1198          ms_srcimps = [],
1199          ms_imps = [],
1200          -- No source file
1201          ms_hspp_file = "",
1202          ms_hspp_opts = dflags,
1203          ms_hspp_buf = Nothing
1204       }
1205
1206   let maybe_simplify mod_guts | simplify = hscSimplify mod_guts
1207                               | otherwise = return mod_guts
1208   guts <- maybe_simplify (mkModGuts cm)
1209   (iface, changed, _details, cgguts)
1210       <- hscNormalIface guts Nothing
1211   hscWriteIface iface changed modSummary
1212   hscGenHardCode cgguts modSummary
1213   return ()
1214
1215 -- Makes a "vanilla" ModGuts.
1216 mkModGuts :: CoreModule -> ModGuts
1217 mkModGuts coreModule = ModGuts {
1218   mg_module = cm_module coreModule,
1219   mg_boot = False,
1220   mg_exports = [],
1221   mg_deps = noDependencies,
1222   mg_dir_imps = emptyModuleEnv,
1223   mg_used_names = emptyNameSet,
1224   mg_rdr_env = emptyGlobalRdrEnv,
1225   mg_fix_env = emptyFixityEnv,
1226   mg_types = emptyTypeEnv,
1227   mg_insts = [],
1228   mg_fam_insts = [],
1229   mg_rules = [],
1230   mg_binds = cm_binds coreModule,
1231   mg_foreign = NoStubs,
1232   mg_warns = NoWarnings,
1233   mg_anns = [],
1234   mg_hpc_info = emptyHpcInfo False,
1235   mg_modBreaks = emptyModBreaks,
1236   mg_vect_info = noVectInfo,
1237   mg_inst_env = emptyInstEnv,
1238   mg_fam_inst_env = emptyFamInstEnv
1239 }
1240
1241 compileCore :: GhcMonad m => Bool -> FilePath -> m CoreModule
1242 compileCore simplify fn = do
1243    -- First, set the target to the desired filename
1244    target <- guessTarget fn Nothing
1245    addTarget target
1246    load LoadAllTargets
1247    -- Then find dependencies
1248    modGraph <- depanal [] True
1249    case find ((== fn) . msHsFilePath) modGraph of
1250      Just modSummary -> do
1251        -- Now we have the module name;
1252        -- parse, typecheck and desugar the module
1253        mod_guts <- coreModule `fmap`
1254                       -- TODO: space leaky: call hsc* directly?
1255                       (desugarModule =<< typecheckModule =<< parseModule modSummary)
1256        liftM gutsToCoreModule $
1257          if simplify
1258           then do
1259              -- If simplify is true: simplify (hscSimplify), then tidy
1260              -- (tidyProgram).
1261              hsc_env <- getSession
1262              simpl_guts <- hscSimplify mod_guts
1263              tidy_guts <- liftIO $ tidyProgram hsc_env simpl_guts
1264              return $ Left tidy_guts
1265           else
1266              return $ Right mod_guts
1267
1268      Nothing -> panic "compileToCoreModule: target FilePath not found in\
1269                            module dependency graph"
1270   where -- two versions, based on whether we simplify (thus run tidyProgram,
1271         -- which returns a (CgGuts, ModDetails) pair, or not (in which case
1272         -- we just have a ModGuts.
1273         gutsToCoreModule :: Either (CgGuts, ModDetails) ModGuts -> CoreModule
1274         gutsToCoreModule (Left (cg, md))  = CoreModule {
1275           cm_module = cg_module cg,    cm_types = md_types md,
1276           cm_imports = cg_dir_imps cg, cm_binds = cg_binds cg
1277         }
1278         gutsToCoreModule (Right mg) = CoreModule {
1279           cm_module  = mg_module mg,                   cm_types   = mg_types mg,
1280           cm_imports = moduleEnvKeys (mg_dir_imps mg), cm_binds   = mg_binds mg
1281          }
1282
1283 -- ---------------------------------------------------------------------------
1284 -- Unloading
1285
1286 unload :: HscEnv -> [Linkable] -> IO ()
1287 unload hsc_env stable_linkables -- Unload everthing *except* 'stable_linkables'
1288   = case ghcLink (hsc_dflags hsc_env) of
1289 #ifdef GHCI
1290         LinkInMemory -> Linker.unload (hsc_dflags hsc_env) stable_linkables
1291 #else
1292         LinkInMemory -> panic "unload: no interpreter"
1293                                 -- urgh.  avoid warnings:
1294                                 hsc_env stable_linkables
1295 #endif
1296         _other -> return ()
1297
1298 -- -----------------------------------------------------------------------------
1299
1300 {- |
1301
1302   Stability tells us which modules definitely do not need to be recompiled.
1303   There are two main reasons for having stability:
1304   
1305    - avoid doing a complete upsweep of the module graph in GHCi when
1306      modules near the bottom of the tree have not changed.
1307
1308    - to tell GHCi when it can load object code: we can only load object code
1309      for a module when we also load object code fo  all of the imports of the
1310      module.  So we need to know that we will definitely not be recompiling
1311      any of these modules, and we can use the object code.
1312
1313   The stability check is as follows.  Both stableObject and
1314   stableBCO are used during the upsweep phase later.
1315
1316 @
1317   stable m = stableObject m || stableBCO m
1318
1319   stableObject m = 
1320         all stableObject (imports m)
1321         && old linkable does not exist, or is == on-disk .o
1322         && date(on-disk .o) > date(.hs)
1323
1324   stableBCO m =
1325         all stable (imports m)
1326         && date(BCO) > date(.hs)
1327 @
1328
1329   These properties embody the following ideas:
1330
1331     - if a module is stable, then:
1332
1333         - if it has been compiled in a previous pass (present in HPT)
1334           then it does not need to be compiled or re-linked.
1335
1336         - if it has not been compiled in a previous pass,
1337           then we only need to read its .hi file from disk and
1338           link it to produce a 'ModDetails'.
1339
1340     - if a modules is not stable, we will definitely be at least
1341       re-linking, and possibly re-compiling it during the 'upsweep'.
1342       All non-stable modules can (and should) therefore be unlinked
1343       before the 'upsweep'.
1344
1345     - Note that objects are only considered stable if they only depend
1346       on other objects.  We can't link object code against byte code.
1347 -}
1348
1349 checkStability
1350         :: HomePackageTable             -- HPT from last compilation
1351         -> [SCC ModSummary]             -- current module graph (cyclic)
1352         -> [ModuleName]                 -- all home modules
1353         -> ([ModuleName],               -- stableObject
1354             [ModuleName])               -- stableBCO
1355
1356 checkStability hpt sccs all_home_mods = foldl checkSCC ([],[]) sccs
1357   where
1358    checkSCC (stable_obj, stable_bco) scc0
1359      | stableObjects = (scc_mods ++ stable_obj, stable_bco)
1360      | stableBCOs    = (stable_obj, scc_mods ++ stable_bco)
1361      | otherwise     = (stable_obj, stable_bco)
1362      where
1363         scc = flattenSCC scc0
1364         scc_mods = map ms_mod_name scc
1365         home_module m   = m `elem` all_home_mods && m `notElem` scc_mods
1366
1367         scc_allimps = nub (filter home_module (concatMap ms_home_allimps scc))
1368             -- all imports outside the current SCC, but in the home pkg
1369         
1370         stable_obj_imps = map (`elem` stable_obj) scc_allimps
1371         stable_bco_imps = map (`elem` stable_bco) scc_allimps
1372
1373         stableObjects = 
1374            and stable_obj_imps
1375            && all object_ok scc
1376
1377         stableBCOs = 
1378            and (zipWith (||) stable_obj_imps stable_bco_imps)
1379            && all bco_ok scc
1380
1381         object_ok ms
1382           | Just t <- ms_obj_date ms  =  t >= ms_hs_date ms 
1383                                          && same_as_prev t
1384           | otherwise = False
1385           where
1386              same_as_prev t = case lookupUFM hpt (ms_mod_name ms) of
1387                                 Just hmi  | Just l <- hm_linkable hmi
1388                                  -> isObjectLinkable l && t == linkableTime l
1389                                 _other  -> True
1390                 -- why '>=' rather than '>' above?  If the filesystem stores
1391                 -- times to the nearset second, we may occasionally find that
1392                 -- the object & source have the same modification time, 
1393                 -- especially if the source was automatically generated
1394                 -- and compiled.  Using >= is slightly unsafe, but it matches
1395                 -- make's behaviour.
1396
1397         bco_ok ms
1398           = case lookupUFM hpt (ms_mod_name ms) of
1399                 Just hmi  | Just l <- hm_linkable hmi ->
1400                         not (isObjectLinkable l) && 
1401                         linkableTime l >= ms_hs_date ms
1402                 _other  -> False
1403
1404 -- -----------------------------------------------------------------------------
1405
1406 -- | Prune the HomePackageTable
1407 --
1408 -- Before doing an upsweep, we can throw away:
1409 --
1410 --   - For non-stable modules:
1411 --      - all ModDetails, all linked code
1412 --   - all unlinked code that is out of date with respect to
1413 --     the source file
1414 --
1415 -- This is VERY IMPORTANT otherwise we'll end up requiring 2x the
1416 -- space at the end of the upsweep, because the topmost ModDetails of the
1417 -- old HPT holds on to the entire type environment from the previous
1418 -- compilation.
1419
1420 pruneHomePackageTable
1421    :: HomePackageTable
1422    -> [ModSummary]
1423    -> ([ModuleName],[ModuleName])
1424    -> HomePackageTable
1425
1426 pruneHomePackageTable hpt summ (stable_obj, stable_bco)
1427   = mapUFM prune hpt
1428   where prune hmi
1429           | is_stable modl = hmi'
1430           | otherwise      = hmi'{ hm_details = emptyModDetails }
1431           where
1432            modl = moduleName (mi_module (hm_iface hmi))
1433            hmi' | Just l <- hm_linkable hmi, linkableTime l < ms_hs_date ms
1434                 = hmi{ hm_linkable = Nothing }
1435                 | otherwise
1436                 = hmi
1437                 where ms = expectJust "prune" (lookupUFM ms_map modl)
1438
1439         ms_map = listToUFM [(ms_mod_name ms, ms) | ms <- summ]
1440
1441         is_stable m = m `elem` stable_obj || m `elem` stable_bco
1442
1443 -- -----------------------------------------------------------------------------
1444
1445 -- Return (names of) all those in modsDone who are part of a cycle
1446 -- as defined by theGraph.
1447 findPartiallyCompletedCycles :: [Module] -> [SCC ModSummary] -> [Module]
1448 findPartiallyCompletedCycles modsDone theGraph
1449    = chew theGraph
1450      where
1451         chew [] = []
1452         chew ((AcyclicSCC _):rest) = chew rest    -- acyclic?  not interesting.
1453         chew ((CyclicSCC vs):rest)
1454            = let names_in_this_cycle = nub (map ms_mod vs)
1455                  mods_in_this_cycle  
1456                     = nub ([done | done <- modsDone, 
1457                                    done `elem` names_in_this_cycle])
1458                  chewed_rest = chew rest
1459              in 
1460              if   notNull mods_in_this_cycle
1461                   && length mods_in_this_cycle < length names_in_this_cycle
1462              then mods_in_this_cycle ++ chewed_rest
1463              else chewed_rest
1464
1465 -- -----------------------------------------------------------------------------
1466
1467 -- | The upsweep
1468 --
1469 -- This is where we compile each module in the module graph, in a pass
1470 -- from the bottom to the top of the graph.
1471 --
1472 -- There better had not be any cyclic groups here -- we check for them.
1473
1474 upsweep
1475     :: GhcMonad m =>
1476        HscEnv                   -- ^ Includes initially-empty HPT
1477     -> HomePackageTable         -- ^ HPT from last time round (pruned)
1478     -> ([ModuleName],[ModuleName]) -- ^ stable modules (see checkStability)
1479     -> IO ()                    -- ^ How to clean up unwanted tmp files
1480     -> [SCC ModSummary]         -- ^ Mods to do (the worklist)
1481     -> m (SuccessFlag,
1482          HscEnv,
1483          [ModSummary])
1484        -- ^ Returns:
1485        --
1486        --  1. A flag whether the complete upsweep was successful.
1487        --  2. The 'HscEnv' with an updated HPT
1488        --  3. A list of modules which succeeded loading.
1489
1490 upsweep hsc_env old_hpt stable_mods cleanup sccs = do
1491    (res, hsc_env, done) <- upsweep' hsc_env old_hpt [] sccs 1 (length sccs)
1492    return (res, hsc_env, reverse done)
1493  where
1494
1495   upsweep' hsc_env _old_hpt done
1496      [] _ _
1497    = return (Succeeded, hsc_env, done)
1498
1499   upsweep' hsc_env _old_hpt done
1500      (CyclicSCC ms:_) _ _
1501    = do liftIO $ fatalErrorMsg (hsc_dflags hsc_env) (cyclicModuleErr ms)
1502         return (Failed, hsc_env, done)
1503
1504   upsweep' hsc_env old_hpt done
1505      (AcyclicSCC mod:mods) mod_index nmods
1506    = do -- putStrLn ("UPSWEEP_MOD: hpt = " ++ 
1507         --           show (map (moduleUserString.moduleName.mi_module.hm_iface) 
1508         --                     (moduleEnvElts (hsc_HPT hsc_env)))
1509         let logger = reportModuleCompilationResult (hsc_callbacks hsc_env)
1510
1511         mb_mod_info
1512             <- handleSourceError
1513                    (\err -> do logger mod (Just err); return Nothing) $ do
1514                  mod_info <- upsweep_mod hsc_env old_hpt stable_mods
1515                                          mod mod_index nmods
1516                  logger mod Nothing -- log warnings
1517                  return (Just mod_info)
1518
1519         liftIO cleanup -- Remove unwanted tmp files between compilations
1520
1521         case mb_mod_info of
1522           Nothing -> return (Failed, hsc_env, done)
1523           Just mod_info -> do
1524                 let this_mod = ms_mod_name mod
1525
1526                         -- Add new info to hsc_env
1527                     hpt1     = addToUFM (hsc_HPT hsc_env) this_mod mod_info
1528                     hsc_env1 = hsc_env { hsc_HPT = hpt1 }
1529
1530                         -- Space-saving: delete the old HPT entry
1531                         -- for mod BUT if mod is a hs-boot
1532                         -- node, don't delete it.  For the
1533                         -- interface, the HPT entry is probaby for the
1534                         -- main Haskell source file.  Deleting it
1535                         -- would force the real module to be recompiled
1536                         -- every time.
1537                     old_hpt1 | isBootSummary mod = old_hpt
1538                              | otherwise = delFromUFM old_hpt this_mod
1539
1540                     done' = mod:done
1541
1542                         -- fixup our HomePackageTable after we've finished compiling
1543                         -- a mutually-recursive loop.  See reTypecheckLoop, below.
1544                 hsc_env2 <- liftIO $ reTypecheckLoop hsc_env1 mod done'
1545
1546                 upsweep' hsc_env2 old_hpt1 done' mods (mod_index+1) nmods
1547
1548 -- | Compile a single module.  Always produce a Linkable for it if
1549 -- successful.  If no compilation happened, return the old Linkable.
1550 upsweep_mod :: GhcMonad m =>
1551                HscEnv
1552             -> HomePackageTable
1553             -> ([ModuleName],[ModuleName])
1554             -> ModSummary
1555             -> Int  -- index of module
1556             -> Int  -- total number of modules
1557             -> m HomeModInfo
1558
1559 upsweep_mod hsc_env old_hpt (stable_obj, stable_bco) summary mod_index nmods
1560    =    let 
1561             this_mod_name = ms_mod_name summary
1562             this_mod    = ms_mod summary
1563             mb_obj_date = ms_obj_date summary
1564             obj_fn      = ml_obj_file (ms_location summary)
1565             hs_date     = ms_hs_date summary
1566
1567             is_stable_obj = this_mod_name `elem` stable_obj
1568             is_stable_bco = this_mod_name `elem` stable_bco
1569
1570             old_hmi = lookupUFM old_hpt this_mod_name
1571
1572             -- We're using the dflags for this module now, obtained by
1573             -- applying any options in its LANGUAGE & OPTIONS_GHC pragmas.
1574             dflags = ms_hspp_opts summary
1575             prevailing_target = hscTarget (hsc_dflags hsc_env)
1576             local_target      = hscTarget dflags
1577
1578             -- If OPTIONS_GHC contains -fasm or -fvia-C, be careful that
1579             -- we don't do anything dodgy: these should only work to change
1580             -- from -fvia-C to -fasm and vice-versa, otherwise we could 
1581             -- end up trying to link object code to byte code.
1582             target = if prevailing_target /= local_target
1583                         && (not (isObjectTarget prevailing_target)
1584                             || not (isObjectTarget local_target))
1585                         then prevailing_target
1586                         else local_target 
1587
1588             -- store the corrected hscTarget into the summary
1589             summary' = summary{ ms_hspp_opts = dflags { hscTarget = target } }
1590
1591             -- The old interface is ok if
1592             --  a) we're compiling a source file, and the old HPT
1593             --     entry is for a source file
1594             --  b) we're compiling a hs-boot file
1595             -- Case (b) allows an hs-boot file to get the interface of its
1596             -- real source file on the second iteration of the compilation
1597             -- manager, but that does no harm.  Otherwise the hs-boot file
1598             -- will always be recompiled
1599             
1600             mb_old_iface 
1601                 = case old_hmi of
1602                      Nothing                              -> Nothing
1603                      Just hm_info | isBootSummary summary -> Just iface
1604                                   | not (mi_boot iface)   -> Just iface
1605                                   | otherwise             -> Nothing
1606                                    where 
1607                                      iface = hm_iface hm_info
1608
1609             compile_it :: GhcMonad m => Maybe Linkable -> m HomeModInfo
1610             compile_it  = compile hsc_env summary' mod_index nmods mb_old_iface
1611
1612             compile_it_discard_iface :: GhcMonad m =>
1613                                         Maybe Linkable -> m HomeModInfo
1614             compile_it_discard_iface 
1615                         = compile hsc_env summary' mod_index nmods Nothing
1616
1617             -- With the HscNothing target we create empty linkables to avoid
1618             -- recompilation.  We have to detect these to recompile anyway if
1619             -- the target changed since the last compile.
1620             is_fake_linkable
1621                | Just hmi <- old_hmi, Just l <- hm_linkable hmi =
1622                   null (linkableUnlinked l)
1623                | otherwise =
1624                    -- we have no linkable, so it cannot be fake
1625                    False
1626
1627             implies False _ = True
1628             implies True x  = x
1629
1630         in
1631         case () of
1632          _
1633                 -- Regardless of whether we're generating object code or
1634                 -- byte code, we can always use an existing object file
1635                 -- if it is *stable* (see checkStability).
1636           | is_stable_obj, Just hmi <- old_hmi -> do
1637                 liftIO $ debugTraceMsg (hsc_dflags hsc_env) 5
1638                            (text "skipping stable obj mod:" <+> ppr this_mod_name)
1639                 return hmi
1640                 -- object is stable, and we have an entry in the
1641                 -- old HPT: nothing to do
1642
1643           | is_stable_obj, isNothing old_hmi -> do
1644                 liftIO $ debugTraceMsg (hsc_dflags hsc_env) 5
1645                            (text "compiling stable on-disk mod:" <+> ppr this_mod_name)
1646                 linkable <- liftIO $ findObjectLinkable this_mod obj_fn
1647                               (expectJust "upsweep1" mb_obj_date)
1648                 compile_it (Just linkable)
1649                 -- object is stable, but we need to load the interface
1650                 -- off disk to make a HMI.
1651
1652           | not (isObjectTarget target), is_stable_bco,
1653             (target /= HscNothing) `implies` not is_fake_linkable ->
1654                 ASSERT(isJust old_hmi) -- must be in the old_hpt
1655                 let Just hmi = old_hmi in do
1656                 liftIO $ debugTraceMsg (hsc_dflags hsc_env) 5
1657                            (text "skipping stable BCO mod:" <+> ppr this_mod_name)
1658                 return hmi
1659                 -- BCO is stable: nothing to do
1660
1661           | not (isObjectTarget target),
1662             Just hmi <- old_hmi,
1663             Just l <- hm_linkable hmi,
1664             not (isObjectLinkable l),
1665             (target /= HscNothing) `implies` not is_fake_linkable,
1666             linkableTime l >= ms_hs_date summary -> do
1667                 liftIO $ debugTraceMsg (hsc_dflags hsc_env) 5
1668                            (text "compiling non-stable BCO mod:" <+> ppr this_mod_name)
1669                 compile_it (Just l)
1670                 -- we have an old BCO that is up to date with respect
1671                 -- to the source: do a recompilation check as normal.
1672
1673           -- When generating object code, if there's an up-to-date
1674           -- object file on the disk, then we can use it.
1675           -- However, if the object file is new (compared to any
1676           -- linkable we had from a previous compilation), then we
1677           -- must discard any in-memory interface, because this
1678           -- means the user has compiled the source file
1679           -- separately and generated a new interface, that we must
1680           -- read from the disk.
1681           --
1682           | isObjectTarget target,
1683             Just obj_date <- mb_obj_date,
1684             obj_date >= hs_date -> do
1685                 case old_hmi of
1686                   Just hmi
1687                     | Just l <- hm_linkable hmi,
1688                       isObjectLinkable l && linkableTime l == obj_date -> do
1689                           liftIO $ debugTraceMsg (hsc_dflags hsc_env) 5
1690                                      (text "compiling mod with new on-disk obj:" <+> ppr this_mod_name)
1691                           compile_it (Just l)
1692                   _otherwise -> do
1693                           liftIO $ debugTraceMsg (hsc_dflags hsc_env) 5
1694                                      (text "compiling mod with new on-disk obj2:" <+> ppr this_mod_name)
1695                           linkable <- liftIO $ findObjectLinkable this_mod obj_fn obj_date
1696                           compile_it_discard_iface (Just linkable)
1697
1698          _otherwise -> do
1699                 liftIO $ debugTraceMsg (hsc_dflags hsc_env) 5
1700                            (text "compiling mod:" <+> ppr this_mod_name)
1701                 compile_it Nothing
1702
1703
1704
1705 -- Filter modules in the HPT
1706 retainInTopLevelEnvs :: [ModuleName] -> HomePackageTable -> HomePackageTable
1707 retainInTopLevelEnvs keep_these hpt
1708    = listToUFM   [ (mod, expectJust "retain" mb_mod_info)
1709                  | mod <- keep_these
1710                  , let mb_mod_info = lookupUFM hpt mod
1711                  , isJust mb_mod_info ]
1712
1713 -- ---------------------------------------------------------------------------
1714 -- Typecheck module loops
1715
1716 {-
1717 See bug #930.  This code fixes a long-standing bug in --make.  The
1718 problem is that when compiling the modules *inside* a loop, a data
1719 type that is only defined at the top of the loop looks opaque; but
1720 after the loop is done, the structure of the data type becomes
1721 apparent.
1722
1723 The difficulty is then that two different bits of code have
1724 different notions of what the data type looks like.
1725
1726 The idea is that after we compile a module which also has an .hs-boot
1727 file, we re-generate the ModDetails for each of the modules that
1728 depends on the .hs-boot file, so that everyone points to the proper
1729 TyCons, Ids etc. defined by the real module, not the boot module.
1730 Fortunately re-generating a ModDetails from a ModIface is easy: the
1731 function TcIface.typecheckIface does exactly that.
1732
1733 Picking the modules to re-typecheck is slightly tricky.  Starting from
1734 the module graph consisting of the modules that have already been
1735 compiled, we reverse the edges (so they point from the imported module
1736 to the importing module), and depth-first-search from the .hs-boot
1737 node.  This gives us all the modules that depend transitively on the
1738 .hs-boot module, and those are exactly the modules that we need to
1739 re-typecheck.
1740
1741 Following this fix, GHC can compile itself with --make -O2.
1742 -}
1743
1744 reTypecheckLoop :: HscEnv -> ModSummary -> ModuleGraph -> IO HscEnv
1745 reTypecheckLoop hsc_env ms graph
1746   | not (isBootSummary ms) && 
1747     any (\m -> ms_mod m == this_mod && isBootSummary m) graph
1748   = do
1749         let mss = reachableBackwards (ms_mod_name ms) graph
1750             non_boot = filter (not.isBootSummary) mss
1751         debugTraceMsg (hsc_dflags hsc_env) 2 $
1752            text "Re-typechecking loop: " <> ppr (map ms_mod_name non_boot)
1753         typecheckLoop hsc_env (map ms_mod_name non_boot)
1754   | otherwise
1755   = return hsc_env
1756  where
1757   this_mod = ms_mod ms
1758
1759 typecheckLoop :: HscEnv -> [ModuleName] -> IO HscEnv
1760 typecheckLoop hsc_env mods = do
1761   new_hpt <-
1762     fixIO $ \new_hpt -> do
1763       let new_hsc_env = hsc_env{ hsc_HPT = new_hpt }
1764       mds <- initIfaceCheck new_hsc_env $ 
1765                 mapM (typecheckIface . hm_iface) hmis
1766       let new_hpt = addListToUFM old_hpt 
1767                         (zip mods [ hmi{ hm_details = details }
1768                                   | (hmi,details) <- zip hmis mds ])
1769       return new_hpt
1770   return hsc_env{ hsc_HPT = new_hpt }
1771   where
1772     old_hpt = hsc_HPT hsc_env
1773     hmis    = map (expectJust "typecheckLoop" . lookupUFM old_hpt) mods
1774
1775 reachableBackwards :: ModuleName -> [ModSummary] -> [ModSummary]
1776 reachableBackwards mod summaries
1777   = [ ms | (ms,_,_) <- reachableG (transposeG graph) root ]
1778   where -- the rest just sets up the graph:
1779         (graph, lookup_node) = moduleGraphNodes False summaries
1780         root  = expectJust "reachableBackwards" (lookup_node HsBootFile mod)
1781
1782 -- ---------------------------------------------------------------------------
1783 -- Topological sort of the module graph
1784
1785 type SummaryNode = (ModSummary, Int, [Int])
1786
1787 topSortModuleGraph
1788           :: Bool
1789           -- ^ Drop hi-boot nodes? (see below)
1790           -> [ModSummary]
1791           -> Maybe ModuleName
1792              -- ^ Root module name.  If @Nothing@, use the full graph.
1793           -> [SCC ModSummary]
1794 -- ^ Calculate SCCs of the module graph, possibly dropping the hi-boot nodes
1795 -- The resulting list of strongly-connected-components is in topologically
1796 -- sorted order, starting with the module(s) at the bottom of the
1797 -- dependency graph (ie compile them first) and ending with the ones at
1798 -- the top.
1799 --
1800 -- Drop hi-boot nodes (first boolean arg)? 
1801 --
1802 -- - @False@:   treat the hi-boot summaries as nodes of the graph,
1803 --              so the graph must be acyclic
1804 --
1805 -- - @True@:    eliminate the hi-boot nodes, and instead pretend
1806 --              the a source-import of Foo is an import of Foo
1807 --              The resulting graph has no hi-boot nodes, but can be cyclic
1808
1809 topSortModuleGraph drop_hs_boot_nodes summaries mb_root_mod
1810   = map (fmap summaryNodeSummary) $ stronglyConnCompG initial_graph
1811   where
1812     (graph, lookup_node) = moduleGraphNodes drop_hs_boot_nodes summaries
1813     
1814     initial_graph = case mb_root_mod of
1815         Nothing -> graph
1816         Just root_mod ->
1817             -- restrict the graph to just those modules reachable from
1818             -- the specified module.  We do this by building a graph with
1819             -- the full set of nodes, and determining the reachable set from
1820             -- the specified node.
1821             let root | Just node <- lookup_node HsSrcFile root_mod, graph `hasVertexG` node = node
1822                      | otherwise = ghcError (ProgramError "module does not exist")
1823             in graphFromEdgedVertices (seq root (reachableG graph root))
1824
1825 summaryNodeKey :: SummaryNode -> Int
1826 summaryNodeKey (_, k, _) = k
1827
1828 summaryNodeSummary :: SummaryNode -> ModSummary
1829 summaryNodeSummary (s, _, _) = s
1830
1831 moduleGraphNodes :: Bool -> [ModSummary]
1832   -> (Graph SummaryNode, HscSource -> ModuleName -> Maybe SummaryNode)
1833 moduleGraphNodes drop_hs_boot_nodes summaries = (graphFromEdgedVertices nodes, lookup_node)
1834   where
1835     numbered_summaries = zip summaries [1..]
1836
1837     lookup_node :: HscSource -> ModuleName -> Maybe SummaryNode
1838     lookup_node hs_src mod = lookupFM node_map (mod, hs_src)
1839
1840     lookup_key :: HscSource -> ModuleName -> Maybe Int
1841     lookup_key hs_src mod = fmap summaryNodeKey (lookup_node hs_src mod)
1842
1843     node_map :: NodeMap SummaryNode
1844     node_map = listToFM [ ((moduleName (ms_mod s), ms_hsc_src s), node)
1845                         | node@(s, _, _) <- nodes ]
1846
1847     -- We use integers as the keys for the SCC algorithm
1848     nodes :: [SummaryNode]
1849     nodes = [ (s, key, out_keys)
1850             | (s, key) <- numbered_summaries
1851              -- Drop the hi-boot ones if told to do so
1852             , not (isBootSummary s && drop_hs_boot_nodes)
1853             , let out_keys = out_edge_keys hs_boot_key (map unLoc (ms_home_srcimps s)) ++
1854                              out_edge_keys HsSrcFile   (map unLoc (ms_home_imps s)) ++
1855                              (-- see [boot-edges] below
1856                               if drop_hs_boot_nodes || ms_hsc_src s == HsBootFile 
1857                               then [] 
1858                               else case lookup_key HsBootFile (ms_mod_name s) of
1859                                     Nothing -> []
1860                                     Just k  -> [k]) ]
1861
1862     -- [boot-edges] if this is a .hs and there is an equivalent
1863     -- .hs-boot, add a link from the former to the latter.  This
1864     -- has the effect of detecting bogus cases where the .hs-boot
1865     -- depends on the .hs, by introducing a cycle.  Additionally,
1866     -- it ensures that we will always process the .hs-boot before
1867     -- the .hs, and so the HomePackageTable will always have the
1868     -- most up to date information.
1869
1870     -- Drop hs-boot nodes by using HsSrcFile as the key
1871     hs_boot_key | drop_hs_boot_nodes = HsSrcFile
1872                 | otherwise          = HsBootFile
1873
1874     out_edge_keys :: HscSource -> [ModuleName] -> [Int]
1875     out_edge_keys hi_boot ms = mapCatMaybes (lookup_key hi_boot) ms
1876         -- If we want keep_hi_boot_nodes, then we do lookup_key with
1877         -- the IsBootInterface parameter True; else False
1878
1879
1880 type NodeKey   = (ModuleName, HscSource)  -- The nodes of the graph are 
1881 type NodeMap a = FiniteMap NodeKey a      -- keyed by (mod, src_file_type) pairs
1882
1883 msKey :: ModSummary -> NodeKey
1884 msKey (ModSummary { ms_mod = mod, ms_hsc_src = boot }) = (moduleName mod,boot)
1885
1886 mkNodeMap :: [ModSummary] -> NodeMap ModSummary
1887 mkNodeMap summaries = listToFM [ (msKey s, s) | s <- summaries]
1888         
1889 nodeMapElts :: NodeMap a -> [a]
1890 nodeMapElts = eltsFM
1891
1892 -- | If there are {-# SOURCE #-} imports between strongly connected
1893 -- components in the topological sort, then those imports can
1894 -- definitely be replaced by ordinary non-SOURCE imports: if SOURCE
1895 -- were necessary, then the edge would be part of a cycle.
1896 warnUnnecessarySourceImports :: GhcMonad m => [SCC ModSummary] -> m ()
1897 warnUnnecessarySourceImports sccs =
1898   logWarnings (listToBag (concatMap (check.flattenSCC) sccs))
1899   where check ms =
1900            let mods_in_this_cycle = map ms_mod_name ms in
1901            [ warn i | m <- ms, i <- ms_home_srcimps m,
1902                       unLoc i `notElem`  mods_in_this_cycle ]
1903
1904         warn :: Located ModuleName -> WarnMsg
1905         warn (L loc mod) = 
1906            mkPlainErrMsg loc
1907                 (ptext (sLit "Warning: {-# SOURCE #-} unnecessary in import of ")
1908                  <+> quotes (ppr mod))
1909
1910 -----------------------------------------------------------------------------
1911 -- Downsweep (dependency analysis)
1912
1913 -- Chase downwards from the specified root set, returning summaries
1914 -- for all home modules encountered.  Only follow source-import
1915 -- links.
1916
1917 -- We pass in the previous collection of summaries, which is used as a
1918 -- cache to avoid recalculating a module summary if the source is
1919 -- unchanged.
1920 --
1921 -- The returned list of [ModSummary] nodes has one node for each home-package
1922 -- module, plus one for any hs-boot files.  The imports of these nodes 
1923 -- are all there, including the imports of non-home-package modules.
1924
1925 downsweep :: GhcMonad m =>
1926              HscEnv
1927           -> [ModSummary]       -- Old summaries
1928           -> [ModuleName]       -- Ignore dependencies on these; treat
1929                                 -- them as if they were package modules
1930           -> Bool               -- True <=> allow multiple targets to have 
1931                                 --          the same module name; this is 
1932                                 --          very useful for ghc -M
1933           -> m [ModSummary]
1934                 -- The elts of [ModSummary] all have distinct
1935                 -- (Modules, IsBoot) identifiers, unless the Bool is true
1936                 -- in which case there can be repeats
1937 downsweep hsc_env old_summaries excl_mods allow_dup_roots
1938    = do -- catch error messages and return them
1939      --handleErrMsg   -- should be covered by GhcMonad now
1940      --          (\err_msg -> printBagOfErrors (hsc_dflags hsc_env) (unitBag err_msg) >> return Nothing) $ do
1941        rootSummaries <- mapM getRootSummary roots
1942        let root_map = mkRootMap rootSummaries
1943        checkDuplicates root_map
1944        summs <- loop (concatMap msDeps rootSummaries) root_map
1945        return summs
1946      where
1947         roots = hsc_targets hsc_env
1948
1949         old_summary_map :: NodeMap ModSummary
1950         old_summary_map = mkNodeMap old_summaries
1951
1952         getRootSummary :: GhcMonad m => Target -> m ModSummary
1953         getRootSummary (Target (TargetFile file mb_phase) obj_allowed maybe_buf)
1954            = do exists <- liftIO $ doesFileExist file
1955                 if exists 
1956                     then summariseFile hsc_env old_summaries file mb_phase 
1957                                        obj_allowed maybe_buf
1958                     else throwOneError $ mkPlainErrMsg noSrcSpan $
1959                            text "can't find file:" <+> text file
1960         getRootSummary (Target (TargetModule modl) obj_allowed maybe_buf)
1961            = do maybe_summary <- summariseModule hsc_env old_summary_map False 
1962                                            (L rootLoc modl) obj_allowed 
1963                                            maybe_buf excl_mods
1964                 case maybe_summary of
1965                    Nothing -> packageModErr modl
1966                    Just s  -> return s
1967
1968         rootLoc = mkGeneralSrcSpan (fsLit "<command line>")
1969
1970         -- In a root module, the filename is allowed to diverge from the module
1971         -- name, so we have to check that there aren't multiple root files
1972         -- defining the same module (otherwise the duplicates will be silently
1973         -- ignored, leading to confusing behaviour).
1974         checkDuplicates :: GhcMonad m => NodeMap [ModSummary] -> m ()
1975         checkDuplicates root_map 
1976            | allow_dup_roots = return ()
1977            | null dup_roots  = return ()
1978            | otherwise       = liftIO $ multiRootsErr (head dup_roots)
1979            where
1980              dup_roots :: [[ModSummary]]        -- Each at least of length 2
1981              dup_roots = filterOut isSingleton (nodeMapElts root_map)
1982
1983         loop :: GhcMonad m =>
1984                 [(Located ModuleName,IsBootInterface)]
1985                         -- Work list: process these modules
1986              -> NodeMap [ModSummary]
1987                         -- Visited set; the range is a list because
1988                         -- the roots can have the same module names
1989                         -- if allow_dup_roots is True
1990              -> m [ModSummary]
1991                         -- The result includes the worklist, except
1992                         -- for those mentioned in the visited set
1993         loop [] done      = return (concat (nodeMapElts done))
1994         loop ((wanted_mod, is_boot) : ss) done 
1995           | Just summs <- lookupFM done key
1996           = if isSingleton summs then
1997                 loop ss done
1998             else
1999                 do { liftIO $ multiRootsErr summs; return [] }
2000           | otherwise
2001           = do mb_s <- summariseModule hsc_env old_summary_map 
2002                                        is_boot wanted_mod True
2003                                        Nothing excl_mods
2004                case mb_s of
2005                    Nothing -> loop ss done
2006                    Just s  -> loop (msDeps s ++ ss) (addToFM done key [s])
2007           where
2008             key = (unLoc wanted_mod, if is_boot then HsBootFile else HsSrcFile)
2009
2010 mkRootMap :: [ModSummary] -> NodeMap [ModSummary]
2011 mkRootMap summaries = addListToFM_C (++) emptyFM 
2012                         [ (msKey s, [s]) | s <- summaries ]
2013
2014 msDeps :: ModSummary -> [(Located ModuleName, IsBootInterface)]
2015 -- (msDeps s) returns the dependencies of the ModSummary s.
2016 -- A wrinkle is that for a {-# SOURCE #-} import we return
2017 --      *both* the hs-boot file
2018 --      *and* the source file
2019 -- as "dependencies".  That ensures that the list of all relevant
2020 -- modules always contains B.hs if it contains B.hs-boot.
2021 -- Remember, this pass isn't doing the topological sort.  It's
2022 -- just gathering the list of all relevant ModSummaries
2023 msDeps s = 
2024     concat [ [(m,True), (m,False)] | m <- ms_home_srcimps s ] 
2025          ++ [ (m,False) | m <- ms_home_imps s ] 
2026
2027 home_imps :: [Located (ImportDecl RdrName)] -> [Located ModuleName]
2028 home_imps imps = [ ideclName i |  L _ i <- imps, isNothing (ideclPkgQual i) ]
2029
2030 ms_home_allimps :: ModSummary -> [ModuleName]
2031 ms_home_allimps ms = map unLoc (ms_home_srcimps ms ++ ms_home_imps ms)
2032
2033 ms_home_srcimps :: ModSummary -> [Located ModuleName]
2034 ms_home_srcimps = home_imps . ms_srcimps
2035
2036 ms_home_imps :: ModSummary -> [Located ModuleName]
2037 ms_home_imps = home_imps . ms_imps
2038
2039 -----------------------------------------------------------------------------
2040 -- Summarising modules
2041
2042 -- We have two types of summarisation:
2043 --
2044 --    * Summarise a file.  This is used for the root module(s) passed to
2045 --      cmLoadModules.  The file is read, and used to determine the root
2046 --      module name.  The module name may differ from the filename.
2047 --
2048 --    * Summarise a module.  We are given a module name, and must provide
2049 --      a summary.  The finder is used to locate the file in which the module
2050 --      resides.
2051
2052 summariseFile
2053         :: GhcMonad m =>
2054            HscEnv
2055         -> [ModSummary]                 -- old summaries
2056         -> FilePath                     -- source file name
2057         -> Maybe Phase                  -- start phase
2058         -> Bool                         -- object code allowed?
2059         -> Maybe (StringBuffer,ClockTime)
2060         -> m ModSummary
2061
2062 summariseFile hsc_env old_summaries file mb_phase obj_allowed maybe_buf
2063         -- we can use a cached summary if one is available and the
2064         -- source file hasn't changed,  But we have to look up the summary
2065         -- by source file, rather than module name as we do in summarise.
2066    | Just old_summary <- findSummaryBySourceFile old_summaries file
2067    = do
2068         let location = ms_location old_summary
2069
2070                 -- return the cached summary if the source didn't change
2071         src_timestamp <- case maybe_buf of
2072                            Just (_,t) -> return t
2073                            Nothing    -> liftIO $ getModificationTime file
2074                 -- The file exists; we checked in getRootSummary above.
2075                 -- If it gets removed subsequently, then this 
2076                 -- getModificationTime may fail, but that's the right
2077                 -- behaviour.
2078
2079         if ms_hs_date old_summary == src_timestamp 
2080            then do -- update the object-file timestamp
2081                   obj_timestamp <-
2082                     if isObjectTarget (hscTarget (hsc_dflags hsc_env)) 
2083                         || obj_allowed -- bug #1205
2084                         then liftIO $ getObjTimestamp location False
2085                         else return Nothing
2086                   return old_summary{ ms_obj_date = obj_timestamp }
2087            else
2088                 new_summary
2089
2090    | otherwise
2091    = new_summary
2092   where
2093     new_summary = do
2094         let dflags = hsc_dflags hsc_env
2095
2096         (dflags', hspp_fn, buf)
2097             <- preprocessFile hsc_env file mb_phase maybe_buf
2098
2099         (srcimps,the_imps, L _ mod_name) <- getImports dflags' buf hspp_fn file
2100
2101         -- Make a ModLocation for this file
2102         location <- liftIO $ mkHomeModLocation dflags mod_name file
2103
2104         -- Tell the Finder cache where it is, so that subsequent calls
2105         -- to findModule will find it, even if it's not on any search path
2106         mod <- liftIO $ addHomeModuleToFinder hsc_env mod_name location
2107
2108         src_timestamp <- case maybe_buf of
2109                            Just (_,t) -> return t
2110                            Nothing    -> liftIO $ getModificationTime file
2111                         -- getMofificationTime may fail
2112
2113         -- when the user asks to load a source file by name, we only
2114         -- use an object file if -fobject-code is on.  See #1205.
2115         obj_timestamp <-
2116             if isObjectTarget (hscTarget (hsc_dflags hsc_env)) 
2117                || obj_allowed -- bug #1205
2118                 then liftIO $ modificationTimeIfExists (ml_obj_file location)
2119                 else return Nothing
2120
2121         return (ModSummary { ms_mod = mod, ms_hsc_src = HsSrcFile,
2122                              ms_location = location,
2123                              ms_hspp_file = hspp_fn,
2124                              ms_hspp_opts = dflags',
2125                              ms_hspp_buf  = Just buf,
2126                              ms_srcimps = srcimps, ms_imps = the_imps,
2127                              ms_hs_date = src_timestamp,
2128                              ms_obj_date = obj_timestamp })
2129
2130 findSummaryBySourceFile :: [ModSummary] -> FilePath -> Maybe ModSummary
2131 findSummaryBySourceFile summaries file
2132   = case [ ms | ms <- summaries, HsSrcFile <- [ms_hsc_src ms],
2133                                  expectJust "findSummaryBySourceFile" (ml_hs_file (ms_location ms)) == file ] of
2134         [] -> Nothing
2135         (x:_) -> Just x
2136
2137 -- Summarise a module, and pick up source and timestamp.
2138 summariseModule
2139           :: GhcMonad m =>
2140              HscEnv
2141           -> NodeMap ModSummary -- Map of old summaries
2142           -> IsBootInterface    -- True <=> a {-# SOURCE #-} import
2143           -> Located ModuleName -- Imported module to be summarised
2144           -> Bool               -- object code allowed?
2145           -> Maybe (StringBuffer, ClockTime)
2146           -> [ModuleName]               -- Modules to exclude
2147           -> m (Maybe ModSummary)       -- Its new summary
2148
2149 summariseModule hsc_env old_summary_map is_boot (L loc wanted_mod) 
2150                 obj_allowed maybe_buf excl_mods
2151   | wanted_mod `elem` excl_mods
2152   = return Nothing
2153
2154   | Just old_summary <- lookupFM old_summary_map (wanted_mod, hsc_src)
2155   = do          -- Find its new timestamp; all the 
2156                 -- ModSummaries in the old map have valid ml_hs_files
2157         let location = ms_location old_summary
2158             src_fn = expectJust "summariseModule" (ml_hs_file location)
2159
2160                 -- check the modification time on the source file, and
2161                 -- return the cached summary if it hasn't changed.  If the
2162                 -- file has disappeared, we need to call the Finder again.
2163         case maybe_buf of
2164            Just (_,t) -> check_timestamp old_summary location src_fn t
2165            Nothing    -> do
2166                 m <- liftIO $ System.IO.Error.try (getModificationTime src_fn)
2167                 case m of
2168                    Right t -> check_timestamp old_summary location src_fn t
2169                    Left e | isDoesNotExistError e -> find_it
2170                           | otherwise             -> liftIO $ ioError e
2171
2172   | otherwise  = find_it
2173   where
2174     dflags = hsc_dflags hsc_env
2175
2176     hsc_src = if is_boot then HsBootFile else HsSrcFile
2177
2178     check_timestamp old_summary location src_fn src_timestamp
2179         | ms_hs_date old_summary == src_timestamp = do
2180                 -- update the object-file timestamp
2181                 obj_timestamp <- liftIO $
2182                     if isObjectTarget (hscTarget (hsc_dflags hsc_env))
2183                        || obj_allowed -- bug #1205
2184                        then getObjTimestamp location is_boot
2185                        else return Nothing
2186                 return (Just old_summary{ ms_obj_date = obj_timestamp })
2187         | otherwise = 
2188                 -- source changed: re-summarise.
2189                 new_summary location (ms_mod old_summary) src_fn src_timestamp
2190
2191     find_it = do
2192         -- Don't use the Finder's cache this time.  If the module was
2193         -- previously a package module, it may have now appeared on the
2194         -- search path, so we want to consider it to be a home module.  If
2195         -- the module was previously a home module, it may have moved.
2196         liftIO $ uncacheModule hsc_env wanted_mod
2197         found <- liftIO $ findImportedModule hsc_env wanted_mod Nothing
2198         case found of
2199              Found location mod 
2200                 | isJust (ml_hs_file location) ->
2201                         -- Home package
2202                          just_found location mod
2203                 | otherwise -> 
2204                         -- Drop external-pkg
2205                         ASSERT(modulePackageId mod /= thisPackage dflags)
2206                         return Nothing
2207                         
2208              err -> liftIO $ noModError dflags loc wanted_mod err
2209                         -- Not found
2210
2211     just_found location mod = do
2212                 -- Adjust location to point to the hs-boot source file, 
2213                 -- hi file, object file, when is_boot says so
2214         let location' | is_boot   = addBootSuffixLocn location
2215                       | otherwise = location
2216             src_fn = expectJust "summarise2" (ml_hs_file location')
2217
2218                 -- Check that it exists
2219                 -- It might have been deleted since the Finder last found it
2220         maybe_t <- liftIO $ modificationTimeIfExists src_fn
2221         case maybe_t of
2222           Nothing -> noHsFileErr loc src_fn
2223           Just t  -> new_summary location' mod src_fn t
2224
2225
2226     new_summary location mod src_fn src_timestamp
2227       = do
2228         -- Preprocess the source file and get its imports
2229         -- The dflags' contains the OPTIONS pragmas
2230         (dflags', hspp_fn, buf) <- preprocessFile hsc_env src_fn Nothing maybe_buf
2231         (srcimps, the_imps, L mod_loc mod_name) <- getImports dflags' buf hspp_fn src_fn
2232
2233         when (mod_name /= wanted_mod) $
2234                 throwOneError $ mkPlainErrMsg mod_loc $ 
2235                               text "File name does not match module name:" 
2236                               $$ text "Saw:" <+> quotes (ppr mod_name)
2237                               $$ text "Expected:" <+> quotes (ppr wanted_mod)
2238
2239                 -- Find the object timestamp, and return the summary
2240         obj_timestamp <- liftIO $
2241            if isObjectTarget (hscTarget (hsc_dflags hsc_env))
2242               || obj_allowed -- bug #1205
2243               then getObjTimestamp location is_boot
2244               else return Nothing
2245
2246         return (Just (ModSummary { ms_mod       = mod,
2247                               ms_hsc_src   = hsc_src,
2248                               ms_location  = location,
2249                               ms_hspp_file = hspp_fn,
2250                               ms_hspp_opts = dflags',
2251                               ms_hspp_buf  = Just buf,
2252                               ms_srcimps   = srcimps,
2253                               ms_imps      = the_imps,
2254                               ms_hs_date   = src_timestamp,
2255                               ms_obj_date  = obj_timestamp }))
2256
2257
2258 getObjTimestamp :: ModLocation -> Bool -> IO (Maybe ClockTime)
2259 getObjTimestamp location is_boot
2260   = if is_boot then return Nothing
2261                else modificationTimeIfExists (ml_obj_file location)
2262
2263
2264 preprocessFile :: GhcMonad m =>
2265                   HscEnv
2266                -> FilePath
2267                -> Maybe Phase -- ^ Starting phase
2268                -> Maybe (StringBuffer,ClockTime)
2269                -> m (DynFlags, FilePath, StringBuffer)
2270 preprocessFile hsc_env src_fn mb_phase Nothing
2271   = do
2272         (dflags', hspp_fn) <- preprocess hsc_env (src_fn, mb_phase)
2273         buf <- liftIO $ hGetStringBuffer hspp_fn
2274         return (dflags', hspp_fn, buf)
2275
2276 preprocessFile hsc_env src_fn mb_phase (Just (buf, _time))
2277   = do
2278         let dflags = hsc_dflags hsc_env
2279         -- case we bypass the preprocessing stage?
2280         let 
2281             local_opts = getOptions dflags buf src_fn
2282         --
2283         (dflags', leftovers, warns)
2284             <- parseDynamicNoPackageFlags dflags local_opts
2285         checkProcessArgsResult leftovers
2286         handleFlagWarnings dflags' warns
2287
2288         let
2289             needs_preprocessing
2290                 | Just (Unlit _) <- mb_phase    = True
2291                 | Nothing <- mb_phase, Unlit _ <- startPhase src_fn  = True
2292                   -- note: local_opts is only required if there's no Unlit phase
2293                 | dopt Opt_Cpp dflags'          = True
2294                 | dopt Opt_Pp  dflags'          = True
2295                 | otherwise                     = False
2296
2297         when needs_preprocessing $
2298            ghcError (ProgramError "buffer needs preprocesing; interactive check disabled")
2299
2300         return (dflags', src_fn, buf)
2301
2302
2303 -----------------------------------------------------------------------------
2304 --                      Error messages
2305 -----------------------------------------------------------------------------
2306
2307 noModError :: DynFlags -> SrcSpan -> ModuleName -> FindResult -> IO ab
2308 -- ToDo: we don't have a proper line number for this error
2309 noModError dflags loc wanted_mod err
2310   = throwOneError $ mkPlainErrMsg loc $ cannotFindModule dflags wanted_mod err
2311                                 
2312 noHsFileErr :: GhcMonad m => SrcSpan -> String -> m a
2313 noHsFileErr loc path
2314   = throwOneError $ mkPlainErrMsg loc $ text "Can't find" <+> text path
2315  
2316 packageModErr :: GhcMonad m => ModuleName -> m a
2317 packageModErr mod
2318   = throwOneError $ mkPlainErrMsg noSrcSpan $
2319         text "module" <+> quotes (ppr mod) <+> text "is a package module"
2320
2321 multiRootsErr :: [ModSummary] -> IO ()
2322 multiRootsErr [] = panic "multiRootsErr"
2323 multiRootsErr summs@(summ1:_)
2324   = throwOneError $ mkPlainErrMsg noSrcSpan $
2325         text "module" <+> quotes (ppr mod) <+> 
2326         text "is defined in multiple files:" <+>
2327         sep (map text files)
2328   where
2329     mod = ms_mod summ1
2330     files = map (expectJust "checkDup" . ml_hs_file . ms_location) summs
2331
2332 cyclicModuleErr :: [ModSummary] -> SDoc
2333 cyclicModuleErr ms
2334   = hang (ptext (sLit "Module imports form a cycle for modules:"))
2335        2 (vcat (map show_one ms))
2336   where
2337     show_one ms = sep [ show_mod (ms_hsc_src ms) (ms_mod ms),
2338                         nest 2 $ ptext (sLit "imports:") <+> 
2339                                    (pp_imps HsBootFile (ms_srcimps ms)
2340                                    $$ pp_imps HsSrcFile  (ms_imps ms))]
2341     show_mod hsc_src mod = ppr mod <> text (hscSourceString hsc_src)
2342     pp_imps src mods = fsep (map (show_mod src) mods)
2343
2344
2345 -- | Inform GHC that the working directory has changed.  GHC will flush
2346 -- its cache of module locations, since it may no longer be valid.
2347 -- Note: if you change the working directory, you should also unload
2348 -- the current program (set targets to empty, followed by load).
2349 workingDirectoryChanged :: GhcMonad m => m ()
2350 workingDirectoryChanged = withSession $ (liftIO . flushFinderCaches)
2351
2352 -- -----------------------------------------------------------------------------
2353 -- inspecting the session
2354
2355 -- | Get the module dependency graph.
2356 getModuleGraph :: GhcMonad m => m ModuleGraph -- ToDo: DiGraph ModSummary
2357 getModuleGraph = liftM hsc_mod_graph getSession
2358
2359 -- | Determines whether a set of modules requires Template Haskell.
2360 --
2361 -- Note that if the session's 'DynFlags' enabled Template Haskell when
2362 -- 'depanal' was called, then each module in the returned module graph will
2363 -- have Template Haskell enabled whether it is actually needed or not.
2364 needsTemplateHaskell :: ModuleGraph -> Bool
2365 needsTemplateHaskell ms =
2366     any (dopt Opt_TemplateHaskell . ms_hspp_opts) ms
2367
2368 -- | Return @True@ <==> module is loaded.
2369 isLoaded :: GhcMonad m => ModuleName -> m Bool
2370 isLoaded m = withSession $ \hsc_env ->
2371   return $! isJust (lookupUFM (hsc_HPT hsc_env) m)
2372
2373 -- | Return the bindings for the current interactive session.
2374 getBindings :: GhcMonad m => m [TyThing]
2375 getBindings = withSession $ \hsc_env ->
2376    -- we have to implement the shadowing behaviour of ic_tmp_ids here
2377    -- (see InteractiveContext) and the quickest way is to use an OccEnv.
2378    let 
2379        tmp_ids = ic_tmp_ids (hsc_IC hsc_env)
2380        filtered = foldr f (const []) tmp_ids emptyUniqSet
2381        f id rest set 
2382            | uniq `elementOfUniqSet` set = rest set
2383            | otherwise  = AnId id : rest (addOneToUniqSet set uniq)
2384            where uniq = getUnique (nameOccName (idName id))
2385    in
2386    return filtered
2387
2388 getPrintUnqual :: GhcMonad m => m PrintUnqualified
2389 getPrintUnqual = withSession $ \hsc_env ->
2390   return (icPrintUnqual (hsc_dflags hsc_env) (hsc_IC hsc_env))
2391
2392 -- | Container for information about a 'Module'.
2393 data ModuleInfo = ModuleInfo {
2394         minf_type_env  :: TypeEnv,
2395         minf_exports   :: NameSet, -- ToDo, [AvailInfo] like ModDetails?
2396         minf_rdr_env   :: Maybe GlobalRdrEnv,   -- Nothing for a compiled/package mod
2397         minf_instances :: [Instance]
2398 #ifdef GHCI
2399         ,minf_modBreaks :: ModBreaks 
2400 #endif
2401         -- ToDo: this should really contain the ModIface too
2402   }
2403         -- We don't want HomeModInfo here, because a ModuleInfo applies
2404         -- to package modules too.
2405
2406 -- | Request information about a loaded 'Module'
2407 getModuleInfo :: GhcMonad m => Module -> m (Maybe ModuleInfo)  -- XXX: Maybe X
2408 getModuleInfo mdl = withSession $ \hsc_env -> do
2409   let mg = hsc_mod_graph hsc_env
2410   if mdl `elem` map ms_mod mg
2411         then liftIO $ getHomeModuleInfo hsc_env (moduleName mdl)
2412         else do
2413   {- if isHomeModule (hsc_dflags hsc_env) mdl
2414         then return Nothing
2415         else -} liftIO $ getPackageModuleInfo hsc_env mdl
2416    -- getPackageModuleInfo will attempt to find the interface, so
2417    -- we don't want to call it for a home module, just in case there
2418    -- was a problem loading the module and the interface doesn't
2419    -- exist... hence the isHomeModule test here.  (ToDo: reinstate)
2420
2421 getPackageModuleInfo :: HscEnv -> Module -> IO (Maybe ModuleInfo)
2422 #ifdef GHCI
2423 getPackageModuleInfo hsc_env mdl = do
2424   (_msgs, mb_avails) <- getModuleExports hsc_env mdl
2425   case mb_avails of
2426     Nothing -> return Nothing
2427     Just avails -> do
2428         eps <- readIORef (hsc_EPS hsc_env)
2429         let 
2430             names  = availsToNameSet avails
2431             pte    = eps_PTE eps
2432             tys    = [ ty | name <- concatMap availNames avails,
2433                             Just ty <- [lookupTypeEnv pte name] ]
2434         --
2435         return (Just (ModuleInfo {
2436                         minf_type_env  = mkTypeEnv tys,
2437                         minf_exports   = names,
2438                         minf_rdr_env   = Just $! nameSetToGlobalRdrEnv names (moduleName mdl),
2439                         minf_instances = error "getModuleInfo: instances for package module unimplemented",
2440                         minf_modBreaks = emptyModBreaks  
2441                 }))
2442 #else
2443 getPackageModuleInfo _hsc_env _mdl = do
2444   -- bogusly different for non-GHCI (ToDo)
2445   return Nothing
2446 #endif
2447
2448 getHomeModuleInfo :: HscEnv -> ModuleName -> IO (Maybe ModuleInfo)
2449 getHomeModuleInfo hsc_env mdl = 
2450   case lookupUFM (hsc_HPT hsc_env) mdl of
2451     Nothing  -> return Nothing
2452     Just hmi -> do
2453       let details = hm_details hmi
2454       return (Just (ModuleInfo {
2455                         minf_type_env  = md_types details,
2456                         minf_exports   = availsToNameSet (md_exports details),
2457                         minf_rdr_env   = mi_globals $! hm_iface hmi,
2458                         minf_instances = md_insts details
2459 #ifdef GHCI
2460                        ,minf_modBreaks = getModBreaks hmi
2461 #endif
2462                         }))
2463
2464 -- | The list of top-level entities defined in a module
2465 modInfoTyThings :: ModuleInfo -> [TyThing]
2466 modInfoTyThings minf = typeEnvElts (minf_type_env minf)
2467
2468 modInfoTopLevelScope :: ModuleInfo -> Maybe [Name]
2469 modInfoTopLevelScope minf
2470   = fmap (map gre_name . globalRdrEnvElts) (minf_rdr_env minf)
2471
2472 modInfoExports :: ModuleInfo -> [Name]
2473 modInfoExports minf = nameSetToList $! minf_exports minf
2474
2475 -- | Returns the instances defined by the specified module.
2476 -- Warning: currently unimplemented for package modules.
2477 modInfoInstances :: ModuleInfo -> [Instance]
2478 modInfoInstances = minf_instances
2479
2480 modInfoIsExportedName :: ModuleInfo -> Name -> Bool
2481 modInfoIsExportedName minf name = elemNameSet name (minf_exports minf)
2482
2483 mkPrintUnqualifiedForModule :: GhcMonad m =>
2484                                ModuleInfo
2485                             -> m (Maybe PrintUnqualified) -- XXX: returns a Maybe X
2486 mkPrintUnqualifiedForModule minf = withSession $ \hsc_env -> do
2487   return (fmap (mkPrintUnqualified (hsc_dflags hsc_env)) (minf_rdr_env minf))
2488
2489 modInfoLookupName :: GhcMonad m =>
2490                      ModuleInfo -> Name
2491                   -> m (Maybe TyThing) -- XXX: returns a Maybe X
2492 modInfoLookupName minf name = withSession $ \hsc_env -> do
2493    case lookupTypeEnv (minf_type_env minf) name of
2494      Just tyThing -> return (Just tyThing)
2495      Nothing      -> do
2496        eps <- liftIO $ readIORef (hsc_EPS hsc_env)
2497        return $! lookupType (hsc_dflags hsc_env) 
2498                             (hsc_HPT hsc_env) (eps_PTE eps) name
2499
2500 #ifdef GHCI
2501 modInfoModBreaks :: ModuleInfo -> ModBreaks
2502 modInfoModBreaks = minf_modBreaks  
2503 #endif
2504
2505 isDictonaryId :: Id -> Bool
2506 isDictonaryId id
2507   = case tcSplitSigmaTy (idType id) of { (_tvs, _theta, tau) -> isDictTy tau }
2508
2509 -- | Looks up a global name: that is, any top-level name in any
2510 -- visible module.  Unlike 'lookupName', lookupGlobalName does not use
2511 -- the interactive context, and therefore does not require a preceding
2512 -- 'setContext'.
2513 lookupGlobalName :: GhcMonad m => Name -> m (Maybe TyThing)
2514 lookupGlobalName name = withSession $ \hsc_env -> do
2515    liftIO $ lookupTypeHscEnv hsc_env name
2516
2517 findGlobalAnns :: (GhcMonad m, Typeable a) => ([Word8] -> a) -> AnnTarget Name -> m [a]
2518 findGlobalAnns deserialize target = withSession $ \hsc_env -> do
2519     ann_env <- liftIO $ prepareAnnotations hsc_env Nothing
2520     return (findAnns deserialize ann_env target)
2521
2522 #ifdef GHCI
2523 -- | get the GlobalRdrEnv for a session
2524 getGRE :: GhcMonad m => m GlobalRdrEnv
2525 getGRE = withSession $ \hsc_env-> return $ ic_rn_gbl_env (hsc_IC hsc_env)
2526 #endif
2527
2528 -- -----------------------------------------------------------------------------
2529
2530 -- | Return all /external/ modules available in the package database.
2531 -- Modules from the current session (i.e., from the 'HomePackageTable') are
2532 -- not included.
2533 packageDbModules :: GhcMonad m =>
2534                     Bool  -- ^ Only consider exposed packages.
2535                  -> m [Module]
2536 packageDbModules only_exposed = do
2537    dflags <- getSessionDynFlags
2538    let pkgs = UFM.eltsUFM (pkgIdMap (pkgState dflags))
2539    return $
2540      [ mkModule pid modname | p <- pkgs
2541                             , not only_exposed || exposed p
2542                             , pid <- [mkPackageId (package p)]
2543                             , modname <- exposedModules p ]
2544
2545 -- -----------------------------------------------------------------------------
2546 -- Misc exported utils
2547
2548 dataConType :: DataCon -> Type
2549 dataConType dc = idType (dataConWrapId dc)
2550
2551 -- | print a 'NamedThing', adding parentheses if the name is an operator.
2552 pprParenSymName :: NamedThing a => a -> SDoc
2553 pprParenSymName a = parenSymOcc (getOccName a) (ppr (getName a))
2554
2555 -- ----------------------------------------------------------------------------
2556
2557 #if 0
2558
2559 -- ToDo:
2560 --   - Data and Typeable instances for HsSyn.
2561
2562 -- ToDo: check for small transformations that happen to the syntax in
2563 -- the typechecker (eg. -e ==> negate e, perhaps for fromIntegral)
2564
2565 -- ToDo: maybe use TH syntax instead of IfaceSyn?  There's already a way
2566 -- to get from TyCons, Ids etc. to TH syntax (reify).
2567
2568 -- :browse will use either lm_toplev or inspect lm_interface, depending
2569 -- on whether the module is interpreted or not.
2570
2571 #endif
2572
2573 -- Extract the filename, stringbuffer content and dynflags associed to a module
2574 --
2575 -- XXX: Explain pre-conditions
2576 getModuleSourceAndFlags :: GhcMonad m => Module -> m (String, StringBuffer, DynFlags)
2577 getModuleSourceAndFlags mod = do
2578   m <- getModSummary (moduleName mod)
2579   case ml_hs_file $ ms_location m of
2580     Nothing -> throw $ mkApiErr (text "No source available for module " <+> ppr mod)
2581     Just sourceFile -> do
2582         source <- liftIO $ hGetStringBuffer sourceFile
2583         return (sourceFile, source, ms_hspp_opts m)
2584
2585
2586 -- | Return module source as token stream, including comments.
2587 --
2588 -- The module must be in the module graph and its source must be available.
2589 -- Throws a 'HscTypes.SourceError' on parse error.
2590 getTokenStream :: GhcMonad m => Module -> m [Located Token]
2591 getTokenStream mod = do
2592   (sourceFile, source, flags) <- getModuleSourceAndFlags mod
2593   let startLoc = mkSrcLoc (mkFastString sourceFile) 0 0
2594   case lexTokenStream source startLoc flags of
2595     POk _ ts  -> return ts
2596     PFailed span err -> throw $ mkSrcErr (unitBag $ mkPlainErrMsg span err)
2597
2598 -- | Give even more information on the source than 'getTokenStream'
2599 -- This function allows reconstructing the source completely with
2600 -- 'showRichTokenStream'.
2601 getRichTokenStream :: GhcMonad m => Module -> m [(Located Token, String)]
2602 getRichTokenStream mod = do
2603   (sourceFile, source, flags) <- getModuleSourceAndFlags mod
2604   let startLoc = mkSrcLoc (mkFastString sourceFile) 0 0
2605   case lexTokenStream source startLoc flags of
2606     POk _ ts -> return $ addSourceToTokens startLoc source ts
2607     PFailed span err -> throw $ mkSrcErr (unitBag $ mkPlainErrMsg span err)
2608
2609 -- | Given a source location and a StringBuffer corresponding to this
2610 -- location, return a rich token stream with the source associated to the
2611 -- tokens.
2612 addSourceToTokens :: SrcLoc -> StringBuffer -> [Located Token]
2613                   -> [(Located Token, String)]
2614 addSourceToTokens _ _ [] = []
2615 addSourceToTokens loc buf (t@(L span _) : ts)
2616     | not (isGoodSrcSpan span) = (t,"") : addSourceToTokens loc buf ts
2617     | otherwise = (t,str) : addSourceToTokens newLoc newBuf ts
2618     where
2619       (newLoc, newBuf, str) = go "" loc buf
2620       start = srcSpanStart span
2621       end = srcSpanEnd span
2622       go acc loc buf | loc < start = go acc nLoc nBuf
2623                      | start <= loc && loc < end = go (ch:acc) nLoc nBuf
2624                      | otherwise = (loc, buf, reverse acc)
2625           where (ch, nBuf) = nextChar buf
2626                 nLoc = advanceSrcLoc loc ch
2627
2628
2629 -- | Take a rich token stream such as produced from 'getRichTokenStream' and
2630 -- return source code almost identical to the original code (except for
2631 -- insignificant whitespace.)
2632 showRichTokenStream :: [(Located Token, String)] -> String
2633 showRichTokenStream ts = go startLoc ts ""
2634     where sourceFile = srcSpanFile (getLoc . fst . head $ ts)
2635           startLoc = mkSrcLoc sourceFile 0 0
2636           go _ [] = id
2637           go loc ((L span _, str):ts)
2638               | not (isGoodSrcSpan span) = go loc ts
2639               | locLine == tokLine = ((replicate (tokCol - locCol) ' ') ++)
2640                                      . (str ++)
2641                                      . go tokEnd ts
2642               | otherwise = ((replicate (tokLine - locLine) '\n') ++)
2643                             . ((replicate tokCol ' ') ++)
2644                             . (str ++)
2645                             . go tokEnd ts
2646               where (locLine, locCol) = (srcLocLine loc, srcLocCol loc)
2647                     (tokLine, tokCol) = (srcSpanStartLine span, srcSpanStartCol span)
2648                     tokEnd = srcSpanEnd span
2649
2650 -- -----------------------------------------------------------------------------
2651 -- Interactive evaluation
2652
2653 -- | Takes a 'ModuleName' and possibly a 'PackageId', and consults the
2654 -- filesystem and package database to find the corresponding 'Module', 
2655 -- using the algorithm that is used for an @import@ declaration.
2656 findModule :: GhcMonad m => ModuleName -> Maybe FastString -> m Module
2657 findModule mod_name maybe_pkg = withSession $ \hsc_env -> liftIO $ -- XXX
2658   let
2659         dflags = hsc_dflags hsc_env
2660         hpt    = hsc_HPT hsc_env
2661         this_pkg = thisPackage dflags
2662   in
2663   case lookupUFM hpt mod_name of
2664     Just mod_info -> return (mi_module (hm_iface mod_info))
2665     _not_a_home_module -> do
2666           res <- findImportedModule hsc_env mod_name maybe_pkg
2667           case res of
2668             Found _ m | modulePackageId m /= this_pkg -> return m
2669                       | otherwise -> ghcError (CmdLineError (showSDoc $
2670                                         text "module" <+> quotes (ppr (moduleName m)) <+>
2671                                         text "is not loaded"))
2672             err -> let msg = cannotFindModule dflags mod_name err in
2673                    ghcError (CmdLineError (showSDoc msg))
2674
2675 #ifdef GHCI
2676 getHistorySpan :: GhcMonad m => History -> m SrcSpan
2677 getHistorySpan h = withSession $ \hsc_env ->
2678                           return$ InteractiveEval.getHistorySpan hsc_env h
2679
2680 obtainTermFromVal :: GhcMonad m => Int ->  Bool -> Type -> a -> m Term
2681 obtainTermFromVal bound force ty a =
2682     withSession $ \hsc_env ->
2683       liftIO $ InteractiveEval.obtainTermFromVal hsc_env bound force ty a
2684
2685 obtainTermFromId :: GhcMonad m => Int -> Bool -> Id -> m Term
2686 obtainTermFromId bound force id =
2687     withSession $ \hsc_env ->
2688       liftIO $ InteractiveEval.obtainTermFromId hsc_env bound force id
2689
2690 #endif