[commit: testsuite] master: Flush stdout after printing in runIO (522f81d)
git at git.haskell.org
git at git.haskell.org
Fri Oct 18 19:43:15 UTC 2013
Repository : ssh://git@git.haskell.org/testsuite
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/522f81d88c119a2f653137e97c6c9b09427bf562/testsuite
>---------------------------------------------------------------
commit 522f81d88c119a2f653137e97c6c9b09427bf562
Author: Joachim Breitner <mail at joachim-breitner.de>
Date: Fri Oct 18 21:42:16 2013 +0200
Flush stdout after printing in runIO
as the docs of runIO tell me to.
>---------------------------------------------------------------
522f81d88c119a2f653137e97c6c9b09427bf562
tests/th/TH_Roles3.hs | 3 ++-
tests/th/TH_Roles4.hs | 3 ++-
2 files changed, 4 insertions(+), 2 deletions(-)
diff --git a/tests/th/TH_Roles3.hs b/tests/th/TH_Roles3.hs
index e42394e..ac96835 100644
--- a/tests/th/TH_Roles3.hs
+++ b/tests/th/TH_Roles3.hs
@@ -3,8 +3,9 @@
module Roles3 where
import Language.Haskell.TH
+import System.IO
$( do { decls <- [d| data Foo a (b :: k) c (d :: k)
type role Foo _ _ representational nominal |]
- ; runIO $ putStrLn (pprint decls)
+ ; runIO $ putStrLn (pprint decls) >> hFlush stdout
; return decls })
diff --git a/tests/th/TH_Roles4.hs b/tests/th/TH_Roles4.hs
index cc7fce1..16dbb67 100644
--- a/tests/th/TH_Roles4.hs
+++ b/tests/th/TH_Roles4.hs
@@ -3,9 +3,10 @@
module Roles4 where
import Language.Haskell.TH
+import System.IO
data Sticky a b = MkSticky (a b)
$( do roles <- reifyRoles (mkName "Sticky")
- runIO $ putStrLn (show roles)
+ runIO $ putStrLn (show roles) >> hFlush stdout
return [] )
More information about the ghc-commits
mailing list