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