[commit: ghc] master: Don't use showPass in the backend (#8973) (c025817)
git at git.haskell.org
git at git.haskell.org
Sun Jun 8 10:21:52 UTC 2014
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/c0258176ad255ac42a68df75ac4287630a6c82c0/ghc
>---------------------------------------------------------------
commit c0258176ad255ac42a68df75ac4287630a6c82c0
Author: Simon Marlow <marlowsd at gmail.com>
Date: Sun Jun 8 11:17:57 2014 +0100
Don't use showPass in the backend (#8973)
>---------------------------------------------------------------
c0258176ad255ac42a68df75ac4287630a6c82c0
compiler/cmm/CmmPipeline.hs | 2 --
compiler/codeGen/StgCmm.hs | 5 +----
compiler/main/CodeOutput.lhs | 1 -
compiler/main/HscMain.hs | 23 +++++++++++++++--------
4 files changed, 16 insertions(+), 15 deletions(-)
diff --git a/compiler/cmm/CmmPipeline.hs b/compiler/cmm/CmmPipeline.hs
index 825ffb8..4314695 100644
--- a/compiler/cmm/CmmPipeline.hs
+++ b/compiler/cmm/CmmPipeline.hs
@@ -38,8 +38,6 @@ cmmPipeline :: HscEnv -- Compilation env including
cmmPipeline hsc_env topSRT prog =
do let dflags = hsc_dflags hsc_env
- showPass dflags "CPSZ"
-
tops <- {-# SCC "tops" #-} mapM (cpsTop hsc_env) prog
(topSRT, cmms) <- {-# SCC "doSRTs" #-} doSRTs dflags topSRT tops
diff --git a/compiler/codeGen/StgCmm.hs b/compiler/codeGen/StgCmm.hs
index 740ab5f..efc89fe 100644
--- a/compiler/codeGen/StgCmm.hs
+++ b/compiler/codeGen/StgCmm.hs
@@ -39,7 +39,6 @@ import DataCon
import Name
import TyCon
import Module
-import ErrUtils
import Outputable
import Stream
import BasicTypes
@@ -62,9 +61,7 @@ codeGen :: DynFlags
codeGen dflags this_mod data_tycons
cost_centre_info stg_binds hpc_info
- = do { liftIO $ showPass dflags "New CodeGen"
-
- -- cg: run the code generator, and yield the resulting CmmGroup
+ = do { -- cg: run the code generator, and yield the resulting CmmGroup
-- Using an IORef to store the state is a bit crude, but otherwise
-- we would need to add a state monad layer.
; cgref <- liftIO $ newIORef =<< initC
diff --git a/compiler/main/CodeOutput.lhs b/compiler/main/CodeOutput.lhs
index 7ae28b3..c0a609b 100644
--- a/compiler/main/CodeOutput.lhs
+++ b/compiler/main/CodeOutput.lhs
@@ -74,7 +74,6 @@ codeOutput dflags this_mod filenm location foreign_stubs pkg_deps cmm_stream
; return cmm
}
- ; showPass dflags "CodeOutput"
; stubs_exist <- outputForeignStubs dflags this_mod location foreign_stubs
; case hscTarget dflags of {
HscAsm -> outputAsm dflags this_mod filenm linted_cmm_stream;
diff --git a/compiler/main/HscMain.hs b/compiler/main/HscMain.hs
index 9b6c4d7..ea31ed7 100644
--- a/compiler/main/HscMain.hs
+++ b/compiler/main/HscMain.hs
@@ -1150,8 +1150,15 @@ hscGenHardCode hsc_env cgguts mod_summary output_filename = do
------------------ Code generation ------------------
- cmms <- {-# SCC "NewCodeGen" #-}
- tryNewCodeGen hsc_env this_mod data_tycons
+ -- The back-end is streamed: each top-level function goes
+ -- from Stg all the way to asm before dealing with the next
+ -- top-level function, so showPass isn't very useful here.
+ -- Hence we have one showPass for the whole backend, the
+ -- next showPass after this will be "Assembler".
+ showPass dflags "CodeGen"
+
+ cmms <- {-# SCC "StgCmm" #-}
+ doCodeGen hsc_env this_mod data_tycons
cost_centre_info
stg_binds hpc_info
@@ -1228,15 +1235,15 @@ hscCompileCmmFile hsc_env filename output_filename = runHsc hsc_env $ do
-------------------- Stuff for new code gen ---------------------
-tryNewCodeGen :: HscEnv -> Module -> [TyCon]
- -> CollectedCCs
- -> [StgBinding]
- -> HpcInfo
- -> IO (Stream IO CmmGroup ())
+doCodeGen :: HscEnv -> Module -> [TyCon]
+ -> CollectedCCs
+ -> [StgBinding]
+ -> HpcInfo
+ -> IO (Stream IO CmmGroup ())
-- Note we produce a 'Stream' of CmmGroups, so that the
-- backend can be run incrementally. Otherwise it generates all
-- the C-- up front, which has a significant space cost.
-tryNewCodeGen hsc_env this_mod data_tycons
+doCodeGen hsc_env this_mod data_tycons
cost_centre_info stg_binds hpc_info = do
let dflags = hsc_dflags hsc_env
More information about the ghc-commits
mailing list