[commit: testsuite] master: Test Trac #7861 (e9aa8a7)
Simon Peyton Jones
simonpj at microsoft.com
Fri May 3 08:44:37 CEST 2013
Repository : ssh://darcs.haskell.org//srv/darcs/testsuite
On branch : master
https://github.com/ghc/testsuite/commit/e9aa8a72d1c2a2686f3ce9ad4c6bb651f0419c27
>---------------------------------------------------------------
commit e9aa8a72d1c2a2686f3ce9ad4c6bb651f0419c27
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Thu May 2 14:11:13 2013 +0100
Test Trac #7861
>---------------------------------------------------------------
tests/typecheck/should_run/T7861.hs | 13 +++++++++++++
.../should_run/T7861.stderr} | 0
.../should_run/T7861.stdout} | 0
tests/typecheck/should_run/all.T | 1 +
4 files changed, 14 insertions(+), 0 deletions(-)
diff --git a/tests/typecheck/should_run/T7861.hs b/tests/typecheck/should_run/T7861.hs
new file mode 100644
index 0000000..1f2066c
--- /dev/null
+++ b/tests/typecheck/should_run/T7861.hs
@@ -0,0 +1,13 @@
+{-# LANGUAGE RankNTypes #-}
+{-# OPTIONS_GHC -fdefer-type-errors #-}
+module Main where
+
+type A a = forall b. a
+
+doA :: A a -> [a]
+doA = undefined
+
+f :: A a -> a
+f = doA
+
+main = do { print "Hello"; f `seq` print "Bad" }
diff --git a/tests/deSugar/should_run/T5472.stdout b/tests/typecheck/should_run/T7861.stderr
similarity index 100%
copy from tests/deSugar/should_run/T5472.stdout
copy to tests/typecheck/should_run/T7861.stderr
diff --git a/tests/th/TH_spliceE4.stdout b/tests/typecheck/should_run/T7861.stdout
similarity index 100%
copy from tests/th/TH_spliceE4.stdout
copy to tests/typecheck/should_run/T7861.stdout
diff --git a/tests/typecheck/should_run/all.T b/tests/typecheck/should_run/all.T
index 55d88ec..1d714a2 100755
--- a/tests/typecheck/should_run/all.T
+++ b/tests/typecheck/should_run/all.T
@@ -109,3 +109,4 @@ test('T5751', normal, compile_and_run, [''])
test('T5913', normal, compile_and_run, [''])
test('T7748', normal, compile_and_run, [''])
test('TcNullaryTC', when(compiler_lt('ghc', '7.7'), skip), compile_and_run, [''])
+test('T7861', exit_code(1), compile_and_run, [''])
More information about the ghc-commits
mailing list