[project @ 2005-05-19 11:15:40 by simonpj]
[ghc-hetmet.git] / ghc / 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         init,
15         newSession,
16
17         -- * Flags and settings
18         DynFlags(..), DynFlag(..), GhcMode(..), HscTarget(..), dopt,
19         parseDynamicFlags,
20         initPackages,
21         getSessionDynFlags,
22         setSessionDynFlags,
23         setMsgHandler,
24
25         -- * Targets
26         Target(..), TargetId(..), Phase,
27         setTargets,
28         getTargets,
29         addTarget,
30         removeTarget,
31         guessTarget,
32         
33         -- * Loading\/compiling the program
34         depanal,
35         load, LoadHowMuch(..), SuccessFlag(..), -- also does depanal
36         loadMsgs,
37         workingDirectoryChanged,
38         checkModule, CheckedModule(..),
39         TypecheckedSource, ParsedSource, RenamedSource,
40
41         -- * Inspecting the module structure of the program
42         ModuleGraph, ModSummary(..),
43         getModuleGraph,
44         isLoaded,
45         topSortModuleGraph,
46
47         -- * Inspecting modules
48         ModuleInfo,
49         getModuleInfo,
50         modInfoTyThings,
51         modInfoTopLevelScope,
52         modInfoPrintUnqualified,
53         modInfoExports,
54         modInfoInstances,
55         modInfoIsExportedName,
56         modInfoLookupName,
57         lookupGlobalName,
58
59         -- * Interactive evaluation
60         getBindings, getPrintUnqual,
61 #ifdef GHCI
62         setContext, getContext, 
63         getNamesInScope,
64         moduleIsInterpreted,
65         getInfo, GetInfoResult,
66         exprType,
67         typeKind,
68         parseName,
69         RunResult(..),
70         runStmt,
71         browseModule,
72         showModule,
73         compileExpr, HValue,
74         lookupName,
75 #endif
76
77         -- * Abstract syntax elements
78
79         -- ** Modules
80         Module, mkModule, pprModule,
81
82         -- ** Names
83         Name, nameModule,
84         
85         -- ** Identifiers
86         Id, idType,
87         isImplicitId, isDeadBinder,
88         isSpecPragmaId, isExportedId, isLocalId, isGlobalId,
89         isRecordSelector,
90         isPrimOpId, isFCallId,
91         isDataConWorkId, idDataCon,
92         isBottomingId, isDictonaryId,
93
94         -- ** Type constructors
95         TyCon, 
96         isClassTyCon, isSynTyCon, isNewTyCon,
97
98         -- ** Data constructors
99         DataCon,
100
101         -- ** Classes
102         Class, 
103         classSCTheta, classTvsFds,
104
105         -- ** Instances
106         Instance,
107
108         -- ** Types and Kinds
109         Type, dropForAlls,
110         Kind,
111
112         -- ** Entities
113         TyThing(..), 
114
115         -- ** Syntax
116         module HsSyn, -- ToDo: remove extraneous bits
117
118         -- * Exceptions
119         GhcException(..), showGhcException,
120
121         -- * Miscellaneous
122         sessionHscEnv,
123         cyclicModuleErr,
124   ) where
125
126 {-
127  ToDo:
128
129   * inline bits of HscMain here to simplify layering: hscGetInfo,
130     hscTcExpr, hscStmt.
131   * we need to expose DynFlags, so should parseDynamicFlags really be
132     part of this interface?
133   * what StaticFlags should we expose, if any?
134 -}
135
136 #include "HsVersions.h"
137
138 #ifdef GHCI
139 import qualified Linker
140 import Linker           ( HValue, extendLinkEnv )
141 import TcRnDriver       ( getModuleContents, tcRnLookupRdrName,
142                           getModuleExports )
143 import RdrName          ( plusGlobalRdrEnv, Provenance(..), 
144                           ImportSpec(..), ImpDeclSpec(..), ImpItemSpec(..),
145                           emptyGlobalRdrEnv, mkGlobalRdrEnv )
146 import HscMain          ( hscGetInfo, GetInfoResult, hscParseIdentifier,
147                           hscStmt, hscTcExpr, hscKcType )
148 import Type             ( tidyType )
149 import VarEnv           ( emptyTidyEnv )
150 import GHC.Exts         ( unsafeCoerce# )
151 import IfaceSyn         ( IfaceDecl )
152 import SrcLoc           ( srcLocSpan, interactiveSrcLoc )
153 #endif
154
155 import Packages         ( initPackages )
156 import NameSet          ( NameSet, nameSetToList, elemNameSet )
157 import RdrName          ( GlobalRdrEnv, GlobalRdrElt(..), RdrName, 
158                           globalRdrEnvElts )
159 import HsSyn
160 import Type             ( Kind, Type, dropForAlls )
161 import Id               ( Id, idType, isImplicitId, isDeadBinder,
162                           isSpecPragmaId, isExportedId, isLocalId, isGlobalId,
163                           isRecordSelector,
164                           isPrimOpId, isFCallId,
165                           isDataConWorkId, idDataCon,
166                           isBottomingId )
167 import TyCon            ( TyCon, isClassTyCon, isSynTyCon, isNewTyCon )
168 import Class            ( Class, classSCTheta, classTvsFds )
169 import DataCon          ( DataCon )
170 import Name             ( Name, nameModule )
171 import NameEnv          ( nameEnvElts )
172 import InstEnv          ( Instance )
173 import SrcLoc           ( Located(..), mkGeneralSrcSpan, SrcSpan, unLoc )
174 import DriverPipeline
175 import DriverPhases     ( Phase(..), isHaskellSrcFilename, startPhase )
176 import GetImports       ( getImports )
177 import Packages         ( isHomePackage )
178 import Finder
179 import HscMain          ( newHscEnv, hscFileCheck, HscResult(..) )
180 import HscTypes
181 import DynFlags
182 import StaticFlags
183 import SysTools         ( initSysTools, cleanTempFiles )
184 import Module
185 import FiniteMap
186 import Panic
187 import Digraph
188 import ErrUtils         ( showPass, Messages, putMsg, debugTraceMsg, mkLocMessage )
189 import qualified ErrUtils
190 import Util
191 import StringBuffer     ( StringBuffer, hGetStringBuffer )
192 import Outputable
193 import SysTools         ( cleanTempFilesExcept )
194 import BasicTypes       ( SuccessFlag(..), succeeded, failed )
195 import TcType           ( tcSplitSigmaTy, isDictTy )
196 import FastString       ( mkFastString )
197
198 import Directory        ( getModificationTime, doesFileExist )
199 import Maybe            ( isJust, isNothing, fromJust )
200 import Maybes           ( orElse, expectJust, mapCatMaybes )
201 import List             ( partition, nub )
202 import qualified List
203 import Monad            ( unless, when )
204 import System           ( exitWith, ExitCode(..) )
205 import Time             ( ClockTime )
206 import EXCEPTION as Exception hiding (handle)
207 import DATA_IOREF
208 import IO
209 import Prelude hiding (init)
210
211 -- -----------------------------------------------------------------------------
212 -- Exception handlers
213
214 -- | Install some default exception handlers and run the inner computation.
215 -- Unless you want to handle exceptions yourself, you should wrap this around
216 -- the top level of your program.  The default handlers output the error
217 -- message(s) to stderr and exit cleanly.
218 defaultErrorHandler :: IO a -> IO a
219 defaultErrorHandler inner = 
220   -- top-level exception handler: any unrecognised exception is a compiler bug.
221   handle (\exception -> do
222            hFlush stdout
223            case exception of
224                 -- an IO exception probably isn't our fault, so don't panic
225                 IOException _ ->  putMsg (show exception)
226                 AsyncException StackOverflow ->
227                         putMsg "stack overflow: use +RTS -K<size> to increase it"
228                 _other ->  putMsg (show (Panic (show exception)))
229            exitWith (ExitFailure 1)
230          ) $
231
232   -- all error messages are propagated as exceptions
233   handleDyn (\dyn -> do
234                 hFlush stdout
235                 case dyn of
236                      PhaseFailed _ code -> exitWith code
237                      Interrupted -> exitWith (ExitFailure 1)
238                      _ -> do putMsg (show (dyn :: GhcException))
239                              exitWith (ExitFailure 1)
240             ) $
241   inner
242
243 -- | Install a default cleanup handler to remove temporary files
244 -- deposited by a GHC run.  This is seperate from
245 -- 'defaultErrorHandler', because you might want to override the error
246 -- handling, but still get the ordinary cleanup behaviour.
247 defaultCleanupHandler :: DynFlags -> IO a -> IO a
248 defaultCleanupHandler dflags inner = 
249    -- make sure we clean up after ourselves
250    later (unless (dopt Opt_KeepTmpFiles dflags) $ 
251             cleanTempFiles dflags) 
252         -- exceptions will be blocked while we clean the temporary files,
253         -- so there shouldn't be any difficulty if we receive further
254         -- signals.
255    inner
256
257
258 -- | Initialises GHC.  This must be done /once/ only.  Takes the
259 -- command-line arguments.  All command-line arguments which aren't
260 -- understood by GHC will be returned.
261
262 init :: [String] -> IO [String]
263 init args = do
264    -- catch ^C
265    installSignalHandlers
266
267    -- Grab the -B option if there is one
268    let (minusB_args, argv1) = partition (prefixMatch "-B") args
269    dflags0 <- initSysTools minusB_args defaultDynFlags
270    writeIORef v_initDynFlags dflags0
271
272    -- Parse the static flags
273    argv2 <- parseStaticFlags argv1
274    return argv2
275
276 GLOBAL_VAR(v_initDynFlags, error "initDynFlags", DynFlags)
277         -- stores the DynFlags between the call to init and subsequent
278         -- calls to newSession.
279
280 -- | Starts a new session.  A session consists of a set of loaded
281 -- modules, a set of options (DynFlags), and an interactive context.
282 -- ToDo: GhcMode should say "keep typechecked code" and\/or "keep renamed
283 -- code".
284 newSession :: GhcMode -> IO Session
285 newSession mode = do
286   dflags0 <- readIORef v_initDynFlags
287   dflags <- initDynFlags dflags0
288   env <- newHscEnv dflags{ ghcMode=mode }
289   ref <- newIORef env
290   return (Session ref)
291
292 -- tmp: this breaks the abstraction, but required because DriverMkDepend
293 -- needs to call the Finder.  ToDo: untangle this.
294 sessionHscEnv :: Session -> IO HscEnv
295 sessionHscEnv (Session ref) = readIORef ref
296
297 withSession :: Session -> (HscEnv -> IO a) -> IO a
298 withSession (Session ref) f = do h <- readIORef ref; f h
299
300 modifySession :: Session -> (HscEnv -> HscEnv) -> IO ()
301 modifySession (Session ref) f = do h <- readIORef ref; writeIORef ref $! f h
302
303 -- -----------------------------------------------------------------------------
304 -- Flags & settings
305
306 -- | Grabs the DynFlags from the Session
307 getSessionDynFlags :: Session -> IO DynFlags
308 getSessionDynFlags s = withSession s (return . hsc_dflags)
309
310 -- | Updates the DynFlags in a Session
311 setSessionDynFlags :: Session -> DynFlags -> IO ()
312 setSessionDynFlags s dflags = modifySession s (\h -> h{ hsc_dflags = dflags })
313
314 -- | Messages during compilation (eg. warnings and progress messages)
315 -- are reported using this callback.  By default, these messages are
316 -- printed to stderr.
317 setMsgHandler :: (String -> IO ()) -> IO ()
318 setMsgHandler = ErrUtils.setMsgHandler
319
320 -- -----------------------------------------------------------------------------
321 -- Targets
322
323 -- ToDo: think about relative vs. absolute file paths. And what
324 -- happens when the current directory changes.
325
326 -- | Sets the targets for this session.  Each target may be a module name
327 -- or a filename.  The targets correspond to the set of root modules for
328 -- the program\/library.  Unloading the current program is achieved by
329 -- setting the current set of targets to be empty, followed by load.
330 setTargets :: Session -> [Target] -> IO ()
331 setTargets s targets = modifySession s (\h -> h{ hsc_targets = targets })
332
333 -- | returns the current set of targets
334 getTargets :: Session -> IO [Target]
335 getTargets s = withSession s (return . hsc_targets)
336
337 -- | Add another target
338 addTarget :: Session -> Target -> IO ()
339 addTarget s target
340   = modifySession s (\h -> h{ hsc_targets = target : hsc_targets h })
341
342 -- | Remove a target
343 removeTarget :: Session -> TargetId -> IO ()
344 removeTarget s target_id
345   = modifySession s (\h -> h{ hsc_targets = filter (hsc_targets h) })
346   where
347    filter targets = [ t | t@(Target id _) <- targets, id /= target_id ]
348
349 -- Attempts to guess what Target a string refers to.  This function implements
350 -- the --make/GHCi command-line syntax for filenames: 
351 --
352 --      - if the string looks like a Haskell source filename, then interpret
353 --        it as such
354 --      - if adding a .hs or .lhs suffix yields the name of an existing file,
355 --        then use that
356 --      - otherwise interpret the string as a module name
357 --
358 guessTarget :: String -> Maybe Phase -> IO Target
359 guessTarget file (Just phase)
360    = return (Target (TargetFile file (Just phase)) Nothing)
361 guessTarget file Nothing
362    | isHaskellSrcFilename file
363    = return (Target (TargetFile file Nothing) Nothing)
364    | otherwise
365    = do exists <- doesFileExist hs_file
366         if exists
367            then return (Target (TargetFile hs_file Nothing) Nothing)
368            else do
369         exists <- doesFileExist lhs_file
370         if exists
371            then return (Target (TargetFile lhs_file Nothing) Nothing)
372            else do
373         return (Target (TargetModule (mkModule file)) Nothing)
374      where 
375          hs_file  = file `joinFileExt` "hs"
376          lhs_file = file `joinFileExt` "lhs"
377
378 -- -----------------------------------------------------------------------------
379 -- Loading the program
380
381 -- Perform a dependency analysis starting from the current targets
382 -- and update the session with the new module graph.
383 depanal :: Session -> [Module] -> IO ()
384 depanal (Session ref) excluded_mods = do
385   hsc_env <- readIORef ref
386   let
387          dflags  = hsc_dflags hsc_env
388          gmode   = ghcMode (hsc_dflags hsc_env)
389          targets = hsc_targets hsc_env
390          old_graph = hsc_mod_graph hsc_env
391         
392   showPass dflags "Chasing dependencies"
393   when (gmode == BatchCompile) $
394         debugTraceMsg dflags 1 (showSDoc (hcat [
395                      text "Chasing modules from: ",
396                         hcat (punctuate comma (map pprTarget targets))]))
397
398   graph <- downsweep hsc_env old_graph excluded_mods
399   writeIORef ref hsc_env{ hsc_mod_graph=graph }
400
401 {-
402 -- | The result of load.
403 data LoadResult
404   = LoadOk      Errors  -- ^ all specified targets were loaded successfully.
405   | LoadFailed  Errors  -- ^ not all modules were loaded.
406
407 type Errors = [String]
408
409 data ErrMsg = ErrMsg { 
410         errMsgSeverity  :: Severity,  -- warning, error, etc.
411         errMsgSpans     :: [SrcSpan],
412         errMsgShortDoc  :: Doc,
413         errMsgExtraInfo :: Doc
414         }
415 -}
416
417 data LoadHowMuch
418    = LoadAllTargets
419    | LoadUpTo Module
420    | LoadDependenciesOf Module
421
422 -- | Try to load the program.  If a Module is supplied, then just
423 -- attempt to load up to this target.  If no Module is supplied,
424 -- then try to load all targets.
425 load :: Session -> LoadHowMuch -> IO SuccessFlag
426 load session how_much = 
427    loadMsgs session how_much ErrUtils.printErrorsAndWarnings
428
429 -- | Version of 'load' that takes a callback function to be invoked
430 -- on compiler errors and warnings as they occur during compilation.
431 loadMsgs :: Session -> LoadHowMuch -> (Messages-> IO ()) -> IO SuccessFlag
432 loadMsgs s@(Session ref) how_much msg_act
433    = do 
434         -- Dependency analysis first.  Note that this fixes the module graph:
435         -- even if we don't get a fully successful upsweep, the full module
436         -- graph is still retained in the Session.  We can tell which modules
437         -- were successfully loaded by inspecting the Session's HPT.
438         depanal s []
439
440         hsc_env <- readIORef ref
441
442         let hpt1      = hsc_HPT hsc_env
443         let dflags    = hsc_dflags hsc_env
444         let mod_graph = hsc_mod_graph hsc_env
445
446         let ghci_mode = ghcMode (hsc_dflags hsc_env) -- this never changes
447         let verb      = verbosity dflags
448
449         -- The "bad" boot modules are the ones for which we have
450         -- B.hs-boot in the module graph, but no B.hs
451         -- The downsweep should have ensured this does not happen
452         -- (see msDeps)
453         let all_home_mods = [ms_mod s | s <- mod_graph, not (isBootSummary s)]
454             bad_boot_mods = [s        | s <- mod_graph, isBootSummary s,
455                                         not (ms_mod s `elem` all_home_mods)]
456         ASSERT( null bad_boot_mods ) return ()
457
458         -- mg2_with_srcimps drops the hi-boot nodes, returning a 
459         -- graph with cycles.  Among other things, it is used for
460         -- backing out partially complete cycles following a failed
461         -- upsweep, and for removing from hpt all the modules
462         -- not in strict downwards closure, during calls to compile.
463         let mg2_with_srcimps :: [SCC ModSummary]
464             mg2_with_srcimps = topSortModuleGraph True mod_graph Nothing
465
466             -- check the stability property for each module.
467             stable_mods@(stable_obj,stable_bco)
468                 | BatchCompile <- ghci_mode = ([],[])
469                 | otherwise = checkStability hpt1 mg2_with_srcimps all_home_mods
470
471             -- prune bits of the HPT which are definitely redundant now,
472             -- to save space.
473             pruned_hpt = pruneHomePackageTable hpt1 
474                                 (flattenSCCs mg2_with_srcimps)
475                                 stable_mods
476
477         evaluate pruned_hpt
478
479         debugTraceMsg dflags 2 (showSDoc (text "Stable obj:" <+> ppr stable_obj $$
480                                 text "Stable BCO:" <+> ppr stable_bco))
481
482         -- Unload any modules which are going to be re-linked this time around.
483         let stable_linkables = [ linkable
484                                | m <- stable_obj++stable_bco,
485                                  Just hmi <- [lookupModuleEnv pruned_hpt m],
486                                  Just linkable <- [hm_linkable hmi] ]
487         unload hsc_env stable_linkables
488
489         -- We could at this point detect cycles which aren't broken by
490         -- a source-import, and complain immediately, but it seems better
491         -- to let upsweep_mods do this, so at least some useful work gets
492         -- done before the upsweep is abandoned.
493         --hPutStrLn stderr "after tsort:\n"
494         --hPutStrLn stderr (showSDoc (vcat (map ppr mg2)))
495
496         -- Now do the upsweep, calling compile for each module in
497         -- turn.  Final result is version 3 of everything.
498
499         -- Topologically sort the module graph, this time including hi-boot
500         -- nodes, and possibly just including the portion of the graph
501         -- reachable from the module specified in the 2nd argument to load.
502         -- This graph should be cycle-free.
503         -- If we're restricting the upsweep to a portion of the graph, we
504         -- also want to retain everything that is still stable.
505         let full_mg :: [SCC ModSummary]
506             full_mg    = topSortModuleGraph False mod_graph Nothing
507
508             maybe_top_mod = case how_much of
509                                 LoadUpTo m           -> Just m
510                                 LoadDependenciesOf m -> Just m
511                                 _                    -> Nothing
512
513             partial_mg0 :: [SCC ModSummary]
514             partial_mg0 = topSortModuleGraph False mod_graph maybe_top_mod
515
516             -- LoadDependenciesOf m: we want the upsweep to stop just
517             -- short of the specified module (unless the specified module
518             -- is stable).
519             partial_mg
520                 | LoadDependenciesOf mod <- how_much
521                 = ASSERT( case last partial_mg0 of 
522                             AcyclicSCC ms -> ms_mod ms == mod; _ -> False )
523                   List.init partial_mg0
524                 | otherwise
525                 = partial_mg0
526   
527             stable_mg = 
528                 [ AcyclicSCC ms
529                 | AcyclicSCC ms <- full_mg,
530                   ms_mod ms `elem` stable_obj++stable_bco,
531                   ms_mod ms `notElem` [ ms_mod ms' | 
532                                         AcyclicSCC ms' <- partial_mg ] ]
533
534             mg = stable_mg ++ partial_mg
535
536         -- clean up between compilations
537         let cleanup = cleanTempFilesExcept dflags
538                           (ppFilesFromSummaries (flattenSCCs mg2_with_srcimps))
539
540         (upsweep_ok, hsc_env1, modsUpswept)
541            <- upsweep (hsc_env { hsc_HPT = emptyHomePackageTable })
542                            pruned_hpt stable_mods cleanup msg_act mg
543
544         -- Make modsDone be the summaries for each home module now
545         -- available; this should equal the domain of hpt3.
546         -- Get in in a roughly top .. bottom order (hence reverse).
547
548         let modsDone = reverse modsUpswept
549
550         -- Try and do linking in some form, depending on whether the
551         -- upsweep was completely or only partially successful.
552
553         if succeeded upsweep_ok
554
555          then 
556            -- Easy; just relink it all.
557            do debugTraceMsg dflags 2 "Upsweep completely successful."
558
559               -- Clean up after ourselves
560               cleanTempFilesExcept dflags (ppFilesFromSummaries modsDone)
561
562               -- Issue a warning for the confusing case where the user
563               -- said '-o foo' but we're not going to do any linking.
564               -- We attempt linking if either (a) one of the modules is
565               -- called Main, or (b) the user said -no-hs-main, indicating
566               -- that main() is going to come from somewhere else.
567               --
568               let ofile = outputFile dflags
569               let no_hs_main = dopt Opt_NoHsMain dflags
570               let mb_main_mod = mainModIs dflags
571               let 
572                 main_mod = mb_main_mod `orElse` "Main"
573                 a_root_is_Main 
574                     = any ((==main_mod).moduleUserString.ms_mod) 
575                           mod_graph
576                 do_linking = a_root_is_Main || no_hs_main
577
578               when (ghci_mode == BatchCompile && isJust ofile && not do_linking) $
579                 debugTraceMsg dflags 1 ("Warning: output was redirected with -o, " ++
580                                    "but no output will be generated\n" ++
581                                    "because there is no " ++ main_mod ++ " module.")
582
583               -- link everything together
584               linkresult <- link ghci_mode dflags do_linking (hsc_HPT hsc_env1)
585
586               loadFinish Succeeded linkresult ref hsc_env1
587
588          else 
589            -- Tricky.  We need to back out the effects of compiling any
590            -- half-done cycles, both so as to clean up the top level envs
591            -- and to avoid telling the interactive linker to link them.
592            do debugTraceMsg dflags 2 "Upsweep partially successful."
593
594               let modsDone_names
595                      = map ms_mod modsDone
596               let mods_to_zap_names 
597                      = findPartiallyCompletedCycles modsDone_names 
598                           mg2_with_srcimps
599               let mods_to_keep
600                      = filter ((`notElem` mods_to_zap_names).ms_mod) 
601                           modsDone
602
603               let hpt4 = retainInTopLevelEnvs (map ms_mod mods_to_keep) 
604                                               (hsc_HPT hsc_env1)
605
606               -- Clean up after ourselves
607               cleanTempFilesExcept dflags (ppFilesFromSummaries mods_to_keep)
608
609               -- there should be no Nothings where linkables should be, now
610               ASSERT(all (isJust.hm_linkable) 
611                         (moduleEnvElts (hsc_HPT hsc_env))) do
612         
613               -- Link everything together
614               linkresult <- link ghci_mode dflags False hpt4
615
616               let hsc_env4 = hsc_env1{ hsc_HPT = hpt4 }
617               loadFinish Failed linkresult ref hsc_env4
618
619 -- Finish up after a load.
620
621 -- If the link failed, unload everything and return.
622 loadFinish all_ok Failed ref hsc_env
623   = do unload hsc_env []
624        writeIORef ref $! discardProg hsc_env
625        return Failed
626
627 -- Empty the interactive context and set the module context to the topmost
628 -- newly loaded module, or the Prelude if none were loaded.
629 loadFinish all_ok Succeeded ref hsc_env
630   = do writeIORef ref $! hsc_env{ hsc_IC = emptyInteractiveContext }
631        return all_ok
632
633
634 -- Forget the current program, but retain the persistent info in HscEnv
635 discardProg :: HscEnv -> HscEnv
636 discardProg hsc_env
637   = hsc_env { hsc_mod_graph = emptyMG, 
638               hsc_IC = emptyInteractiveContext,
639               hsc_HPT = emptyHomePackageTable }
640
641 -- used to fish out the preprocess output files for the purposes of
642 -- cleaning up.  The preprocessed file *might* be the same as the
643 -- source file, but that doesn't do any harm.
644 ppFilesFromSummaries summaries = [ fn | Just fn <- map ms_hspp_file summaries ]
645
646 -- -----------------------------------------------------------------------------
647 -- Check module
648
649 data CheckedModule = 
650   CheckedModule { parsedSource      :: ParsedSource,
651                   renamedSource     :: Maybe RenamedSource,
652                   typecheckedSource :: Maybe TypecheckedSource,
653                   checkedModuleInfo :: Maybe ModuleInfo
654                 }
655         -- ToDo: improvements that could be made here:
656         --  if the module succeeded renaming but not typechecking,
657         --  we can still get back the GlobalRdrEnv and exports, so
658         --  perhaps the ModuleInfo should be split up into separate
659         --  fields within CheckedModule.
660
661 type ParsedSource      = Located (HsModule RdrName)
662 type RenamedSource     = HsGroup Name
663 type TypecheckedSource = LHsBinds Id
664
665 -- | This is the way to get access to parsed and typechecked source code
666 -- for a module.  'checkModule' loads all the dependencies of the specified
667 -- module in the Session, and then attempts to typecheck the module.  If
668 -- successful, it returns the abstract syntax for the module.
669 checkModule :: Session -> Module -> (Messages -> IO ()) 
670         -> IO (Maybe CheckedModule)
671 checkModule session@(Session ref) mod msg_act = do
672         -- load up the dependencies first
673    r <- loadMsgs session (LoadDependenciesOf mod) msg_act
674    if (failed r) then return Nothing else do
675
676         -- now parse & typecheck the module
677    hsc_env <- readIORef ref   
678    let mg  = hsc_mod_graph hsc_env
679    case [ ms | ms <- mg, ms_mod ms == mod ] of
680         [] -> return Nothing
681         (ms:_) -> do 
682            -- Add in the OPTIONS from the source file This is nasty:
683            -- we've done this once already, in the compilation manager
684            -- It might be better to cache the flags in the
685            -- ml_hspp_file field, say
686            let dflags0 = hsc_dflags hsc_env
687                hspp_buf = expectJust "GHC.checkModule" (ms_hspp_buf ms)
688                opts = getOptionsFromStringBuffer hspp_buf
689            (dflags1,leftovers) <- parseDynamicFlags dflags0 (map snd opts)
690            if (not (null leftovers))
691                 then do let filename = fromJust (ml_hs_file (ms_location ms))
692                         msg_act (optionsErrorMsgs leftovers opts filename)
693                         return Nothing
694                 else do
695
696            r <- hscFileCheck hsc_env{hsc_dflags=dflags1} msg_act ms
697            case r of
698                 HscFail -> 
699                    return Nothing
700                 HscChecked parsed renamed Nothing ->
701                    return (Just (CheckedModule {
702                                         parsedSource = parsed,
703                                         renamedSource = renamed,
704                                         typecheckedSource = Nothing,
705                                         checkedModuleInfo = Nothing }))
706                 HscChecked parsed renamed
707                            (Just (tc_binds, rdr_env, details)) -> do
708                    let minf = ModuleInfo {
709                                 minf_type_env  = md_types details,
710                                 minf_exports   = md_exports details,
711                                 minf_rdr_env   = Just rdr_env,
712                                 minf_instances = md_insts details
713                               }
714                    return (Just (CheckedModule {
715                                         parsedSource = parsed,
716                                         renamedSource = renamed,
717                                         typecheckedSource = Just tc_binds,
718                                         checkedModuleInfo = Just minf }))
719
720 -- ---------------------------------------------------------------------------
721 -- Unloading
722
723 unload :: HscEnv -> [Linkable] -> IO ()
724 unload hsc_env stable_linkables -- Unload everthing *except* 'stable_linkables'
725   = case ghcMode (hsc_dflags hsc_env) of
726         BatchCompile  -> return ()
727         JustTypecheck -> return ()
728 #ifdef GHCI
729         Interactive -> Linker.unload (hsc_dflags hsc_env) stable_linkables
730 #else
731         Interactive -> panic "unload: no interpreter"
732 #endif
733         other -> panic "unload: strange mode"
734
735 -- -----------------------------------------------------------------------------
736 -- checkStability
737
738 {-
739   Stability tells us which modules definitely do not need to be recompiled.
740   There are two main reasons for having stability:
741   
742    - avoid doing a complete upsweep of the module graph in GHCi when
743      modules near the bottom of the tree have not changed.
744
745    - to tell GHCi when it can load object code: we can only load object code
746      for a module when we also load object code fo  all of the imports of the
747      module.  So we need to know that we will definitely not be recompiling
748      any of these modules, and we can use the object code.
749
750   NB. stability is of no importance to BatchCompile at all, only Interactive.
751   (ToDo: what about JustTypecheck?)
752
753   The stability check is as follows.  Both stableObject and
754   stableBCO are used during the upsweep phase later.
755
756   -------------------
757   stable m = stableObject m || stableBCO m
758
759   stableObject m = 
760         all stableObject (imports m)
761         && old linkable does not exist, or is == on-disk .o
762         && date(on-disk .o) > date(.hs)
763
764   stableBCO m =
765         all stable (imports m)
766         && date(BCO) > date(.hs)
767   -------------------    
768
769   These properties embody the following ideas:
770
771     - if a module is stable:
772         - if it has been compiled in a previous pass (present in HPT)
773           then it does not need to be compiled or re-linked.
774         - if it has not been compiled in a previous pass,
775           then we only need to read its .hi file from disk and
776           link it to produce a ModDetails.
777
778     - if a modules is not stable, we will definitely be at least
779       re-linking, and possibly re-compiling it during the upsweep.
780       All non-stable modules can (and should) therefore be unlinked
781       before the upsweep.
782
783     - Note that objects are only considered stable if they only depend
784       on other objects.  We can't link object code against byte code.
785 -}
786
787 checkStability
788         :: HomePackageTable             -- HPT from last compilation
789         -> [SCC ModSummary]             -- current module graph (cyclic)
790         -> [Module]                     -- all home modules
791         -> ([Module],                   -- stableObject
792             [Module])                   -- stableBCO
793
794 checkStability hpt sccs all_home_mods = foldl checkSCC ([],[]) sccs
795   where
796    checkSCC (stable_obj, stable_bco) scc0
797      | stableObjects = (scc_mods ++ stable_obj, stable_bco)
798      | stableBCOs    = (stable_obj, scc_mods ++ stable_bco)
799      | otherwise     = (stable_obj, stable_bco)
800      where
801         scc = flattenSCC scc0
802         scc_mods = map ms_mod scc
803         home_module m   = m `elem` all_home_mods && m `notElem` scc_mods
804
805         scc_allimps = nub (filter home_module (concatMap ms_allimps scc))
806             -- all imports outside the current SCC, but in the home pkg
807         
808         stable_obj_imps = map (`elem` stable_obj) scc_allimps
809         stable_bco_imps = map (`elem` stable_bco) scc_allimps
810
811         stableObjects = 
812            and stable_obj_imps
813            && all object_ok scc
814
815         stableBCOs = 
816            and (zipWith (||) stable_obj_imps stable_bco_imps)
817            && all bco_ok scc
818
819         object_ok ms
820           | Just t <- ms_obj_date ms  =  t >= ms_hs_date ms 
821                                          && same_as_prev t
822           | otherwise = False
823           where
824              same_as_prev t = case lookupModuleEnv hpt (ms_mod ms) of
825                                 Nothing  -> True
826                                 Just hmi  | Just l <- hm_linkable hmi
827                                  -> isObjectLinkable l && t == linkableTime l
828                 -- why '>=' rather than '>' above?  If the filesystem stores
829                 -- times to the nearset second, we may occasionally find that
830                 -- the object & source have the same modification time, 
831                 -- especially if the source was automatically generated
832                 -- and compiled.  Using >= is slightly unsafe, but it matches
833                 -- make's behaviour.
834
835         bco_ok ms
836           = case lookupModuleEnv hpt (ms_mod ms) of
837                 Nothing  -> False
838                 Just hmi  | Just l <- hm_linkable hmi ->
839                         not (isObjectLinkable l) && 
840                         linkableTime l >= ms_hs_date ms
841
842 ms_allimps :: ModSummary -> [Module]
843 ms_allimps ms = map unLoc (ms_srcimps ms ++ ms_imps ms)
844
845 -- -----------------------------------------------------------------------------
846 -- Prune the HomePackageTable
847
848 -- Before doing an upsweep, we can throw away:
849 --
850 --   - For non-stable modules:
851 --      - all ModDetails, all linked code
852 --   - all unlinked code that is out of date with respect to
853 --     the source file
854 --
855 -- This is VERY IMPORTANT otherwise we'll end up requiring 2x the
856 -- space at the end of the upsweep, because the topmost ModDetails of the
857 -- old HPT holds on to the entire type environment from the previous
858 -- compilation.
859
860 pruneHomePackageTable
861    :: HomePackageTable
862    -> [ModSummary]
863    -> ([Module],[Module])
864    -> HomePackageTable
865
866 pruneHomePackageTable hpt summ (stable_obj, stable_bco)
867   = mapModuleEnv prune hpt
868   where prune hmi
869           | is_stable modl = hmi'
870           | otherwise      = hmi'{ hm_details = emptyModDetails }
871           where
872            modl = mi_module (hm_iface hmi)
873            hmi' | Just l <- hm_linkable hmi, linkableTime l < ms_hs_date ms
874                 = hmi{ hm_linkable = Nothing }
875                 | otherwise
876                 = hmi
877                 where ms = expectJust "prune" (lookupModuleEnv ms_map modl)
878
879         ms_map = mkModuleEnv [(ms_mod ms, ms) | ms <- summ]
880
881         is_stable m = m `elem` stable_obj || m `elem` stable_bco
882
883 -- -----------------------------------------------------------------------------
884
885 -- Return (names of) all those in modsDone who are part of a cycle
886 -- as defined by theGraph.
887 findPartiallyCompletedCycles :: [Module] -> [SCC ModSummary] -> [Module]
888 findPartiallyCompletedCycles modsDone theGraph
889    = chew theGraph
890      where
891         chew [] = []
892         chew ((AcyclicSCC v):rest) = chew rest    -- acyclic?  not interesting.
893         chew ((CyclicSCC vs):rest)
894            = let names_in_this_cycle = nub (map ms_mod vs)
895                  mods_in_this_cycle  
896                     = nub ([done | done <- modsDone, 
897                                    done `elem` names_in_this_cycle])
898                  chewed_rest = chew rest
899              in 
900              if   notNull mods_in_this_cycle
901                   && length mods_in_this_cycle < length names_in_this_cycle
902              then mods_in_this_cycle ++ chewed_rest
903              else chewed_rest
904
905 -- -----------------------------------------------------------------------------
906 -- The upsweep
907
908 -- This is where we compile each module in the module graph, in a pass
909 -- from the bottom to the top of the graph.
910
911 -- There better had not be any cyclic groups here -- we check for them.
912
913 upsweep
914     :: HscEnv                   -- Includes initially-empty HPT
915     -> HomePackageTable         -- HPT from last time round (pruned)
916     -> ([Module],[Module])      -- stable modules (see checkStability)
917     -> IO ()                    -- How to clean up unwanted tmp files
918     -> (Messages -> IO ())      -- Compiler error message callback
919     -> [SCC ModSummary]         -- Mods to do (the worklist)
920     -> IO (SuccessFlag,
921            HscEnv,              -- With an updated HPT
922            [ModSummary])        -- Mods which succeeded
923
924 upsweep hsc_env old_hpt stable_mods cleanup msg_act mods
925    = upsweep' hsc_env old_hpt stable_mods cleanup msg_act mods 1 (length mods)
926
927 upsweep' hsc_env old_hpt stable_mods cleanup msg_act
928      [] _ _
929    = return (Succeeded, hsc_env, [])
930
931 upsweep' hsc_env old_hpt stable_mods cleanup msg_act
932      (CyclicSCC ms:_) _ _
933    = do putMsg (showSDoc (cyclicModuleErr ms))
934         return (Failed, hsc_env, [])
935
936 upsweep' hsc_env old_hpt stable_mods cleanup msg_act
937      (AcyclicSCC mod:mods) mod_index nmods
938    = do -- putStrLn ("UPSWEEP_MOD: hpt = " ++ 
939         --           show (map (moduleUserString.moduleName.mi_module.hm_iface) 
940         --                     (moduleEnvElts (hsc_HPT hsc_env)))
941
942         mb_mod_info <- upsweep_mod hsc_env old_hpt stable_mods msg_act mod 
943                        mod_index nmods
944
945         cleanup         -- Remove unwanted tmp files between compilations
946
947         case mb_mod_info of
948             Nothing -> return (Failed, hsc_env, [])
949             Just mod_info -> do 
950                 { let this_mod = ms_mod mod
951
952                         -- Add new info to hsc_env
953                       hpt1     = extendModuleEnv (hsc_HPT hsc_env) 
954                                         this_mod mod_info
955                       hsc_env1 = hsc_env { hsc_HPT = hpt1 }
956
957                         -- Space-saving: delete the old HPT entry
958                         -- for mod BUT if mod is a hs-boot
959                         -- node, don't delete it.  For the
960                         -- interface, the HPT entry is probaby for the
961                         -- main Haskell source file.  Deleting it
962                         -- would force .. (what?? --SDM)
963                       old_hpt1 | isBootSummary mod = old_hpt
964                                | otherwise = delModuleEnv old_hpt this_mod
965
966                 ; (restOK, hsc_env2, modOKs) 
967                         <- upsweep' hsc_env1 old_hpt1 stable_mods cleanup 
968                                 msg_act mods (mod_index+1) nmods
969                 ; return (restOK, hsc_env2, mod:modOKs)
970                 }
971
972
973 -- Compile a single module.  Always produce a Linkable for it if 
974 -- successful.  If no compilation happened, return the old Linkable.
975 upsweep_mod :: HscEnv
976             -> HomePackageTable
977             -> ([Module],[Module])
978             -> (Messages -> IO ())
979             -> ModSummary
980             -> Int  -- index of module
981             -> Int  -- total number of modules
982             -> IO (Maybe HomeModInfo)   -- Nothing => Failed
983
984 upsweep_mod hsc_env old_hpt (stable_obj, stable_bco) msg_act summary mod_index nmods
985    = do 
986         let 
987             this_mod    = ms_mod summary
988             mb_obj_date = ms_obj_date summary
989             obj_fn      = ml_obj_file (ms_location summary)
990             hs_date     = ms_hs_date summary
991
992             compile_it :: Maybe Linkable -> IO (Maybe HomeModInfo)
993             compile_it  = upsweep_compile hsc_env old_hpt this_mod 
994                                 msg_act summary mod_index nmods
995
996         case ghcMode (hsc_dflags hsc_env) of
997             BatchCompile ->
998                 case () of
999                    -- Batch-compilating is easy: just check whether we have
1000                    -- an up-to-date object file.  If we do, then the compiler
1001                    -- needs to do a recompilation check.
1002                    _ | Just obj_date <- mb_obj_date, obj_date >= hs_date -> do
1003                            linkable <- 
1004                                 findObjectLinkable this_mod obj_fn obj_date
1005                            compile_it (Just linkable)
1006
1007                      | otherwise ->
1008                            compile_it Nothing
1009
1010             interactive ->
1011                 case () of
1012                     _ | is_stable_obj, isJust old_hmi ->
1013                            return old_hmi
1014                         -- object is stable, and we have an entry in the
1015                         -- old HPT: nothing to do
1016
1017                       | is_stable_obj, isNothing old_hmi -> do
1018                            linkable <-
1019                                 findObjectLinkable this_mod obj_fn 
1020                                         (expectJust "upseep1" mb_obj_date)
1021                            compile_it (Just linkable)
1022                         -- object is stable, but we need to load the interface
1023                         -- off disk to make a HMI.
1024
1025                       | is_stable_bco -> 
1026                            ASSERT(isJust old_hmi) -- must be in the old_hpt
1027                            return old_hmi
1028                         -- BCO is stable: nothing to do
1029
1030                       | Just hmi <- old_hmi,
1031                         Just l <- hm_linkable hmi, not (isObjectLinkable l),
1032                         linkableTime l >= ms_hs_date summary ->
1033                            compile_it (Just l)
1034                         -- we have an old BCO that is up to date with respect
1035                         -- to the source: do a recompilation check as normal.
1036
1037                       | otherwise ->
1038                           compile_it Nothing
1039                         -- no existing code at all: we must recompile.
1040                    where
1041                     is_stable_obj = this_mod `elem` stable_obj
1042                     is_stable_bco = this_mod `elem` stable_bco
1043
1044                     old_hmi = lookupModuleEnv old_hpt this_mod
1045
1046 -- Run hsc to compile a module
1047 upsweep_compile hsc_env old_hpt this_mod msg_act summary
1048                 mod_index nmods
1049                 mb_old_linkable = do
1050   let
1051         -- The old interface is ok if it's in the old HPT 
1052         --      a) we're compiling a source file, and the old HPT
1053         --         entry is for a source file
1054         --      b) we're compiling a hs-boot file
1055         -- Case (b) allows an hs-boot file to get the interface of its
1056         -- real source file on the second iteration of the compilation
1057         -- manager, but that does no harm.  Otherwise the hs-boot file
1058         -- will always be recompiled
1059
1060         mb_old_iface 
1061                 = case lookupModuleEnv old_hpt this_mod of
1062                      Nothing                              -> Nothing
1063                      Just hm_info | isBootSummary summary -> Just iface
1064                                   | not (mi_boot iface)   -> Just iface
1065                                   | otherwise             -> Nothing
1066                                    where 
1067                                      iface = hm_iface hm_info
1068
1069   compresult <- compile hsc_env msg_act summary mb_old_linkable mb_old_iface
1070                         mod_index nmods
1071
1072   case compresult of
1073         -- Compilation failed.  Compile may still have updated the PCS, tho.
1074         CompErrs -> return Nothing
1075
1076         -- Compilation "succeeded", and may or may not have returned a new
1077         -- linkable (depending on whether compilation was actually performed
1078         -- or not).
1079         CompOK new_details new_iface new_linkable
1080               -> do let new_info = HomeModInfo { hm_iface = new_iface,
1081                                                  hm_details = new_details,
1082                                                  hm_linkable = new_linkable }
1083                     return (Just new_info)
1084
1085
1086 -- Filter modules in the HPT
1087 retainInTopLevelEnvs :: [Module] -> HomePackageTable -> HomePackageTable
1088 retainInTopLevelEnvs keep_these hpt
1089    = mkModuleEnv [ (mod, expectJust "retain" mb_mod_info)
1090                  | mod <- keep_these
1091                  , let mb_mod_info = lookupModuleEnv hpt mod
1092                  , isJust mb_mod_info ]
1093
1094 -- ---------------------------------------------------------------------------
1095 -- Topological sort of the module graph
1096
1097 topSortModuleGraph
1098           :: Bool               -- Drop hi-boot nodes? (see below)
1099           -> [ModSummary]
1100           -> Maybe Module
1101           -> [SCC ModSummary]
1102 -- Calculate SCCs of the module graph, possibly dropping the hi-boot nodes
1103 -- The resulting list of strongly-connected-components is in topologically
1104 -- sorted order, starting with the module(s) at the bottom of the
1105 -- dependency graph (ie compile them first) and ending with the ones at
1106 -- the top.
1107 --
1108 -- Drop hi-boot nodes (first boolean arg)? 
1109 --
1110 --   False:     treat the hi-boot summaries as nodes of the graph,
1111 --              so the graph must be acyclic
1112 --
1113 --   True:      eliminate the hi-boot nodes, and instead pretend
1114 --              the a source-import of Foo is an import of Foo
1115 --              The resulting graph has no hi-boot nodes, but can by cyclic
1116
1117 topSortModuleGraph drop_hs_boot_nodes summaries Nothing
1118   = stronglyConnComp (fst (moduleGraphNodes drop_hs_boot_nodes summaries))
1119 topSortModuleGraph drop_hs_boot_nodes summaries (Just mod)
1120   = stronglyConnComp (map vertex_fn (reachable graph root))
1121   where 
1122         -- restrict the graph to just those modules reachable from
1123         -- the specified module.  We do this by building a graph with
1124         -- the full set of nodes, and determining the reachable set from
1125         -- the specified node.
1126         (nodes, lookup_key) = moduleGraphNodes drop_hs_boot_nodes summaries
1127         (graph, vertex_fn, key_fn) = graphFromEdges' nodes
1128         root 
1129           | Just key <- lookup_key HsSrcFile mod, Just v <- key_fn key = v
1130           | otherwise  = throwDyn (ProgramError "module does not exist")
1131
1132 moduleGraphNodes :: Bool -> [ModSummary]
1133   -> ([(ModSummary, Int, [Int])], HscSource -> Module -> Maybe Int)
1134 moduleGraphNodes drop_hs_boot_nodes summaries = (nodes, lookup_key)
1135    where
1136         -- Drop hs-boot nodes by using HsSrcFile as the key
1137         hs_boot_key | drop_hs_boot_nodes = HsSrcFile
1138                     | otherwise          = HsBootFile   
1139
1140         -- We use integers as the keys for the SCC algorithm
1141         nodes :: [(ModSummary, Int, [Int])]     
1142         nodes = [(s, expectJust "topSort" (lookup_key (ms_hsc_src s) (ms_mod s)), 
1143                      out_edge_keys hs_boot_key (map unLoc (ms_srcimps s)) ++
1144                      out_edge_keys HsSrcFile   (map unLoc (ms_imps s))    )
1145                 | s <- summaries
1146                 , not (isBootSummary s && drop_hs_boot_nodes) ]
1147                 -- Drop the hi-boot ones if told to do so
1148
1149         key_map :: NodeMap Int
1150         key_map = listToFM ([(ms_mod s, ms_hsc_src s) | s <- summaries]
1151                            `zip` [1..])
1152
1153         lookup_key :: HscSource -> Module -> Maybe Int
1154         lookup_key hs_src mod = lookupFM key_map (mod, hs_src)
1155
1156         out_edge_keys :: HscSource -> [Module] -> [Int]
1157         out_edge_keys hi_boot ms = mapCatMaybes (lookup_key hi_boot) ms
1158                 -- If we want keep_hi_boot_nodes, then we do lookup_key with
1159                 -- the IsBootInterface parameter True; else False
1160
1161
1162 type NodeKey   = (Module, HscSource)      -- The nodes of the graph are 
1163 type NodeMap a = FiniteMap NodeKey a      -- keyed by (mod, src_file_type) pairs
1164
1165 msKey :: ModSummary -> NodeKey
1166 msKey (ModSummary { ms_mod = mod, ms_hsc_src = boot }) = (mod,boot)
1167
1168 emptyNodeMap :: NodeMap a
1169 emptyNodeMap = emptyFM
1170
1171 mkNodeMap :: [ModSummary] -> NodeMap ModSummary
1172 mkNodeMap summaries = listToFM [ (msKey s, s) | s <- summaries]
1173         
1174 nodeMapElts :: NodeMap a -> [a]
1175 nodeMapElts = eltsFM
1176
1177 -- -----------------------------------------------------------------
1178 -- The unlinked image
1179 -- 
1180 -- The compilation manager keeps a list of compiled, but as-yet unlinked
1181 -- binaries (byte code or object code).  Even when it links bytecode
1182 -- it keeps the unlinked version so it can re-link it later without
1183 -- recompiling.
1184
1185 type UnlinkedImage = [Linkable] -- the unlinked images (should be a set, really)
1186
1187 findModuleLinkable_maybe :: [Linkable] -> Module -> Maybe Linkable
1188 findModuleLinkable_maybe lis mod
1189    = case [LM time nm us | LM time nm us <- lis, nm == mod] of
1190         []   -> Nothing
1191         [li] -> Just li
1192         many -> pprPanic "findModuleLinkable" (ppr mod)
1193
1194 delModuleLinkable :: [Linkable] -> Module -> [Linkable]
1195 delModuleLinkable ls mod = [ l | l@(LM _ nm _) <- ls, nm /= mod ]
1196
1197 -----------------------------------------------------------------------------
1198 -- Downsweep (dependency analysis)
1199
1200 -- Chase downwards from the specified root set, returning summaries
1201 -- for all home modules encountered.  Only follow source-import
1202 -- links.
1203
1204 -- We pass in the previous collection of summaries, which is used as a
1205 -- cache to avoid recalculating a module summary if the source is
1206 -- unchanged.
1207 --
1208 -- The returned list of [ModSummary] nodes has one node for each home-package
1209 -- module, plus one for any hs-boot files.  The imports of these nodes 
1210 -- are all there, including the imports of non-home-package modules.
1211
1212 downsweep :: HscEnv
1213           -> [ModSummary]       -- Old summaries
1214           -> [Module]           -- Ignore dependencies on these; treat them as
1215                                 -- if they were package modules
1216           -> IO [ModSummary]
1217 downsweep hsc_env old_summaries excl_mods
1218    = do rootSummaries <- mapM getRootSummary roots
1219         checkDuplicates rootSummaries
1220         loop (concatMap msDeps rootSummaries) 
1221              (mkNodeMap rootSummaries)
1222      where
1223         roots = hsc_targets hsc_env
1224
1225         old_summary_map :: NodeMap ModSummary
1226         old_summary_map = mkNodeMap old_summaries
1227
1228         getRootSummary :: Target -> IO ModSummary
1229         getRootSummary (Target (TargetFile file mb_phase) maybe_buf)
1230            = do exists <- doesFileExist file
1231                 if exists 
1232                     then summariseFile hsc_env old_summaries file mb_phase maybe_buf
1233                     else do
1234                 throwDyn (CmdLineError ("can't find file: " ++ file))   
1235         getRootSummary (Target (TargetModule modl) maybe_buf)
1236            = do maybe_summary <- summariseModule hsc_env old_summary_map False 
1237                                            (L rootLoc modl) maybe_buf excl_mods
1238                 case maybe_summary of
1239                    Nothing -> packageModErr modl
1240                    Just s  -> return s
1241
1242         rootLoc = mkGeneralSrcSpan FSLIT("<command line>")
1243
1244         -- In a root module, the filename is allowed to diverge from the module
1245         -- name, so we have to check that there aren't multiple root files
1246         -- defining the same module (otherwise the duplicates will be silently
1247         -- ignored, leading to confusing behaviour).
1248         checkDuplicates :: [ModSummary] -> IO ()
1249         checkDuplicates summaries = mapM_ check summaries
1250           where check summ = 
1251                   case dups of
1252                         []     -> return ()
1253                         [_one] -> return ()
1254                         many   -> multiRootsErr modl many
1255                    where modl = ms_mod summ
1256                          dups = 
1257                            [ expectJust "checkDup" (ml_hs_file (ms_location summ'))
1258                            | summ' <- summaries, ms_mod summ' == modl ]
1259
1260         loop :: [(Located Module,IsBootInterface)]
1261                         -- Work list: process these modules
1262              -> NodeMap ModSummary
1263                         -- Visited set
1264              -> IO [ModSummary]
1265                         -- The result includes the worklist, except
1266                         -- for those mentioned in the visited set
1267         loop [] done      = return (nodeMapElts done)
1268         loop ((wanted_mod, is_boot) : ss) done 
1269           | key `elemFM` done = loop ss done
1270           | otherwise         = do { mb_s <- summariseModule hsc_env old_summary_map 
1271                                                  is_boot wanted_mod Nothing excl_mods
1272                                    ; case mb_s of
1273                                         Nothing -> loop ss done
1274                                         Just s  -> loop (msDeps s ++ ss) 
1275                                                         (addToFM done key s) }
1276           where
1277             key = (unLoc wanted_mod, if is_boot then HsBootFile else HsSrcFile)
1278
1279 msDeps :: ModSummary -> [(Located Module, IsBootInterface)]
1280 -- (msDeps s) returns the dependencies of the ModSummary s.
1281 -- A wrinkle is that for a {-# SOURCE #-} import we return
1282 --      *both* the hs-boot file
1283 --      *and* the source file
1284 -- as "dependencies".  That ensures that the list of all relevant
1285 -- modules always contains B.hs if it contains B.hs-boot.
1286 -- Remember, this pass isn't doing the topological sort.  It's
1287 -- just gathering the list of all relevant ModSummaries
1288 msDeps s = 
1289     concat [ [(m,True), (m,False)] | m <- ms_srcimps s ] 
1290          ++ [ (m,False) | m <- ms_imps s ] 
1291
1292 -----------------------------------------------------------------------------
1293 -- Summarising modules
1294
1295 -- We have two types of summarisation:
1296 --
1297 --    * Summarise a file.  This is used for the root module(s) passed to
1298 --      cmLoadModules.  The file is read, and used to determine the root
1299 --      module name.  The module name may differ from the filename.
1300 --
1301 --    * Summarise a module.  We are given a module name, and must provide
1302 --      a summary.  The finder is used to locate the file in which the module
1303 --      resides.
1304
1305 summariseFile
1306         :: HscEnv
1307         -> [ModSummary]                 -- old summaries
1308         -> FilePath                     -- source file name
1309         -> Maybe Phase                  -- start phase
1310         -> Maybe (StringBuffer,ClockTime)
1311         -> IO ModSummary
1312
1313 summariseFile hsc_env old_summaries file mb_phase maybe_buf
1314         -- we can use a cached summary if one is available and the
1315         -- source file hasn't changed,  But we have to look up the summary
1316         -- by source file, rather than module name as we do in summarise.
1317    | Just old_summary <- findSummaryBySourceFile old_summaries file
1318    = do
1319         let location = ms_location old_summary
1320
1321                 -- return the cached summary if the source didn't change
1322         src_timestamp <- case maybe_buf of
1323                            Just (_,t) -> return t
1324                            Nothing    -> getModificationTime file
1325
1326         if ms_hs_date old_summary == src_timestamp 
1327            then do -- update the object-file timestamp
1328                   obj_timestamp <- getObjTimestamp location False
1329                   return old_summary{ ms_obj_date = obj_timestamp }
1330            else
1331                 new_summary
1332
1333    | otherwise
1334    = new_summary
1335   where
1336     new_summary = do
1337         let dflags = hsc_dflags hsc_env
1338
1339         (dflags', hspp_fn, buf)
1340             <- preprocessFile dflags file mb_phase maybe_buf
1341
1342         (srcimps,the_imps, L _ mod) <- getImports dflags' buf hspp_fn
1343
1344         -- Make a ModLocation for this file
1345         location <- mkHomeModLocation dflags mod file
1346
1347         -- Tell the Finder cache where it is, so that subsequent calls
1348         -- to findModule will find it, even if it's not on any search path
1349         addHomeModuleToFinder hsc_env mod location
1350
1351         src_timestamp <- case maybe_buf of
1352                            Just (_,t) -> return t
1353                            Nothing    -> getModificationTime file
1354
1355         obj_timestamp <- modificationTimeIfExists (ml_obj_file location)
1356
1357         return (ModSummary { ms_mod = mod, ms_hsc_src = HsSrcFile,
1358                              ms_location = location,
1359                              ms_hspp_file = Just hspp_fn,
1360                              ms_hspp_buf  = Just buf,
1361                              ms_srcimps = srcimps, ms_imps = the_imps,
1362                              ms_hs_date = src_timestamp,
1363                              ms_obj_date = obj_timestamp })
1364
1365 findSummaryBySourceFile :: [ModSummary] -> FilePath -> Maybe ModSummary
1366 findSummaryBySourceFile summaries file
1367   = case [ ms | ms <- summaries, HsSrcFile <- [ms_hsc_src ms],
1368                                  fromJust (ml_hs_file (ms_location ms)) == file ] of
1369         [] -> Nothing
1370         (x:xs) -> Just x
1371
1372 -- Summarise a module, and pick up source and timestamp.
1373 summariseModule
1374           :: HscEnv
1375           -> NodeMap ModSummary -- Map of old summaries
1376           -> IsBootInterface    -- True <=> a {-# SOURCE #-} import
1377           -> Located Module     -- Imported module to be summarised
1378           -> Maybe (StringBuffer, ClockTime)
1379           -> [Module]           -- Modules to exclude
1380           -> IO (Maybe ModSummary)      -- Its new summary
1381
1382 summariseModule hsc_env old_summary_map is_boot (L loc wanted_mod) maybe_buf excl_mods
1383   | wanted_mod `elem` excl_mods
1384   = return Nothing
1385
1386   | Just old_summary <- lookupFM old_summary_map (wanted_mod, hsc_src)
1387   = do          -- Find its new timestamp; all the 
1388                 -- ModSummaries in the old map have valid ml_hs_files
1389         let location = ms_location old_summary
1390             src_fn = expectJust "summariseModule" (ml_hs_file location)
1391
1392                 -- return the cached summary if the source didn't change
1393         src_timestamp <- case maybe_buf of
1394                            Just (_,t) -> return t
1395                            Nothing    -> getModificationTime src_fn
1396
1397         if ms_hs_date old_summary == src_timestamp 
1398            then do -- update the object-file timestamp
1399                   obj_timestamp <- getObjTimestamp location is_boot
1400                   return (Just old_summary{ ms_obj_date = obj_timestamp })
1401            else
1402                 -- source changed: re-summarise
1403                 new_summary location src_fn maybe_buf src_timestamp
1404
1405   | otherwise
1406   = do  found <- findModule hsc_env wanted_mod True {-explicit-}
1407         case found of
1408              Found location pkg 
1409                 | not (isHomePackage pkg) -> return Nothing
1410                         -- Drop external-pkg
1411                 | isJust (ml_hs_file location) -> just_found location
1412                         -- Home package
1413              err -> noModError dflags loc wanted_mod err
1414                         -- Not found
1415   where
1416     dflags = hsc_dflags hsc_env
1417
1418     hsc_src = if is_boot then HsBootFile else HsSrcFile
1419
1420     just_found location = do
1421                 -- Adjust location to point to the hs-boot source file, 
1422                 -- hi file, object file, when is_boot says so
1423         let location' | is_boot   = addBootSuffixLocn location
1424                       | otherwise = location
1425             src_fn = expectJust "summarise2" (ml_hs_file location')
1426
1427                 -- Check that it exists
1428                 -- It might have been deleted since the Finder last found it
1429         maybe_t <- modificationTimeIfExists src_fn
1430         case maybe_t of
1431           Nothing -> noHsFileErr loc src_fn
1432           Just t  -> new_summary location' src_fn Nothing t
1433
1434
1435     new_summary location src_fn maybe_bug src_timestamp
1436       = do
1437         -- Preprocess the source file and get its imports
1438         -- The dflags' contains the OPTIONS pragmas
1439         (dflags', hspp_fn, buf) <- preprocessFile dflags src_fn Nothing maybe_buf
1440         (srcimps, the_imps, L mod_loc mod_name) <- getImports dflags' buf hspp_fn
1441
1442         when (mod_name /= wanted_mod) $
1443                 throwDyn (ProgramError 
1444                    (showSDoc (mkLocMessage mod_loc $ 
1445                               text "file name does not match module name"
1446                               <+> quotes (ppr mod_name))))
1447
1448                 -- Find the object timestamp, and return the summary
1449         obj_timestamp <- getObjTimestamp location is_boot
1450
1451         return (Just ( ModSummary { ms_mod       = wanted_mod, 
1452                                     ms_hsc_src   = hsc_src,
1453                                     ms_location  = location,
1454                                     ms_hspp_file = Just hspp_fn,
1455                                     ms_hspp_buf  = Just buf,
1456                                     ms_srcimps   = srcimps,
1457                                     ms_imps      = the_imps,
1458                                     ms_hs_date   = src_timestamp,
1459                                     ms_obj_date  = obj_timestamp }))
1460
1461
1462 getObjTimestamp location is_boot
1463   = if is_boot then return Nothing
1464                else modificationTimeIfExists (ml_obj_file location)
1465
1466
1467 preprocessFile :: DynFlags -> FilePath -> Maybe Phase -> Maybe (StringBuffer,ClockTime)
1468   -> IO (DynFlags, FilePath, StringBuffer)
1469 preprocessFile dflags src_fn mb_phase Nothing
1470   = do
1471         (dflags', hspp_fn) <- preprocess dflags (src_fn, mb_phase)
1472         buf <- hGetStringBuffer hspp_fn
1473         return (dflags', hspp_fn, buf)
1474
1475 preprocessFile dflags src_fn mb_phase (Just (buf, time))
1476   = do
1477         -- case we bypass the preprocessing stage?
1478         let 
1479             local_opts = getOptionsFromStringBuffer buf
1480         --
1481         (dflags', errs) <- parseDynamicFlags dflags (map snd local_opts)
1482
1483         let
1484             needs_preprocessing
1485                 | Just (Unlit _) <- mb_phase    = True
1486                 | Nothing <- mb_phase, Unlit _ <- startPhase src_fn  = True
1487                   -- note: local_opts is only required if there's no Unlit phase
1488                 | dopt Opt_Cpp dflags'          = True
1489                 | dopt Opt_Pp  dflags'          = True
1490                 | otherwise                     = False
1491
1492         when needs_preprocessing $
1493            ghcError (ProgramError "buffer needs preprocesing; interactive check disabled")
1494
1495         return (dflags', src_fn, buf)
1496
1497
1498 -----------------------------------------------------------------------------
1499 --                      Error messages
1500 -----------------------------------------------------------------------------
1501
1502 noModError :: DynFlags -> SrcSpan -> Module -> FindResult -> IO ab
1503 -- ToDo: we don't have a proper line number for this error
1504 noModError dflags loc wanted_mod err
1505   = throwDyn $ ProgramError $ showSDoc $
1506     mkLocMessage loc $ cantFindError dflags wanted_mod err
1507                                 
1508 noHsFileErr loc path
1509   = throwDyn $ CmdLineError $ showSDoc $
1510     mkLocMessage loc $ text "Can't find" <+> text path
1511  
1512 packageModErr mod
1513   = throwDyn (CmdLineError (showSDoc (text "module" <+>
1514                                    quotes (ppr mod) <+>
1515                                    text "is a package module")))
1516
1517 multiRootsErr mod files
1518   = throwDyn (ProgramError (showSDoc (
1519         text "module" <+> quotes (ppr mod) <+> 
1520         text "is defined in multiple files:" <+>
1521         sep (map text files))))
1522
1523 cyclicModuleErr :: [ModSummary] -> SDoc
1524 cyclicModuleErr ms
1525   = hang (ptext SLIT("Module imports form a cycle for modules:"))
1526        2 (vcat (map show_one ms))
1527   where
1528     show_one ms = sep [ show_mod (ms_hsc_src ms) (ms_mod ms),
1529                         nest 2 $ ptext SLIT("imports:") <+> 
1530                                    (pp_imps HsBootFile (ms_srcimps ms)
1531                                    $$ pp_imps HsSrcFile  (ms_imps ms))]
1532     show_mod hsc_src mod = ppr mod <> text (hscSourceString hsc_src)
1533     pp_imps src mods = fsep (map (show_mod src) mods)
1534
1535
1536 -- | Inform GHC that the working directory has changed.  GHC will flush
1537 -- its cache of module locations, since it may no longer be valid.
1538 -- Note: if you change the working directory, you should also unload
1539 -- the current program (set targets to empty, followed by load).
1540 workingDirectoryChanged :: Session -> IO ()
1541 workingDirectoryChanged s = withSession s $ \hsc_env ->
1542   flushFinderCache (hsc_FC hsc_env)
1543
1544 -- -----------------------------------------------------------------------------
1545 -- inspecting the session
1546
1547 -- | Get the module dependency graph.
1548 getModuleGraph :: Session -> IO ModuleGraph -- ToDo: DiGraph ModSummary
1549 getModuleGraph s = withSession s (return . hsc_mod_graph)
1550
1551 isLoaded :: Session -> Module -> IO Bool
1552 isLoaded s m = withSession s $ \hsc_env ->
1553   return $! isJust (lookupModuleEnv (hsc_HPT hsc_env) m)
1554
1555 getBindings :: Session -> IO [TyThing]
1556 getBindings s = withSession s (return . nameEnvElts . ic_type_env . hsc_IC)
1557
1558 getPrintUnqual :: Session -> IO PrintUnqualified
1559 getPrintUnqual s = withSession s (return . icPrintUnqual . hsc_IC)
1560
1561 -- | Container for information about a 'Module'.
1562 data ModuleInfo = ModuleInfo {
1563         minf_type_env  :: TypeEnv,
1564         minf_exports   :: NameSet,
1565         minf_rdr_env   :: Maybe GlobalRdrEnv,   -- Nothing for a compiled/package mod
1566         minf_instances :: [Instance]
1567         -- ToDo: this should really contain the ModIface too
1568   }
1569         -- We don't want HomeModInfo here, because a ModuleInfo applies
1570         -- to package modules too.
1571
1572 -- | Request information about a loaded 'Module'
1573 getModuleInfo :: Session -> Module -> IO (Maybe ModuleInfo)
1574 getModuleInfo s mdl = withSession s $ \hsc_env -> do
1575   case lookupModuleEnv (hsc_HPT hsc_env) mdl of
1576     Nothing  -> do
1577 #ifdef GHCI
1578         mb_names <- getModuleExports hsc_env mdl
1579         case mb_names of
1580            Nothing -> return Nothing
1581            Just names -> do
1582                 eps <- readIORef (hsc_EPS hsc_env)
1583                 let 
1584                     pte    = eps_PTE eps
1585                     n_list = nameSetToList names
1586                     tys    = [ ty | name <- n_list,
1587                                     Just ty <- [lookupTypeEnv pte name] ]
1588                 --
1589                 return (Just (ModuleInfo {
1590                                 minf_type_env  = mkTypeEnv tys,
1591                                 minf_exports   = names,
1592                                 minf_rdr_env   = Just $! nameSetToGlobalRdrEnv names mdl,
1593                                 minf_instances = error "getModuleInfo: instances for package module unimplemented"
1594                         }))
1595 #else
1596         -- bogusly different for non-GHCI (ToDo)
1597         return Nothing
1598 #endif
1599     Just hmi -> 
1600         let details = hm_details hmi in
1601         return (Just (ModuleInfo {
1602                         minf_type_env  = md_types details,
1603                         minf_exports   = md_exports details,
1604                         minf_rdr_env   = mi_globals $! hm_iface hmi,
1605                         minf_instances = md_insts details
1606                         }))
1607
1608         -- ToDo: we should be able to call getModuleInfo on a package module,
1609         -- even one that isn't loaded yet.
1610
1611 -- | The list of top-level entities defined in a module
1612 modInfoTyThings :: ModuleInfo -> [TyThing]
1613 modInfoTyThings minf = typeEnvElts (minf_type_env minf)
1614
1615 modInfoTopLevelScope :: ModuleInfo -> Maybe [Name]
1616 modInfoTopLevelScope minf
1617   = fmap (map gre_name . globalRdrEnvElts) (minf_rdr_env minf)
1618
1619 modInfoExports :: ModuleInfo -> [Name]
1620 modInfoExports minf = nameSetToList $! minf_exports minf
1621
1622 -- | Returns the instances defined by the specified module.
1623 -- Warning: currently unimplemented for package modules.
1624 modInfoInstances :: ModuleInfo -> [Instance]
1625 modInfoInstances = minf_instances
1626
1627 modInfoIsExportedName :: ModuleInfo -> Name -> Bool
1628 modInfoIsExportedName minf name = elemNameSet name (minf_exports minf)
1629
1630 modInfoPrintUnqualified :: ModuleInfo -> Maybe PrintUnqualified
1631 modInfoPrintUnqualified minf = fmap unQualInScope (minf_rdr_env minf)
1632
1633 modInfoLookupName :: Session -> ModuleInfo -> Name -> IO (Maybe TyThing)
1634 modInfoLookupName s minf name = withSession s $ \hsc_env -> do
1635    case lookupTypeEnv (minf_type_env minf) name of
1636      Just tyThing -> return (Just tyThing)
1637      Nothing      -> do
1638        eps <- readIORef (hsc_EPS hsc_env)
1639        return $! lookupType (hsc_HPT hsc_env) (eps_PTE eps) name
1640
1641 isDictonaryId :: Id -> Bool
1642 isDictonaryId id
1643   = case tcSplitSigmaTy (idType id) of { (tvs, theta, tau) -> isDictTy tau }
1644
1645 -- | Looks up a global name: that is, any top-level name in any
1646 -- visible module.  Unlike 'lookupName', lookupGlobalName does not use
1647 -- the interactive context, and therefore does not require a preceding
1648 -- 'setContext'.
1649 lookupGlobalName :: Session -> Name -> IO (Maybe TyThing)
1650 lookupGlobalName s name = withSession s $ \hsc_env -> do
1651    eps <- readIORef (hsc_EPS hsc_env)
1652    return $! lookupType (hsc_HPT hsc_env) (eps_PTE eps) name
1653
1654 #if 0
1655
1656 data ObjectCode
1657   = ByteCode
1658   | BinaryCode FilePath
1659
1660 -- ToDo: typechecks abstract syntax or renamed abstract syntax.  Issues:
1661 --   - typechecked syntax includes extra dictionary translation and
1662 --     AbsBinds which need to be translated back into something closer to
1663 --     the original source.
1664
1665 -- ToDo:
1666 --   - Data and Typeable instances for HsSyn.
1667
1668 -- ToDo:
1669 --   - things that aren't in the output of the renamer:
1670 --     - the export list
1671 --     - the imports
1672
1673 -- ToDo:
1674 --   - things that aren't in the output of the typechecker right now:
1675 --     - the export list
1676 --     - the imports
1677 --     - type signatures
1678 --     - type/data/newtype declarations
1679 --     - class declarations
1680 --     - instances
1681 --   - extra things in the typechecker's output:
1682 --     - default methods are turned into top-level decls.
1683 --     - dictionary bindings
1684
1685 -- ToDo: check for small transformations that happen to the syntax in
1686 -- the typechecker (eg. -e ==> negate e, perhaps for fromIntegral)
1687
1688 -- ToDo: maybe use TH syntax instead of IfaceSyn?  There's already a way
1689 -- to get from TyCons, Ids etc. to TH syntax (reify).
1690
1691 -- :browse will use either lm_toplev or inspect lm_interface, depending
1692 -- on whether the module is interpreted or not.
1693
1694 -- This is for reconstructing refactored source code
1695 -- Calls the lexer repeatedly.
1696 -- ToDo: add comment tokens to token stream
1697 getTokenStream :: Session -> Module -> IO [Located Token]
1698 #endif
1699
1700 -- -----------------------------------------------------------------------------
1701 -- Interactive evaluation
1702
1703 #ifdef GHCI
1704
1705 -- | Set the interactive evaluation context.
1706 --
1707 -- Setting the context doesn't throw away any bindings; the bindings
1708 -- we've built up in the InteractiveContext simply move to the new
1709 -- module.  They always shadow anything in scope in the current context.
1710 setContext :: Session
1711            -> [Module]  -- entire top level scope of these modules
1712            -> [Module]  -- exports only of these modules
1713            -> IO ()
1714 setContext (Session ref) toplevs exports = do 
1715   hsc_env <- readIORef ref
1716   let old_ic  = hsc_IC     hsc_env
1717       hpt     = hsc_HPT    hsc_env
1718
1719   mapM_ (checkModuleExists hsc_env hpt) exports
1720   export_env  <- mkExportEnv hsc_env exports
1721   toplev_envs <- mapM (mkTopLevEnv hpt) toplevs
1722   let all_env = foldr plusGlobalRdrEnv export_env toplev_envs
1723   writeIORef ref hsc_env{ hsc_IC = old_ic { ic_toplev_scope = toplevs,
1724                                             ic_exports      = exports,
1725                                             ic_rn_gbl_env   = all_env } }
1726
1727 -- Make a GlobalRdrEnv based on the exports of the modules only.
1728 mkExportEnv :: HscEnv -> [Module] -> IO GlobalRdrEnv
1729 mkExportEnv hsc_env mods = do
1730   mb_name_sets <- mapM (getModuleExports hsc_env) mods
1731   let 
1732         gres = [ nameSetToGlobalRdrEnv name_set mod
1733                | (Just name_set, mod) <- zip mb_name_sets mods ]
1734   --
1735   return $! foldr plusGlobalRdrEnv emptyGlobalRdrEnv gres
1736
1737 nameSetToGlobalRdrEnv :: NameSet -> Module -> GlobalRdrEnv
1738 nameSetToGlobalRdrEnv names mod =
1739   mkGlobalRdrEnv [ GRE  { gre_name = name, gre_prov = vanillaProv mod }
1740                  | name <- nameSetToList names ]
1741
1742 vanillaProv :: Module -> Provenance
1743 -- We're building a GlobalRdrEnv as if the user imported
1744 -- all the specified modules into the global interactive module
1745 vanillaProv mod = Imported [ImpSpec { is_decl = decl, is_item = ImpAll}]
1746   where
1747     decl = ImpDeclSpec { is_mod = mod, is_as = mod, 
1748                          is_qual = False, 
1749                          is_dloc = srcLocSpan interactiveSrcLoc }
1750
1751 checkModuleExists :: HscEnv -> HomePackageTable -> Module -> IO ()
1752 checkModuleExists hsc_env hpt mod = 
1753   case lookupModuleEnv hpt mod of
1754     Just mod_info -> return ()
1755     _not_a_home_module -> do
1756           res <- findPackageModule hsc_env mod True
1757           case res of
1758             Found _ _ -> return  ()
1759             err -> let msg = cantFindError (hsc_dflags hsc_env) mod err in
1760                    throwDyn (CmdLineError (showSDoc msg))
1761
1762 mkTopLevEnv :: HomePackageTable -> Module -> IO GlobalRdrEnv
1763 mkTopLevEnv hpt modl
1764  = case lookupModuleEnv hpt modl of
1765       Nothing ->        
1766          throwDyn (ProgramError ("mkTopLevEnv: not a home module " 
1767                         ++ showSDoc (pprModule modl)))
1768       Just details ->
1769          case mi_globals (hm_iface details) of
1770                 Nothing  -> 
1771                    throwDyn (ProgramError ("mkTopLevEnv: not interpreted " 
1772                                                 ++ showSDoc (pprModule modl)))
1773                 Just env -> return env
1774
1775 -- | Get the interactive evaluation context, consisting of a pair of the
1776 -- set of modules from which we take the full top-level scope, and the set
1777 -- of modules from which we take just the exports respectively.
1778 getContext :: Session -> IO ([Module],[Module])
1779 getContext s = withSession s (\HscEnv{ hsc_IC=ic } ->
1780                                 return (ic_toplev_scope ic, ic_exports ic))
1781
1782 -- | Returns 'True' if the specified module is interpreted, and hence has
1783 -- its full top-level scope available.
1784 moduleIsInterpreted :: Session -> Module -> IO Bool
1785 moduleIsInterpreted s modl = withSession s $ \h ->
1786  case lookupModuleEnv (hsc_HPT h) modl of
1787       Just details       -> return (isJust (mi_globals (hm_iface details)))
1788       _not_a_home_module -> return False
1789
1790 -- | Looks up an identifier in the current interactive context (for :info)
1791 {-# DEPRECATED getInfo "we should be using parseName/lookupName instead" #-}
1792 getInfo :: Session -> String -> IO [GetInfoResult]
1793 getInfo s id = withSession s $ \hsc_env -> hscGetInfo hsc_env id
1794
1795 -- | Returns all names in scope in the current interactive context
1796 getNamesInScope :: Session -> IO [Name]
1797 getNamesInScope s = withSession s $ \hsc_env -> do
1798   return (map gre_name (globalRdrEnvElts (ic_rn_gbl_env (hsc_IC hsc_env))))
1799
1800 -- | Parses a string as an identifier, and returns the list of 'Name's that
1801 -- the identifier can refer to in the current interactive context.
1802 parseName :: Session -> String -> IO [Name]
1803 parseName s str = withSession s $ \hsc_env -> do
1804    maybe_rdr_name <- hscParseIdentifier (hsc_dflags hsc_env) str
1805    case maybe_rdr_name of
1806         Nothing -> return []
1807         Just (L _ rdr_name) -> do
1808             mb_names <- tcRnLookupRdrName hsc_env rdr_name
1809             case mb_names of
1810                 Nothing -> return []
1811                 Just ns -> return ns
1812                 -- ToDo: should return error messages
1813
1814 -- | Returns the 'TyThing' for a 'Name'.  The 'Name' may refer to any
1815 -- entity known to GHC, including 'Name's defined using 'runStmt'.
1816 lookupName :: Session -> Name -> IO (Maybe TyThing)
1817 lookupName s name = withSession s $ \hsc_env -> do
1818   case lookupTypeEnv (ic_type_env (hsc_IC hsc_env)) name of
1819         Just tt -> return (Just tt)
1820         Nothing -> do
1821             eps <- readIORef (hsc_EPS hsc_env)
1822             return $! lookupType (hsc_HPT hsc_env) (eps_PTE eps) name
1823
1824 -- -----------------------------------------------------------------------------
1825 -- Getting the type of an expression
1826
1827 -- | Get the type of an expression
1828 exprType :: Session -> String -> IO (Maybe Type)
1829 exprType s expr = withSession s $ \hsc_env -> do
1830    maybe_stuff <- hscTcExpr hsc_env expr
1831    case maybe_stuff of
1832         Nothing -> return Nothing
1833         Just ty -> return (Just tidy_ty)
1834              where 
1835                 tidy_ty = tidyType emptyTidyEnv ty
1836                 dflags  = hsc_dflags hsc_env
1837
1838 -- -----------------------------------------------------------------------------
1839 -- Getting the kind of a type
1840
1841 -- | Get the kind of a  type
1842 typeKind  :: Session -> String -> IO (Maybe Kind)
1843 typeKind s str = withSession s $ \hsc_env -> do
1844    maybe_stuff <- hscKcType hsc_env str
1845    case maybe_stuff of
1846         Nothing -> return Nothing
1847         Just kind -> return (Just kind)
1848
1849 -----------------------------------------------------------------------------
1850 -- cmCompileExpr: compile an expression and deliver an HValue
1851
1852 compileExpr :: Session -> String -> IO (Maybe HValue)
1853 compileExpr s expr = withSession s $ \hsc_env -> do
1854   maybe_stuff <- hscStmt hsc_env ("let __cmCompileExpr = "++expr)
1855   case maybe_stuff of
1856         Nothing -> return Nothing
1857         Just (new_ic, names, hval) -> do
1858                         -- Run it!
1859                 hvals <- (unsafeCoerce# hval) :: IO [HValue]
1860
1861                 case (names,hvals) of
1862                   ([n],[hv]) -> return (Just hv)
1863                   _          -> panic "compileExpr"
1864
1865 -- -----------------------------------------------------------------------------
1866 -- running a statement interactively
1867
1868 data RunResult
1869   = RunOk [Name]                -- ^ names bound by this evaluation
1870   | RunFailed                   -- ^ statement failed compilation
1871   | RunException Exception      -- ^ statement raised an exception
1872
1873 -- | Run a statement in the current interactive context.  Statemenet
1874 -- may bind multple values.
1875 runStmt :: Session -> String -> IO RunResult
1876 runStmt (Session ref) expr
1877    = do 
1878         hsc_env <- readIORef ref
1879
1880         -- Turn off -fwarn-unused-bindings when running a statement, to hide
1881         -- warnings about the implicit bindings we introduce.
1882         let dflags'  = dopt_unset (hsc_dflags hsc_env) Opt_WarnUnusedBinds
1883             hsc_env' = hsc_env{ hsc_dflags = dflags' }
1884
1885         maybe_stuff <- hscStmt hsc_env' expr
1886
1887         case maybe_stuff of
1888            Nothing -> return RunFailed
1889            Just (new_hsc_env, names, hval) -> do
1890
1891                 let thing_to_run = unsafeCoerce# hval :: IO [HValue]
1892                 either_hvals <- sandboxIO thing_to_run
1893
1894                 case either_hvals of
1895                     Left e -> do
1896                         -- on error, keep the *old* interactive context,
1897                         -- so that 'it' is not bound to something
1898                         -- that doesn't exist.
1899                         return (RunException e)
1900
1901                     Right hvals -> do
1902                         -- Get the newly bound things, and bind them.  
1903                         -- Don't need to delete any shadowed bindings;
1904                         -- the new ones override the old ones. 
1905                         extendLinkEnv (zip names hvals)
1906                         
1907                         writeIORef ref new_hsc_env
1908                         return (RunOk names)
1909
1910
1911 -- We run the statement in a "sandbox" to protect the rest of the
1912 -- system from anything the expression might do.  For now, this
1913 -- consists of just wrapping it in an exception handler, but see below
1914 -- for another version.
1915
1916 sandboxIO :: IO a -> IO (Either Exception a)
1917 sandboxIO thing = Exception.try thing
1918
1919 {-
1920 -- This version of sandboxIO runs the expression in a completely new
1921 -- RTS main thread.  It is disabled for now because ^C exceptions
1922 -- won't be delivered to the new thread, instead they'll be delivered
1923 -- to the (blocked) GHCi main thread.
1924
1925 -- SLPJ: when re-enabling this, reflect a wrong-stat error as an exception
1926
1927 sandboxIO :: IO a -> IO (Either Int (Either Exception a))
1928 sandboxIO thing = do
1929   st_thing <- newStablePtr (Exception.try thing)
1930   alloca $ \ p_st_result -> do
1931     stat <- rts_evalStableIO st_thing p_st_result
1932     freeStablePtr st_thing
1933     if stat == 1
1934         then do st_result <- peek p_st_result
1935                 result <- deRefStablePtr st_result
1936                 freeStablePtr st_result
1937                 return (Right result)
1938         else do
1939                 return (Left (fromIntegral stat))
1940
1941 foreign import "rts_evalStableIO"  {- safe -}
1942   rts_evalStableIO :: StablePtr (IO a) -> Ptr (StablePtr a) -> IO CInt
1943   -- more informative than the C type!
1944 -}
1945
1946 -- ---------------------------------------------------------------------------
1947 -- cmBrowseModule: get all the TyThings defined in a module
1948
1949 {-# DEPRECATED browseModule "we should be using getModuleInfo instead" #-}
1950 browseModule :: Session -> Module -> Bool -> IO [IfaceDecl]
1951 browseModule s modl exports_only = withSession s $ \hsc_env -> do
1952   mb_decls <- getModuleContents hsc_env modl exports_only
1953   case mb_decls of
1954         Nothing -> return []            -- An error of some kind
1955         Just ds -> return ds
1956
1957
1958 -----------------------------------------------------------------------------
1959 -- show a module and it's source/object filenames
1960
1961 showModule :: Session -> ModSummary -> IO String
1962 showModule s mod_summary = withSession s $ \hsc_env -> do
1963   case lookupModuleEnv (hsc_HPT hsc_env) (ms_mod mod_summary) of
1964         Nothing       -> panic "missing linkable"
1965         Just mod_info -> return (showModMsg obj_linkable mod_summary)
1966                       where
1967                          obj_linkable = isObjectLinkable (fromJust (hm_linkable mod_info))
1968
1969 #endif /* GHCI */