[project @ 2000-11-01 17:15:28 by simonpj]
[ghc-hetmet.git] / ghc / compiler / main / HscMain.lhs
index 7ef69b2..bf5857e 100644 (file)
@@ -10,28 +10,22 @@ module HscMain ( HscResult(..), hscMain,
 #include "HsVersions.h"
 
 import Maybe           ( isJust )
-import Monad           ( when )
-import IO              ( hPutStr, hPutStrLn, hClose, stderr, 
-                         openFile, IOMode(..) )
+import IO              ( hPutStr, hPutStrLn, stderr )
 import HsSyn
 
-import RdrHsSyn                ( RdrNameHsModule )
-import FastString      ( unpackFS )
 import StringBuffer    ( hGetStringBuffer )
 import Parser          ( parse )
 import Lex             ( PState(..), ParseResult(..) )
 import SrcLoc          ( mkSrcLoc )
 
 import Rename          ( renameModule, checkOldIface, closeIfaceDecls )
-
 import Rules           ( emptyRuleBase )
-import PrelInfo                ( wiredInThings )
+import PrelInfo                ( wiredInThingEnv, wiredInThings )
 import PrelNames       ( knownKeyNames )
 import PrelRules       ( builtinRules )
 import MkIface         ( completeIface, mkModDetailsFromIface, mkModDetails,
                          writeIface )
 import TcModule                ( TcResults(..), typecheckModule )
-import TcEnv           ( tcEnvTyCons, tcEnvClasses )
 import InstEnv         ( emptyInstEnv )
 import Desugar         ( deSugar )
 import SimplCore       ( core2core )
@@ -44,36 +38,28 @@ import SimplStg             ( stg2stg )
 import CodeGen         ( codeGen )
 import CodeOutput      ( codeOutput )
 
-import Module          ( ModuleName, moduleNameUserString, 
-                         moduleUserString, moduleName, emptyModuleEnv,
-                         extendModuleEnv )
+import Module          ( ModuleName, moduleName, mkModuleInThisPackage )
 import CmdLineOpts
-import ErrUtils                ( ghcExit, doIfSet, dumpIfSet_dyn )
+import ErrUtils                ( dumpIfSet_dyn )
+import Util            ( unJust )
 import UniqSupply      ( mkSplitUniqSupply )
 
 import Bag             ( emptyBag )
 import Outputable
-import Char            ( isSpace )
 import StgInterp       ( stgToInterpSyn )
 import HscStats                ( ppSourceStats )
 import HscTypes                ( ModDetails, ModIface(..), PersistentCompilerState(..),
-                         PersistentRenamerState(..), WhatsImported(..),
-                         HomeSymbolTable, PackageSymbolTable, ImportVersion, 
-                         GenAvailInfo(..), RdrAvailInfo, OrigNameEnv(..),
-                         PackageRuleBase, HomeIfaceTable, PackageIfaceTable,
-                         extendTypeEnv, groupTyThings, TypeEnv, TyThing,
+                         PersistentRenamerState(..), ModuleLocation(..),
+                         HomeSymbolTable, 
+                         OrigNameEnv(..), PackageRuleBase, HomeIfaceTable, 
                          typeEnvClasses, typeEnvTyCons, emptyIfaceTable )
-import RnMonad         ( ExportItem, ParsedIface(..) )
-import CmSummarise     ( ModSummary(..), name_of_summary, ms_get_imports,
-                         mimp_name )
 import InterpSyn       ( UnlinkedIBind )
 import StgInterp       ( ItblEnv )
 import FiniteMap       ( FiniteMap, plusFM, emptyFM, addToFM )
-import OccName         ( OccName, pprOccName )
-import Name            ( Name, nameModule, emptyNameEnv, nameOccName, 
-                         getName, extendNameEnv_C, nameEnvElts )
-import VarEnv          ( emptyVarEnv )
-import Module          ( Module, mkModuleName, lookupModuleEnvByName )
+import OccName         ( OccName )
+import Name            ( Name, nameModule, nameOccName, getName  )
+import Name            ( emptyNameEnv )
+import Module          ( Module, lookupModuleEnvByName )
 
 \end{code}
 
@@ -99,21 +85,19 @@ data HscResult
 
 hscMain
   :: DynFlags
-  -> ModSummary       -- summary, including source filename
-  -> Maybe ModIface   -- old interface, if available
+  -> Bool                      -- source unchanged?
+  -> ModuleLocation            -- location info
+  -> Maybe ModIface            -- old interface, if available
   -> HomeSymbolTable           -- for home module ModDetails
   -> HomeIfaceTable
   -> PersistentCompilerState    -- IN: persistent compiler state
   -> IO HscResult
 
-hscMain dflags summary maybe_old_iface hst hit pcs
+hscMain dflags source_unchanged location maybe_old_iface hst hit pcs
  = do {
-      -- ????? source_unchanged :: Bool -- extracted from summary?
-      let source_unchanged = trace "WARNING: source_unchanged?!" False
-      ;
-      putStrLn "checking old iface ...";
+      putStrLn "CHECKING OLD IFACE";
       (pcs_ch, check_errs, (recomp_reqd, maybe_checked_iface))
-         <- checkOldIface dflags hit hst pcs (ms_mod summary)
+         <- checkOldIface dflags hit hst pcs (unJust (ml_hi_file location) "hscMain")
                          source_unchanged maybe_old_iface;
       if check_errs then
          return (HscFail pcs_ch)
@@ -123,18 +107,19 @@ hscMain dflags summary maybe_old_iface hst hit pcs
           what_next | recomp_reqd || no_old_iface = hscRecomp 
                     | otherwise                   = hscNoRecomp
       ;
-      putStrLn "doing what_next ...";
-      what_next dflags summary maybe_checked_iface
+      what_next dflags location maybe_checked_iface
                 hst hit pcs_ch
       }}
 
 
