[commit: ghc] master: Tests for #10945 and #10946 (f64f7c3)
git at git.haskell.org
git at git.haskell.org
Thu Oct 8 12:14:29 UTC 2015
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/f64f7c36ef9395da1cc7b686aaf1b019204cd0fc/ghc
>---------------------------------------------------------------
commit f64f7c36ef9395da1cc7b686aaf1b019204cd0fc
Author: Jan Stolarek <jan.stolarek at p.lodz.pl>
Date: Thu Oct 8 14:10:42 2015 +0200
Tests for #10945 and #10946
>---------------------------------------------------------------
f64f7c36ef9395da1cc7b686aaf1b019204cd0fc
testsuite/tests/th/T10945.hs | 14 ++++++++++++++
testsuite/tests/th/{T5971.hs => T10946.hs} | 6 ++++--
testsuite/tests/th/all.T | 2 ++
3 files changed, 20 insertions(+), 2 deletions(-)
diff --git a/testsuite/tests/th/T10945.hs b/testsuite/tests/th/T10945.hs
new file mode 100644
index 0000000..be7a792
--- /dev/null
+++ b/testsuite/tests/th/T10945.hs
@@ -0,0 +1,14 @@
+{-# LANGUAGE TemplateHaskell #-}
+
+module T10945 where
+
+import Language.Haskell.TH
+
+$$(return [
+ SigD (mkName "m")
+ (ForallT [PlainTV (mkName "a")]
+ []
+ (AppT (AppT ArrowT (VarT (mkName "a"))) (VarT (mkName "a"))))
+ , FunD (mkName "m")
+ [Clause [VarP (mkName "x")] (NormalB (VarE (mkName "x"))) []]
+ ])
diff --git a/testsuite/tests/th/T5971.hs b/testsuite/tests/th/T10946.hs
similarity index 54%
copy from testsuite/tests/th/T5971.hs
copy to testsuite/tests/th/T10946.hs
index bca58ea..e234d91 100644
--- a/testsuite/tests/th/T5971.hs
+++ b/testsuite/tests/th/T10946.hs
@@ -1,6 +1,8 @@
{-# LANGUAGE TemplateHaskell #-}
-module T5971 where
+
+module T10946 where
import Language.Haskell.TH
-_ = $(newName "x" >>= varE)
+m :: a -> a
+m x = $$([||_||])
diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T
index 9d4736c..8304737 100644
--- a/testsuite/tests/th/all.T
+++ b/testsuite/tests/th/all.T
@@ -360,3 +360,5 @@ test('TH_namePackage', normal, compile_and_run, ['-v0'])
test('T10811', normal, compile, ['-v0'])
test('T10810', normal, compile, ['-v0'])
test('T10891', normal, compile, ['-v0'])
+test('T10945', expect_broken(10945), compile, ['-v0'])
+test('T10946', expect_broken(10946), compile, ['-v0'])
More information about the ghc-commits
mailing list