[commit: ghc] wip/testsuite-fragile: Testsuite: use 'fragile' instead of 'skip' for T3424, T14697 (00f267e)

git at git.haskell.org git at git.haskell.org
Fri Mar 8 01:45:31 UTC 2019


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

On branch  : wip/testsuite-fragile
Link       : http://ghc.haskell.org/trac/ghc/changeset/00f267e51e8c0852a8234eb531f215775378309c/ghc

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

commit 00f267e51e8c0852a8234eb531f215775378309c
Author: Vladislav Zavialov <vlad.z.4096 at gmail.com>
Date:   Thu Mar 7 10:33:41 2019 +0300

    Testsuite: use 'fragile' instead of 'skip' for T3424, T14697
    
    Also, replace some tabs with spaces to avoid a "mixed indent" warning that vim
    gives me.


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

00f267e51e8c0852a8234eb531f215775378309c
 testsuite/tests/perf/compiler/all.T |  7 +++----
 testsuite/tests/rts/all.T           | 16 +++++++---------
 2 files changed, 10 insertions(+), 13 deletions(-)

diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T
index c6548c1..ff80c74 100644
--- a/testsuite/tests/perf/compiler/all.T
+++ b/testsuite/tests/perf/compiler/all.T
@@ -356,10 +356,9 @@ test('T13719',
 test('T14697',
      [ collect_compiler_stats('bytes allocated',10),
        # This generates too large of a command-line for poor Windows and
-       # Darwin. The failure is non-deterministic, so we 'skip' it rather than
-       # 'expect_broken'. The solution is to teach the testsuite driver to
-       # invoke GHC with a response file, see Trac #15072
-       when(opsys('mingw32') or opsys('darwin'), skip),
+       # Darwin. The solution is to teach the testsuite driver to
+       # invoke GHC with a response file.
+       when(opsys('mingw32') or opsys('darwin'), fragile(15072)),
        pre_cmd('./genT14697'),
        extra_files(['genT14697']),
        extra_hc_opts('$(cat T14697-flags)'), # 10k -optP arguments
diff --git a/testsuite/tests/rts/all.T b/testsuite/tests/rts/all.T
index ac0fbff..4d2be2b 100644
--- a/testsuite/tests/rts/all.T
+++ b/testsuite/tests/rts/all.T
@@ -74,7 +74,7 @@ test('T2047', [ignore_stdout, extra_run_opts('+RTS -c -RTS')],
 # Skip GHCi due to #2786
 test('T2783', [ omit_ways(['ghci']), exit_code(1)
               , expect_broken_for(2783, ['threaded1'])
-	      ], compile_and_run, [''])
+              ], compile_and_run, [''])
 
 # Test the work-stealing deque implementation.  We run this test in
 # both threaded1 (-threaded -debug) and threaded2 (-threaded) ways.
@@ -99,17 +99,15 @@ test('stack003', [ omit_ways('ghci'), # uses unboxed tuples
 
 # Test that +RTS -K0 (e.g. no stack limit) parses correctly
 test('stack004', [ extra_run_opts('+RTS -K0 -RTS')
-		 , expect_broken_for(14913, ['ghci'])
-		 ], compile_and_run, [''])
+                 , expect_broken_for(14913, ['ghci'])
+                 ], compile_and_run, [''])
 
 test('atomicinc', [ c_src, only_ways(['normal','threaded1', 'threaded2']) ], compile_and_run, [''])
 test('atomicxchg', [ c_src, only_ways(['threaded1', 'threaded2']) ],
 compile_and_run, [''])
 
 test('T3424',
-     [ # Skip due to non-deterministic timeouts on CI, see Trac #16349
-       when(unregisterised(), skip),
-       # And it's slow in general
+     [ when(unregisterised(), fragile(16349)),
        when(fast(), skip),
        only_ways(['normal','threaded1','ghci'])
      ],
@@ -219,7 +217,7 @@ test('T5435_v_asm_a', [extra_files(['T5435.hs', 'T5435_asm.c']),
 test('T5435_v_asm_b', [extra_files(['T5435.hs', 'T5435_asm.c']),
                       when(arch('powerpc64') or arch('powerpc64le'),
                           expect_broken(11259)),
-		      when(opsys('darwin') or opsys('mingw32'), skip)],
+                      when(opsys('darwin') or opsys('mingw32'), skip)],
      makefile_test, ['T5435_v_asm_b'])
 test('T5435_v_gcc', [extra_files(['T5435.hs', 'T5435_gcc.c']),
                      when(arch('powerpc64') or arch('powerpc64le'),
@@ -413,8 +411,8 @@ test('T13617', [ unless(opsys('mingw32'), skip)],
 # Test is being skipped on darwin due to it's flakiness.
 test('T12903', [ when(opsys('mingw32'), skip)
                , when(opsys('darwin'), skip)
-	           , omit_ways(['ghci', 'profasm'])]
-	       , compile_and_run, [''])
+               , omit_ways(['ghci', 'profasm'])]
+               , compile_and_run, [''])
 
 test('T13832', exit_code(1), compile_and_run, ['-threaded'])
 test('T13894', normal, compile_and_run, [''])



More information about the ghc-commits mailing list