[commit: testsuite] master: Test Trac #8570 (162765e)

git at git.haskell.org git at git.haskell.org
Fri Nov 29 07:32:10 UTC 2013


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

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

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

commit 162765e02c0b2acfc731d47362c37db6cf00fcdf
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Fri Nov 29 07:30:09 2013 +0000

    Test Trac #8570


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

162765e02c0b2acfc731d47362c37db6cf00fcdf
 tests/typecheck/should_fail/T8570.hs     |    7 +++++++
 tests/typecheck/should_fail/T8570.stderr |    6 ++++++
 tests/typecheck/should_fail/T8570a.hs    |    3 +++
 tests/typecheck/should_fail/T8570b.hs    |    3 +++
 tests/typecheck/should_fail/all.T        |    2 ++
 5 files changed, 21 insertions(+)

diff --git a/tests/typecheck/should_fail/T8570.hs b/tests/typecheck/should_fail/T8570.hs
new file mode 100644
index 0000000..4542160
--- /dev/null
+++ b/tests/typecheck/should_fail/T8570.hs
@@ -0,0 +1,7 @@
+module T8570 where
+
+import T8570a (Image(filepath), logo)
+import T8570b (Field(Image))
+
+foo = let Image {filepath = x} = logo in x
+
diff --git a/tests/typecheck/should_fail/T8570.stderr b/tests/typecheck/should_fail/T8570.stderr
new file mode 100644
index 0000000..18653ea
--- /dev/null
+++ b/tests/typecheck/should_fail/T8570.stderr
@@ -0,0 +1,6 @@
+
+T8570.hs:6:18:
+    Constructor ‛Image’ does not have field ‛filepath’
+    In the pattern: Image {filepath = x}
+    In a pattern binding: Image {filepath = x} = logo
+    In the expression: let Image {filepath = x} = logo in x
diff --git a/tests/typecheck/should_fail/T8570a.hs b/tests/typecheck/should_fail/T8570a.hs
new file mode 100644
index 0000000..32bea50
--- /dev/null
+++ b/tests/typecheck/should_fail/T8570a.hs
@@ -0,0 +1,3 @@
+module T8570a where
+data Image = Image { filepath :: () }
+logo = Image ()
\ No newline at end of file
diff --git a/tests/typecheck/should_fail/T8570b.hs b/tests/typecheck/should_fail/T8570b.hs
new file mode 100644
index 0000000..c293fd6
--- /dev/null
+++ b/tests/typecheck/should_fail/T8570b.hs
@@ -0,0 +1,3 @@
+module T8570b where
+
+data Field = Image
diff --git a/tests/typecheck/should_fail/all.T b/tests/typecheck/should_fail/all.T
index 0050d65..93eb007 100644
--- a/tests/typecheck/should_fail/all.T
+++ b/tests/typecheck/should_fail/all.T
@@ -327,3 +327,5 @@ test('T8450', normal, compile_fail, [''])
 test('T8514', normal, compile_fail, [''])
 test('ContextStack1', normal, compile_fail, ['-fcontext-stack=10'])
 test('ContextStack2', normal, compile_fail, ['-ftype-function-depth=10'])
+test('T8570', extra_clean(['T85570a.o', 'T8570a.hi','T85570b.o', 'T8570b.hi']),
+     multimod_compile_fail, ['T8570', '-v0'])



More information about the ghc-commits mailing list