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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/5159aff23372adb2edb55976b7ded28b15151cbd

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

commit 5159aff23372adb2edb55976b7ded28b15151cbd
Author: Simon Peyton Jones <[email protected]>
Date:   Thu Sep 29 16:55:58 2011 +0100

    Test Trac #5508

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

 tests/th/T5508.hs     |    9 +++++++++
 tests/th/T5508.stderr |    6 ++++++
 tests/th/all.T        |    1 +
 3 files changed, 16 insertions(+), 0 deletions(-)

diff --git a/tests/th/T5508.hs b/tests/th/T5508.hs
new file mode 100644
index 0000000..ee82e8f
--- /dev/null
+++ b/tests/th/T5508.hs
@@ -0,0 +1,9 @@
+{-# LANGUAGE TemplateHaskell #-}
+
+module T5508 where
+
+import Language.Haskell.TH
+
+thb = $(do { let x = mkName "x"
+                 v = return (LamE [VarP x] $ VarE x)
+           ; [| $v . id |] })
diff --git a/tests/th/T5508.stderr b/tests/th/T5508.stderr
new file mode 100644
index 0000000..ff0383d
--- /dev/null
+++ b/tests/th/T5508.stderr
@@ -0,0 +1,6 @@
+T5508.hs:(7,9)-(9,28): Splicing expression
+    do { let x = mkName "x"
+             v = return (LamE [VarP x] $ VarE x);
+         [| $v . id |] }
+  ======>
+    ((\ x -> x) . id)
diff --git a/tests/th/all.T b/tests/th/all.T
index 9d588eb..1adf313 100644
--- a/tests/th/all.T
+++ b/tests/th/all.T
@@ -207,3 +207,4 @@ test('TH_lookupName',
 test('T5452', normal, compile, ['-v0'])
 test('T5434', extra_clean(['T5434a.hi','T5434a.o']), 
               multimod_compile, ['T5434','-v0 -Wall'])
+test('T5508', normal, compile, ['-v0 -ddump-splices'])



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

Reply via email to