[commit: ghc] master: Adding missing test files for #9071 (59b4e6d)
git at git.haskell.org
git at git.haskell.org
Tue May 6 08:46:27 UTC 2014
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/59b4e6d0ba504b33cc7064d489b8ec485a7703f4/ghc
>---------------------------------------------------------------
commit 59b4e6d0ba504b33cc7064d489b8ec485a7703f4
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Tue May 6 09:46:14 2014 +0100
Adding missing test files for #9071
>---------------------------------------------------------------
59b4e6d0ba504b33cc7064d489b8ec485a7703f4
testsuite/tests/deriving/should_fail/T9071-2.hs | 7 +++++++
testsuite/tests/deriving/should_fail/T9071.hs | 8 ++++++++
testsuite/tests/deriving/should_fail/T9071.stderr | 10 ++++++++++
testsuite/tests/deriving/should_fail/T9071_2.hs | 7 +++++++
testsuite/tests/deriving/should_fail/T9071_2.stderr | 8 ++++++++
testsuite/tests/deriving/should_fail/T9071a.hs | 4 ++++
6 files changed, 44 insertions(+)
diff --git a/testsuite/tests/deriving/should_fail/T9071-2.hs b/testsuite/tests/deriving/should_fail/T9071-2.hs
new file mode 100644
index 0000000..7a2f474
--- /dev/null
+++ b/testsuite/tests/deriving/should_fail/T9071-2.hs
@@ -0,0 +1,7 @@
+{-# LANGUAGE DeriveFunctor #-}
+module T9071_2 where
+
+newtype Mu f = Mu (f (Mu f))
+
+newtype K1 a b = K1 a
+newtype F1 a = F1 (Mu (K1 a)) deriving Functor
diff --git a/testsuite/tests/deriving/should_fail/T9071.hs b/testsuite/tests/deriving/should_fail/T9071.hs
new file mode 100644
index 0000000..dc64f42
--- /dev/null
+++ b/testsuite/tests/deriving/should_fail/T9071.hs
@@ -0,0 +1,8 @@
+{-# LANGUAGE DeriveFunctor #-}
+module T9071 where
+
+import T9071a
+
+newtype K a b = K a
+newtype F a = F (Mu (K a)) deriving Functor
+
diff --git a/testsuite/tests/deriving/should_fail/T9071.stderr b/testsuite/tests/deriving/should_fail/T9071.stderr
new file mode 100644
index 0000000..259adba
--- /dev/null
+++ b/testsuite/tests/deriving/should_fail/T9071.stderr
@@ -0,0 +1,10 @@
+[1 of 2] Compiling T9071a ( T9071a.hs, T9071a.o )
+[2 of 2] Compiling T9071 ( T9071.hs, T9071.o )
+
+T9071.hs:7:37:
+ No instance for (Functor K)
+ arising from the first field of ‘F’ (type ‘Mu (K a)’)
+ Possible fix:
+ use a standalone 'deriving instance' declaration,
+ so you can specify the instance context yourself
+ When deriving the instance for (Functor F)
diff --git a/testsuite/tests/deriving/should_fail/T9071_2.hs b/testsuite/tests/deriving/should_fail/T9071_2.hs
new file mode 100644
index 0000000..7a2f474
--- /dev/null
+++ b/testsuite/tests/deriving/should_fail/T9071_2.hs
@@ -0,0 +1,7 @@
+{-# LANGUAGE DeriveFunctor #-}
+module T9071_2 where
+
+newtype Mu f = Mu (f (Mu f))
+
+newtype K1 a b = K1 a
+newtype F1 a = F1 (Mu (K1 a)) deriving Functor
diff --git a/testsuite/tests/deriving/should_fail/T9071_2.stderr b/testsuite/tests/deriving/should_fail/T9071_2.stderr
new file mode 100644
index 0000000..ae0fcdb
--- /dev/null
+++ b/testsuite/tests/deriving/should_fail/T9071_2.stderr
@@ -0,0 +1,8 @@
+
+T9071_2.hs:7:40:
+ No instance for (Functor Mu)
+ arising from the first field of ‘F1’ (type ‘Mu (K1 a)’)
+ Possible fix:
+ use a standalone 'deriving instance' declaration,
+ so you can specify the instance context yourself
+ When deriving the instance for (Functor F1)
diff --git a/testsuite/tests/deriving/should_fail/T9071a.hs b/testsuite/tests/deriving/should_fail/T9071a.hs
new file mode 100644
index 0000000..bf3a126
--- /dev/null
+++ b/testsuite/tests/deriving/should_fail/T9071a.hs
@@ -0,0 +1,4 @@
+module T9071a where
+
+newtype Mu f = Mu (f (Mu f))
+
More information about the ghc-commits
mailing list