Repository : ssh://darcs.haskell.org//srv/darcs/testsuite

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/914e12f270e6f94cd64d8ed409f83b0f6250e162

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

commit 914e12f270e6f94cd64d8ed409f83b0f6250e162
Author: Simon Marlow <marlo...@gmail.com>
Date:   Tue May 1 11:40:34 2012 +0100

    follow changes in the GHC API

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

 tests/annotations/should_run/annrun01.hs |    4 ++--
 1 files changed, 2 insertions(+), 2 deletions(-)

diff --git a/tests/annotations/should_run/annrun01.hs 
b/tests/annotations/should_run/annrun01.hs
index 691e6a3..d7c8e6b 100644
--- a/tests/annotations/should_run/annrun01.hs
+++ b/tests/annotations/should_run/annrun01.hs
@@ -4,7 +4,7 @@ module Main where
 
 import GHC
 import MonadUtils  ( liftIO )
-import DynFlags    ( defaultLogAction )
+import DynFlags    ( defaultLogAction, defaultFlushOut )
 import Annotations ( AnnTarget(..), CoreAnnTarget )
 import Serialized  ( deserializeWithData )
 import Panic
@@ -17,7 +17,7 @@ import Data.List
 import Data.Function
 
 main :: IO ()
-main = defaultErrorHandler defaultLogAction
+main = defaultErrorHandler defaultLogAction defaultFlushOut
      $ runGhc (Just cTop) $ do
     liftIO $ putStrLn "Initializing Package Database"
     dflags <- getSessionDynFlags



_______________________________________________
Cvs-ghc mailing list
Cvs-ghc@haskell.org
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to