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