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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/1f40cdc8e3067128cb1c9e2c1dff0c1385a9e42e

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

commit 1f40cdc8e3067128cb1c9e2c1dff0c1385a9e42e
Author: Daniel Fischer <[email protected]>
Date:   Sun Jul 3 22:54:00 2011 +0200

    Pass defaultLogAction to defaultErrorHandler in annrun01

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

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

diff --git a/tests/ghc-regress/annotations/should_run/annrun01.hs 
b/tests/ghc-regress/annotations/should_run/annrun01.hs
index 0b4b877..e626dad 100644
--- a/tests/ghc-regress/annotations/should_run/annrun01.hs
+++ b/tests/ghc-regress/annotations/should_run/annrun01.hs
@@ -4,7 +4,7 @@ module Main where
 
 import GHC
 import MonadUtils  ( liftIO )
-import DynFlags    ( defaultDynFlags )
+import DynFlags    ( defaultLogAction )
 import Annotations ( AnnTarget(..), CoreAnnTarget )
 import Serialized  ( deserializeWithData )
 import Panic
@@ -16,7 +16,7 @@ import qualified Language.Haskell.TH as TH
 import Data.List
 import Data.Function
 
-main = defaultErrorHandler (defaultDynFlags (panic "No settings"))
+main = defaultErrorHandler defaultLogAction
      $ runGhc (Just cTop) $ do
     liftIO $ putStrLn "Initializing Package Database"
     dflags <- getSessionDynFlags



_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to