Cmm back end upgrades
[ghc-hetmet.git] / compiler / main / GHC.hs
index 85ecf58..3b8f51e 100644 (file)
@@ -41,7 +41,8 @@ module GHC (
        workingDirectoryChanged,
        checkModule, checkAndLoadModule, CheckedModule(..),
        TypecheckedSource, ParsedSource, RenamedSource,
-        compileToCore, compileToCoreModule,
+        compileToCore, compileToCoreModule, compileToCoreSimplified,
+        compileCoreToObj,
 
        -- * Parsing Haddock comments
        parseHaddockComment,
@@ -74,6 +75,7 @@ module GHC (
        setContext, getContext, 
        getNamesInScope,
        getRdrNamesInScope,
+        getGRE,
        moduleIsInterpreted,
        getInfo,
        exprType,
@@ -92,7 +94,7 @@ module GHC (
         InteractiveEval.forward,
        showModule,
         isModuleInterpreted,
-       compileExpr, HValue, dynCompileExpr,
+       InteractiveEval.compileExpr, HValue, dynCompileExpr,
        lookupName,
         GHC.obtainTerm, GHC.obtainTerm1, GHC.obtainTermB, reconstructType,
         modInfoModBreaks,
@@ -216,7 +218,8 @@ import TcRnMonad        ( initIfaceCheck )
 import Packages
 import NameSet
 import RdrName
-import HsSyn 
+import qualified HsSyn -- hack as we want to reexport the whole module
+import HsSyn hiding ((<.>))
 import Type             hiding (typeKind)
 import TcType           hiding (typeKind)
 import Id
@@ -228,21 +231,24 @@ import FunDeps
 import DataCon
 import Name             hiding ( varName )
 import OccName         ( parenSymOcc )
-import InstEnv         ( Instance, instanceDFunId, pprInstance, pprInstanceHdr )
+import InstEnv         ( Instance, instanceDFunId, pprInstance, pprInstanceHdr,
+                          emptyInstEnv )
+import FamInstEnv       ( emptyFamInstEnv )
 import SrcLoc
 import CoreSyn
+import TidyPgm
 import DriverPipeline
 import DriverPhases    ( HscSource(..), Phase(..), isHaskellSrcFilename, startPhase )
 import HeaderInfo      ( getImports, getOptions )
 import Finder
-import HscMain          hiding (compileExpr)
+import HscMain
 import HscTypes
 import DynFlags
 import StaticFlags
 import SysTools     ( initSysTools, cleanTempFiles, cleanTempFilesExcept,
                       cleanTempDirs )
 import Module
-import UniqFM
+import LazyUniqFM
 import UniqSet
 import Unique
 import FiniteMap
@@ -260,17 +266,20 @@ import BasicTypes
 import Maybes          ( expectJust, mapCatMaybes )
 import HaddockParse
 import HaddockLex       ( tokenise )
+import FastString
 
 import Control.Concurrent
-import System.Directory ( getModificationTime, doesFileExist )
+import System.Directory ( getModificationTime, doesFileExist,
+                          getCurrentDirectory )
 import Data.Maybe
 import Data.List
 import qualified Data.List as List
 import Control.Monad
 import System.Exit     ( exitWith, ExitCode(..) )
-import System.Time     ( ClockTime )
+import System.Time     ( ClockTime, getClockTime )
 import Control.Exception as Exception hiding (handle)
 import Data.IORef
+import System.FilePath
 import System.IO
 import System.IO.Error ( try, isDoesNotExistError )
 import Prelude hiding (init)
@@ -389,7 +398,7 @@ guessOutputFile s = modifySession s $ \env ->
             let isMain = (== mainModIs dflags) . ms_mod
             [ms] <- return (filter isMain mod_graph)
             ml_hs_file (ms_location ms)
-        guessedName = fmap basenameOf mainModuleSrcPath
+        guessedName = fmap dropExtension mainModuleSrcPath
     in
     case outputFile dflags of
         Just _ -> env
@@ -450,8 +459,8 @@ guessTarget file Nothing
           else do
        return (Target (TargetModule (mkModuleName file)) Nothing)
      where 
-        hs_file  = file `joinFileExt` "hs"
-        lhs_file = file `joinFileExt` "lhs"
+        hs_file  = file <.> "hs"
+        lhs_file = file <.> "lhs"
 
 -- -----------------------------------------------------------------------------
 -- Extending the program scope
@@ -482,7 +491,10 @@ setGlobalTypeScope session ids
 -- Parsing Haddock comments
 
 parseHaddockComment :: String -> Either String (HsDoc RdrName)
-parseHaddockComment string = parseHaddockParagraphs (tokenise string)
+parseHaddockComment string = 
+  case parseHaddockParagraphs (tokenise string) of
+    MyLeft x  -> Left x
+    MyRight x -> Right x
 
 -- -----------------------------------------------------------------------------
 -- Loading the program
@@ -773,7 +785,7 @@ data CheckedModule =
                  renamedSource     :: Maybe RenamedSource,
                  typecheckedSource :: Maybe TypecheckedSource,
                  checkedModuleInfo :: Maybe ModuleInfo,
-                  coreModule        :: Maybe CoreModule
+                  coreModule        :: Maybe ModGuts
                }
        -- ToDo: improvements that could be made here:
        --  if the module succeeded renaming but not typechecking,
@@ -863,12 +875,6 @@ checkModule_ ref ms compile_to_core load
                                  then deSugarModule hsc_env ms tcg
                                  else return Nothing              
 
-                   let mb_core = fmap (\ mg ->
-                                        CoreModule { cm_module = mg_module mg,
-                                                     cm_types  = mg_types mg,
-                                                     cm_binds  = mg_binds mg })
-                                    mb_guts
-
                    -- If we are loading this module so that we can typecheck
                    -- dependent modules, generate an interface and stuff it
                    -- all in the HomePackageTable.
@@ -886,7 +892,7 @@ checkModule_ ref ms compile_to_core load
                                        renamedSource = rn_info,
                                        typecheckedSource = Just tc_binds,
                                        checkedModuleInfo = Just minf,
-                                        coreModule = mb_core }))
+                                        coreModule = mb_guts }))
 
 -- | This is the way to get access to the Core bindings corresponding
 -- to a module. 'compileToCore' invokes 'checkModule' to parse, typecheck, and
