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