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

On branch  : master

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

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

commit c1d0a6f6793df8aac2ca8fab5d6c8dcc83b08955
Author: Ian Lynagh <[email protected]>
Date:   Tue Jul 19 20:58:39 2011 +0100

    Add a test for #5332 (unboxed singleton tuples and TH)

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

 tests/ghc-regress/th/TH_unboxedSingleton.hs |    7 +++++++
 tests/ghc-regress/th/all.T                  |    2 ++
 2 files changed, 9 insertions(+), 0 deletions(-)

diff --git a/tests/ghc-regress/th/TH_unboxedSingleton.hs 
b/tests/ghc-regress/th/TH_unboxedSingleton.hs
new file mode 100644
index 0000000..d932285
--- /dev/null
+++ b/tests/ghc-regress/th/TH_unboxedSingleton.hs
@@ -0,0 +1,7 @@
+{-# LANGUAGE TemplateHaskell, UnboxedTuples #-}
+
+module TH_unboxedSingleton where
+
+f :: () -> (# Int #)
+f () = $( [| (# 3 #) |] )
+
diff --git a/tests/ghc-regress/th/all.T b/tests/ghc-regress/th/all.T
index 47ac833..7ca7f09 100644
--- a/tests/ghc-regress/th/all.T
+++ b/tests/ghc-regress/th/all.T
@@ -181,3 +181,5 @@ test('T4949', normal, compile, ['-v0'])
 test('T5126', normal, compile, ['-v0'])
 test('T5217', normal, compile, ['-v0 -dsuppress-uniques -ddump-splices'])
 test('T5037', normal, compile, ['-v0'])
+test('TH_unboxedSingleton', normal, compile, ['-v0'])
+



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

Reply via email to