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