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