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