@@ -894,7 +900,90 @@ checkModule_ ref ms compile_to_core load
 -- the module name, type declarations, and function declarations) if
 -- successful.
 compileToCoreModule :: Session -> FilePath -> IO (Maybe CoreModule)
-compileToCoreModule session fn = do
+compileToCoreModule = compileCore False
+
+-- | Like compileToCoreModule, but invokes the simplifier, so
+-- as to return simplified and tidied Core.
+compileToCoreSimplified :: Session -> FilePath -> IO (Maybe CoreModule)
+compileToCoreSimplified = compileCore True
+
+-- | Provided for backwards-compatibility: compileToCore returns just the Core
+-- bindings, but for most purposes, you probably want to call
+-- compileToCoreModule.
+compileToCore :: Session -> FilePath -> IO (Maybe [CoreBind])
+compileToCore session fn = do
+   maybeCoreModule <- compileToCoreModule session fn
+   return $ fmap cm_binds maybeCoreModule
+
+-- | Takes a CoreModule and compiles the bindings therein
+-- to object code. The first argument is a bool flag indicating
+-- whether to run the simplifier.
+-- The resulting .o, .hi, and executable files, if any, are stored in the
+-- current directory, and named according to the module name.
+-- Returns True iff compilation succeeded.
+-- This has only so far been tested with a single self-contained module.
+compileCoreToObj :: Bool -> Session -> CoreModule -> IO Bool
+compileCoreToObj simplify session cm@(CoreModule{ cm_module = mName }) = do
+  hscEnv      <- sessionHscEnv session
+  dflags      <- getSessionDynFlags session
+  currentTime <- getClockTime
+  cwd         <- getCurrentDirectory
+  modLocation <- mkHiOnlyModLocation dflags (hiSuf dflags) cwd
+                   ((moduleNameSlashes . moduleName) mName)
+
+  let modSummary = ModSummary { ms_mod = mName,
+         ms_hsc_src = ExtCoreFile,
+         ms_location = modLocation,
+         -- By setting the object file timestamp to Nothing,
+         -- we always force recompilation, which is what we
+         -- want. (Thus it doesn't matter what the timestamp
+         -- for the (nonexistent) source file is.)
+         ms_hs_date = currentTime,
+         ms_obj_date = Nothing,
+         -- Only handling the single-module case for now, so no imports.
+         ms_srcimps = [],
+         ms_imps = [],
+         -- No source file
+         ms_hspp_file = "",
+         ms_hspp_opts = dflags,
+         ms_hspp_buf = Nothing
+      }
+
+  mbHscResult <- evalComp
+     ((if simplify then hscSimplify else return) (mkModGuts cm)
+     >>= hscNormalIface >>= hscWriteIface >>= hscOneShot)
+     (CompState{ compHscEnv=hscEnv,
+                 compModSummary=modSummary,
+                 compOldIface=Nothing})
+  return $ isJust mbHscResult
+
+-- Makes a "vanilla" ModGuts.
+mkModGuts :: CoreModule -> ModGuts
+mkModGuts coreModule = ModGuts {
+  mg_module = cm_module coreModule,
+  mg_boot = False,
+  mg_exports = [],
+  mg_deps = noDependencies,
+  mg_dir_imps = emptyModuleEnv,
+  mg_used_names = emptyNameSet,
+  mg_rdr_env = emptyGlobalRdrEnv,
+  mg_fix_env = emptyFixityEnv,
+  mg_types = emptyTypeEnv,
+  mg_insts = [],
+  mg_fam_insts = [],
+  mg_rules = [],
+  mg_binds = cm_binds coreModule,
+  mg_foreign = NoStubs,
+  mg_deprecs = NoDeprecs,
+  mg_hpc_info = emptyHpcInfo False,
+  mg_modBreaks = emptyModBreaks,
+  mg_vect_info = noVectInfo,
+  mg_inst_env = emptyInstEnv,
+  mg_fam_inst_env = emptyFamInstEnv
+}
+
+compileCore :: Bool -> Session -> FilePath -> IO (Maybe CoreModule)
+compileCore simplify session fn = do
    -- First, set the target to the desired filename
    target <- guessTarget fn Nothing
    addTarget session target
