[project @ 2000-11-21 14:31:58 by simonmar]
[ghc-hetmet.git] / ghc / compiler / main / HscMain.lhs
index 74c7a87..34917d3 100644 (file)
@@ -9,17 +9,18 @@ module HscMain ( HscResult(..), hscMain, hscExpr,
 
 #include "HsVersions.h"
 
-import Maybe           ( isJust )
-import IO              ( hPutStrLn, stderr )
+#ifdef GHCI
+import RdrHsSyn                ( RdrNameHsExpr )
+import CoreToStg       ( coreToStgExpr )
+import StringBuffer    ( stringToStringBuffer, freeStringBuffer )
+#endif
+
 import HsSyn
 
-import StringBuffer    ( hGetStringBuffer, 
-                         stringToStringBuffer, freeStringBuffer )
+import StringBuffer    ( hGetStringBuffer )
 import Parser
-import RdrHsSyn                ( RdrNameHsExpr )
 import Lex             ( PState(..), ParseResult(..) )
 import SrcLoc          ( mkSrcLoc )
-
 import Rename
 import Rules           ( emptyRuleBase )
 import PrelInfo                ( wiredInThingEnv, wiredInThings )
@@ -33,16 +34,18 @@ import SimplCore
 import OccurAnal       ( occurAnalyseBinds )
 import CoreUtils       ( coreBindsSize )
 import CoreTidy                ( tidyCorePgm )
-import CoreToStg       ( topCoreBindsToStg, coreToStgExpr )
+import CoreToStg       ( topCoreBindsToStg )
 import StgSyn          ( collectFinalStgBinders )
 import SimplStg                ( stg2stg )
 import CodeGen         ( codeGen )
 import CodeOutput      ( codeOutput )
 
-import Module          ( ModuleName, moduleName, mkModuleInThisPackage )
+import Module          ( ModuleName, moduleName, mkHomeModule )
 import CmdLineOpts
 import ErrUtils                ( dumpIfSet_dyn, showPass )
 import Util            ( unJust )
+import Unique          ( Uniquable(..) )
+import PrelNames       ( ioTyConKey )
 import UniqSupply      ( mkSplitUniqSupply )
 
 import Bag             ( emptyBag )
@@ -55,6 +58,7 @@ import HscTypes               ( ModDetails, ModIface(..), PersistentCompilerState(..),
                          HomeSymbolTable, 
                          OrigNameEnv(..), PackageRuleBase, HomeIfaceTable, 
                          typeEnvClasses, typeEnvTyCons, emptyIfaceTable )
+import Type            ( splitTyConApp_maybe )
 import FiniteMap       ( FiniteMap, plusFM, emptyFM, addToFM )
 import OccName         ( OccName )
 import Name            ( Name, nameModule, nameOccName, getName  )
@@ -62,6 +66,8 @@ import Name           ( emptyNameEnv )
 import Module          ( Module, lookupModuleEnvByName )
 
 import Monad           ( when )
+import Maybe           ( isJust )
+import IO              ( hPutStrLn, stderr )
 \end{code}
 
 
@@ -73,14 +79,21 @@ import Monad                ( when )
 
 \begin{code}
 data HscResult
-   = HscOK   ModDetails             -- new details (HomeSymbolTable additions)
-            (Maybe ModIface)        -- new iface (if any compilation was done)
-            (Maybe String)          -- generated stub_h filename (in /tmp)
-            (Maybe String)          -- generated stub_c filename (in /tmp)
-            (Maybe ([UnlinkedIBind],ItblEnv)) -- interpreted code, if any
-             PersistentCompilerState -- updated PCS
-
-   | HscFail PersistentCompilerState -- updated PCS
+   -- compilation failed
+   = HscFail     PersistentCompilerState -- updated PCS
+   -- concluded that it wasn't necessary
+   | HscNoRecomp PersistentCompilerState -- updated PCS
+                 ModDetails             -- new details (HomeSymbolTable additions)
+                ModIface                -- new iface (if any compilation was done)
+   -- did recompilation
+   | HscRecomp   PersistentCompilerState -- updated PCS
+                 ModDetails             -- new details (HomeSymbolTable additions)
+                 ModIface               -- new iface (if any compilation was done)
+                (Maybe String)          -- generated stub_h filename (in /tmp)
+                (Maybe String)          -- generated stub_c filename (in /tmp)
+                (Maybe ([UnlinkedIBind],ItblEnv)) -- interpreted code, if any
+             
+
        -- no errors or warnings; the individual passes
        -- (parse/rename/typecheck) print messages themselves
 
@@ -103,7 +116,7 @@ hscMain ghci_mode dflags source_unchanged location maybe_old_iface hst hit pcs
 
       (pcs_ch, errs_found, (recomp_reqd, maybe_checked_iface))
          <- checkOldIface dflags hit hst pcs 
-               (unJust (ml_hi_file location) "hscMain")
+               (unJust "hscMain" (ml_hi_file location))
                source_unchanged maybe_old_iface;
 
       if errs_found then
@@ -122,16 +135,11 @@ hscMain ghci_mode dflags source_unchanged location maybe_old_iface hst hit pcs
 -- we definitely expect to have the old interface available
 hscNoRecomp ghci_mode dflags location (Just old_iface) hst hit pcs_ch
  | ghci_mode == OneShot
- = return (HscOK
-           (panic "hscNoRecomp:OneShot") -- no details
-           Nothing -- makes run_phase Hsc stop
-           Nothing Nothing -- foreign export stuff
-           Nothing -- ibinds
-           pcs_ch)
+ = let bomb = panic "hscNoRecomp:OneShot"
+   in  return (HscNoRecomp pcs_ch bomb bomb)
  | otherwise
  = do {
-      hPutStrLn stderr "COMPILATION NOT REQUIRED";
-      let this_mod = mi_module old_iface
+      hPutStrLn stderr "compilation not required";
       ;
       -- CLOSURE
       (pcs_cl, closure_errs, cl_hs_decls) 
@@ -154,17 +162,13 @@ hscNoRecomp ghci_mode dflags location (Just old_iface) hst hit pcs_ch
       -- create a new details from the closed, typechecked, old iface
       let new_details = mkModDetailsFromIface env_tc local_insts local_rules
       ;
-      return (HscOK new_details
-                   Nothing -- tells CM to use old iface and linkables
-                   Nothing Nothing -- foreign export stuff
-                    Nothing -- ibinds
-                   pcs_tc)
+      return (HscNoRecomp pcs_tc new_details old_iface)
       }}}}
 
 
 hscRecomp ghci_mode dflags location maybe_checked_iface hst hit pcs_ch
  = do  {
-       ; hPutStrLn stderr "COMPILATION IS REQUIRED";
+       ; hPutStrLn stderr "compilation IS required";
 
          -- what target are we shooting for?
        ; let toInterp = dopt_HscLang dflags == HscInterpreted
@@ -172,12 +176,12 @@ hscRecomp ghci_mode dflags location maybe_checked_iface hst hit pcs_ch
            -------------------
            -- PARSE
            -------------------
-       ; maybe_parsed <- myParseModule dflags (unJust (ml_hspp_file location) 
-                                                       "hscRecomp:hspp")
+       ; maybe_parsed <- myParseModule dflags 
+                             (unJust "hscRecomp:hspp" (ml_hspp_file location))
        ; case maybe_parsed of {
             Nothing -> return (HscFail pcs_ch);
             Just rdr_module -> do {
-       ; let this_mod = mkModuleInThisPackage (hsModuleName rdr_module)
+       ; let this_mod = mkHomeModule (hsModuleName rdr_module)
     
            -------------------
            -- RENAME
@@ -223,8 +227,8 @@ hscRecomp ghci_mode dflags location maybe_checked_iface hst hit pcs_ch
            -------------------
        ; let new_details = mkModDetails env_tc local_insts tidy_binds 
                                         top_level_ids orphan_rules
-       ; final_iface <- mkFinalIface dflags location maybe_checked_iface 
-                                     new_iface new_details
+       ; final_iface <- mkFinalIface ghci_mode dflags location 
+                                      maybe_checked_iface new_iface new_details
 
            -------------------
            -- COMPLETE CODE GENERATION
@@ -236,14 +240,14 @@ hscRecomp ghci_mode dflags location maybe_checked_iface hst hit pcs_ch
                   hit (pcs_PIT pcs_tc)       
 
          -- and the answer is ...
-       ; return (HscOK new_details (Just final_iface)
-                       maybe_stub_h_filename maybe_stub_c_filename
-                       maybe_ibinds pcs_tc)
+       ; return (HscRecomp pcs_tc new_details final_iface
+                            maybe_stub_h_filename maybe_stub_c_filename
+                           maybe_ibinds)
          }}}}}}}
 
 
 
