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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/199016b4d21df889d5b78e2f8c4cac01c6b46d84

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

commit 199016b4d21df889d5b78e2f8c4cac01c6b46d84
Author: Paolo Capriotti <[email protected]>
Date:   Mon Apr 2 15:55:33 2012 +0100

    Add testcase for #5984

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

 tests/th/T5984.hs     |    8 ++++++++
 tests/th/T5984.stderr |   10 ++++++++++
 tests/th/T5984_Lib.hs |   13 +++++++++++++
 tests/th/all.T        |    3 ++-
 4 files changed, 33 insertions(+), 1 deletions(-)

diff --git a/tests/th/T5984.hs b/tests/th/T5984.hs
new file mode 100644
index 0000000..63f21b6
--- /dev/null
+++ b/tests/th/T5984.hs
@@ -0,0 +1,8 @@
+{-# LANGUAGE TemplateHaskell #-}
+
+module T5984 where
+
+import T5984_Lib
+
+$nt
+$dt
diff --git a/tests/th/T5984.stderr b/tests/th/T5984.stderr
new file mode 100644
index 0000000..50c7cbf
--- /dev/null
+++ b/tests/th/T5984.stderr
@@ -0,0 +1,10 @@
+T5984.hs:1:1: Splicing declarations
+    nt
+  ======>
+    T5984.hs:7:1-3
+    newtype Foo = Foo Int
+T5984.hs:1:1: Splicing declarations
+    dt
+  ======>
+    T5984.hs:8:1-3
+    data Bar = Bar Int
diff --git a/tests/th/T5984_Lib.hs b/tests/th/T5984_Lib.hs
new file mode 100644
index 0000000..c3abfa2
--- /dev/null
+++ b/tests/th/T5984_Lib.hs
@@ -0,0 +1,13 @@
+{-# LANGUAGE TemplateHaskell #-}
+
+module T5984_Lib where
+
+import Language.Haskell.TH
+
+nt :: Q [Dec]
+nt = return [NewtypeD [] foo [] (NormalC foo [(NotStrict, ConT ''Int)]) []]
+  where foo = mkName "Foo"
+
+dt :: Q [Dec]
+dt = return [DataD [] bar [] [NormalC bar [(NotStrict, ConT ''Int)]] []]
+  where bar = mkName "Bar"
diff --git a/tests/th/all.T b/tests/th/all.T
index 4bf6a32..89b599b 100644
--- a/tests/th/all.T
+++ b/tests/th/all.T
@@ -228,4 +228,5 @@ test('T5886', extra_clean(['T5886a.hi','T5886a.o']),
 test('T4135', normal, compile, ['-v0'])
 test('T5971', normal, compile_fail, ['-v0 -dsuppress-uniques'])
 test('T5968', normal, compile, ['-v0'])
-
+test('T5984', extra_clean(['T5984_Lib.hi', 'T5984_Lib.o']),
+              multimod_compile, ['T5984', '-v0 -ddump-splices'])



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

Reply via email to