[commit: ghc] master: Test case for #9305 (47640ca)

git at git.haskell.org git at git.haskell.org
Sat Jul 12 22:28:04 UTC 2014


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/47640ca4e5cdb2882f0b30dec7b34f8c5c734171/ghc

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

commit 47640ca4e5cdb2882f0b30dec7b34f8c5c734171
Author: Joachim Breitner <mail at joachim-breitner.de>
Date:   Sun Jul 13 00:27:54 2014 +0200

    Test case for #9305


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

47640ca4e5cdb2882f0b30dec7b34f8c5c734171
 testsuite/tests/typecheck/should_fail/T9305.hs     | 8 ++++++++
 testsuite/tests/typecheck/should_fail/T9305.stderr | 8 ++++++++
 testsuite/tests/typecheck/should_fail/all.T        | 2 +-
 3 files changed, 17 insertions(+), 1 deletion(-)

diff --git a/testsuite/tests/typecheck/should_fail/T9305.hs b/testsuite/tests/typecheck/should_fail/T9305.hs
new file mode 100644
index 0000000..b6ad3b7
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/T9305.hs
@@ -0,0 +1,8 @@
+{-# LANGUAGE DeriveFunctor#-}
+module Main where
+
+data Event a b = Event a deriving (Functor)
+
+newtype F f = F (f (F f))
+
+data EventF a = EventF (F (Event a)) deriving (Functor)
diff --git a/testsuite/tests/typecheck/should_fail/T9305.stderr b/testsuite/tests/typecheck/should_fail/T9305.stderr
new file mode 100644
index 0000000..1610423
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/T9305.stderr
@@ -0,0 +1,8 @@
+
+T9305.hs:8:48:
+    No instance for (Functor Event)
+      arising from the first field of ‘EventF’ (type ‘F (Event a)’)
+    Possible fix:
+      use a standalone 'deriving instance' declaration,
+        so you can specify the instance context yourself
+    When deriving the instance for (Functor EventF)
diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T
index a1dab9d..c1dbd58 100644
--- a/testsuite/tests/typecheck/should_fail/all.T
+++ b/testsuite/tests/typecheck/should_fail/all.T
@@ -334,4 +334,4 @@ test('T8912', normal, compile_fail, [''])
 test('T9033', normal, compile_fail, [''])
 test('T8883', normal, compile_fail, [''])
 test('T9196', normal, compile_fail, [''])
-
+test('T9305', normal, compile_fail, [''])



More information about the ghc-commits mailing list