-hscNoRecomp dflags summary maybe_checked_iface hst hit pcs_ch
+hscNoRecomp dflags location maybe_checked_iface hst hit pcs_ch
  = do {
+      hPutStrLn stderr "COMPILATION NOT REQUIRED";
       -- we definitely expect to have the old interface available
       let old_iface = case maybe_checked_iface of 
                          Just old_if -> old_if
                          Nothing -> panic "hscNoRecomp:old_iface"
+          this_mod = mi_module old_iface
       ;
       -- CLOSURE
       (pcs_cl, closure_errs, cl_hs_decls) 
@@ -145,16 +130,15 @@ hscNoRecomp dflags summary maybe_checked_iface hst hit pcs_ch
 
       -- TYPECHECK
       maybe_tc_result
-         <- typecheckModule dflags (ms_mod summary) pcs_cl hst hit cl_hs_decls;
+         <- typecheckModule dflags this_mod pcs_cl hst hit cl_hs_decls;
       case maybe_tc_result of {
          Nothing -> return (HscFail pcs_cl);
          Just tc_result -> do {
 
-      let pcs_tc        = tc_pcs tc_result
-          env_tc        = tc_env tc_result
-          binds_tc      = tc_binds tc_result
-          local_insts   = tc_insts tc_result
-          local_rules   = tc_rules tc_result
+      let pcs_tc      = tc_pcs tc_result
+          env_tc      = tc_env tc_result
+          local_insts = tc_insts tc_result
+          local_rules = tc_rules tc_result
       ;
       -- create a new details from the closed, typechecked, old iface
       let new_details = mkModDetailsFromIface env_tc local_insts local_rules
@@ -167,19 +151,23 @@ hscNoRecomp dflags summary maybe_checked_iface hst hit pcs_ch
       }}}}
 
 
-hscRecomp dflags summary maybe_checked_iface hst hit pcs_ch
+hscRecomp dflags location maybe_checked_iface hst hit pcs_ch
  = do {
+      hPutStrLn stderr "COMPILATION IS REQUIRED";
+
       -- what target are we shooting for?
       let toInterp = dopt_HscLang dflags == HscInterpreted
-          this_mod = ms_mod summary
       ;
       -- PARSE
-      maybe_parsed <- myParseModule dflags summary;
+      maybe_parsed 
+         <- myParseModule dflags (unJust (ml_hspp_file location) "hscRecomp:hspp");
       case maybe_parsed of {
          Nothing -> return (HscFail pcs_ch);
          Just rdr_module -> do {
 
       -- RENAME
+      let this_mod = mkModuleInThisPackage (hsModuleName rdr_module)
+      ;
       show_pass dflags "Renamer";
       (pcs_rn, maybe_rn_result) 
          <- renameModule dflags hit hst pcs_ch this_mod rdr_module;
@@ -192,12 +180,12 @@ hscRecomp dflags summary maybe_checked_iface hst hit pcs_ch
       maybe_tc_result
          <- typecheckModule dflags this_mod pcs_rn hst hit rn_hs_decls;
       case maybe_tc_result of {
-         Nothing -> return (HscFail pcs_rn);
+         Nothing -> do { hPutStrLn stderr "Typechecked failed" 
+                      ; return (HscFail pcs_rn) } ;
          Just tc_result -> do {
 
       let pcs_tc        = tc_pcs tc_result
           env_tc        = tc_env tc_result
-          binds_tc      = tc_binds tc_result
           local_insts   = tc_insts tc_result
       ;
       -- DESUGAR, SIMPLIFY, TIDY-CORE
@@ -213,41 +201,44 @@ hscRecomp dflags summary maybe_checked_iface hst hit pcs_ch
       let new_details = mkModDetails env_tc local_insts tidy_binds 
                                     top_level_ids orphan_rules
       ;
-      -- and possibly create a new ModIface
-      let maybe_final_iface_and_sdoc 
-             = completeIface maybe_checked_iface new_iface new_details 
-          maybe_final_iface
-             = case maybe_final_iface_and_sdoc of 
-                  Just (fif, sdoc) -> Just fif; Nothing -> Nothing
-      ;
-      -- Write the interface file
-      writeIface maybe_final_iface
+      -- and the final interface
+      final_iface 
+         <- mkFinalIface dflags location maybe_checked_iface new_iface new_details
       ;
       -- do the rest of code generation/emission
       (maybe_stub_h_filename, maybe_stub_c_filename, maybe_ibinds)
-         <- restOfCodeGeneration dflags toInterp summary
+         <- restOfCodeGeneration dflags toInterp this_mod
+              (map ideclName (hsModuleImports rdr_module))
                cost_centre_info foreign_stuff env_tc stg_binds oa_tidy_binds
                hit (pcs_PIT pcs_tc)       
       ;
       -- and the answer is ...
-      return (HscOK new_details maybe_final_iface 
+      return (HscOK new_details (Just final_iface)
                    maybe_stub_h_filename maybe_stub_c_filename
                     maybe_ibinds pcs_tc)
       }}}}}}}
 
 
