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