[commit: ghc] master: Test Trac #13300 (499a15d)
git at git.haskell.org
git at git.haskell.org
Tue Feb 21 17:45:02 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/499a15db0d71a9d0b91cbd5f509dabff50df2566/ghc
>---------------------------------------------------------------
commit 499a15db0d71a9d0b91cbd5f509dabff50df2566
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Tue Feb 21 17:44:02 2017 +0000
Test Trac #13300
>---------------------------------------------------------------
499a15db0d71a9d0b91cbd5f509dabff50df2566
testsuite/tests/typecheck/should_fail/T13300.hs | 10 ++++++++++
testsuite/tests/typecheck/should_fail/T13300.stderr | 6 ++++++
testsuite/tests/typecheck/should_fail/all.T | 1 +
3 files changed, 17 insertions(+)
diff --git a/testsuite/tests/typecheck/should_fail/T13300.hs b/testsuite/tests/typecheck/should_fail/T13300.hs
new file mode 100644
index 0000000..2803b42
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/T13300.hs
@@ -0,0 +1,10 @@
+{-# LANGUAGE GADTs #-}
+module T13300 where
+
+data W where
+ WI :: Int
+ WD :: Double
+
+data Superblock
+ = A { f :: W }
+ | B { f :: W }
diff --git a/testsuite/tests/typecheck/should_fail/T13300.stderr b/testsuite/tests/typecheck/should_fail/T13300.stderr
new file mode 100644
index 0000000..5bc8e4d
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/T13300.stderr
@@ -0,0 +1,6 @@
+
+T13300.hs:5:3: error:
+ • Data constructor ‘WI’ returns type ‘Int’
+ instead of an instance of its parent type ‘W’
+ • In the definition of data constructor ‘WI’
+ In the data type declaration for ‘W’
diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T
index e9cad8f..a9c5f80 100644
--- a/testsuite/tests/typecheck/should_fail/all.T
+++ b/testsuite/tests/typecheck/should_fail/all.T
@@ -426,3 +426,4 @@ test('StrictBinds', normal, compile_fail, [''])
test('T13105', normal, compile_fail, [''])
test('LevPolyBounded', normal, compile_fail, [''])
test('T13292', normal, multimod_compile, ['T13292', '-v0 -fdefer-type-errors'])
+test('T13300', normal, compile_fail, [''])
More information about the ghc-commits
mailing list