[commit: testsuite] master: Test Trac #7959 (c746681)
Simon Peyton Jones
simonpj at microsoft.com
Thu Jun 6 14:46:56 CEST 2013
Repository : ssh://darcs.haskell.org//srv/darcs/testsuite
On branch : master
https://github.com/ghc/testsuite/commit/c746681e68b1f85584493bd2d543e867eaa672c5
>---------------------------------------------------------------
commit c746681e68b1f85584493bd2d543e867eaa672c5
Author: Krzysztof Gogolewski <krz.gogolewski at gmail.com>
Date: Mon Jun 3 17:08:35 2013 +0200
Test Trac #7959
>---------------------------------------------------------------
tests/deriving/should_fail/T7959.hs | 6 ++++++
tests/deriving/should_fail/T7959.stderr | 8 ++++++++
tests/deriving/should_fail/all.T | 1 +
3 files changed, 15 insertions(+), 0 deletions(-)
diff --git a/tests/deriving/should_fail/T7959.hs b/tests/deriving/should_fail/T7959.hs
new file mode 100644
index 0000000..a798bb0
--- /dev/null
+++ b/tests/deriving/should_fail/T7959.hs
@@ -0,0 +1,6 @@
+{-# LANGUAGE NullaryTypeClasses, StandaloneDeriving #-}
+module T7959 where
+
+class A
+deriving instance A
+data B deriving A
diff --git a/tests/deriving/should_fail/T7959.stderr b/tests/deriving/should_fail/T7959.stderr
new file mode 100644
index 0000000..0e805a6
--- /dev/null
+++ b/tests/deriving/should_fail/T7959.stderr
@@ -0,0 +1,8 @@
+
+T7959.hs:5:1:
+ Cannot derive instances for nullary classes
+ In the stand-alone deriving instance for âAâ
+
+T7959.hs:6:17:
+ Cannot derive instances for nullary classes
+ In the data declaration for âBâ
diff --git a/tests/deriving/should_fail/all.T b/tests/deriving/should_fail/all.T
index ad96a11..c2d304e 100644
--- a/tests/deriving/should_fail/all.T
+++ b/tests/deriving/should_fail/all.T
@@ -40,3 +40,4 @@ test('T1133A',
run_command,
['$MAKE --no-print-directory -s T1133A'])
test('T5863a', normal, compile_fail, [''])
+test('T7959', normal, compile_fail, [''])
More information about the ghc-commits
mailing list