@@ -912,17 +1001,34 @@ compileToCoreModule session fn = do
            maybeCheckedModule <- checkModule session mod True
            case maybeCheckedModule of
              Nothing -> return Nothing 
-             Just checkedMod -> return $ coreModule checkedMod
+             Just checkedMod -> (liftM $ fmap gutsToCoreModule) $
+                                case (coreModule checkedMod) of
+                                  Just mg | simplify -> (sessionHscEnv session)
+                                  -- If simplify is true: simplify (hscSimplify),
+                                  -- then tidy (tidyProgram).
+                                   >>= \ hscEnv -> evalComp (hscSimplify mg)
+                                         (CompState{ compHscEnv=hscEnv,
+                                                     compModSummary=modSummary,
+                                                     compOldIface=Nothing})
+                                          >>= (tidyProgram hscEnv)
+                                          >>= (return . Just . Left)
+                                  Just guts -> return $ Just $ Right guts
+                                  Nothing   -> return Nothing
          Nothing -> panic "compileToCoreModule: target FilePath not found in\
                            module dependency graph"
+  where -- two versions, based on whether we simplify (thus run tidyProgram,
+        -- which returns a (CgGuts, ModDetails) pair, or not (in which case
+        -- we just have a ModGuts.
+        gutsToCoreModule :: Either (CgGuts, ModDetails) ModGuts -> CoreModule
+        gutsToCoreModule (Left (cg, md))  = CoreModule {
+          cm_module = cg_module cg,    cm_types = md_types md,
+          cm_imports = cg_dir_imps cg, cm_binds = cg_binds cg
+        }
+        gutsToCoreModule (Right mg) = CoreModule {
+          cm_module  = mg_module mg,                   cm_types   = mg_types mg,
+          cm_imports = moduleEnvKeys (mg_dir_imps mg), cm_binds   = mg_binds mg
+         }
 
--- | Provided for backwards-compatibility: compileToCore returns just the Core
--- bindings, but for most purposes, you probably want to call
--- compileToCoreModule.
-compileToCore :: Session -> FilePath -> IO (Maybe [CoreBind])
-compileToCore session fn = do
-   maybeCoreModule <- compileToCoreModule session fn
-   return $ fmap cm_binds maybeCoreModule
 -- ---------------------------------------------------------------------------
 -- Unloading
 
@@ -1149,7 +1255,7 @@ upsweep hsc_env old_hpt stable_mods cleanup sccs = do
        cleanup         -- Remove unwanted tmp files between compilations
 
         case mb_mod_info of
-           Nothing -> return (Failed, hsc_env, [])
+           Nothing -> return (Failed, hsc_env, done)
            Just mod_info -> do 
                let this_mod = ms_mod_name mod
 
@@ -1500,7 +1606,7 @@ warnUnnecessarySourceImports dflags sccs =
        warn :: Located ModuleName -> WarnMsg
        warn (L loc mod) = 
           mkPlainErrMsg loc
-               (ptext SLIT("Warning: {-# SOURCE #-} unnecessary in import of ")
+               (ptext (sLit "Warning: {-# SOURCE #-} unnecessary in import of ")
                 <+> quotes (ppr mod))
 
 -----------------------------------------------------------------------------
@@ -1557,7 +1663,7 @@ downsweep hsc_env old_summaries excl_mods allow_dup_roots
                   Nothing -> packageModErr modl
                   Just s  -> return s
 
-       rootLoc = mkGeneralSrcSpan FSLIT("<command line>")
+       rootLoc = mkGeneralSrcSpan (fsLit "<command line>")
 
        -- In a root module, the filename is allowed to diverge from the module
        -- name, so we have to check that there aren't multiple root files
@@ -1666,7 +1772,7 @@ summariseFile hsc_env old_summaries file mb_phase maybe_buf
        let dflags = hsc_dflags hsc_env
 
        (dflags', hspp_fn, buf)
-           <- preprocessFile dflags file mb_phase maybe_buf
+           <- preprocessFile hsc_env file mb_phase maybe_buf
 
         (srcimps,the_imps, L _ mod_name) <- getImports dflags' buf hspp_fn file
 
@@ -1787,13 +1893,14 @@ summariseModule hsc_env old_summary_map is_boot (L loc wanted_mod) maybe_buf exc
       = do
        -- Preprocess the source file and get its imports
        -- The dflags' contains the OPTIONS pragmas
-       (dflags', hspp_fn, buf) <- preprocessFile dflags src_fn Nothing maybe_buf
+       (dflags', hspp_fn, buf) <- preprocessFile hsc_env src_fn Nothing maybe_buf
         (srcimps, the_imps, L mod_loc mod_name) <- getImports dflags' buf hspp_fn src_fn
 
        when (mod_name /= wanted_mod) $
                throwDyn $ mkPlainErrMsg mod_loc $ 
-                             text "file name does not match module name"
-                             <+> quotes (ppr mod_name)
+                             text "File name does not match module name:" 
+                             $$ text "Saw:" <+> quotes (ppr mod_name)
+                              $$ text "Expected:" <+> quotes (ppr wanted_mod)
 
                -- Find the object timestamp, and return the summary
        obj_timestamp <- getObjTimestamp location is_boot
@@ -1816,16 +1923,17 @@ getObjTimestamp location is_boot
               else modificationTimeIfExists (ml_obj_file location)
 
 
-preprocessFile :: DynFlags -> FilePath -> Maybe Phase -> Maybe (StringBuffer,ClockTime)
+preprocessFile :: HscEnv -> FilePath -> Maybe Phase -> Maybe (StringBuffer,ClockTime)
   -> IO (DynFlags, FilePath, StringBuffer)
-preprocessFile dflags src_fn mb_phase Nothing
+preprocessFile hsc_env src_fn mb_phase Nothing
   = do
-       (dflags', hspp_fn) <- preprocess dflags (src_fn, mb_phase)
+       (dflags', hspp_fn) <- preprocess hsc_env (src_fn, mb_phase)
        buf <- hGetStringBuffer hspp_fn
        return (dflags', hspp_fn, buf)
 
-preprocessFile dflags src_fn mb_phase (Just (buf, _time))
+preprocessFile hsc_env src_fn mb_phase (Just (buf, _time))
   = do
+        let dflags = hsc_dflags hsc_env
        -- case we bypass the preprocessing stage?
        let 
            local_opts = getOptions buf src_fn
@@ -1879,11 +1987,11 @@ multiRootsErr summs@(summ1:_)
 
 cyclicModuleErr :: [ModSummary] -> SDoc
 cyclicModuleErr ms
-  = hang (ptext SLIT("Module imports form a cycle for modules:"))
+  = hang (ptext (sLit "Module imports form a cycle for modules:"))
        2 (vcat (map show_one ms))
   where
     show_one ms = sep [ show_mod (ms_hsc_src ms) (ms_mod ms),
-                       nest 2 $ ptext SLIT("imports:") <+> 
+                       nest 2 $ ptext (sLit "imports:") <+> 
                                   (pp_imps HsBootFile (ms_srcimps ms)
                                   $$ pp_imps HsSrcFile  (ms_imps ms))]
     show_mod hsc_src mod = ppr mod <> text (hscSourceString hsc_src)
@@ -2049,6 +2157,12 @@ lookupGlobalName s name = withSession s $ \hsc_env -> do
    return $! lookupType (hsc_dflags hsc_env) 
                        (hsc_HPT hsc_env) (eps_PTE eps) name
 
+#ifdef GHCI
+-- | get the GlobalRdrEnv for a session
+getGRE :: Session -> IO GlobalRdrEnv
+getGRE s = withSession s $ \hsc_env-> return $ ic_rn_gbl_env (hsc_IC hsc_env)
+#endif
+
 -- -----------------------------------------------------------------------------
 -- Misc exported utils