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