[project @ 2005-04-13 13:17:35 by simonmar]
[ghc-hetmet.git] / ghc / compiler / main / HscMain.lhs
index 7b3e84b..0c3e183 100644 (file)
@@ -8,18 +8,19 @@
 module HscMain ( 
        HscResult(..),
        hscMain, newHscEnv, hscCmmFile, 
-       hscBufferCheck, hscFileCheck,
+       hscFileCheck,
+       hscParseIdentifier,
 #ifdef GHCI
-       , hscStmt, hscTcExpr, hscKcType
-       , hscGetInfo, GetInfoResult
-       , compileExpr
+       hscStmt, hscTcExpr, hscKcType,
+       hscGetInfo, GetInfoResult,
+       compileExpr,
 #endif
        ) where
 
 #include "HsVersions.h"
 
 #ifdef GHCI
-import HsSyn           ( Stmt(..), LStmt, LHsExpr, LHsType )
+import HsSyn           ( Stmt(..), LHsExpr )
 import IfaceSyn                ( IfaceDecl, IfaceInst )
 import Module          ( Module )
 import CodeOutput      ( outputForeignStubs )
@@ -28,34 +29,33 @@ import Linker               ( HValue, linkExpr )
 import TidyPgm         ( tidyCoreExpr )
 import CorePrep                ( corePrepExpr )
 import Flattening      ( flattenExpr )
-import TcRnDriver      ( tcRnStmt, tcRnExpr, tcRnGetInfo, tcRnType ) 
+import TcRnDriver      ( tcRnStmt, tcRnExpr, tcRnGetInfo, GetInfoResult, tcRnType ) 
 import RdrName         ( rdrNameOcc )
 import OccName         ( occNameUserString )
 import Type            ( Type )
 import PrelNames       ( iNTERACTIVE )
-import StringBuffer    ( stringToStringBuffer )
 import Kind            ( Kind )
-import Var             ( Id )
 import CoreLint                ( lintUnfolding )
 import DsMeta          ( templateHaskellNames )
 import BasicTypes      ( Fixity )
 import SrcLoc          ( SrcLoc, noSrcLoc )
 #endif
 
-import RdrName         ( RdrName )
-import HsSyn           ( HsModule )
+import Var             ( Id )
+import Module          ( emptyModuleEnv )
+import RdrName         ( GlobalRdrEnv, RdrName )
+import HsSyn           ( HsModule, LHsBinds, LStmt, LHsType )
 import SrcLoc          ( Located(..) )
-import StringBuffer    ( hGetStringBuffer )
+import StringBuffer    ( hGetStringBuffer, stringToStringBuffer )
 import Parser
 import Lexer           ( P(..), ParseResult(..), mkPState )
 import SrcLoc          ( mkSrcLoc )
 import TcRnDriver      ( tcRnModule, tcRnExtCore )
-import TcRnTypes       ( TcGblEnv )
+import TcRnTypes       ( TcGblEnv(..) )
 import TcIface         ( typecheckIface )
 import IfaceEnv                ( initNameCache )
 import LoadIface       ( ifaceStats, initExternalPackageState )
 import PrelInfo                ( wiredInThings, basicKnownKeyNames )
-import RdrName         ( GlobalRdrEnv )
 import MkIface         ( checkOldIface, mkIface )
 import Desugar
 import Flattening       ( flatten )
@@ -69,7 +69,7 @@ import CodeGen                ( codeGen )
 import CmmParse                ( parseCmmFile )
 import CodeOutput      ( codeOutput )
 
-import CmdLineOpts
+import DynFlags
 import DriverPhases     ( HscSource(..) )
 import ErrUtils
 import UniqSupply      ( mkSplitUniqSupply )
@@ -99,16 +99,20 @@ import DATA_IOREF   ( newIORef, readIORef )
 %************************************************************************
 
 \begin{code}
