summaryrefslogtreecommitdiff
path: root/testsuite/tests/deriving
diff options
context:
space:
mode:
authorSimon Peyton Jones <simonpj@microsoft.com>2014-03-07 16:45:55 +0000
committerSimon Peyton Jones <simonpj@microsoft.com>2014-03-07 16:51:37 +0000
commitcdac487bcd9928d77738f6e79ead7b9bb4bc00fd (patch)
tree76a3750754f317b81987e00a66c4ce188eecf181 /testsuite/tests/deriving
parent3efcb0a7d147e05f86501783144bcd0ad3757e93 (diff)
downloadhaskell-cdac487bcd9928d77738f6e79ead7b9bb4bc00fd.tar.gz
Make -XDeriveFunctor more generous about non-last arguments (Trac #8678)
When deriving Functor, Foldable, Traversable, we need only look at the way that the last type argument is treated. It's fine for there to be existentials etc, provided they don't affect the last type argument. See Note [Check that the type variable is truly universal] in TcDeriv.
Diffstat (limited to 'testsuite/tests/deriving')
-rw-r--r--testsuite/tests/deriving/should_compile/T8678.hs12
-rw-r--r--testsuite/tests/deriving/should_compile/all.T3
-rw-r--r--testsuite/tests/deriving/should_fail/T3101.stderr2
3 files changed, 15 insertions, 2 deletions
diff --git a/testsuite/tests/deriving/should_compile/T8678.hs b/testsuite/tests/deriving/should_compile/T8678.hs
new file mode 100644
index 0000000000..655f530b5b
--- /dev/null
+++ b/testsuite/tests/deriving/should_compile/T8678.hs
@@ -0,0 +1,12 @@
+{-# LANGUAGE DataKinds, DeriveFunctor, FlexibleInstances, GADTs, KindSignatures, StandaloneDeriving #-}
+module T8678 where
+
+data {- kind -} Nat = Z | S Nat
+
+-- GADT in parameter other than the last
+data NonStandard :: Nat -> * -> * -> * where
+ Standard :: a -> NonStandard (S n) a b
+ Non :: NonStandard n a b -> b -> NonStandard (S n) a b
+
+deriving instance (Show a, Show b) => Show (NonStandard n a b)
+deriving instance Functor (NonStandard n a)
diff --git a/testsuite/tests/deriving/should_compile/all.T b/testsuite/tests/deriving/should_compile/all.T
index 8620c36dc5..5d9c7337f1 100644
--- a/testsuite/tests/deriving/should_compile/all.T
+++ b/testsuite/tests/deriving/should_compile/all.T
@@ -44,4 +44,5 @@ test('AutoDeriveTypeable', normal, compile, [''])
test('T8138', reqlib('primitive'), compile, ['-O2'])
test('T8631', normal, compile, [''])
test('T8758', extra_clean(['T8758a.o', 'T8758a.hi']), multimod_compile, ['T8758a', '-v0'])
-test('T8851', expect_broken(8851), compile, ['']) \ No newline at end of file
+test('T8851', expect_broken(8851), compile, [''])
+test('T8678', normal, compile, [''])
diff --git a/testsuite/tests/deriving/should_fail/T3101.stderr b/testsuite/tests/deriving/should_fail/T3101.stderr
index 58069283dc..7c976178c4 100644
--- a/testsuite/tests/deriving/should_fail/T3101.stderr
+++ b/testsuite/tests/deriving/should_fail/T3101.stderr
@@ -1,6 +1,6 @@
T3101.hs:9:12:
Can't make a derived instance of ‘Show Boom’:
- Constructor ‘Boom’ must have a Haskell-98 type
+ Constructor ‘Boom’ has a higher-rank type
Possible fix: use a standalone deriving declaration instead
In the data declaration for ‘Boom’