[commit: ghc] master: Make -ddump-splices output to stdout (fixes #8796) (73f976c)

git at git.haskell.org git at git.haskell.org
Thu Feb 5 23:42:50 UTC 2015


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/73f976c47f00060baaeead9e0331ab265a84251c/ghc

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

commit 73f976c47f00060baaeead9e0331ab265a84251c
Author: Alexander Vershilov <alexander.vershilov at gmail.com>
Date:   Thu Feb 5 17:43:32 2015 -0600

    Make -ddump-splices output to stdout (fixes #8796)
    
    Summary:
    Fixes debug output so all info messages will use
    stdout. Fixes #8796.
    
    Make -ddump-splices output to stdout (fixes #8796)
    Make -dverbose-core2core use stdout (fixes #8796)
    
    Reviewers: simonpj, austin
    
    Reviewed By: austin
    
    Subscribers: thomie
    
    Differential Revision: https://phabricator.haskell.org/D627
    
    GHC Trac Issues: #8796


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

73f976c47f00060baaeead9e0331ab265a84251c
 compiler/simplCore/SimplMonad.hs           | 2 +-
 compiler/simplCore/Simplify.hs             | 4 ++--
 compiler/typecheck/TcRnMonad.hs            | 2 +-
 compiler/vectorise/Vectorise/Monad.hs      | 2 +-
 compiler/vectorise/Vectorise/Monad/Base.hs | 4 ++--
 5 files changed, 7 insertions(+), 7 deletions(-)

diff --git a/compiler/simplCore/SimplMonad.hs b/compiler/simplCore/SimplMonad.hs
index 451bf34..0069106 100644
--- a/compiler/simplCore/SimplMonad.hs
+++ b/compiler/simplCore/SimplMonad.hs
@@ -135,7 +135,7 @@ traceSmpl :: String -> SDoc -> SimplM ()
 traceSmpl herald doc
   = do { dflags <- getDynFlags
        ; when (dopt Opt_D_dump_simpl_trace dflags) $ liftIO $
-         printInfoForUser dflags alwaysQualify $
+         printOutputForUser dflags alwaysQualify $
          hang (text herald) 2 doc }
 
 {-
diff --git a/compiler/simplCore/Simplify.hs b/compiler/simplCore/Simplify.hs
index db7f5a6..3614bb3 100644
--- a/compiler/simplCore/Simplify.hs
+++ b/compiler/simplCore/Simplify.hs
@@ -1440,10 +1440,10 @@ completeCall env var cont
       | not (dopt Opt_D_dump_inlinings dflags) = return ()
       | not (dopt Opt_D_verbose_core2core dflags)
       = when (isExternalName (idName var)) $
-            liftIO $ printInfoForUser dflags alwaysQualify $
+            liftIO $ printOutputForUser dflags alwaysQualify $
                 sep [text "Inlining done:", nest 4 (ppr var)]
       | otherwise
-      = liftIO $ printInfoForUser dflags alwaysQualify $
+      = liftIO $ printOutputForUser dflags alwaysQualify $
            sep [text "Inlining done: " <> ppr var,
                 nest 4 (vcat [text "Inlined fn: " <+> nest 2 (ppr unfolding),
                               text "Cont:  " <+> ppr cont])]
diff --git a/compiler/typecheck/TcRnMonad.hs b/compiler/typecheck/TcRnMonad.hs
index 374a859..84ae0b9 100644
--- a/compiler/typecheck/TcRnMonad.hs
+++ b/compiler/typecheck/TcRnMonad.hs
@@ -551,7 +551,7 @@ printForUserTcRn :: SDoc -> TcRn ()
 printForUserTcRn doc
   = do { dflags <- getDynFlags
        ; printer <- getPrintUnqualified dflags
-       ; liftIO (printInfoForUser dflags printer doc) }
+       ; liftIO (printOutputForUser dflags printer doc) }
 
 -- | Typechecker debug
 debugDumpTcRn :: SDoc -> TcRn ()
diff --git a/compiler/vectorise/Vectorise/Monad.hs b/compiler/vectorise/Vectorise/Monad.hs
index 3e6c33a..4e9726a 100644
--- a/compiler/vectorise/Vectorise/Monad.hs
+++ b/compiler/vectorise/Vectorise/Monad.hs
@@ -105,7 +105,7 @@ initV hsc_env guts info thing_inside
                Yes genv _ x -> return $ Just (new_info genv, x)
                No reason    -> do { unqual <- mkPrintUnqualifiedDs
                                   ; liftIO $ 
-                                      printInfoForUser dflags unqual $ 
+                                      printOutputForUser dflags unqual $
                                         mkDumpDoc "Warning: vectorisation failure:" reason
                                   ; return Nothing
                                   }
diff --git a/compiler/vectorise/Vectorise/Monad/Base.hs b/compiler/vectorise/Vectorise/Monad/Base.hs
index 3cb6adb..a3089e3 100644
--- a/compiler/vectorise/Vectorise/Monad/Base.hs
+++ b/compiler/vectorise/Vectorise/Monad/Base.hs
@@ -117,7 +117,7 @@ emitVt :: String -> SDoc -> VM ()
 emitVt herald doc
   = liftDs $ do
       dflags <- getDynFlags
-      liftIO . printInfoForUser dflags alwaysQualify $
+      liftIO . printOutputForUser dflags alwaysQualify $
         hang (text herald) 2 doc
 
 -- |Output a trace message if -ddump-vt-trace is active.
@@ -144,7 +144,7 @@ dumpVt :: String -> SDoc -> VM ()
 dumpVt header doc 
   = do { unqual <- liftDs mkPrintUnqualifiedDs
        ; dflags <- liftDs getDynFlags
-       ; liftIO $ printInfoForUser dflags unqual (mkDumpDoc header doc)
+       ; liftIO $ printOutputForUser dflags unqual (mkDumpDoc header doc)
        }
 
 



More information about the ghc-commits mailing list