Typo in comment.
[ghc-hetmet.git] / compiler / main / HscMain.lhs
index 0563f34..463c303 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,6 +76,7 @@ import CodeGen                ( codeGen )
 import CmmParse                ( parseCmmFile )
 import CodeOutput      ( codeOutput )
 import NameEnv          ( emptyNameEnv )
+import Breakpoints      ( noDbgSites )
 
 import DynFlags
 import ErrUtils
@@ -90,9 +91,11 @@ import ParserCoreUtils
 import FastString
 import UniqFM          ( emptyUFM )
 import Bag             ( unitBag )
-import Monad           ( unless )
-import IO
-import DATA_IOREF      ( newIORef, readIORef )
+
+import Control.Monad
+import System.Exit
+import System.IO
+import Data.IORef
 \end{code}
 
 
@@ -190,7 +193,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
@@ -465,7 +468,7 @@ hscFileFrontEnd =
                          -------------------
                          -- DESUGAR
                          -------------------
-                         -> {-# SCC "DeSugar" #-} deSugar hsc_env tc_result
+                         -> {-# SCC "DeSugar" #-} deSugar hsc_env (ms_location mod_summary) tc_result
 
 --------------------------------------------------------------
 -- Simplifiers
@@ -582,7 +585,8 @@ hscCompile cgguts
                      cg_tycons   = tycons,
                      cg_dir_imps = dir_imps,
                      cg_foreign  = foreign_stubs,
-                     cg_dep_pkgs = dependencies } = cgguts
+                     cg_dep_pkgs = dependencies,
+                    cg_hpc_info = hpc_info } = cgguts
              dflags = hsc_dflags hsc_env
              location = ms_location mod_summary
              data_tycons = filter isDataTyCon tycons
@@ -602,7 +606,7 @@ hscCompile cgguts
          abstractC <- {-# SCC "CodeGen" #-}
                       codeGen dflags this_mod data_tycons
                               foreign_stubs dir_imps cost_centre_info
-                              stg_binds
+                              stg_binds hpc_info
          ------------------  Code output -----------------------
          (stub_h_exists,stub_c_exists)
              <- codeOutput dflags this_mod location foreign_stubs 
@@ -683,6 +687,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_rules     = [panic "no rules"] }
                                   -- Rules are CoreRules, not the
                                   -- RuleDecls we get out of the typechecker
@@ -733,8 +738,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"
@@ -889,7 +898,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.