[commit: ghc] master: Test Trac #7862 (2b67b8f)

git at git.haskell.org git at git.haskell.org
Tue Nov 11 13:10:24 UTC 2014


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/2b67b8f9b259c95ef9394c3a8ff801dc00e968d9/ghc

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

commit 2b67b8f9b259c95ef9394c3a8ff801dc00e968d9
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Tue Nov 11 13:06:21 2014 +0000

    Test Trac #7862


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

2b67b8f9b259c95ef9394c3a8ff801dc00e968d9
 testsuite/tests/indexed-types/should_fail/T7862.hs    | 19 +++++++++++++++++++
 .../tests/indexed-types/should_fail/T7862.stderr      | 17 +++++++++++++++++
 testsuite/tests/indexed-types/should_fail/all.T       |  2 +-
 3 files changed, 37 insertions(+), 1 deletion(-)

diff --git a/testsuite/tests/indexed-types/should_fail/T7862.hs b/testsuite/tests/indexed-types/should_fail/T7862.hs
new file mode 100644
index 0000000..98b99ab
--- /dev/null
+++ b/testsuite/tests/indexed-types/should_fail/T7862.hs
@@ -0,0 +1,19 @@
+{-# LANGUAGE TypeFamilies, FlexibleContexts #-}
+
+module T7862 where
+
+type family Scalar t
+
+newtype Tower s a = Tower [a]
+
+type instance Scalar (Tower s a) = a
+
+class (Num (Scalar t), Num t) => Mode t where
+    (<+>) :: t -> t -> t
+
+instance (Num a) => Mode (Tower s a) where
+    Tower as <+> _ = undefined
+      where
+        _ = (Tower as) <+> (Tower as)
+
+instance Num a => Num (Tower s a) where
diff --git a/testsuite/tests/indexed-types/should_fail/T7862.stderr b/testsuite/tests/indexed-types/should_fail/T7862.stderr
new file mode 100644
index 0000000..c2583d8
--- /dev/null
+++ b/testsuite/tests/indexed-types/should_fail/T7862.stderr
@@ -0,0 +1,17 @@
+
+T7862.hs:17:24:
+    Overlapping instances for Num (Tower s0 a)
+      arising from a use of ‘<+>’
+    Matching givens (or their superclasses):
+      (Num (Tower s a))
+        bound by the instance declaration at T7862.hs:14:10-36
+    Matching instances:
+      instance Num a => Num (Tower s a) -- Defined at T7862.hs:19:10
+    (The choice depends on the instantiation of ‘a, s0’)
+    In the expression: (Tower as) <+> (Tower as)
+    In a pattern binding: _ = (Tower as) <+> (Tower as)
+    In an equation for ‘<+>’:
+        (Tower as) <+> _
+          = undefined
+          where
+              _ = (Tower as) <+> (Tower as)
diff --git a/testsuite/tests/indexed-types/should_fail/all.T b/testsuite/tests/indexed-types/should_fail/all.T
index 0fbee70..286360a 100644
--- a/testsuite/tests/indexed-types/should_fail/all.T
+++ b/testsuite/tests/indexed-types/should_fail/all.T
@@ -130,4 +130,4 @@ test('T9433', normal, compile_fail, [''])
 test('BadSock', normal, compile_fail, [''])
 test('T9580', normal, multimod_compile_fail, ['T9580', ''])
 test('T9662', normal, compile_fail, [''])
-
+test('T7862', normal, compile_fail, [''])



More information about the ghc-commits mailing list