Re-working of the breakpoint support
[ghc-hetmet.git] / compiler / main / HscMain.lhs
index 041ea15..4413c52 100644 (file)
@@ -54,7 +54,7 @@ import HsSyn          ( HsModule, LHsBinds, HsGroup, LIE, LImportDecl, HsDoc,
 import SrcLoc          ( Located(..) )
 import StringBuffer    ( hGetStringBuffer, stringToStringBuffer )
 import Parser
-import Lexer           ( P(..), ParseResult(..), mkPState )
+import Lexer
 import SrcLoc          ( mkSrcLoc )
 import TcRnDriver      ( tcRnModule, tcRnExtCore )
 import TcIface         ( typecheckIface )
@@ -76,7 +76,6 @@ import CodeGen                ( codeGen )
 import CmmParse                ( parseCmmFile )
 import CodeOutput      ( codeOutput )
 import NameEnv          ( emptyNameEnv )
-import Breakpoints      ( noDbgSites )
 
 import DynFlags
 import ErrUtils
@@ -93,6 +92,7 @@ import UniqFM         ( emptyUFM )
 import Bag             ( unitBag )
 
 import Control.Monad
+import System.Exit
 import System.IO
 import Data.IORef
 \end{code}
@@ -192,7 +192,7 @@ data HscStatus
                       -- This is a hack. We can't compile C files here
                       -- since it's done in DriverPipeline. For now we
                       -- just return True if we want the caller to compile
-                      -- it for us.
+                      -- them for us.
 
 -- Status of a compilation to byte-code.
 data InteractiveStatus
@@ -288,31 +288,26 @@ hscMkCompiler norecomp messenger frontend backend
 --        1         2         3         4         5         6         7         8          9
 -- Compile Haskell, boot and extCore in OneShot mode.
 hscCompileOneShot :: Compiler HscStatus
-hscCompileOneShot hsc_env mod_summary =
-    compiler hsc_env mod_summary
-    where mkComp = hscMkCompiler norecompOneShot oneShotMsg
-          -- How to compile nonBoot files.
-          nonBootComp inp = hscSimplify inp >>= hscNormalIface >>=
-                            hscWriteIface >>= hscOneShot
-          -- How to compile boot files.
-          bootComp inp = hscSimpleIface inp >>= hscWriteIface >>= hscConst (HscRecomp False)
-          compiler
-              = case ms_hsc_src mod_summary of
-                ExtCoreFile
-                    -> mkComp hscCoreFrontEnd nonBootComp
-                HsSrcFile
-                    -> mkComp hscFileFrontEnd nonBootComp
-                HsBootFile
-                    -> mkComp hscFileFrontEnd bootComp
+hscCompileOneShot = hscCompileHardCode norecompOneShot oneShotMsg hscOneShot (hscConst (HscRecomp False))
 
 -- Compile Haskell, boot and extCore in batch mode.
 hscCompileBatch :: Compiler (HscStatus, ModIface, ModDetails)
-hscCompileBatch hsc_env mod_summary
-    = compiler hsc_env mod_summary
-    where mkComp = hscMkCompiler norecompBatch batchMsg
+hscCompileBatch = hscCompileHardCode norecompBatch batchMsg hscBatch hscNothing
+
+-- Compile to hardcode (C,asm,...). This general structure is shared by OneShot and Batch.
+hscCompileHardCode :: NoRecomp result                                  -- No recomp necessary
+                   -> (Maybe (Int,Int) -> Bool -> Comp ())             -- Message callback
+                   -> ((ModIface, ModDetails, CgGuts) -> Comp result)  -- Compile normal file
+                   -> ((ModIface, ModDetails, ModGuts) -> Comp result) -- Compile boot file
+                   -> Compiler result
+hscCompileHardCode norecomp msg compNormal compBoot hsc_env mod_summary =
+    compiler hsc_env mod_summary
+    where mkComp = hscMkCompiler norecomp msg
+          -- How to compile nonBoot files.
           nonBootComp inp = hscSimplify inp >>= hscNormalIface >>=
-                            hscWriteIface >>= hscBatch
-          bootComp inp = hscSimpleIface inp >>= hscWriteIface >>= hscNothing
+                            hscWriteIface >>= compNormal
+          -- How to compile boot files.
+          bootComp inp = hscSimpleIface inp >>= hscWriteIface >>= compBoot
           compiler
               = case ms_hsc_src mod_summary of
                 ExtCoreFile
@@ -640,7 +635,7 @@ hscInteractive (iface, details, cgguts)
          prepd_binds <- {-# SCC "CorePrep" #-}
                         corePrepPgm dflags core_binds data_tycons ;
          -----------------  Generate byte code ------------------
-         comp_bc <- byteCodeGen dflags prepd_binds data_tycons
+         comp_bc <- byteCodeGen dflags prepd_binds data_tycons (md_modBreaks details)
          ------------------ Create f-x-dynamic C-side stuff ---
          (istub_h_exists, istub_c_exists) 
              <- outputForeignStubs dflags this_mod location foreign_stubs
@@ -686,7 +681,7 @@ hscFileCheck hsc_env mod_summary = do {
                                md_exports   = tcg_exports   tc_result,
                                md_insts     = tcg_insts     tc_result,
                                md_fam_insts = tcg_fam_insts tc_result,
-                                md_dbg_sites = noDbgSites,
+                                md_modBreaks = emptyModBreaks,      
                                md_rules     = [panic "no rules"] }
                                   -- Rules are CoreRules, not the
                                   -- RuleDecls we get out of the typechecker
@@ -737,8 +732,12 @@ myParseModule dflags src_filename maybe_src_buf
 
        PFailed span err -> return (Left (mkPlainErrMsg span err));
 
-       POk _ rdr_module -> do {
+       POk pst rdr_module -> do {
 
+      let {ms = getMessages pst};
+      printErrorsAndWarnings dflags ms;
+      when (errorsFound dflags ms) $ exitWith (ExitFailure 1);
+      
       dumpIfSet_dyn dflags Opt_D_dump_parsed "Parser" (ppr rdr_module) ;
       
       dumpIfSet_dyn dflags Opt_D_source_stats "Source Statistics"
@@ -893,7 +892,11 @@ hscParseThing parser dflags str
        PFailed span err -> do { printError span err;
                                  return Nothing };
 
-       POk _ thing -> do {
+       POk pst thing -> do {
+
+      let {ms = getMessages pst};
+      printErrorsAndWarnings dflags ms;
+      when (errorsFound dflags ms) $ exitWith (ExitFailure 1);
 
       --ToDo: can't free the string buffer until we've finished this
       -- compilation sweep and all the identifiers have gone away.