-newHscEnv :: GhciMode -> DynFlags -> IO HscEnv
-newHscEnv ghci_mode dflags
+newHscEnv :: DynFlags -> IO HscEnv
+newHscEnv dflags
   = do         { eps_var <- newIORef initExternalPackageState
        ; us      <- mkSplitUniqSupply 'r'
        ; nc_var  <- newIORef (initNameCache us knownKeyNames)
-       ; return (HscEnv { hsc_mode   = ghci_mode,
-                          hsc_dflags = dflags,
+       ; fc_var  <- newIORef emptyModuleEnv
+       ; return (HscEnv { hsc_dflags = dflags,
+                          hsc_targets = [],
+                          hsc_mod_graph = [],
+                          hsc_IC     = emptyInteractiveContext,
                           hsc_HPT    = emptyHomePackageTable,
                           hsc_EPS    = eps_var,
-                          hsc_NC     = nc_var } ) }
+                          hsc_NC     = nc_var,
+                          hsc_FC     = fc_var } ) }
                        
 
 knownKeyNames :: [Name]        -- Put here to avoid loops involving DsMeta,
@@ -133,7 +137,9 @@ data HscResult
    = HscFail
 
    -- In IDE mode: we just do the static/dynamic checks
-   | HscChecked (Located (HsModule RdrName)) (Maybe TcGblEnv)
+   | HscChecked 
+       (Located (HsModule RdrName))
+       (Maybe (LHsBinds Id, GlobalRdrEnv, ModDetails))
 
    -- Concluded that it wasn't necessary
    | HscNoRecomp ModDetails             -- new details (HomeSymbolTable additions)
