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