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