X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=compiler%2Fmain%2FHscMain.lhs;h=d5ad093bc9d3ef10f5cfa92ebd48e166e65a68d0;hb=0a5613f40b0e32cf59966e6b56b807cdbe80aa7b;hp=e95be761b94c67f3bd311053691d7cb0d98ce9b2;hpb=1dfe7f1ee44b6ae59e072eec720984b136fc1dc5;p=ghc-hetmet.git diff --git a/compiler/main/HscMain.lhs b/compiler/main/HscMain.lhs index e95be76..d5ad093 100644 --- a/compiler/main/HscMain.lhs +++ b/compiler/main/HscMain.lhs @@ -17,10 +17,14 @@ module HscMain , hscStmt, hscTcExpr, hscKcType , compileExpr #endif + , HsCompiler(..) + , hscOneShotCompiler, hscNothingCompiler + , hscInteractiveCompiler, hscBatchCompiler , hscCompileOneShot -- :: Compiler HscStatus , hscCompileBatch -- :: Compiler (HscStatus, ModIface, ModDetails) , hscCompileNothing -- :: Compiler (HscStatus, ModIface, ModDetails) , hscCompileInteractive -- :: Compiler (InteractiveStatus, ModIface, ModDetails) + , hscCheckRecompBackend , HscStatus' (..) , InteractiveStatus, HscStatus @@ -109,10 +113,10 @@ import LazyUniqFM ( emptyUFM ) import UniqSupply ( initUs_ ) import Bag ( unitBag ) import Exception -import MonadUtils +-- import MonadUtils import Control.Monad -import System.IO +-- import System.IO import Data.IORef \end{code} #include "HsVersions.h" @@ -180,7 +184,7 @@ hscParse mod_summary = do Just b -> return b Nothing -> liftIO $ hGetStringBuffer src_filename - let loc = mkSrcLoc (mkFastString src_filename) 1 0 + let loc = mkSrcLoc (mkFastString src_filename) 1 1 case unP parseModule (mkPState buf loc dflags) of PFailed span err -> @@ -213,7 +217,7 @@ hscTypecheck mod_summary rdr_module = do -- exception/signal an error. type RenamedStuff = (Maybe (HsGroup Name, [LImportDecl Name], Maybe [LIE Name], - Maybe (HsDoc Name), HaddockModInfo Name)) + Maybe LHsDocString)) -- | Rename and typecheck a module, additionally returning the renamed syntax hscTypecheckRename :: @@ -226,12 +230,12 @@ hscTypecheckRename mod_summary rdr_module = do <- {-# SCC "Typecheck-Rename" #-} ioMsgMaybe $ tcRnModule hsc_env (ms_hsc_src mod_summary) True rdr_module - let rn_info = do decl <- tcg_rn_decls tc_result - imports <- tcg_rn_imports tc_result - let exports = tcg_rn_exports tc_result - let doc = tcg_doc tc_result - let hmi = tcg_hmi tc_result - return (decl,imports,exports,doc,hmi) + let -- This 'do' is in the Maybe monad! + rn_info = do { decl <- tcg_rn_decls tc_result + ; let imports = tcg_rn_imports tc_result + exports = tcg_rn_exports tc_result + doc_hdr = tcg_doc_hdr tc_result + ; return (decl,imports,exports,doc_hdr) } return (tc_result, rn_info) @@ -313,7 +317,8 @@ data HscStatus' a -- result type. Therefore we need to artificially distinguish some types. We -- do this by adding type tags which will simply be ignored by the caller. type HscStatus = HscStatus' () -type InteractiveStatus = HscStatus' (CompiledByteCode, ModBreaks) +type InteractiveStatus = HscStatus' (Maybe (CompiledByteCode, ModBreaks)) + -- INVARIANT: result is @Nothing@ <=> input was a boot file type OneShotResult = HscStatus type BatchResult = (HscStatus, ModIface, ModDetails) @@ -332,12 +337,6 @@ type Compiler result = GhcMonad m => data HsCompiler a = HsCompiler { - -- | The main interface. - hscCompile :: GhcMonad m => - HscEnv -> ModSummary -> Bool - -> Maybe ModIface -> Maybe (Int, Int) - -> m a, - -- | Called when no recompilation is necessary. hscNoRecomp :: GhcMonad m => ModIface -> m a, @@ -346,6 +345,9 @@ data HsCompiler a hscRecompile :: GhcMonad m => ModSummary -> Maybe Fingerprint -> m a, + hscBackend :: GhcMonad m => + TcGblEnv -> ModSummary -> Maybe Fingerprint -> m a, + -- | Code generation for Boot modules. hscGenBootOutput :: GhcMonad m => TcGblEnv -> ModSummary -> Maybe Fingerprint -> m a, @@ -381,6 +383,22 @@ genericHscCompile compiler hscMessage -> do hscMessage mb_mod_index True mod_summary hscRecompile compiler mod_summary mb_old_hash +hscCheckRecompBackend :: HsCompiler a -> TcGblEnv -> Compiler a +hscCheckRecompBackend compiler tc_result + hsc_env mod_summary source_unchanged mb_old_iface _m_of_n = + withTempSession (\_ -> hsc_env) $ do + (recomp_reqd, mb_checked_iface) + <- {-# SCC "checkOldIface" #-} + liftIO $ checkOldIface hsc_env mod_summary + source_unchanged mb_old_iface + + let mb_old_hash = fmap mi_iface_hash mb_checked_iface + case mb_checked_iface of + Just iface | not recomp_reqd + -> hscNoRecomp compiler iface{ mi_globals = Just (tcg_rdr_env tc_result) } + _otherwise + -> hscBackend compiler tc_result mod_summary mb_old_hash + genericHscRecompile :: GhcMonad m => HsCompiler a -> ModSummary -> Maybe Fingerprint @@ -390,12 +408,18 @@ genericHscRecompile compiler mod_summary mb_old_hash panic "GHC does not currently support reading External Core files" | otherwise = do tc_result <- hscFileFrontEnd mod_summary - case ms_hsc_src mod_summary of - HsBootFile -> - hscGenBootOutput compiler tc_result mod_summary mb_old_hash - _other -> do - guts <- hscDesugar mod_summary tc_result - hscGenOutput compiler guts mod_summary mb_old_hash + hscBackend compiler tc_result mod_summary mb_old_hash + +genericHscBackend :: GhcMonad m => + HsCompiler a + -> TcGblEnv -> ModSummary -> Maybe Fingerprint + -> m a +genericHscBackend compiler tc_result mod_summary mb_old_hash + | HsBootFile <- ms_hsc_src mod_summary = + hscGenBootOutput compiler tc_result mod_summary mb_old_hash + | otherwise = do + guts <- hscDesugar mod_summary tc_result + hscGenOutput compiler guts mod_summary mb_old_hash -------------------------------------------------------------- -- Compilers @@ -405,24 +429,14 @@ hscOneShotCompiler :: HsCompiler OneShotResult hscOneShotCompiler = HsCompiler { - hscCompile = \hsc_env mod_summary src_changed mb_old_iface mb_i_of_n -> do - -- One-shot mode needs a knot-tying mutable variable for interface - -- files. See TcRnTypes.TcGblEnv.tcg_type_env_var. - type_env_var <- liftIO $ newIORef emptyNameEnv - let - mod = ms_mod mod_summary - hsc_env' = hsc_env{ hsc_type_env_var = Just (mod, type_env_var) } - --- - genericHscCompile hscOneShotCompiler - oneShotMsg hsc_env' mod_summary src_changed - mb_old_iface mb_i_of_n - - , hscNoRecomp = \_old_iface -> do + hscNoRecomp = \_old_iface -> do withSession (liftIO . dumpIfaceStats) return HscNoRecomp , hscRecompile = genericHscRecompile hscOneShotCompiler + , hscBackend = genericHscBackend hscOneShotCompiler + , hscGenBootOutput = \tc_result mod_summary mb_old_iface -> do (iface, changed, _) <- hscSimpleIface tc_result mb_old_iface hscWriteIface iface changed mod_summary @@ -439,7 +453,18 @@ hscOneShotCompiler = -- Compile Haskell, boot and extCore in OneShot mode. hscCompileOneShot :: Compiler OneShotResult -hscCompileOneShot = hscCompile hscOneShotCompiler +hscCompileOneShot hsc_env mod_summary src_changed mb_old_iface mb_i_of_n = do + -- One-shot mode needs a knot-tying mutable variable for interface + -- files. See TcRnTypes.TcGblEnv.tcg_type_env_var. + type_env_var <- liftIO $ newIORef emptyNameEnv + let + mod = ms_mod mod_summary + hsc_env' = hsc_env{ hsc_type_env_var = Just (mod, type_env_var) } + --- + genericHscCompile hscOneShotCompiler + oneShotMsg hsc_env' mod_summary src_changed + mb_old_iface mb_i_of_n + -------------------------------------------------------------- @@ -447,14 +472,14 @@ hscBatchCompiler :: HsCompiler BatchResult hscBatchCompiler = HsCompiler { - hscCompile = genericHscCompile hscBatchCompiler batchMsg - - , hscNoRecomp = \iface -> do + hscNoRecomp = \iface -> do details <- genModDetails iface return (HscNoRecomp, iface, details) , hscRecompile = genericHscRecompile hscBatchCompiler + , hscBackend = genericHscBackend hscBatchCompiler + , hscGenBootOutput = \tc_result mod_summary mb_old_iface -> do (iface, changed, details) <- hscSimpleIface tc_result mb_old_iface @@ -472,22 +497,24 @@ hscBatchCompiler = -- Compile Haskell, boot and extCore in batch mode. hscCompileBatch :: Compiler (HscStatus, ModIface, ModDetails) -hscCompileBatch = hscCompile hscBatchCompiler +hscCompileBatch = genericHscCompile hscBatchCompiler batchMsg -------------------------------------------------------------- hscInteractiveCompiler :: HsCompiler InteractiveResult hscInteractiveCompiler = HsCompiler { - hscCompile = genericHscCompile hscInteractiveCompiler batchMsg - - , hscNoRecomp = \iface -> do + hscNoRecomp = \iface -> do details <- genModDetails iface return (HscNoRecomp, iface, details) , hscRecompile = genericHscRecompile hscInteractiveCompiler - , hscGenBootOutput = \_ _ _ -> panic "hscCompileInteractive: HsBootFile" + , hscBackend = genericHscBackend hscInteractiveCompiler + + , hscGenBootOutput = \tc_result _mod_summary mb_old_iface -> do + (iface, _changed, details) <- hscSimpleIface tc_result mb_old_iface + return (HscRecomp False Nothing, iface, details) , hscGenOutput = \guts0 mod_summary mb_old_iface -> do guts <- hscSimplify guts0 @@ -498,16 +525,14 @@ hscInteractiveCompiler = -- Compile Haskell, extCore to bytecode. hscCompileInteractive :: Compiler (InteractiveStatus, ModIface, ModDetails) -hscCompileInteractive = hscCompile hscInteractiveCompiler +hscCompileInteractive = genericHscCompile hscInteractiveCompiler batchMsg -------------------------------------------------------------- hscNothingCompiler :: HsCompiler NothingResult hscNothingCompiler = HsCompiler { - hscCompile = genericHscCompile hscNothingCompiler batchMsg - - , hscNoRecomp = \iface -> do + hscNoRecomp = \iface -> do details <- genModDetails iface return (HscNoRecomp, iface, details) @@ -517,18 +542,22 @@ hscNothingCompiler = panic "hscCompileNothing: cannot do external core" _otherwise -> do tc_result <- hscFileFrontEnd mod_summary - hscGenBootOutput hscNothingCompiler tc_result mod_summary mb_old_hash + hscBackend hscNothingCompiler tc_result mod_summary mb_old_hash - , hscGenBootOutput = \tc_result _mod_summary mb_old_iface -> do + , hscBackend = \tc_result _mod_summary mb_old_iface -> do (iface, _changed, details) <- hscSimpleIface tc_result mb_old_iface return (HscRecomp False (), iface, details) + , hscGenBootOutput = \_ _ _ -> + panic "hscCompileNothing: hscGenBootOutput should not be called" + , hscGenOutput = \_ _ _ -> panic "hscCompileNothing: hscGenOutput should not be called" } + -- Type-check Haskell and .hs-boot only (no external core) hscCompileNothing :: Compiler (HscStatus, ModIface, ModDetails) -hscCompileNothing = hscCompile hscNothingCompiler +hscCompileNothing = genericHscCompile hscNothingCompiler batchMsg -------------------------------------------------------------- -- NoRecomp handlers @@ -693,10 +722,11 @@ hscGenHardCode cgguts mod_summary stg_binds hpc_info --- Optionally run experimental Cmm transformations --- - cmms <- optionallyConvertAndOrCPS hsc_env cmms + -- cmms <- optionallyConvertAndOrCPS hsc_env cmms -- unless certain dflags are on, the identity function ------------------ Code output ----------------------- rawcmms <- cmmToRawCmm cmms + dumpIfSet_dyn dflags Opt_D_dump_cmmz "Raw Cmm" (ppr rawcmms) (_stub_h_exists, stub_c_exists) <- codeOutput dflags this_mod location foreign_stubs dependencies rawcmms @@ -733,7 +763,8 @@ hscInteractive (iface, details, cgguts) mod_summary ------------------ Create f-x-dynamic C-side stuff --- (_istub_h_exists, istub_c_exists) <- outputForeignStubs dflags this_mod location foreign_stubs - return (HscRecomp istub_c_exists (comp_bc, mod_breaks), iface, details) + return (HscRecomp istub_c_exists (Just (comp_bc, mod_breaks)) + , iface, details) #else hscInteractive _ _ = panic "GHC not compiled with interpreter" #endif @@ -747,7 +778,7 @@ hscCmmFile hsc_env filename = do parseCmmFile dflags filename cmms <- liftIO $ optionallyConvertAndOrCPS hsc_env [cmm] rawCmms <- liftIO $ cmmToRawCmm cmms - liftIO $ codeOutput dflags no_mod no_loc NoStubs [] rawCmms + _ <- liftIO $ codeOutput dflags no_mod no_loc NoStubs [] rawCmms return () where no_mod = panic "hscCmmFile: no_mod" @@ -763,11 +794,8 @@ tryNewCodeGen :: HscEnv -> Module -> [TyCon] -> [Module] -> HpcInfo -> IO [Cmm] tryNewCodeGen hsc_env this_mod data_tycons imported_mods - cost_centre_info stg_binds hpc_info - | not (dopt Opt_TryNewCodeGen (hsc_dflags hsc_env)) - = return [] - | otherwise - = do { let dflags = hsc_dflags hsc_env + cost_centre_info stg_binds hpc_info = + do { let dflags = hsc_dflags hsc_env ; prog <- StgCmm.codeGen dflags this_mod data_tycons imported_mods cost_centre_info stg_binds hpc_info ; dumpIfSet_dyn dflags Opt_D_dump_cmmz "Cmm produced by new codegen" @@ -776,8 +804,8 @@ tryNewCodeGen hsc_env this_mod data_tycons imported_mods ; prog <- return $ map (runTx $ runCmmOpts cmmCfgOptsZ) prog -- Control flow optimisation - -- Note: Have to thread the module's SRT through all the procedures - -- because we greedily build it as we go. + -- We are building a single SRT for the entire module, so + -- we must thread it through all the procedures as we cps-convert them. ; us <- mkSplitUniqSupply 'S' ; let topSRT = initUs_ us emptySRT ; (topSRT, prog) <- foldM (protoCmmCPSZ hsc_env) (topSRT, []) prog @@ -786,10 +814,8 @@ tryNewCodeGen hsc_env this_mod data_tycons imported_mods ; prog <- return $ map (runTx $ runCmmOpts cmmCfgOptsZ) (srtToData topSRT : prog) -- Control flow optimisation, again - ; dumpIfSet_dyn dflags Opt_D_dump_cmmz "Output Cmm" (pprCmms prog) - ; let prog' = map cmmOfZgraph prog - ; dumpIfSet_dyn dflags Opt_D_dump_cmmz "Raw Cmm" (ppr prog') + ; dumpIfSet_dyn dflags Opt_D_dump_cmmz "Output Cmm" (ppr prog') ; return prog' } @@ -828,7 +854,6 @@ testCmmConversion hsc_env cmm = let cvt = cmmOfZgraph $ cfopts $ chosen_graph dumpIfSet_dyn dflags Opt_D_dump_cvt_cmm "C-- post-conversion" (ppr cvt) return cvt - -- return cmm -- don't use the conversion myCoreToStg :: DynFlags -> Module -> [CoreBind] -> IO ( [(StgBinding,[(Id,[Id])])] -- output program @@ -964,7 +989,7 @@ hscParseThing parser dflags str buf <- liftIO $ stringToStringBuffer str - let loc = mkSrcLoc (fsLit "") 1 0 + let loc = mkSrcLoc (fsLit "") 1 1 case unP parser (mkPState buf loc dflags) of