[commit: ghc] wip/kavon-nosplit-llvm: when compiling a .cmm file, carry any ManglerInfo through to the next phase (4790509)

git at git.haskell.org git at git.haskell.org
Tue Mar 13 03:44:56 UTC 2018


Repository : ssh://git@git.haskell.org/ghc

On branch  : wip/kavon-nosplit-llvm
Link       : http://ghc.haskell.org/trac/ghc/changeset/4790509e7b52f5904d50ac937998b47b347fedac/ghc

>---------------------------------------------------------------

commit 4790509e7b52f5904d50ac937998b47b347fedac
Author: Kavon Farvardin <kavon at farvard.in>
Date:   Mon Mar 12 22:43:41 2018 -0500

    when compiling a .cmm file, carry any ManglerInfo through to the next phase


>---------------------------------------------------------------

4790509e7b52f5904d50ac937998b47b347fedac
 compiler/main/DriverPipeline.hs | 8 ++++++--
 compiler/main/HscMain.hs        | 6 +++---
 2 files changed, 9 insertions(+), 5 deletions(-)

diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs
index acf1d04..902086d 100644
--- a/compiler/main/DriverPipeline.hs
+++ b/compiler/main/DriverPipeline.hs
@@ -1140,9 +1140,13 @@ runPhase (RealPhase Cmm) input_fn dflags
 
         PipeState{hsc_env} <- getPipeState
 
-        liftIO $ hscCompileCmmFile hsc_env input_fn output_fn
+        mangInfo <- liftIO $ hscCompileCmmFile hsc_env input_fn output_fn
         
-        return (RealPhase next_phase, output_fn)
+        let kind = case next_phase of
+                     LlvmOpt -> RealPhaseWithInfo
+                     _       -> \ _ p -> RealPhase p
+
+        return (kind mangInfo next_phase, output_fn)
 
 -----------------------------------------------------------------------------
 -- Cc phase
diff --git a/compiler/main/HscMain.hs b/compiler/main/HscMain.hs
index 6ad0b7c..3dd16f9 100644
--- a/compiler/main/HscMain.hs
+++ b/compiler/main/HscMain.hs
@@ -1392,7 +1392,7 @@ hscInteractive hsc_env cgguts mod_summary = do
 
 ------------------------------
 
-hscCompileCmmFile :: HscEnv -> FilePath -> FilePath -> IO ()
+hscCompileCmmFile :: HscEnv -> FilePath -> FilePath -> IO ManglerInfo
 hscCompileCmmFile hsc_env filename output_filename = runHsc hsc_env $ do
     let dflags = hsc_dflags hsc_env
     cmm <- ioMsgMaybe $ parseCmmFile dflags filename
@@ -1406,9 +1406,9 @@ hscCompileCmmFile hsc_env filename output_filename = runHsc hsc_env $ do
             -- lest we reproduce #11784.
             mod_name = mkModuleName $ "Cmm$" ++ FilePath.takeFileName filename
             cmm_mod = mkModule (thisPackage dflags) mod_name
-        _ <- codeOutput dflags cmm_mod output_filename no_loc NoStubs [] []
+        (_,_,_,info) <- codeOutput dflags cmm_mod output_filename no_loc NoStubs [] []
              rawCmms
-        return ()
+        return info
   where
     no_loc = ModLocation{ ml_hs_file  = Just filename,
                           ml_hi_file  = panic "hscCompileCmmFile: no hi file",



More information about the ghc-commits mailing list