From a9b147907b69d7c5a71644f3fcba6dec3fc632f6 Mon Sep 17 00:00:00 2001 From: Ben Gamari <ben@smart-cactus.org> Date: Thu, 7 Nov 2019 10:29:56 -0500 Subject: [PATCH] testsuite: Fix putStrLn in saks028 Bizarrely, `saks028` previously failed reliably, but only on Windows (#17450). The test would exit with a zero exit code but simply didn't emit the expected text to stderr. I believe this was due to the fact that the test used `putStrLn`, resulting in the output ending up on stdout. This worked on other platforms since (apparently) we redirect stdout to stderr when evaluating splices. However, on Windows it seems that the redirected output wasn't flushed as it was on other platforms. Anyways, it seems like the right thing to do here is to be explicit about our desire for the output to end up on stderr. Closes #17450. --- testsuite/tests/saks/should_compile/saks028.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/saks/should_compile/saks028.hs b/testsuite/tests/saks/should_compile/saks028.hs index 9d15db593cc3..51c1e52c6bd2 100644 --- a/testsuite/tests/saks/should_compile/saks028.hs +++ b/testsuite/tests/saks/should_compile/saks028.hs @@ -3,6 +3,7 @@ module SAKS_028 where +import System.IO import Data.Kind import Language.Haskell.TH hiding (Type) @@ -10,5 +11,5 @@ type Functor' :: (Type -> Type) -> Constraint class Functor' f do sig <- reifyType ('' Functor') - runIO $ putStrLn $ pprint sig + runIO $ hPutStrLn stderr $ pprint sig return [] -- GitLab