[commit: ghc] ghc-7.8: Test #9371 (indexed-types/should_fail/T9371) (2085bd3)

git at git.haskell.org git at git.haskell.org
Mon Dec 15 15:03:57 UTC 2014


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

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

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

commit 2085bd38a84777edc64fc50ac8ed2f45d513de07
Author: Richard Eisenberg <eir at cis.upenn.edu>
Date:   Sun Aug 3 17:54:54 2014 -0400

    Test #9371 (indexed-types/should_fail/T9371)
    
    (cherry picked from commit a09508b792eed24fc4d8a363df2635026bfa2de6)


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

2085bd38a84777edc64fc50ac8ed2f45d513de07
 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 dde335d..cca56db 100644
--- a/testsuite/tests/indexed-types/should_fail/all.T
+++ b/testsuite/tests/indexed-types/should_fail/all.T
@@ -121,3 +121,4 @@ test('T8368a', normal, compile_fail, [''])
 test('T8518', normal, compile_fail, [''])
 test('T9160', normal, compile_fail, [''])
 test('T9433', normal, compile_fail, [''])
+test('T9371', normal, compile_fail, [''])



More information about the ghc-commits mailing list