X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=compiler%2Fmain%2FHscMain.lhs;h=0563f3442ce883d8dae81e18f3f1a3a04cf353be;hp=986d2ce6d904238d21be30a13c2281bfe3c60fda;hb=b00b5bc04ff36a551552470060064f0b7d84ca30;hpb=2c1ea2cedb1a8034b0828e24b554a35f56bb8924 diff --git a/compiler/main/HscMain.lhs b/compiler/main/HscMain.lhs index 986d2ce..0563f34 100644 --- a/compiler/main/HscMain.lhs +++ b/compiler/main/HscMain.lhs @@ -30,6 +30,7 @@ import Module ( Module ) import CodeOutput ( outputForeignStubs ) import ByteCodeGen ( byteCodeGen, coreExprToBCOs ) import Linker ( HValue, linkExpr ) +import CoreSyn ( CoreExpr ) import CoreTidy ( tidyExpr ) import CorePrep ( corePrepExpr ) import Flattening ( flattenExpr ) @@ -38,17 +39,18 @@ import SimplCore ( simplifyExpr ) import TcRnDriver ( tcRnStmt, tcRnExpr, tcRnType ) import Type ( Type ) import PrelNames ( iNTERACTIVE ) -import Kind ( Kind ) +import {- Kind parts of -} Type ( Kind ) import CoreLint ( lintUnfolding ) import DsMeta ( templateHaskellNames ) -import SrcLoc ( noSrcLoc ) +import SrcLoc ( SrcSpan, noSrcLoc, interactiveSrcLoc, srcLocSpan ) import VarEnv ( emptyTidyEnv ) #endif import Var ( Id ) import Module ( emptyModuleEnv, ModLocation(..) ) import RdrName ( GlobalRdrEnv, RdrName, emptyGlobalRdrEnv ) -import HsSyn ( HsModule, LHsBinds, HsGroup, LIE, LImportDecl ) +import HsSyn ( HsModule, LHsBinds, HsGroup, LIE, LImportDecl, HsDoc, + HaddockModInfo ) import SrcLoc ( Located(..) ) import StringBuffer ( hGetStringBuffer, stringToStringBuffer ) import Parser @@ -68,7 +70,6 @@ import TidyPgm ( tidyProgram, mkBootModDetails ) import CorePrep ( corePrepPgm ) import CoreToStg ( coreToStg ) import TyCon ( isDataTyCon ) -import Packages ( mkHomeModules ) import Name ( Name, NamedThing(..) ) import SimplStg ( stg2stg ) import CodeGen ( codeGen ) @@ -87,7 +88,7 @@ import MkExternalCore ( emitExternalCore ) import ParserCore import ParserCoreUtils import FastString -import Maybes ( expectJust ) +import UniqFM ( emptyUFM ) import Bag ( unitBag ) import Monad ( unless ) import IO @@ -107,7 +108,8 @@ newHscEnv dflags = do { eps_var <- newIORef initExternalPackageState ; us <- mkSplitUniqSupply 'r' ; nc_var <- newIORef (initNameCache us knownKeyNames) - ; fc_var <- newIORef emptyModuleEnv + ; fc_var <- newIORef emptyUFM + ; mlc_var <- newIORef emptyModuleEnv ; return (HscEnv { hsc_dflags = dflags, hsc_targets = [], hsc_mod_graph = [], @@ -116,6 +118,7 @@ newHscEnv dflags hsc_EPS = eps_var, hsc_NC = nc_var, hsc_FC = fc_var, + hsc_MLC = mlc_var, hsc_global_rdr_env = emptyGlobalRdrEnv, hsc_global_type_env = emptyNameEnv } ) } @@ -174,7 +177,8 @@ data HscChecked -- parsed (Located (HsModule RdrName)) -- renamed - (Maybe (HsGroup Name,[LImportDecl Name],Maybe [LIE Name])) + (Maybe (HsGroup Name, [LImportDecl Name], Maybe [LIE Name], + Maybe (HsDoc Name), HaddockModInfo Name)) -- typechecked (Maybe (LHsBinds Id, GlobalRdrEnv, ModDetails)) @@ -217,6 +221,9 @@ data CompState get :: Comp CompState get = Comp $ \s -> return (s,s) +modify :: (CompState -> CompState) -> Comp () +modify f = Comp $ \s -> return ((), f s) + gets :: (CompState -> a) -> Comp a gets getter = do st <- get return (getter st) @@ -253,6 +260,10 @@ hscMkCompiler norecomp messenger frontend backend <- {-# SCC "checkOldIface" #-} liftIO $ checkOldIface hsc_env mod_summary source_unchanged mbOldIface + -- save the interface that comes back from checkOldIface. + -- In one-shot mode we don't have the old iface until this + -- point, when checkOldIface reads it from the disk. + modify (\s -> s{ compOldIface = mbCheckedIface }) case mbCheckedIface of Just iface | not recomp_reqd -> do messenger mbModIndex False @@ -390,9 +401,9 @@ batchMsg mb_mod_index recomp liftIO $ do if recomp then showMsg "Compiling " - else showMsg "Skipping " - - + else if verbosity (hsc_dflags hsc_env) >= 1 + then showMsg "Skipping " + else return () -------------------------------------------------------------- -- FrontEnds @@ -454,10 +465,7 @@ hscFileFrontEnd = ------------------- -- DESUGAR ------------------- - -> do (warns, maybe_ds_result) <- {-# SCC "DeSugar" #-} - deSugar hsc_env tc_result - printBagOfWarnings dflags warns - return maybe_ds_result + -> {-# SCC "DeSugar" #-} deSugar hsc_env tc_result -------------------------------------------------------------- -- Simplifiers @@ -519,7 +527,7 @@ hscNormalIface simpl_result <- {-# SCC "MkFinalIface" #-} mkIface hsc_env maybe_old_iface simpl_result details -- Emit external core - emitExternalCore (hsc_dflags hsc_env) cg_guts -- Move this? --Lemmih 03/07/2006 + emitExternalCore (hsc_dflags hsc_env) (availsToNameSet (mg_exports simpl_result)) cg_guts -- Move this? --Lemmih 03/07/2006 dumpIfaceStats hsc_env ------------------- @@ -533,9 +541,11 @@ hscNormalIface simpl_result hscWriteIface :: (ModIface, Bool, ModDetails, a) -> Comp (ModIface, ModDetails, a) hscWriteIface (iface, no_change, details, a) = do mod_summary <- gets compModSummary + hsc_env <- gets compHscEnv + let dflags = hsc_dflags hsc_env liftIO $ do unless no_change - $ writeIfaceFile (ms_location mod_summary) iface + $ writeIfaceFile dflags (ms_location mod_summary) iface return (iface, details, a) hscIgnoreIface :: (ModIface, Bool, ModDetails, a) -> Comp (ModIface, ModDetails, a) @@ -572,7 +582,6 @@ hscCompile cgguts cg_tycons = tycons, cg_dir_imps = dir_imps, cg_foreign = foreign_stubs, - cg_home_mods = home_mods, cg_dep_pkgs = dependencies } = cgguts dflags = hsc_dflags hsc_env location = ms_location mod_summary @@ -588,10 +597,10 @@ hscCompile cgguts ----------------- Convert to STG ------------------ (stg_binds, cost_centre_info) <- {-# SCC "CoreToStg" #-} - myCoreToStg dflags home_mods this_mod prepd_binds + myCoreToStg dflags this_mod prepd_binds ------------------ Code generation ------------------ abstractC <- {-# SCC "CodeGen" #-} - codeGen dflags home_mods this_mod data_tycons + codeGen dflags this_mod data_tycons foreign_stubs dir_imps cost_centre_info stg_binds ------------------ Code output ----------------------- @@ -668,17 +677,21 @@ hscFileCheck hsc_env mod_summary = do { ; case maybe_tc_result of { Nothing -> return (Just (HscChecked rdr_module Nothing 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"] } + let type_env = tcg_type_env tc_result + md = ModDetails { + md_types = type_env, + md_exports = tcg_exports tc_result, + md_insts = tcg_insts tc_result, + md_fam_insts = tcg_fam_insts tc_result, + md_rules = [panic "no rules"] } -- Rules are CoreRules, not the -- RuleDecls we get out of the typechecker rnInfo = do decl <- tcg_rn_decls tc_result imports <- tcg_rn_imports tc_result let exports = tcg_rn_exports tc_result - return (decl,imports,exports) + let doc = tcg_doc tc_result + hmi = tcg_hmi tc_result + return (decl,imports,exports,doc,hmi) return (Just (HscChecked rdr_module rnInfo (Just (tcg_binds tc_result, @@ -689,7 +702,7 @@ hscFileCheck hsc_env mod_summary = do { hscCmmFile :: DynFlags -> FilePath -> IO Bool hscCmmFile dflags filename = do - maybe_cmm <- parseCmmFile dflags (mkHomeModules []) filename + maybe_cmm <- parseCmmFile dflags filename case maybe_cmm of Nothing -> return False Just cmm -> do @@ -732,13 +745,13 @@ myParseModule dflags src_filename maybe_src_buf }} -myCoreToStg dflags home_mods this_mod prepd_binds +myCoreToStg dflags this_mod prepd_binds = do stg_binds <- {-# SCC "Core2Stg" #-} - coreToStg home_mods prepd_binds + coreToStg (thisPackage dflags) prepd_binds (stg_binds2, cost_centre_info) <- {-# SCC "Stg2Stg" #-} - stg2stg dflags home_mods this_mod stg_binds + stg2stg dflags this_mod stg_binds return (stg_binds2, cost_centre_info) \end{code} @@ -798,14 +811,22 @@ hscStmt hsc_env stmt Nothing -> return Nothing ; Just (new_ic, bound_names, tc_expr) -> do { + + -- Desugar it + ; let rdr_env = ic_rn_gbl_env new_ic + type_env = ic_type_env new_ic + ; mb_ds_expr <- deSugarExpr hsc_env iNTERACTIVE rdr_env type_env tc_expr + + ; case mb_ds_expr of { + Nothing -> return Nothing ; + Just ds_expr -> do { + -- Then desugar, code gen, and link it - ; hval <- compileExpr hsc_env iNTERACTIVE - (ic_rn_gbl_env new_ic) - (ic_type_env new_ic) - tc_expr + ; let src_span = srcLocSpan interactiveSrcLoc + ; hval <- compileExpr hsc_env src_span ds_expr ; return (Just (hsc_env{ hsc_IC=new_ic }, bound_names, hval)) - }}}}} + }}}}}}} hscTcExpr -- Typecheck an expression (but don't run it) :: HscEnv @@ -832,10 +853,8 @@ 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 (hsc_dflags hsc_env) (text "not an type:" <+> quotes (text str)) ; - return Nothing } ; - Nothing -> return Nothing } } + Just ty -> tcRnType hsc_env icontext ty ; + Nothing -> return Nothing } } #endif \end{code} @@ -887,18 +906,12 @@ hscParseThing parser dflags str \begin{code} #ifdef GHCI -compileExpr :: HscEnv - -> Module -> GlobalRdrEnv -> TypeEnv - -> LHsExpr Id - -> IO HValue +compileExpr :: HscEnv -> SrcSpan -> CoreExpr -> IO HValue -compileExpr hsc_env this_mod rdr_env type_env tc_expr +compileExpr hsc_env srcspan ds_expr = do { let { dflags = hsc_dflags hsc_env ; lint_on = dopt Opt_DoCoreLinting dflags } - -- Desugar it - ; ds_expr <- deSugarExpr hsc_env this_mod rdr_env type_env tc_expr - -- Flatten it ; flat_expr <- flattenExpr hsc_env ds_expr @@ -924,7 +937,7 @@ compileExpr hsc_env this_mod rdr_env type_env tc_expr ; bcos <- coreExprToBCOs dflags prepd_expr -- link it - ; hval <- linkExpr hsc_env bcos + ; hval <- linkExpr hsc_env srcspan bcos ; return hval }