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