-mkFinalIface dflags location maybe_old_iface new_iface new_details
+mkFinalIface ghci_mode 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 when (dopt Opt_D_dump_hi_diffs dflags)
@@ -252,10 +256,14 @@ mkFinalIface dflags location maybe_old_iface new_iface new_details
                              "UNCHANGED FINAL INTERFACE" (pprIface new_iface)
               return new_iface
       (new_iface, Just sdoc_diffs)
-         -> do dumpIfSet_dyn dflags Opt_D_dump_hi_diffs "INTERFACE HAS CHANGED" sdoc_diffs
-               dumpIfSet_dyn dflags Opt_D_dump_hi "NEW FINAL INTERFACE" (pprIface new_iface)
+         -> do dumpIfSet_dyn dflags Opt_D_dump_hi_diffs "INTERFACE HAS CHANGED" 
+                                    sdoc_diffs
+               dumpIfSet_dyn dflags Opt_D_dump_hi "NEW FINAL INTERFACE" 
+                                    (pprIface new_iface)
                -- Write the interface file
-               writeIface (unJust (ml_hi_file location) "hscRecomp:hi") new_iface
+               when (ghci_mode /= Interactive) 
+                    (writeIface (unJust "hscRecomp:hi" (ml_hi_file location))
+                                new_iface)
                return new_iface
 
 