-myParseModule dflags summary
+
+mkFinalIface dflags location maybe_old_iface new_iface new_details
+ = case completeIface maybe_old_iface new_iface new_details of
+      (new_iface, Nothing) -- no change in the interfacfe
+         -> do if dopt Opt_D_dump_hi_diffs dflags  then
+                       printDump (text "INTERFACE UNCHANGED")
+                 else  return ()
+              return new_iface
+      (new_iface, Just sdoc)
+         -> do dumpIfSet_dyn dflags Opt_D_dump_hi_diffs "NEW INTERFACE" sdoc
+               -- Write the interface file
+               writeIface (unJust (ml_hi_file location) "hscRecomp:hi") new_iface
+               return new_iface
+
+
+myParseModule dflags src_filename
  = do --------------------------  Parser  ----------------
       show_pass dflags "Parser"
       -- _scc_     "Parser"
 
-      let src_filename -- name of the preprocessed source file
-            = case ms_ppsource summary of
-                 Just (filename, fingerprint) -> filename
-                 Nothing -> pprPanic 
-                               "myParseModule:summary is not of a source module"
-                               (ppr summary)
-
       buf <- hGetStringBuffer True{-expand tabs-} src_filename
 
       let glaexts | dopt Opt_GlasgowExts dflags = 1#
@@ -270,37 +261,35 @@ myParseModule dflags summary
       }}
 
 
-restOfCodeGeneration dflags toInterp summary cost_centre_info 
+restOfCodeGeneration dflags toInterp this_mod imported_module_names cost_centre_info 
                      foreign_stuff env_tc stg_binds oa_tidy_binds
                      hit pit -- these last two for mapping ModNames to Modules
  | toInterp
  = do (ibinds,itbl_env) 
          <- stgToInterpSyn (map fst stg_binds) local_tycons local_classes
       return (Nothing, Nothing, Just (ibinds,itbl_env))
+
  | otherwise
  = do --------------------------  Code generation -------------------------------
       show_pass dflags "CodeGen"
       -- _scc_     "CodeGen"
       abstractC <- codeGen dflags this_mod imported_modules
                            cost_centre_info fe_binders
-                           local_tycons local_classes stg_binds
+                           local_tycons stg_binds
 
       --------------------------  Code output -------------------------------
       show_pass dflags "CodeOutput"
       -- _scc_     "CodeOutput"
-      ncg_uniqs <- mkSplitUniqSupply 'n'
       (maybe_stub_h_name, maybe_stub_c_name)
-         <- codeOutput dflags this_mod local_tycons local_classes
+         <- codeOutput dflags this_mod local_tycons
                        oa_tidy_binds stg_binds
-                       c_code h_code abstractC ncg_uniqs
+                       c_code h_code abstractC
 
       return (maybe_stub_h_name, maybe_stub_c_name, Nothing)
  where
     local_tycons     = typeEnvTyCons env_tc
     local_classes    = typeEnvClasses env_tc
-    this_mod         = ms_mod summary
-    imported_modules = map (mod_name_to_Module.mimp_name) 
-                          (ms_get_imports summary)
+    imported_modules = map mod_name_to_Module imported_module_names
     (fe_binders,h_code,c_code) = foreign_stuff
 
     mod_name_to_Module :: ModuleName -> Module
@@ -379,18 +368,13 @@ initPersistentCompilerState
   = do prs <- initPersistentRenamerState
        return (
         PCS { pcs_PIT   = emptyIfaceTable,
-              pcs_PST   = initPackageDetails,
+              pcs_PTE   = wiredInThingEnv,
              pcs_insts = emptyInstEnv,
              pcs_rules = emptyRuleBase,
              pcs_PRS   = prs
             }
         )
 
-initPackageDetails :: PackageSymbolTable
-initPackageDetails = extendTypeEnv emptyModuleEnv (groupTyThings wiredInThings)
-
---initPackageDetails = panic "initPackageDetails"
-
 initPersistentRenamerState :: IO PersistentRenamerState
   = do ns <- mkSplitUniqSupply 'r'
        return (