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