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