[commit: testsuite] master: Test #8492 (d5872bb)

git at git.haskell.org git at git.haskell.org
Fri Nov 1 12:22:10 UTC 2013


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

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

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

commit d5872bb88d77ecc579f0e2feb95a2ffcfeea9bbb
Author: Krzysztof Gogolewski <krz.gogolewski at gmail.com>
Date:   Fri Nov 1 12:34:48 2013 +0100

    Test #8492


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

d5872bb88d77ecc579f0e2feb95a2ffcfeea9bbb
 tests/typecheck/should_run/T8492.hs                              |    6 ++++++
 .../cgrun033.stdout => typecheck/should_run/T8492.stdout}        |    0
 tests/typecheck/should_run/all.T                                 |    1 +
 3 files changed, 7 insertions(+)

diff --git a/tests/typecheck/should_run/T8492.hs b/tests/typecheck/should_run/T8492.hs
new file mode 100644
index 0000000..0fe5a14
--- /dev/null
+++ b/tests/typecheck/should_run/T8492.hs
@@ -0,0 +1,6 @@
+module Main where
+
+x :: ((->) Int) Bool
+x = (==0)
+
+main = print $ x 0
diff --git a/tests/codeGen/should_run/cgrun033.stdout b/tests/typecheck/should_run/T8492.stdout
similarity index 100%
copy from tests/codeGen/should_run/cgrun033.stdout
copy to tests/typecheck/should_run/T8492.stdout
diff --git a/tests/typecheck/should_run/all.T b/tests/typecheck/should_run/all.T
index 410a199..fe87cec 100755
--- a/tests/typecheck/should_run/all.T
+++ b/tests/typecheck/should_run/all.T
@@ -113,3 +113,4 @@ test('T7861', exit_code(1), compile_and_run, [''])
 test('TcTypeNatSimpleRun', normal, compile_and_run, [''])
 test('TcCoercible', when(compiler_lt('ghc', '7.7'), skip), compile_and_run, [''])
 test('T8119', normal, ghci_script, ['T8119.script'])
+test('T8492', normal, compile_and_run, [''])



More information about the ghc-commits mailing list