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