[commit: ghc] wip/rae: Test #9371 (indexed-types/should_fail/T9371) (64cd1be)
git at git.haskell.org
git at git.haskell.org
Thu Aug 7 18:07:36 UTC 2014
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/rae
Link : http://ghc.haskell.org/trac/ghc/changeset/64cd1bef7b1d7ffe9825c0635bdc00c2ba3f09ce/ghc
>---------------------------------------------------------------
commit 64cd1bef7b1d7ffe9825c0635bdc00c2ba3f09ce
Author: Richard Eisenberg <eir at cis.upenn.edu>
Date: Sun Aug 3 17:54:54 2014 -0400
Test #9371 (indexed-types/should_fail/T9371)
>---------------------------------------------------------------
64cd1bef7b1d7ffe9825c0635bdc00c2ba3f09ce
testsuite/tests/indexed-types/should_fail/T9371.hs | 25 ++++++++++++++++++++++
.../tests/indexed-types/should_fail/T9371.stderr | 5 +++++
testsuite/tests/indexed-types/should_fail/all.T | 1 +
3 files changed, 31 insertions(+)
diff --git a/testsuite/tests/indexed-types/should_fail/T9371.hs b/testsuite/tests/indexed-types/should_fail/T9371.hs
new file mode 100644
index 0000000..cfec4c0
--- /dev/null
+++ b/testsuite/tests/indexed-types/should_fail/T9371.hs
@@ -0,0 +1,25 @@
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE UndecidableInstances #-}
+
+module T9371 where
+
+import Data.Monoid
+
+class C x where
+ data D x :: *
+ makeD :: D x
+
+instance {-# OVERLAPPABLE #-} Monoid x => C x where
+ data D x = D1 (Either x ())
+ makeD = D1 (Left mempty)
+
+instance (Monoid x, Monoid y) => C (x, y) where
+ data D (x,y) = D2 (x,y)
+ makeD = D2 (mempty, mempty)
+
+instance Show x => Show (D x) where
+ show (D1 x) = show x
+
+
+main = print (makeD :: D (String, String))
diff --git a/testsuite/tests/indexed-types/should_fail/T9371.stderr b/testsuite/tests/indexed-types/should_fail/T9371.stderr
new file mode 100644
index 0000000..695a7b4
--- /dev/null
+++ b/testsuite/tests/indexed-types/should_fail/T9371.stderr
@@ -0,0 +1,5 @@
+
+T9371.hs:14:10:
+ Conflicting family instance declarations:
+ D -- Defined at T9371.hs:14:10
+ D (x, y) -- Defined at T9371.hs:18:10
diff --git a/testsuite/tests/indexed-types/should_fail/all.T b/testsuite/tests/indexed-types/should_fail/all.T
index 0851c08..6d284cf 100644
--- a/testsuite/tests/indexed-types/should_fail/all.T
+++ b/testsuite/tests/indexed-types/should_fail/all.T
@@ -125,3 +125,4 @@ test('T9171', normal, compile_fail, [''])
test('T9097', normal, compile_fail, [''])
test('T9160', normal, compile_fail, [''])
test('T9357', normal, compile_fail, [''])
+test('T9371', normal, compile_fail, [''])
More information about the ghc-commits
mailing list