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