@@ -166,7 +172,7 @@ hscMain hsc_env msg_act mod_summary
        source_unchanged have_object maybe_old_iface
  = do {
       (recomp_reqd, maybe_checked_iface) <- 
-               _scc_ "checkOldIface" 
+               {-# SCC "checkOldIface" #-}
                checkOldIface hsc_env mod_summary 
                              source_unchanged maybe_old_iface;
 
@@ -183,7 +189,7 @@ hscMain hsc_env msg_act mod_summary
 -- hscNoRecomp definitely expects to have the old interface available
 hscNoRecomp hsc_env msg_act mod_summary 
            have_object (Just old_iface)
- | isOneShot (hsc_mode hsc_env)
+ | isOneShot (ghcMode (hsc_dflags hsc_env))
  = do {
       compilationProgressMsg (hsc_dflags hsc_env) $
        "compilation IS NOT required";
@@ -196,7 +202,7 @@ hscNoRecomp hsc_env msg_act mod_summary
  = do  { compilationProgressMsg (hsc_dflags hsc_env) $
                ("Skipping  " ++ showModMsg have_object mod_summary)
 
-       ; new_details <- _scc_ "tcRnIface"
+       ; new_details <- {-# SCC "tcRnIface" #-}
                     typecheckIface hsc_env old_iface ;
        ; dumpIfaceStats hsc_env
 
@@ -207,14 +213,17 @@ hscNoRecomp hsc_env msg_act mod_summary
 hscRecomp hsc_env msg_act mod_summary
          have_object maybe_checked_iface
  = case ms_hsc_src mod_summary of
-     HsSrcFile -> do { front_res <- hscFileFrontEnd hsc_env msg_act mod_summary
-                    ; hscBackEnd hsc_env mod_summary maybe_checked_iface front_res }
+     HsSrcFile -> do 
+       front_res <- hscFileFrontEnd hsc_env msg_act mod_summary
+       hscBackEnd hsc_env mod_summary maybe_checked_iface front_res
 
-     HsBootFile -> do { front_res <- hscFileFrontEnd hsc_env msg_act mod_summary
-                     ; hscBootBackEnd hsc_env mod_summary maybe_checked_iface front_res }
+     HsBootFile -> do
+       front_res <- hscFileFrontEnd hsc_env msg_act mod_summary
+       hscBootBackEnd hsc_env mod_summary maybe_checked_iface front_res
 
-     ExtCoreFile -> do { front_res <- hscCoreFrontEnd hsc_env msg_act mod_summary
-                      ; hscBackEnd hsc_env mod_summary maybe_checked_iface front_res }
+     ExtCoreFile -> do
+       front_res <- hscCoreFrontEnd hsc_env msg_act mod_summary
+       hscBackEnd hsc_env mod_summary maybe_checked_iface front_res
 
 hscCoreFrontEnd hsc_env msg_act mod_summary = do {
            -------------------
@@ -228,7 +237,7 @@ hscCoreFrontEnd hsc_env msg_act mod_summary = do {
            -------------------
            -- RENAME and TYPECHECK
            -------------------
-       ; (tc_msgs, maybe_tc_result) <- _scc_ "TypeCheck" 
+       ; (tc_msgs, maybe_tc_result) <- {-# SCC "TypeCheck" #-}
                              tcRnExtCore hsc_env rdr_module
        ; msg_act tc_msgs
        ; case maybe_tc_result of
@@ -241,9 +250,9 @@ hscFileFrontEnd hsc_env msg_act mod_summary = do {
            -------------------
            -- DISPLAY PROGRESS MESSAGE
            -------------------
-         let one_shot  = isOneShot (hsc_mode hsc_env)
+         let one_shot  = isOneShot (ghcMode (hsc_dflags hsc_env))
        ; let dflags    = hsc_dflags hsc_env
-       ; let toInterp  = dopt_HscTarget dflags == HscInterpreted
+       ; let toInterp  = hscTarget dflags == HscInterpreted
        ; when (not one_shot) $
                 compilationProgressMsg dflags $
                 ("Compiling " ++ showModMsg (not toInterp) mod_summary)
@@ -265,7 +274,7 @@ hscFileFrontEnd hsc_env msg_act mod_summary = do {
            -- RENAME and TYPECHECK
            -------------------
          (tc_msgs, maybe_tc_result) 
-               <- _scc_ "Typecheck-Rename" 
+               <- {-# SCC "Typecheck-Rename" #-}
                   tcRnModule hsc_env (ms_hsc_src mod_summary) rdr_module
 
        ; msg_act tc_msgs
@@ -276,7 +285,7 @@ hscFileFrontEnd hsc_env msg_act mod_summary = do {
            -------------------
            -- DESUGAR
            -------------------
-       ; (warns, maybe_ds_result) <- _scc_ "DeSugar" 
+       ; (warns, maybe_ds_result) <- {-# SCC "DeSugar" #-}
                             deSugar hsc_env tc_result
        ; msg_act (warns, emptyBag)
        ; case maybe_ds_result of
@@ -285,19 +294,61 @@ hscFileFrontEnd hsc_env msg_act mod_summary = do {
        }}}}}
 
 ------------------------------
+
+hscFileCheck :: HscEnv -> MessageAction -> ModSummary -> IO HscResult
+hscFileCheck hsc_env msg_act mod_summary = do {
+           -------------------
+           -- PARSE
+           -------------------
+       ; let hspp_file = expectJust "hscFileFrontEnd" (ms_hspp_file mod_summary)
+             hspp_buf  = ms_hspp_buf  mod_summary
+
+       ; maybe_parsed <- myParseModule (hsc_dflags hsc_env) hspp_file hspp_buf
+
+       ; case maybe_parsed of {
+            Left err -> do { msg_act (unitBag err, emptyBag)
+                           ; return HscFail } ;
+            Right rdr_module -> do {
+
+           -------------------
+           -- RENAME and TYPECHECK
+           -------------------
+         (tc_msgs, maybe_tc_result) 
+               <- _scc_ "Typecheck-Rename" 
+                  tcRnModule hsc_env (ms_hsc_src mod_summary) rdr_module
+
+       ; msg_act tc_msgs
+       ; case maybe_tc_result of {
+            Nothing -> return (HscChecked rdr_module Nothing);
+            Just tc_result -> do
+               let md = ModDetails { 
+                               md_types   = tcg_type_env tc_result,
+                               md_exports = tcg_exports  tc_result,
+                               md_insts   = tcg_insts    tc_result,
+                               md_rules   = [panic "no rules"] }
+                                  -- rules are IdCoreRules, not the
+                                  -- RuleDecls we get out of the typechecker
+               return (HscChecked rdr_module 
+                                       (Just (tcg_binds tc_result,
+                                              tcg_rdr_env tc_result,
+                                              md)))
+       }}}}
+
+------------------------------
 hscBootBackEnd :: HscEnv -> ModSummary -> Maybe ModIface -> Maybe ModGuts -> IO HscResult
 -- For hs-boot files, there's no code generation to do
 
 hscBootBackEnd hsc_env mod_summary maybe_checked_iface Nothing 
   = return HscFail
 hscBootBackEnd hsc_env mod_summary maybe_checked_iface (Just ds_result)
-  = do { final_iface <- _scc_ "MkFinalIface" 
+  = do { final_iface <- {-# SCC "MkFinalIface" #-}
                         mkIface hsc_env (ms_location mod_summary)
                                 maybe_checked_iface ds_result
 
-       ; let { final_details = ModDetails { md_types = mg_types ds_result,
-                                            md_insts = mg_insts ds_result,
-                                            md_rules = mg_rules ds_result } }
+       ; let { final_details = ModDetails { md_types   = mg_types ds_result,
+                                            md_exports = mg_exports ds_result,
+                                            md_insts   = mg_insts ds_result,
+                                            md_rules   = mg_rules ds_result } }
          -- And the answer is ...
        ; dumpIfaceStats hsc_env
 
@@ -316,13 +367,13 @@ hscBackEnd hsc_env mod_summary maybe_checked_iface (Just ds_result)
   = do         {       -- OMITTED: 
                -- ; seqList imported_modules (return ())
 
-         let one_shot  = isOneShot (hsc_mode hsc_env)
+         let one_shot  = isOneShot (ghcMode dflags)
              dflags    = hsc_dflags hsc_env
 
            -------------------
            -- FLATTENING
            -------------------
-       ; flat_result <- _scc_ "Flattening"
+       ; flat_result <- {-# SCC "Flattening" #-}
                         flatten hsc_env ds_result
 
 
@@ -352,13 +403,13 @@ hscBackEnd hsc_env mod_summary maybe_checked_iface (Just ds_result)
            -------------------
            -- SIMPLIFY
            -------------------
-       ; simpl_result <- _scc_ "Core2Core"
+       ; simpl_result <- {-# SCC "Core2Core" #-}
                          core2core hsc_env flat_result
 
            -------------------
            -- TIDY
            -------------------
-       ; tidy_result <- _scc_ "CoreTidy"
+       ; tidy_result <- {-# SCC "CoreTidy" #-}
                         tidyCorePgm hsc_env simpl_result
 
        -- Emit external core
@@ -374,7 +425,7 @@ hscBackEnd hsc_env mod_summary maybe_checked_iface (Just ds_result)
            -- This has to happen *after* code gen so that the back-end
            -- info has been set.  Not yet clear if it matters waiting
            -- until after code output
-       ; new_iface <- _scc_ "MkFinalIface" 
+       ; new_iface <- {-# SCC "MkFinalIface" #-}
                        mkIface hsc_env (ms_location mod_summary)
                                maybe_checked_iface tidy_result
 
@@ -390,9 +441,10 @@ hscBackEnd hsc_env mod_summary maybe_checked_iface (Just ds_result)
        ; final_details <- 
             if one_shot then return (error "no final details")
                         else return $! ModDetails { 
-                                          md_types = mg_types tidy_result,
-                                          md_insts = mg_insts tidy_result,
-                                          md_rules = mg_rules tidy_result }
+                                          md_types   = mg_types tidy_result,
+                                          md_exports = mg_exports tidy_result,
+                                          md_insts   = mg_insts tidy_result,
+                                          md_rules   = mg_rules tidy_result }
 
            -------------------
            -- CONVERT TO STG and COMPLETE CODE GENERATION
@@ -409,44 +461,6 @@ hscBackEnd hsc_env mod_summary maybe_checked_iface (Just ds_result)
         }
 
 
-hscFileCheck hsc_env msg_act hspp_file = do {
-           -------------------
-           -- PARSE
-           -------------------
-       ; maybe_parsed <- myParseModule (hsc_dflags hsc_env)  hspp_file Nothing
-
-       ; case maybe_parsed of {
-            Left err -> do { msg_act (unitBag err, emptyBag) ;
-                           ; return HscFail ;
-                           };
-            Right rdr_module -> hscBufferTypecheck hsc_env rdr_module msg_act
-       }}
-
-
--- Perform static/dynamic checks on the source code in a StringBuffer
--- This is a temporary solution: it'll read in interface files lazily, whereas
--- we probably want to use the compilation manager to load in all the modules
--- in a project.
-hscBufferCheck :: HscEnv -> StringBuffer -> MessageAction -> IO HscResult
-hscBufferCheck hsc_env buffer msg_act = do
-       let loc  = mkSrcLoc (mkFastString "*edit*") 1 0
-        showPass (hsc_dflags hsc_env) "Parser"
-       case unP parseModule (mkPState buffer loc (hsc_dflags hsc_env)) of
-               PFailed span err -> do
-                  msg_act (emptyBag, unitBag (mkPlainErrMsg span err))
-                  return HscFail
-               POk _ rdr_module -> do
-                  hscBufferTypecheck hsc_env rdr_module msg_act
-
-hscBufferTypecheck hsc_env rdr_module msg_act = do
-       (tc_msgs, maybe_tc_result) <- _scc_ "Typecheck-Rename" 
-                                       tcRnModule hsc_env HsSrcFile rdr_module
-       msg_act tc_msgs
-       case maybe_tc_result of
-           Nothing  -> return (HscChecked rdr_module Nothing)
-                               -- space leak on rdr_module!
-           Just r -> return (HscChecked rdr_module (Just r))
-
 
 hscCodeGen dflags 
     ModGuts{  -- This is the last use of the ModGuts in a compilation.
@@ -461,10 +475,10 @@ hscCodeGen dflags
            -------------------
            -- PREPARE FOR CODE GENERATION
            -- Do saturation and convert to A-normal form
-  prepd_binds <- _scc_ "CorePrep"
+  prepd_binds <- {-# SCC "CorePrep" #-}
                 corePrepPgm dflags core_binds type_env;
 
-  case dopt_HscTarget dflags of
+  case hscTarget dflags of
       HscNothing -> return (False, False, Nothing)
 
       HscInterpreted ->
@@ -484,11 +498,11 @@ hscCodeGen dflags
       other ->
        do
            -----------------  Convert to STG ------------------
-           (stg_binds, cost_centre_info) <- _scc_ "CoreToStg"
+           (stg_binds, cost_centre_info) <- {-# SCC "CoreToStg" #-}
                         myCoreToStg dflags this_mod prepd_binds        
 
             ------------------  Code generation ------------------
-           abstractC <- _scc_ "CodeGen"
+           abstractC <- {-# SCC "CodeGen" #-}
                         codeGen dflags this_mod type_env foreign_stubs
                                 dir_imps cost_centre_info stg_binds
 
@@ -514,9 +528,9 @@ hscCmmFile dflags filename = do
 
 
 myParseModule dflags src_filename maybe_src_buf
- = do --------------------------  Parser  ----------------
-      showPass dflags "Parser"
-      _scc_  "Parser" do
+ =    --------------------------  Parser  ----------------
+      showPass dflags "Parser" >>
+      {-# SCC "Parser" #-} do
 
        -- sometimes we already have the buffer in memory, perhaps
        -- because we needed to parse the imports out of it, or get the 
@@ -545,10 +559,10 @@ myParseModule dflags src_filename maybe_src_buf
 
 myCoreToStg dflags this_mod prepd_binds
  = do 
-      stg_binds <- _scc_ "Core2Stg" 
+      stg_binds <- {-# SCC "Core2Stg" #-}
             coreToStg dflags prepd_binds
 
-      (stg_binds2, cost_centre_info) <- _scc_ "Core2Stg" 
+      (stg_binds2, cost_centre_info) <- {-# SCC "Core2Stg" #-}
             stg2stg dflags this_mod stg_binds
 
       return (stg_binds2, cost_centre_info)
@@ -591,11 +605,10 @@ A naked expression returns a singleton Name [it].
 #ifdef GHCI
 hscStmt                -- Compile a stmt all the way to an HValue, but don't run it
   :: HscEnv
-  -> InteractiveContext                -- Context for compiling
   -> String                    -- The statement
-  -> IO (Maybe (InteractiveContext, [Name], HValue))
+  -> IO (Maybe (HscEnv, [Name], HValue))
 
-hscStmt hsc_env icontext stmt
+hscStmt hsc_env stmt
   = do { maybe_stmt <- hscParseStmt (hsc_dflags hsc_env) stmt
        ; case maybe_stmt of {
             Nothing      -> return Nothing ;   -- Parse error
@@ -603,8 +616,8 @@ hscStmt hsc_env icontext stmt
             Just (Just parsed_stmt) -> do {    -- The real stuff
 
                -- Rename and typecheck it
-         maybe_tc_result
-                <- tcRnStmt hsc_env icontext parsed_stmt
+         let icontext = hsc_IC hsc_env
+       ; maybe_tc_result <- tcRnStmt hsc_env icontext parsed_stmt
 
        ; case maybe_tc_result of {
                Nothing -> return Nothing ;
@@ -616,20 +629,20 @@ hscStmt hsc_env icontext stmt
                              (ic_type_env new_ic)
                              tc_expr
 
-       ; return (Just (new_ic, bound_names, hval))
+       ; return (Just (hsc_env{ hsc_IC=new_ic }, bound_names, hval))
        }}}}}
 
 hscTcExpr      -- Typecheck an expression (but don't run it)
   :: HscEnv
-  -> InteractiveContext                -- Context for compiling
   -> String                    -- The expression
   -> IO (Maybe Type)
 
-hscTcExpr hsc_env icontext expr
+hscTcExpr hsc_env expr
   = do { maybe_stmt <- hscParseStmt (hsc_dflags hsc_env) expr
+       ; let icontext = hsc_IC hsc_env
        ; case maybe_stmt of {
             Nothing      -> return Nothing ;   -- Parse error
-            Just (Just (L _ (ExprStmt expr _)))
+            Just (Just (L _ (ExprStmt expr _ _)))
                        -> tcRnExpr hsc_env icontext expr ;
             Just other -> do { errorMsg ("not an expression: `" ++ expr ++ "'") ;
                                return Nothing } ;
@@ -637,17 +650,18 @@ hscTcExpr hsc_env icontext expr
 
 hscKcType      -- Find the kind of a type
   :: HscEnv
-  -> InteractiveContext                -- Context for compiling
   -> String                    -- The type
   -> IO (Maybe Kind)
 
-hscKcType hsc_env icontext str
+hscKcType hsc_env str
   = do { maybe_type <- hscParseType (hsc_dflags hsc_env) str
+       ; let icontext = hsc_IC hsc_env
        ; case maybe_type of {
             Just ty    -> tcRnType hsc_env icontext ty ;
             Just other -> do { errorMsg ("not an type: `" ++ str ++ "'") ;
                                return Nothing } ;
             Nothing    -> return Nothing } }
+#endif
 \end{code}
 
 \begin{code}
@@ -667,8 +681,8 @@ hscParseThing :: Outputable thing
        -- Nothing => Parse error (message already printed)
        -- Just x  => success
 hscParseThing parser dflags str
- = do showPass dflags "Parser"
-      _scc_ "Parser"  do
+ = showPass dflags "Parser" >>
+      {-# SCC "Parser" #-} do
 
       buf <- stringToStringBuffer str
 
@@ -686,7 +700,6 @@ hscParseThing parser dflags str
       dumpIfSet_dyn dflags Opt_D_dump_parsed "Parser" (ppr thing);
       return (Just thing)
       }}
-#endif
 \end{code}
 
 %************************************************************************
@@ -697,30 +710,23 @@ hscParseThing parser dflags str
 
 \begin{code}
 #ifdef GHCI
-type GetInfoResult = (String, (IfaceDecl, Fixity, SrcLoc, [(IfaceInst,SrcLoc)]))
-
 hscGetInfo -- like hscStmt, but deals with a single identifier
   :: HscEnv
-  -> InteractiveContext                -- Context for compiling
   -> String                    -- The identifier
   -> IO [GetInfoResult]
 
-hscGetInfo hsc_env ic str
+hscGetInfo hsc_env str
    = do maybe_rdr_name <- hscParseIdentifier (hsc_dflags hsc_env) str
        case maybe_rdr_name of {
          Nothing -> return [];
          Just (L _ rdr_name) -> do
 
-       maybe_tc_result <- tcRnGetInfo hsc_env ic rdr_name
-
-       let     -- str' is the the naked occurrence name
-               -- after stripping off qualification and parens (+)
-          str' = occNameUserString (rdrNameOcc rdr_name)
+       maybe_tc_result <- tcRnGetInfo hsc_env (hsc_IC hsc_env) rdr_name
 
-       case maybe_tc_result of {
-            Nothing     -> return [] ;
-            Just things -> return [(str', t) | t <- things]
-       }}
+       case maybe_tc_result of
+            Nothing     -> return []
+            Just things -> return things
+       }
 #endif
 \end{code}