[commit: ghc] wip/rae: Test #9109 in typecheck/should_fail/T9109 (e476202)
git at git.haskell.org
git at git.haskell.org
Tue Nov 18 20:22:16 UTC 2014
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/rae
Link : http://ghc.haskell.org/trac/ghc/changeset/e476202322624457f17081f3527b96636a989988/ghc
>---------------------------------------------------------------
commit e476202322624457f17081f3527b96636a989988
Author: Richard Eisenberg <eir at cis.upenn.edu>
Date: Tue Nov 18 15:19:20 2014 -0500
Test #9109 in typecheck/should_fail/T9109
>---------------------------------------------------------------
e476202322624457f17081f3527b96636a989988
testsuite/tests/typecheck/should_fail/T9109.hs | 8 ++++++++
testsuite/tests/typecheck/should_fail/T9109.stderr | 15 +++++++++++++++
testsuite/tests/typecheck/should_fail/all.T | 1 +
3 files changed, 24 insertions(+)
diff --git a/testsuite/tests/typecheck/should_fail/T9109.hs b/testsuite/tests/typecheck/should_fail/T9109.hs
new file mode 100644
index 0000000..725cb66
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/T9109.hs
@@ -0,0 +1,8 @@
+{-# LANGUAGE GADTs #-}
+
+module T9109 where
+
+data G a where
+ GBool :: G Bool
+
+foo GBool = True
diff --git a/testsuite/tests/typecheck/should_fail/T9109.stderr b/testsuite/tests/typecheck/should_fail/T9109.stderr
new file mode 100644
index 0000000..5ef2340
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/T9109.stderr
@@ -0,0 +1,15 @@
+
+T9109.hs:8:13:
+ Couldn't match expected type ‘t’ with actual type ‘Bool’
+ ‘t’ is untouchable
+ inside the constraints (t1 ~ Bool)
+ bound by a pattern with constructor
+ GBool :: G Bool,
+ in an equation for ‘foo’
+ at T9109.hs:8:5-9
+ ‘t’ is a rigid type variable bound by
+ the inferred type of foo :: G t1 -> t at T9109.hs:8:1
+ Possible fix: add a type signature for ‘foo’
+ Relevant bindings include foo :: G t1 -> t (bound at T9109.hs:8:1)
+ In the expression: True
+ In an equation for ‘foo’: foo GBool = True
diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T
index 14df71e..28709e8 100644
--- a/testsuite/tests/typecheck/should_fail/all.T
+++ b/testsuite/tests/typecheck/should_fail/all.T
@@ -344,3 +344,4 @@ test('T9739', normal, compile_fail, [''])
test('T9774', normal, compile_fail, [''])
test('T9318', normal, compile_fail, [''])
test('T9201', normal, compile_fail, [''])
+test('T9109', normal, compile_fail, [''])
More information about the ghc-commits
mailing list