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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/6fec11b4630a14acfbc917ae814c938e8cd65b6c

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

commit 6fec11b4630a14acfbc917ae814c938e8cd65b6c
Author: Simon Peyton Jones <simo...@microsoft.com>
Date:   Fri Dec 7 10:22:12 2012 +0000

    Test Trac #7445

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

 tests/th/Makefile  |    3 +++
 tests/th/T7445.hs  |    6 ++++++
 tests/th/T7445a.hs |   13 +++++++++++++
 tests/th/all.T     |    4 ++++
 4 files changed, 26 insertions(+), 0 deletions(-)

diff --git a/tests/th/Makefile b/tests/th/Makefile
index 0dca106..37134ce 100644
--- a/tests/th/Makefile
+++ b/tests/th/Makefile
@@ -8,6 +8,9 @@ T2386:
        '$(TEST_HC)' $(TEST_HC_OPTS) -v0 -c T2386_Lib.hs -fforce-recomp
        '$(TEST_HC)' $(TEST_HC_OPTS) -v0 -c T2386.hs -fforce-recomp
 
+T7445:
+       '$(TEST_HC)' $(TEST_HC_OPTS) -v0 -c T7445a.hs -fforce-recomp
+       '$(TEST_HC)' $(TEST_HC_OPTS) -v0 -c T7445.hs -fforce-recomp
 
 HC_OPTS = -XTemplateHaskell -package template-haskell
 
diff --git a/tests/th/T7445.hs b/tests/th/T7445.hs
new file mode 100644
index 0000000..03371e3
--- /dev/null
+++ b/tests/th/T7445.hs
@@ -0,0 +1,6 @@
+{-# LANGUAGE TemplateHaskell #-}
+
+module T7445 where
+import T7445a
+
+moo = $(foo)
diff --git a/tests/th/T7445a.hs b/tests/th/T7445a.hs
new file mode 100644
index 0000000..75719a1
--- /dev/null
+++ b/tests/th/T7445a.hs
@@ -0,0 +1,13 @@
+{-# LANGUAGE DeriveDataTypeable, FlexibleContexts #-}
+module T7445a ( foo ) where
+
+import Data.Data
+import Language.Haskell.TH.Quote
+import Language.Haskell.TH
+
+data Expr
+    =  IntExpr Integer
+    deriving (Show, Typeable, Data)
+
+foo :: ExpQ
+foo = dataToExpQ (const Nothing) (IntExpr 1)
diff --git a/tests/th/all.T b/tests/th/all.T
index 07faaf7..78e7655 100644
--- a/tests/th/all.T
+++ b/tests/th/all.T
@@ -254,3 +254,7 @@ test('T7092', extra_clean(['T7092a.hi','T7092a.o']),
               multimod_compile, ['T7092','-v0'])
 test('T7276', normal, compile_fail, ['-v0'])
 test('T7276a', combined_output, ghci_script, ['T7276a.script'])
+
+test('T7445', extra_clean(['T7445a.hi', 'T7445a.o']),
+             run_command,
+             ['$MAKE -s --no-print-directory T7445'] )



_______________________________________________
Cvs-ghc mailing list
Cvs-ghc@haskell.org
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to