[commit: testsuite] master: Added testcase for Trac #7681, a Template Haskell missing feature. (ab6e671)

Richard Eisenberg eir at cis.upenn.edu
Tue Feb 12 05:10:47 CET 2013


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

On branch  : master

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

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

commit ab6e6711358704cc40cf26935dd7a36ae10ada25
Author: Richard Eisenberg <eir at cis.upenn.edu>
Date:   Mon Feb 11 23:06:41 2013 -0500

    Added testcase for Trac #7681, a Template Haskell missing feature.

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

 tests/th/T7681.hs |   12 ++++++++++++
 tests/th/all.T    |    1 +
 2 files changed, 13 insertions(+), 0 deletions(-)

diff --git a/tests/th/T7681.hs b/tests/th/T7681.hs
new file mode 100644
index 0000000..c7f43e7
--- /dev/null
+++ b/tests/th/T7681.hs
@@ -0,0 +1,12 @@
+{-# LANGUAGE EmptyCase, TemplateHaskell, LambdaCase #-}
+
+module T7681 where
+
+data Void
+
+foo :: Void -> a
+foo x = $( [| case x of {} |] )
+
+bar :: Void -> a
+bar = $( [| \case {} |] )
+
diff --git a/tests/th/all.T b/tests/th/all.T
index caaa3df..b279dcd 100644
--- a/tests/th/all.T
+++ b/tests/th/all.T
@@ -269,3 +269,4 @@ test('T7532',
      ['T7532', '-v0'])
 test('T2222', normal, compile, ['-v0'])
 test('T1849', normal, ghci_script, ['T1849.script'])
+test('T7681', normal, compile, ['-v0'])
\ No newline at end of file





More information about the ghc-commits mailing list