Repository : ssh://darcs.haskell.org//srv/darcs/testsuite

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/3f93d3714af8413876d304f43b0f1c0dec663682

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

commit 3f93d3714af8413876d304f43b0f1c0dec663682
Author: Simon Peyton Jones <[email protected]>
Date:   Wed Aug 29 11:34:32 2012 +0100

    Teat Trac #7175

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

 tests/typecheck/should_fail/T7175.hs     |   11 +++++++++++
 tests/typecheck/should_fail/T7175.stderr |    6 ++++++
 tests/typecheck/should_fail/all.T        |    1 +
 3 files changed, 18 insertions(+), 0 deletions(-)

diff --git a/tests/typecheck/should_fail/T7175.hs 
b/tests/typecheck/should_fail/T7175.hs
new file mode 100644
index 0000000..909834c
--- /dev/null
+++ b/tests/typecheck/should_fail/T7175.hs
@@ -0,0 +1,11 @@
+{-# LANGUAGE TypeFamilies, GADTs #-}
+
+module T7175 where
+
+type family F a
+
+data G1 a where
+   G1C :: F Int
+
+data G2 a where
+   G2C :: F Int
diff --git a/tests/typecheck/should_fail/T7175.stderr 
b/tests/typecheck/should_fail/T7175.stderr
new file mode 100644
index 0000000..92272b6
--- /dev/null
+++ b/tests/typecheck/should_fail/T7175.stderr
@@ -0,0 +1,6 @@
+
+T7175.hs:8:4:
+    Data constructor `G1C' returns type `F Int'
+      instead of an instance of its parent type `G1 a'
+    In the definition of data constructor `G1C'
+    In the data declaration for `G1'
diff --git a/tests/typecheck/should_fail/all.T 
b/tests/typecheck/should_fail/all.T
index c7e3474..7e6f208 100644
--- a/tests/typecheck/should_fail/all.T
+++ b/tests/typecheck/should_fail/all.T
@@ -280,3 +280,4 @@ test('T7019a', normal, compile_fail,[''])
 test('T5978', normal, compile_fail, [''])
 test('TcMultiWayIfFail', if_compiler_lt('ghc', '7.5', skip), compile_fail, 
[''])
 test('T2534', normal, compile_fail, [''])
+test('T7175', normal, compile_fail, [''])



_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to