13af006303d072502fb26450ff65b66c5321488a
[ghc-hetmet.git] / ghc / compiler / main / HscMain.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1993-2000
3 %
4
5 \section[GHC_Main]{Main driver for Glasgow Haskell compiler}
6
7 \begin{code}
8 module HscMain ( 
9         HscResult(..),
10         hscMain, newHscEnv, hscCmmFile, 
11         hscFileCheck,
12         hscParseIdentifier,
13 #ifdef GHCI
14         hscStmt, hscTcExpr, hscKcType,
15         hscGetInfo, GetInfoResult,
16         compileExpr,
17 #endif
18         ) where
19
20 #include "HsVersions.h"
21
22 #ifdef GHCI
23 import HsSyn            ( Stmt(..), LHsExpr, LStmt, LHsType )
24 import IfaceSyn         ( IfaceDecl, IfaceInst )
25 import Module           ( Module )
26 import CodeOutput       ( outputForeignStubs )
27 import ByteCodeGen      ( byteCodeGen, coreExprToBCOs )
28 import Linker           ( HValue, linkExpr )
29 import CoreTidy         ( tidyExpr )
30 import CorePrep         ( corePrepExpr )
31 import Flattening       ( flattenExpr )
32 import TcRnDriver       ( tcRnStmt, tcRnExpr, tcRnGetInfo, GetInfoResult, tcRnType ) 
33 import RdrName          ( rdrNameOcc )
34 import OccName          ( occNameUserString )
35 import Type             ( Type )
36 import PrelNames        ( iNTERACTIVE )
37 import Kind             ( Kind )
38 import CoreLint         ( lintUnfolding )
39 import DsMeta           ( templateHaskellNames )
40 import BasicTypes       ( Fixity )
41 import SrcLoc           ( SrcLoc, noSrcLoc )
42 import VarEnv           ( emptyTidyEnv )
43 #endif
44
45 import Var              ( Id )
46 import Module           ( emptyModuleEnv )
47 import RdrName          ( GlobalRdrEnv, RdrName )
48 import HsSyn            ( HsModule, LHsBinds, HsGroup )
49 import SrcLoc           ( Located(..) )
50 import StringBuffer     ( hGetStringBuffer, stringToStringBuffer )
51 import Parser
52 import Lexer            ( P(..), ParseResult(..), mkPState )
53 import SrcLoc           ( mkSrcLoc )
54 import TcRnDriver       ( tcRnModule, tcRnExtCore )
55 import TcIface          ( typecheckIface )
56 import TcRnMonad        ( initIfaceCheck, TcGblEnv(..) )
57 import IfaceEnv         ( initNameCache )
58 import LoadIface        ( ifaceStats, initExternalPackageState )
59 import PrelInfo         ( wiredInThings, basicKnownKeyNames )
60 import MkIface          ( checkOldIface, mkIface, writeIfaceFile )
61 import Desugar
62 import Flattening       ( flatten )
63 import SimplCore
64 import TidyPgm          ( tidyProgram, mkBootModDetails )
65 import CorePrep         ( corePrepPgm )
66 import CoreToStg        ( coreToStg )
67 import TyCon            ( isDataTyCon )
68 import Name             ( Name, NamedThing(..) )
69 import SimplStg         ( stg2stg )
70 import CodeGen          ( codeGen )
71 import CmmParse         ( parseCmmFile )
72 import CodeOutput       ( codeOutput )
73
74 import DynFlags
75 import DriverPhases     ( HscSource(..) )
76 import ErrUtils
77 import UniqSupply       ( mkSplitUniqSupply )
78
79 import Outputable
80 import HscStats         ( ppSourceStats )
81 import HscTypes
82 import MkExternalCore   ( emitExternalCore )
83 import ParserCore
84 import ParserCoreUtils
85 import FastString
86 import Maybes           ( expectJust )
87 import Bag              ( unitBag, emptyBag )
88 import Monad            ( when )
89 import Maybe            ( isJust )
90 import IO
91 import DATA_IOREF       ( newIORef, readIORef )
92 \end{code}
93
94
95 %************************************************************************
96 %*                                                                      *
97                 Initialisation
98 %*                                                                      *
99 %************************************************************************
100
101 \begin{code}
102 newHscEnv :: DynFlags -> IO HscEnv
103 newHscEnv dflags
104   = do  { eps_var <- newIORef initExternalPackageState
105         ; us      <- mkSplitUniqSupply 'r'
106         ; nc_var  <- newIORef (initNameCache us knownKeyNames)
107         ; fc_var  <- newIORef emptyModuleEnv
108         ; return (HscEnv { hsc_dflags = dflags,
109                            hsc_targets = [],
110                            hsc_mod_graph = [],
111                            hsc_IC     = emptyInteractiveContext,
112                            hsc_HPT    = emptyHomePackageTable,
113                            hsc_EPS    = eps_var,
114                            hsc_NC     = nc_var,
115                            hsc_FC     = fc_var } ) }
116                         
117
118 knownKeyNames :: [Name] -- Put here to avoid loops involving DsMeta,
119                         -- where templateHaskellNames are defined
120 knownKeyNames = map getName wiredInThings 
121               ++ basicKnownKeyNames
122 #ifdef GHCI
123               ++ templateHaskellNames
124 #endif
125 \end{code}
126
127
128 %************************************************************************
129 %*                                                                      *
130                 The main compiler pipeline
131 %*                                                                      *
132 %************************************************************************
133
134 \begin{code}
135 data HscResult
136    -- Compilation failed
137    = HscFail
138
139    -- In IDE mode: we just do the static/dynamic checks
140    | HscChecked 
141         (Located (HsModule RdrName))                    -- parsed
142         (Maybe (HsGroup Name))                          -- renamed
143         (Maybe (LHsBinds Id, GlobalRdrEnv, ModDetails)) -- typechecked
144
145    -- Concluded that it wasn't necessary
146    | HscNoRecomp ModDetails              -- new details (HomeSymbolTable additions)
147                  ModIface                -- new iface (if any compilation was done)
148
149    -- Did recompilation
150    | HscRecomp   ModDetails             -- new details (HomeSymbolTable additions)
151                  ModIface               -- new iface (if any compilation was done)
152                  Bool                   -- stub_h exists
153                  Bool                   -- stub_c exists
154                  (Maybe CompiledByteCode)
155
156
157 -- What to do when we have compiler error or warning messages
158 type MessageAction = Messages -> IO ()
159
160         -- no errors or warnings; the individual passes
161         -- (parse/rename/typecheck) print messages themselves
162
163 hscMain
164   :: HscEnv
165   -> MessageAction      -- What to do with errors/warnings
166   -> ModSummary
167   -> Bool               -- True <=> source unchanged
168   -> Bool               -- True <=> have an object file (for msgs only)
169   -> Maybe ModIface     -- Old interface, if available
170   -> Maybe (Int, Int)   -- Just (i,n) <=> module i of n (for msgs)
171   -> IO HscResult
172
173 hscMain hsc_env msg_act mod_summary
174         source_unchanged have_object maybe_old_iface
175         mb_mod_index
176  = do {
177       (recomp_reqd, maybe_checked_iface) <- 
178                 {-# SCC "checkOldIface" #-}
179                 checkOldIface hsc_env mod_summary 
180                               source_unchanged maybe_old_iface;
181
182       let no_old_iface = not (isJust maybe_checked_iface)
183           what_next | recomp_reqd || no_old_iface = hscRecomp 
184                     | otherwise                   = hscNoRecomp
185
186       ; what_next hsc_env msg_act mod_summary have_object 
187                   maybe_checked_iface
188                   mb_mod_index
189       }
190
191
192 ------------------------------
193 hscNoRecomp hsc_env msg_act mod_summary 
194             have_object (Just old_iface)
195             mb_mod_index
196  | isOneShot (ghcMode (hsc_dflags hsc_env))
197  = do {
198       compilationProgressMsg (hsc_dflags hsc_env) $
199         "compilation IS NOT required";
200       dumpIfaceStats hsc_env ;
201
202       let { bomb = panic "hscNoRecomp:OneShot" };
203       return (HscNoRecomp bomb bomb)
204       }
205  | otherwise
206  = do   { compilationProgressMsg (hsc_dflags hsc_env) $
207                 (showModuleIndex mb_mod_index ++ 
208                  "Skipping  " ++ showModMsg have_object mod_summary)
209
210         ; new_details <- {-# SCC "tcRnIface" #-}
211                          initIfaceCheck hsc_env $
212                          typecheckIface old_iface ;
213         ; dumpIfaceStats hsc_env
214
215         ; return (HscNoRecomp new_details old_iface)
216     }
217
218 hscNoRecomp hsc_env msg_act mod_summary 
219             have_object Nothing
220             mb_mod_index
221   = panic "hscNoRecomp" -- hscNoRecomp definitely expects to 
222                         -- have the old interface available
223
224 ------------------------------
225 hscRecomp hsc_env msg_act mod_summary
226           have_object maybe_old_iface
227           mb_mod_index
228  = case ms_hsc_src mod_summary of
229      HsSrcFile -> do 
230         front_res <- hscFileFrontEnd hsc_env msg_act mod_summary mb_mod_index
231         hscBackEnd hsc_env mod_summary maybe_old_iface front_res
232
233      HsBootFile -> do
234         front_res <- hscFileFrontEnd hsc_env msg_act mod_summary mb_mod_index
235         hscBootBackEnd hsc_env mod_summary maybe_old_iface front_res
236
237      ExtCoreFile -> do
238         front_res <- hscCoreFrontEnd hsc_env msg_act mod_summary
239         hscBackEnd hsc_env mod_summary maybe_old_iface front_res
240
241 hscCoreFrontEnd hsc_env msg_act mod_summary = do {
242             -------------------
243             -- PARSE
244             -------------------
245         ; inp <- readFile (expectJust "hscCoreFrontEnd" (ms_hspp_file mod_summary))
246         ; case parseCore inp 1 of
247             FailP s        -> putMsg s{-ToDo: wrong-} >> return Nothing
248             OkP rdr_module -> do {
249     
250             -------------------
251             -- RENAME and TYPECHECK
252             -------------------
253         ; (tc_msgs, maybe_tc_result) <- {-# SCC "TypeCheck" #-}
254                               tcRnExtCore hsc_env rdr_module
255         ; msg_act tc_msgs
256         ; case maybe_tc_result of
257              Nothing       -> return Nothing
258              Just mod_guts -> return (Just mod_guts)    -- No desugaring to do!
259         }}
260          
261
262 hscFileFrontEnd hsc_env msg_act mod_summary mb_mod_index = do {
263             -------------------
264             -- DISPLAY PROGRESS MESSAGE
265             -------------------
266           let one_shot  = isOneShot (ghcMode (hsc_dflags hsc_env))
267         ; let dflags    = hsc_dflags hsc_env
268         ; let toInterp  = hscTarget dflags == HscInterpreted
269         ; when (not one_shot) $
270                  compilationProgressMsg dflags $
271                  (showModuleIndex mb_mod_index ++
272                   "Compiling " ++ showModMsg (not toInterp) mod_summary)
273                         
274             -------------------
275             -- PARSE
276             -------------------
277         ; let hspp_file = expectJust "hscFileFrontEnd" (ms_hspp_file mod_summary)
278               hspp_buf  = ms_hspp_buf  mod_summary
279
280         ; maybe_parsed <- myParseModule (hsc_dflags hsc_env) hspp_file hspp_buf
281
282         ; case maybe_parsed of {
283              Left err -> do { msg_act (unitBag err, emptyBag)
284                             ; return Nothing } ;
285              Right rdr_module -> do {
286
287             -------------------
288             -- RENAME and TYPECHECK
289             -------------------
290           (tc_msgs, maybe_tc_result) 
291                 <- {-# SCC "Typecheck-Rename" #-}
292                    tcRnModule hsc_env (ms_hsc_src mod_summary) False rdr_module
293
294         ; msg_act tc_msgs
295         ; case maybe_tc_result of {
296              Nothing -> return Nothing ;
297              Just tc_result -> do {
298
299             -------------------
300             -- DESUGAR
301             -------------------
302         ; (warns, maybe_ds_result) <- {-# SCC "DeSugar" #-}
303                              deSugar hsc_env tc_result
304         ; msg_act (warns, emptyBag)
305         ; return maybe_ds_result
306         }}}}}
307
308 ------------------------------
309
310 hscFileCheck :: HscEnv -> MessageAction -> ModSummary -> IO HscResult
311 hscFileCheck hsc_env msg_act mod_summary = do {
312             -------------------
313             -- PARSE
314             -------------------
315         ; let hspp_file = expectJust "hscFileFrontEnd" (ms_hspp_file mod_summary)
316               hspp_buf  = ms_hspp_buf  mod_summary
317
318         ; maybe_parsed <- myParseModule (hsc_dflags hsc_env) hspp_file hspp_buf
319
320         ; case maybe_parsed of {
321              Left err -> do { msg_act (unitBag err, emptyBag)
322                             ; return HscFail } ;
323              Right rdr_module -> do {
324
325             -------------------
326             -- RENAME and TYPECHECK
327             -------------------
328           (tc_msgs, maybe_tc_result) 
329                 <- _scc_ "Typecheck-Rename" 
330                    tcRnModule hsc_env (ms_hsc_src mod_summary) 
331                         True{-save renamed syntax-}
332                         rdr_module
333
334         ; msg_act tc_msgs
335         ; case maybe_tc_result of {
336              Nothing -> return (HscChecked rdr_module Nothing Nothing);
337              Just tc_result -> do
338                 let md = ModDetails { 
339                                 md_types   = tcg_type_env tc_result,
340                                 md_exports = tcg_exports  tc_result,
341                                 md_insts   = tcg_insts    tc_result,
342                                 md_rules   = [panic "no rules"] }
343                                    -- Rules are CoreRules, not the
344                                    -- RuleDecls we get out of the typechecker
345                 return (HscChecked rdr_module 
346                                    (tcg_rn_decls tc_result)
347                                    (Just (tcg_binds tc_result,
348                                           tcg_rdr_env tc_result,
349                                           md)))
350         }}}}
351
352 ------------------------------
353 hscBootBackEnd :: HscEnv -> ModSummary -> Maybe ModIface -> Maybe ModGuts -> IO HscResult
354 -- For hs-boot files, there's no code generation to do
355
356 hscBootBackEnd hsc_env mod_summary maybe_old_iface Nothing 
357   = return HscFail
358 hscBootBackEnd hsc_env mod_summary maybe_old_iface (Just ds_result)
359   = do  { details <- mkBootModDetails hsc_env ds_result
360
361         ; (new_iface, no_change) 
362                 <- {-# SCC "MkFinalIface" #-}
363                    mkIface hsc_env maybe_old_iface ds_result details
364
365         ; writeIfaceFile hsc_env (ms_location mod_summary) new_iface no_change
366
367         ; let { final_details = ModDetails { md_types   = mg_types ds_result,
368                                              md_exports = mg_exports ds_result,
369                                              md_insts   = mg_insts ds_result,
370                                              md_rules   = mg_rules ds_result } }
371           -- And the answer is ...
372         ; dumpIfaceStats hsc_env
373
374         ; return (HscRecomp final_details
375                             new_iface
376                             False False Nothing)
377         }
378
379 ------------------------------
380 hscBackEnd :: HscEnv -> ModSummary -> Maybe ModIface -> Maybe ModGuts -> IO HscResult
381
382 hscBackEnd hsc_env mod_summary maybe_old_iface Nothing 
383   = return HscFail
384
385 hscBackEnd hsc_env mod_summary maybe_old_iface (Just ds_result) 
386   = do  {       -- OMITTED: 
387                 -- ; seqList imported_modules (return ())
388
389           let one_shot  = isOneShot (ghcMode dflags)
390               dflags    = hsc_dflags hsc_env
391
392             -------------------
393             -- FLATTENING
394             -------------------
395         ; flat_result <- {-# SCC "Flattening" #-}
396                          flatten hsc_env ds_result
397
398
399 {-      TEMP: need to review space-leak fixing here
400         NB: even the code generator can force one of the
401             thunks for constructor arguments, for newtypes in particular
402
403         ; let   -- Rule-base accumulated from imported packages
404              pkg_rule_base = eps_rule_base (hsc_EPS hsc_env)
405
406                 -- In one-shot mode, ZAP the external package state at
407                 -- this point, because we aren't going to need it from
408                 -- now on.  We keep the name cache, however, because
409                 -- tidyCore needs it.
410              pcs_middle 
411                  | one_shot  = pcs_tc{ pcs_EPS = error "pcs_EPS missing" }
412                  | otherwise = pcs_tc
413
414         ; pkg_rule_base `seq` pcs_middle `seq` return ()
415 -}
416
417         -- alive at this point:  
418         --      pcs_middle
419         --      flat_result
420         --      pkg_rule_base
421
422             -------------------
423             -- SIMPLIFY
424             -------------------
425         ; simpl_result <- {-# SCC "Core2Core" #-}
426                           core2core hsc_env flat_result
427
428             -------------------
429             -- TIDY
430             -------------------
431         ; (cg_guts, details) <- {-# SCC "CoreTidy" #-}
432                                  tidyProgram hsc_env simpl_result
433
434         -- Alive at this point:  
435         --      tidy_result, pcs_final
436         --      hsc_env
437
438             -------------------
439             -- BUILD THE NEW ModIface and ModDetails
440             --  and emit external core if necessary
441             -- This has to happen *after* code gen so that the back-end
442             -- info has been set.  Not yet clear if it matters waiting
443             -- until after code output
444         ; (new_iface, no_change)
445                 <- {-# SCC "MkFinalIface" #-}
446                    mkIface hsc_env maybe_old_iface simpl_result details
447
448         ; writeIfaceFile hsc_env (ms_location mod_summary) new_iface no_change
449
450             -- Space leak reduction: throw away the new interface if
451             -- we're in one-shot mode; we won't be needing it any
452             -- more.
453         ; final_iface <- if one_shot then return (error "no final iface")
454                          else return new_iface
455
456             -- Build the final ModDetails (except in one-shot mode, where
457             -- we won't need this information after compilation).
458         ; final_details <- if one_shot then return (error "no final details")
459                            else return $! details
460
461         -- Emit external core
462         ; emitExternalCore dflags cg_guts
463
464             -------------------
465             -- CONVERT TO STG and COMPLETE CODE GENERATION
466         ; (stub_h_exists, stub_c_exists, maybe_bcos)
467                 <- hscCodeGen dflags cg_guts
468
469           -- And the answer is ...
470         ; dumpIfaceStats hsc_env
471
472         ; return (HscRecomp final_details
473                             final_iface
474                             stub_h_exists stub_c_exists
475                             maybe_bcos)
476          }
477
478
479
480 hscCodeGen dflags 
481     CgGuts{  -- This is the last use of the ModGuts in a compilation.
482               -- From now on, we just use the bits we need.
483         cg_module   = this_mod,
484         cg_binds    = core_binds,
485         cg_tycons   = tycons,
486         cg_dir_imps = dir_imps,
487         cg_foreign  = foreign_stubs,
488         cg_dep_pkgs = dependencies     }  = do {
489
490   let { data_tycons = filter isDataTyCon tycons } ;
491         -- cg_tycons includes newtypes, for the benefit of External Core,
492         -- but we don't generate any code for newtypes
493
494             -------------------
495             -- PREPARE FOR CODE GENERATION
496             -- Do saturation and convert to A-normal form
497   prepd_binds <- {-# SCC "CorePrep" #-}
498                  corePrepPgm dflags core_binds data_tycons ;
499
500   case hscTarget dflags of
501       HscNothing -> return (False, False, Nothing)
502
503       HscInterpreted ->
504 #ifdef GHCI
505         do  -----------------  Generate byte code ------------------
506             comp_bc <- byteCodeGen dflags prepd_binds data_tycons
507         
508             ------------------ Create f-x-dynamic C-side stuff ---
509             (istub_h_exists, istub_c_exists) 
510                <- outputForeignStubs dflags foreign_stubs
511             
512             return ( istub_h_exists, istub_c_exists, Just comp_bc )
513 #else
514         panic "GHC not compiled with interpreter"
515 #endif
516
517       other ->
518         do
519             -----------------  Convert to STG ------------------
520             (stg_binds, cost_centre_info) <- {-# SCC "CoreToStg" #-}
521                          myCoreToStg dflags this_mod prepd_binds        
522
523             ------------------  Code generation ------------------
524             abstractC <- {-# SCC "CodeGen" #-}
525                          codeGen dflags this_mod data_tycons foreign_stubs
526                                  dir_imps cost_centre_info stg_binds
527
528             ------------------  Code output -----------------------
529             (stub_h_exists, stub_c_exists)
530                      <- codeOutput dflags this_mod foreign_stubs 
531                                 dependencies abstractC
532
533             return (stub_h_exists, stub_c_exists, Nothing)
534    }
535
536
537 hscCmmFile :: DynFlags -> FilePath -> IO Bool
538 hscCmmFile dflags filename = do
539   maybe_cmm <- parseCmmFile dflags filename
540   case maybe_cmm of
541     Nothing -> return False
542     Just cmm -> do
543         codeOutput dflags no_mod NoStubs [] [cmm]
544         return True
545   where
546         no_mod = panic "hscCmmFile: no_mod"
547
548
549 myParseModule dflags src_filename maybe_src_buf
550  =    --------------------------  Parser  ----------------
551       showPass dflags "Parser" >>
552       {-# SCC "Parser" #-} do
553
554         -- sometimes we already have the buffer in memory, perhaps
555         -- because we needed to parse the imports out of it, or get the 
556         -- module name.
557       buf <- case maybe_src_buf of
558                 Just b  -> return b
559                 Nothing -> hGetStringBuffer src_filename
560
561       let loc  = mkSrcLoc (mkFastString src_filename) 1 0
562
563       case unP parseModule (mkPState buf loc dflags) of {
564
565         PFailed span err -> return (Left (mkPlainErrMsg span err));
566
567         POk _ rdr_module -> do {
568
569       dumpIfSet_dyn dflags Opt_D_dump_parsed "Parser" (ppr rdr_module) ;
570       
571       dumpIfSet_dyn dflags Opt_D_source_stats "Source Statistics"
572                            (ppSourceStats False rdr_module) ;
573       
574       return (Right rdr_module)
575         -- ToDo: free the string buffer later.
576       }}
577
578
579 myCoreToStg dflags this_mod prepd_binds
580  = do 
581       stg_binds <- {-# SCC "Core2Stg" #-}
582              coreToStg dflags prepd_binds
583
584       (stg_binds2, cost_centre_info) <- {-# SCC "Core2Stg" #-}
585              stg2stg dflags this_mod stg_binds
586
587       return (stg_binds2, cost_centre_info)
588 \end{code}
589
590
591 %************************************************************************
592 %*                                                                      *
593 \subsection{Compiling a do-statement}
594 %*                                                                      *
595 %************************************************************************
596
597 When the UnlinkedBCOExpr is linked you get an HValue of type
598         IO [HValue]
599 When you run it you get a list of HValues that should be 
600 the same length as the list of names; add them to the ClosureEnv.
601
602 A naked expression returns a singleton Name [it].
603
604         What you type                   The IO [HValue] that hscStmt returns
605         -------------                   ------------------------------------
606         let pat = expr          ==>     let pat = expr in return [coerce HVal x, coerce HVal y, ...]
607                                         bindings: [x,y,...]
608
609         pat <- expr             ==>     expr >>= \ pat -> return [coerce HVal x, coerce HVal y, ...]
610                                         bindings: [x,y,...]
611
612         expr (of IO type)       ==>     expr >>= \ v -> return [v]
613           [NB: result not printed]      bindings: [it]
614           
615
616         expr (of non-IO type, 
617           result showable)      ==>     let v = expr in print v >> return [v]
618                                         bindings: [it]
619
620         expr (of non-IO type, 
621           result not showable)  ==>     error
622
623 \begin{code}
624 #ifdef GHCI
625 hscStmt         -- Compile a stmt all the way to an HValue, but don't run it
626   :: HscEnv
627   -> String                     -- The statement
628   -> IO (Maybe (HscEnv, [Name], HValue))
629
630 hscStmt hsc_env stmt
631   = do  { maybe_stmt <- hscParseStmt (hsc_dflags hsc_env) stmt
632         ; case maybe_stmt of {
633              Nothing      -> return Nothing ;   -- Parse error
634              Just Nothing -> return Nothing ;   -- Empty line
635              Just (Just parsed_stmt) -> do {    -- The real stuff
636
637                 -- Rename and typecheck it
638           let icontext = hsc_IC hsc_env
639         ; maybe_tc_result <- tcRnStmt hsc_env icontext parsed_stmt
640
641         ; case maybe_tc_result of {
642                 Nothing -> return Nothing ;
643                 Just (new_ic, bound_names, tc_expr) -> do {
644
645                 -- Then desugar, code gen, and link it
646         ; hval <- compileExpr hsc_env iNTERACTIVE 
647                               (ic_rn_gbl_env new_ic) 
648                               (ic_type_env new_ic)
649                               tc_expr
650
651         ; return (Just (hsc_env{ hsc_IC=new_ic }, bound_names, hval))
652         }}}}}
653
654 hscTcExpr       -- Typecheck an expression (but don't run it)
655   :: HscEnv
656   -> String                     -- The expression
657   -> IO (Maybe Type)
658
659 hscTcExpr hsc_env expr
660   = do  { maybe_stmt <- hscParseStmt (hsc_dflags hsc_env) expr
661         ; let icontext = hsc_IC hsc_env
662         ; case maybe_stmt of {
663              Nothing      -> return Nothing ;   -- Parse error
664              Just (Just (L _ (ExprStmt expr _ _)))
665                         -> tcRnExpr hsc_env icontext expr ;
666              Just other -> do { errorMsg ("not an expression: `" ++ expr ++ "'") ;
667                                 return Nothing } ;
668              } }
669
670 hscKcType       -- Find the kind of a type
671   :: HscEnv
672   -> String                     -- The type
673   -> IO (Maybe Kind)
674
675 hscKcType hsc_env str
676   = do  { maybe_type <- hscParseType (hsc_dflags hsc_env) str
677         ; let icontext = hsc_IC hsc_env
678         ; case maybe_type of {
679              Just ty    -> tcRnType hsc_env icontext ty ;
680              Just other -> do { errorMsg ("not an type: `" ++ str ++ "'") ;
681                                 return Nothing } ;
682              Nothing    -> return Nothing } }
683 #endif
684 \end{code}
685
686 \begin{code}
687 #ifdef GHCI
688 hscParseStmt :: DynFlags -> String -> IO (Maybe (Maybe (LStmt RdrName)))
689 hscParseStmt = hscParseThing parseStmt
690
691 hscParseType :: DynFlags -> String -> IO (Maybe (LHsType RdrName))
692 hscParseType = hscParseThing parseType
693 #endif
694
695 hscParseIdentifier :: DynFlags -> String -> IO (Maybe (Located RdrName))
696 hscParseIdentifier = hscParseThing parseIdentifier
697
698 hscParseThing :: Outputable thing
699               => Lexer.P thing
700               -> DynFlags -> String
701               -> IO (Maybe thing)
702         -- Nothing => Parse error (message already printed)
703         -- Just x  => success
704 hscParseThing parser dflags str
705  = showPass dflags "Parser" >>
706       {-# SCC "Parser" #-} do
707
708       buf <- stringToStringBuffer str
709
710       let loc  = mkSrcLoc FSLIT("<interactive>") 1 0
711
712       case unP parser (mkPState buf loc dflags) of {
713
714         PFailed span err -> do { printError span err;
715                                  return Nothing };
716
717         POk _ thing -> do {
718
719       --ToDo: can't free the string buffer until we've finished this
720       -- compilation sweep and all the identifiers have gone away.
721       dumpIfSet_dyn dflags Opt_D_dump_parsed "Parser" (ppr thing);
722       return (Just thing)
723       }}
724 \end{code}
725
726 %************************************************************************
727 %*                                                                      *
728 \subsection{Getting information about an identifer}
729 %*                                                                      *
730 %************************************************************************
731
732 \begin{code}
733 #ifdef GHCI
734 hscGetInfo -- like hscStmt, but deals with a single identifier
735   :: HscEnv
736   -> String                     -- The identifier
737   -> IO [GetInfoResult]
738
739 hscGetInfo hsc_env str
740    = do maybe_rdr_name <- hscParseIdentifier (hsc_dflags hsc_env) str
741         case maybe_rdr_name of {
742           Nothing -> return [];
743           Just (L _ rdr_name) -> do
744
745         maybe_tc_result <- tcRnGetInfo hsc_env (hsc_IC hsc_env) rdr_name
746
747         case maybe_tc_result of
748              Nothing     -> return []
749              Just things -> return things
750         }
751 #endif
752 \end{code}
753
754 %************************************************************************
755 %*                                                                      *
756         Desugar, simplify, convert to bytecode, and link an expression
757 %*                                                                      *
758 %************************************************************************
759
760 \begin{code}
761 #ifdef GHCI
762 compileExpr :: HscEnv 
763             -> Module -> GlobalRdrEnv -> TypeEnv
764             -> LHsExpr Id
765             -> IO HValue
766
767 compileExpr hsc_env this_mod rdr_env type_env tc_expr
768   = do  { let { dflags  = hsc_dflags hsc_env ;
769                 lint_on = dopt Opt_DoCoreLinting dflags }
770               
771                 -- Desugar it
772         ; ds_expr <- deSugarExpr hsc_env this_mod rdr_env type_env tc_expr
773         
774                 -- Flatten it
775         ; flat_expr <- flattenExpr hsc_env ds_expr
776
777                 -- Simplify it
778         ; simpl_expr <- simplifyExpr dflags flat_expr
779
780                 -- Tidy it (temporary, until coreSat does cloning)
781         ; let tidy_expr = tidyExpr emptyTidyEnv simpl_expr
782
783                 -- Prepare for codegen
784         ; prepd_expr <- corePrepExpr dflags tidy_expr
785
786                 -- Lint if necessary
787                 -- ToDo: improve SrcLoc
788         ; if lint_on then 
789                 case lintUnfolding noSrcLoc [] prepd_expr of
790                    Just err -> pprPanic "compileExpr" err
791                    Nothing  -> return ()
792           else
793                 return ()
794
795                 -- Convert to BCOs
796         ; bcos <- coreExprToBCOs dflags prepd_expr
797
798                 -- link it
799         ; hval <- linkExpr hsc_env bcos
800
801         ; return hval
802      }
803 #endif
804 \end{code}
805
806
807 %************************************************************************
808 %*                                                                      *
809         Statistics on reading interfaces
810 %*                                                                      *
811 %************************************************************************
812
813 \begin{code}
814 dumpIfaceStats :: HscEnv -> IO ()
815 dumpIfaceStats hsc_env
816   = do  { eps <- readIORef (hsc_EPS hsc_env)
817         ; dumpIfSet (dump_if_trace || dump_rn_stats)
818                     "Interface statistics"
819                     (ifaceStats eps) }
820   where
821     dflags = hsc_dflags hsc_env
822     dump_rn_stats = dopt Opt_D_dump_rn_stats dflags
823     dump_if_trace = dopt Opt_D_dump_if_trace dflags
824 \end{code}
825
826 %************************************************************************
827 %*                                                                      *
828         Progress Messages: Module i of n
829 %*                                                                      *
830 %************************************************************************
831
832 \begin{code}
833 showModuleIndex Nothing = ""
834 showModuleIndex (Just (i,n)) = "[" ++ padded ++ " of " ++ n_str ++ "] "
835     where
836         n_str = show n
837         i_str = show i
838         padded = replicate (length n_str - length i_str) ' ' ++ i_str
839 \end{code}
840