[commit: ghc] master: Flush after TH in #8884 test case (df409de)

git at git.haskell.org git at git.haskell.org
Fri Mar 21 12:48:32 UTC 2014


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

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

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

commit df409de9550dc8a07e010964a54112266d809341
Author: Joachim Breitner <mail at joachim-breitner.de>
Date:   Fri Mar 21 13:46:15 2014 +0100

    Flush after TH in #8884 test case
    
    (I recall that this was needed in some cases in the past, and might fix
    the validate error on travis.)


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

df409de9550dc8a07e010964a54112266d809341
 testsuite/tests/th/T8884.hs |    2 ++
 1 file changed, 2 insertions(+)

diff --git a/testsuite/tests/th/T8884.hs b/testsuite/tests/th/T8884.hs
index 782bf90..ca6ed9c 100644
--- a/testsuite/tests/th/T8884.hs
+++ b/testsuite/tests/th/T8884.hs
@@ -3,6 +3,7 @@
 module T8884 where
 
 import Language.Haskell.TH
+import System.IO
 
 type family Foo a where
   Foo x = x
@@ -16,6 +17,7 @@ $( do FamilyI foo@(ClosedTypeFamilyD _ tvbs1 m_kind1 eqns1) [] <- reify ''Foo
       runIO $ putStrLn $ pprint foo
       runIO $ putStrLn $ pprint baz
       runIO $ putStrLn $ pprint inst
+      runIO $ hFlush stdout
       return [ ClosedTypeFamilyD (mkName "Foo'") tvbs1 m_kind1 eqns1
              , FamilyD TypeFam (mkName "Baz'") tvbs2 m_kind2
              , TySynInstD (mkName "Baz'") eqn2 ] )



More information about the ghc-commits mailing list