Repository : ssh://darcs.haskell.org//srv/darcs/packages/base

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/a5b99c1a7fb2835b38efd5a94b45c3448287008b

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

commit a5b99c1a7fb2835b38efd5a94b45c3448287008b
Author: Simon Peyton Jones <[email protected]>
Date:   Fri Mar 30 12:54:34 2012 +0100

    Test Trac #5962

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

 tests/T5962.hs                         |    8 ++++++++
 tests/{IO/4808.stdout => T5962.stdout} |    0 
 tests/all.T                            |    1 +
 3 files changed, 9 insertions(+), 0 deletions(-)

diff --git a/tests/T5962.hs b/tests/T5962.hs
new file mode 100644
index 0000000..92a130d
--- /dev/null
+++ b/tests/T5962.hs
@@ -0,0 +1,8 @@
+module Main where
+
+import Data.Typeable
+
+unitToUnit_a = typeOf (\() -> ())
+unitToUnit_b = mkFunTy (typeOf ()) (typeOf ())
+
+main = print (unitToUnit_a == unitToUnit_b)
diff --git a/tests/IO/4808.stdout b/tests/T5962.stdout
similarity index 100%
copy from tests/IO/4808.stdout
copy to tests/T5962.stdout
diff --git a/tests/all.T b/tests/all.T
index ae00389..aaa476c 100644
--- a/tests/all.T
+++ b/tests/all.T
@@ -117,4 +117,5 @@ test('weak001', normal, compile_and_run, [''])
 test('4006', if_msys(expect_fail), compile_and_run, [''])
 
 test('5943', normal, compile_and_run, [''])
+test('T5962', normal, compile_and_run, [''])
 



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

Reply via email to