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