@@ -387,6 +395,11 @@ hscExpr
   -> String                    -- The expression
   -> IO ( PersistentCompilerState, Maybe UnlinkedIExpr )
 
+#ifndef GHCI
+hscExpr dflags hst hit pcs this_module expr
+  = panic "hscExpr: non-interactive build"
+#else 
+
 hscExpr dflags hst hit pcs0 this_module expr
   = do {       -- Parse it
        maybe_parsed <- hscParseExpr dflags expr;
@@ -402,17 +415,28 @@ hscExpr dflags hst hit pcs0 this_module expr
                Just (print_unqual, rn_expr) -> do {
 
                -- Typecheck it
-       maybe_tc_expr <- typecheckExpr dflags pcs1 hst print_unqual rn_expr;
-       case maybe_tc_expr of
+       maybe_tc_return
+          <- typecheckExpr dflags pcs1 hst print_unqual this_module rn_expr;
+       case maybe_tc_return of
                Nothing -> return (pcs1, Nothing)
-               Just tc_expr -> do {
+               Just (pcs2, tc_expr, ty) -> do {
+
+       let { is_IO_type = case splitTyConApp_maybe ty of {
+                           Just (tycon, _) -> getUnique tycon == ioTyConKey;
+                           Nothing -> False }
+            };
+
+        if (not is_IO_type)
+               then hscExpr dflags hst hit pcs2 this_module 
+                       ("print (" ++ expr ++ ")")
+               else do
 
                -- Desugar it
-       ds_expr <- deSugarExpr dflags pcs1 hst this_module 
+       ds_expr <- deSugarExpr dflags pcs2 hst this_module
                        print_unqual tc_expr;
        
                -- Simplify it
-       simpl_expr <- simplifyExpr dflags pcs1 hst ds_expr;
+       simpl_expr <- simplifyExpr dflags pcs2 hst ds_expr;
 
                -- Convert to STG
        stg_expr <- coreToStgExpr dflags simpl_expr;
@@ -422,7 +446,7 @@ hscExpr dflags hst hit pcs0 this_module expr
                -- Convert to InterpSyn
        unlinked_iexpr <- stgExprToInterpSyn dflags stg_expr;
 
-       return (pcs1, Just unlinked_iexpr);
+       return (pcs2, Just unlinked_iexpr);
      }}}}
 
 hscParseExpr :: DynFlags -> String -> IO (Maybe RdrNameHsExpr)
@@ -437,25 +461,25 @@ hscParseExpr dflags str
       -- of the string...)
       let glaexts = 1#
       --let glaexts | dopt Opt_GlasgowExts dflags = 1#
-      --                 | otherwise                   = 0#
+      --           | otherwise                   = 0#
 
       case parse buf PState{ bol = 0#, atbol = 1#,
                             context = [], glasgow_exts = glaexts,
                             loc = mkSrcLoc SLIT("<no file>") 0 } of {
 
-       PFailed err -> do { freeStringBuffer buf
-                         ; hPutStrLn stderr (showSDoc err)
-                          ; return Nothing };
+       PFailed err -> do { freeStringBuffer buf;
+                           hPutStrLn stderr (showSDoc err);
+                            return Nothing };
 
        POk _ (PExpr rdr_expr) -> do {
 
-      -- ToDo:
-      -- freeStringBuffer buf;
-
+      --ToDo: can't free the string buffer until we've finished this
+      -- compilation sweep and all the identifiers have gone away.
+      --freeStringBuffer buf;
       dumpIfSet_dyn dflags Opt_D_dump_parsed "Parser" (ppr rdr_expr);
-      
       return (Just rdr_expr)
       }}
+#endif
 \end{code}
 
 %************************************************************************