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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/3e2f2580b2c4196617b25d5a218ad7e360e4c76b

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

commit 3e2f2580b2c4196617b25d5a218ad7e360e4c76b
Author: Dimitrios Vytiniotis <[email protected]>
Date:   Tue Jun 14 18:03:36 2011 +0100

    Test case for canonicalization bug.

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

 .../typecheck/should_compile/GivenTypeSynonym.hs   |   14 ++++++++++++++
 tests/ghc-regress/typecheck/should_compile/all.T   |    1 +
 2 files changed, 15 insertions(+), 0 deletions(-)

diff --git a/tests/ghc-regress/typecheck/should_compile/GivenTypeSynonym.hs 
b/tests/ghc-regress/typecheck/should_compile/GivenTypeSynonym.hs
new file mode 100644
index 0000000..918eb78
--- /dev/null
+++ b/tests/ghc-regress/typecheck/should_compile/GivenTypeSynonym.hs
@@ -0,0 +1,14 @@
+{-# LANGUAGE TypeFamilies #-}
+module Main where 
+
+data A a
+
+type T a = A a
+
+
+f :: (A a ~ T Int) => a -> Int 
+f x = x 
+
+
+main :: IO ()
+main = return ()
\ No newline at end of file
diff --git a/tests/ghc-regress/typecheck/should_compile/all.T 
b/tests/ghc-regress/typecheck/should_compile/all.T
index 4dbbf0d..e7fed26 100644
--- a/tests/ghc-regress/typecheck/should_compile/all.T
+++ b/tests/ghc-regress/typecheck/should_compile/all.T
@@ -343,3 +343,4 @@ test('tc249', normal, compile, [''])
 
 test('GivenOverlapping', normal, compile, [''])
 test('SilentParametersOverlapping', normal, compile, [''])
+test('GivenTypeSynonym', normal, compile, [''])
\ No newline at end of file



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

Reply via email to