Repository : ssh://darcs.haskell.org//srv/darcs/testsuite

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/2ca9e3a0ecf969531a6b68414ed2775e6511d4e1

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

commit 2ca9e3a0ecf969531a6b68414ed2775e6511d4e1
Author: Simon Peyton Jones <[email protected]>
Date:   Sat Jun 11 14:44:01 2011 +0100

    Test Trac #2436

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

 tests/ghc-regress/rename/should_compile/T2436.hs  |   14 ++++++++++++++
 tests/ghc-regress/rename/should_compile/T2436a.hs |    4 ++++
 tests/ghc-regress/rename/should_compile/all.T     |    5 +++++
 3 files changed, 23 insertions(+), 0 deletions(-)

diff --git a/tests/ghc-regress/rename/should_compile/T2436.hs 
b/tests/ghc-regress/rename/should_compile/T2436.hs
new file mode 100644
index 0000000..5cfd641
--- /dev/null
+++ b/tests/ghc-regress/rename/should_compile/T2436.hs
@@ -0,0 +1,14 @@
+{-# LANGUAGE TypeFamilies #-}
+{-# OPTIONS_GHC -fwarn-duplicate-exports #-}
+
+module T2436( C(..), T(..), module T2436a, S(..) ) where
+
+import T2436a
+
+class C a where
+  data T a
+
+instance C Int where
+  data T Int = TInt Int
+
+data instance S Int = SInt
\ No newline at end of file
diff --git a/tests/ghc-regress/rename/should_compile/T2436a.hs 
b/tests/ghc-regress/rename/should_compile/T2436a.hs
new file mode 100644
index 0000000..4813fd9
--- /dev/null
+++ b/tests/ghc-regress/rename/should_compile/T2436a.hs
@@ -0,0 +1,4 @@
+{-# LANGUAGE TypeFamilies #-}
+module T2436a( S ) where
+
+data family S a
\ No newline at end of file
diff --git a/tests/ghc-regress/rename/should_compile/all.T 
b/tests/ghc-regress/rename/should_compile/all.T
index dd1d7d4..73eda29 100644
--- a/tests/ghc-regress/rename/should_compile/all.T
+++ b/tests/ghc-regress/rename/should_compile/all.T
@@ -170,3 +170,8 @@ test('mc09', normal, compile, [''])
 test('mc10', normal, compile, [''])
 test('mc11', normal, compile, [''])
 test('mc12', normal, compile, [''])
+test('T2436',
+     [ only_compiler_types(['ghc']),
+       extra_clean(['T2436a.hi', 'T2436a.o']) ],
+     multimod_compile,
+     ['T2436', '-v0'])



_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to