[commit: ghc] master: Test Trac #10524 (0e1e798)

git at git.haskell.org git at git.haskell.org
Fri Jun 26 16:53:34 UTC 2015


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/0e1e7987bdcec0e9be309cbe97fa1c92551997f7/ghc

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

commit 0e1e7987bdcec0e9be309cbe97fa1c92551997f7
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Fri Jun 26 16:00:45 2015 +0100

    Test Trac #10524


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

0e1e7987bdcec0e9be309cbe97fa1c92551997f7
 testsuite/tests/deriving/should_fail/T10524.hs     |  8 ++++++++
 testsuite/tests/deriving/should_fail/T10524.stderr | 10 ++++++++++
 testsuite/tests/deriving/should_fail/all.T         |  1 +
 3 files changed, 19 insertions(+)

diff --git a/testsuite/tests/deriving/should_fail/T10524.hs b/testsuite/tests/deriving/should_fail/T10524.hs
new file mode 100644
index 0000000..43d93bf
--- /dev/null
+++ b/testsuite/tests/deriving/should_fail/T10524.hs
@@ -0,0 +1,8 @@
+{-# LANGUAGE DeriveDataTypeable #-}
+{-# LANGUAGE PolyKinds #-}
+module T10524 where
+
+import Data.Data
+
+newtype WrappedFunctor f a = WrapFunctor (f a) deriving (Data, Typeable)
+
diff --git a/testsuite/tests/deriving/should_fail/T10524.stderr b/testsuite/tests/deriving/should_fail/T10524.stderr
new file mode 100644
index 0000000..1569972
--- /dev/null
+++ b/testsuite/tests/deriving/should_fail/T10524.stderr
@@ -0,0 +1,10 @@
+
+T10524.hs:7:58: error:
+    No instance for (Typeable WrappedFunctor)
+      arising from the 'deriving' clause of a data type declaration
+      GHC can't yet do polykinded
+        Typeable (WrappedFunctor :: (k -> *) -> k -> *)
+    Possible fix:
+      use a standalone 'deriving instance' declaration,
+        so you can specify the instance context yourself
+    When deriving the instance for (Data (WrappedFunctor f a))
diff --git a/testsuite/tests/deriving/should_fail/all.T b/testsuite/tests/deriving/should_fail/all.T
index adc72fc..2e25113 100644
--- a/testsuite/tests/deriving/should_fail/all.T
+++ b/testsuite/tests/deriving/should_fail/all.T
@@ -54,3 +54,4 @@ test('T9071_2', normal, compile_fail, [''])
 test('T9687', normal, compile_fail, [''])
 
 test('T8984', normal, compile_fail, [''])
+test('T10524', normal, compile_fail, [''])



More information about the ghc-commits mailing list