[commit: ghc] master: Testsuite: benign test fixes (b0569e8)

git at git.haskell.org git at git.haskell.org
Thu Apr 28 18:14:11 UTC 2016


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

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

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

commit b0569e881f66c3e987bc1108ad771a706399f5ff
Author: Thomas Miedema <thomasmiedema at gmail.com>
Date:   Thu Apr 28 17:08:53 2016 +0200

    Testsuite: benign test fixes


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

b0569e881f66c3e987bc1108ad771a706399f5ff
 testsuite/tests/deSugar/should_fail/all.T         | 2 +-
 testsuite/tests/gadt/gadt-fd.hs                   | 5 +++++
 testsuite/tests/gadt/lazypatok.hs                 | 2 +-
 testsuite/tests/parser/unicode/all.T              | 0
 testsuite/tests/partial-sigs/should_compile/all.T | 1 -
 testsuite/tests/programs/okeefe_neural/test.T     | 8 +++++++-
 testsuite/tests/rename/should_fail/all.T          | 0
 testsuite/tests/typecheck/T11824/all.T            | 0
 8 files changed, 14 insertions(+), 4 deletions(-)

diff --git a/testsuite/tests/deSugar/should_fail/all.T b/testsuite/tests/deSugar/should_fail/all.T
index 1a501ba..f403c74 100644
--- a/testsuite/tests/deSugar/should_fail/all.T
+++ b/testsuite/tests/deSugar/should_fail/all.T
@@ -3,4 +3,4 @@
 #	extra run flags
 #	expected process return value, if not zero
 
-test('DsStrictFail', expect_fail, compile_and_run, [''])
+test('DsStrictFail', exit_code(1), compile_and_run, [''])
diff --git a/testsuite/tests/gadt/gadt-fd.hs b/testsuite/tests/gadt/gadt-fd.hs
index 7efac22..7d966c3 100644
--- a/testsuite/tests/gadt/gadt-fd.hs
+++ b/testsuite/tests/gadt/gadt-fd.hs
@@ -1,4 +1,9 @@
 {-# LANGUAGE GADTs #-}
+{-# LANGUAGE MultiParamTypeClasses #-}
+{-# LANGUAGE KindSignatures #-}
+{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE FunctionalDependencies #-}
+{-# LANGUAGE UndecidableInstances #-}
 
 -- Trac #345
 
diff --git a/testsuite/tests/gadt/lazypatok.hs b/testsuite/tests/gadt/lazypatok.hs
index 9903a66..44fae2f 100644
--- a/testsuite/tests/gadt/lazypatok.hs
+++ b/testsuite/tests/gadt/lazypatok.hs
@@ -1,6 +1,6 @@
 {-# LANGUAGE GADTs #-}
 
--- It's not clear whether this one should succed or fail,
+-- It's not clear whether this one should succeed or fail,
 -- Arguably it should succeed because the type refinement on
 -- T1 should make (y::Int).  Currently, though, it fails.
 
diff --git a/testsuite/tests/partial-sigs/should_compile/all.T b/testsuite/tests/partial-sigs/should_compile/all.T
index ba25a11..cc8f478 100644
--- a/testsuite/tests/partial-sigs/should_compile/all.T
+++ b/testsuite/tests/partial-sigs/should_compile/all.T
@@ -29,7 +29,6 @@ test('HigherRank1', normal, compile, ['-ddump-types -fno-warn-partial-type-signa
 test('HigherRank2', normal, compile, ['-ddump-types -fno-warn-partial-type-signatures'])
 test('LocalDefinitionBug', normal, compile, ['-ddump-types -fno-warn-partial-type-signatures'])
 test('Meltdown', normal, compile, ['-ddump-types -fno-warn-partial-type-signatures'])
-# Bug
 test('MonoLocalBinds', normal, compile, ['-ddump-types -fno-warn-partial-type-signatures'])
 test('NamedTyVar', normal, compile, ['-ddump-types -fno-warn-partial-type-signatures'])
 test('NamedWildcardInDataFamilyInstanceLHS', normal, compile, ['-ddump-types -fno-warn-partial-type-signatures'])
diff --git a/testsuite/tests/programs/okeefe_neural/test.T b/testsuite/tests/programs/okeefe_neural/test.T
index e905ec0..e7e1f78 100644
--- a/testsuite/tests/programs/okeefe_neural/test.T
+++ b/testsuite/tests/programs/okeefe_neural/test.T
@@ -1,6 +1,12 @@
 
 # this one causes the compiler to run out of heap in the simplifier
 
+# TODO. What's the purpose of this test? If you give it 100Mb of heap, it
+# compiles fine (though it takes a while). Is that too much?
+# Does the fact that this test is marked expect_fail (instead of expect_broken)
+# mean anything?
+# Is it necessary to also run the resulting program? It doesn't seem to ever
+# complete, at least not in a few minutes. What is the expected output?
 def set_opts( name, opts ):
   opts.expect = 'fail'
 
@@ -9,4 +15,4 @@ test('okeefe_neural',
       set_opts,
       extra_clean(['Main.hi'])],
      multimod_compile_and_run,
-     ['Main', '-package lang +RTS -M64m -RTS'])
+     ['Main', '+RTS -M64m -RTS'])



More information about the ghc-commits mailing list