[commit: ghc] ghc-7.8: Test #6147, which was fixed with the roles commit. (d99fcc1)

git at git.haskell.org git at git.haskell.org
Mon Feb 17 09:15:18 UTC 2014


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

On branch  : ghc-7.8
Link       : http://ghc.haskell.org/trac/ghc/changeset/d99fcc16581a752711eabdb07ef1d39a1798dff6/ghc

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

commit d99fcc16581a752711eabdb07ef1d39a1798dff6
Author: Richard Eisenberg <eir at cis.upenn.edu>
Date:   Sun Feb 9 11:25:42 2014 -0500

    Test #6147, which was fixed with the roles commit.
    
    (cherry picked from commit 9e0c1ae57526bacaca044a7ce5a6491fb6a7cb42)


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

d99fcc16581a752711eabdb07ef1d39a1798dff6
 testsuite/tests/deriving/should_fail/T6147.hs     |   13 +++++++++++++
 testsuite/tests/deriving/should_fail/T6147.stderr |   11 +++++++++++
 testsuite/tests/deriving/should_fail/all.T        |    1 +
 3 files changed, 25 insertions(+)

diff --git a/testsuite/tests/deriving/should_fail/T6147.hs b/testsuite/tests/deriving/should_fail/T6147.hs
new file mode 100644
index 0000000..f57f5af
--- /dev/null
+++ b/testsuite/tests/deriving/should_fail/T6147.hs
@@ -0,0 +1,13 @@
+{-# LANGUAGE GeneralizedNewtypeDeriving, TypeFamilies #-}
+module T6147 where
+
+data family T a
+data instance T Int = T_Int Int
+
+class C a where
+  foo :: a -> T a
+
+instance C Int where
+  foo = T_Int
+
+newtype Foo = Foo Int deriving(C)
diff --git a/testsuite/tests/deriving/should_fail/T6147.stderr b/testsuite/tests/deriving/should_fail/T6147.stderr
new file mode 100644
index 0000000..ffe584c
--- /dev/null
+++ b/testsuite/tests/deriving/should_fail/T6147.stderr
@@ -0,0 +1,11 @@
+
+T6147.hs:13:32:
+    Could not coerce from ‛T Int’ to ‛T Foo’
+      because the first type argument of ‛T’ has role Nominal,
+      but the arguments ‛Int’ and ‛Foo’ differ
+      arising from the coercion of the method ‛foo’ from type
+                   ‛Int -> T Int’ to type ‛Foo -> T Foo’
+    Possible fix:
+      use a standalone 'deriving instance' declaration,
+        so you can specify the instance context yourself
+    When deriving the instance for (C Foo)
diff --git a/testsuite/tests/deriving/should_fail/all.T b/testsuite/tests/deriving/should_fail/all.T
index b2b99ff..1ffa5fc 100644
--- a/testsuite/tests/deriving/should_fail/all.T
+++ b/testsuite/tests/deriving/should_fail/all.T
@@ -48,3 +48,4 @@ test('T7148', normal, compile_fail, [''])
 test('T7148a', normal, compile_fail, [''])
 test('T7800', normal, multimod_compile_fail, ['T7800',''])
 test('T5498', normal, compile_fail, [''])
+test('T6147', normal, compile_fail, [''])
\ No newline at end of file



More information about the ghc-commits mailing list