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