[commit: testsuite] master: Added test for #7667. (9cea38e)

git at git.haskell.org git at git.haskell.org
Tue Oct 15 17:29:09 UTC 2013


Repository : ssh://git@git.haskell.org/testsuite

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/9cea38ecb4e256f9859d54916770b45e86b0b101/testsuite

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

commit 9cea38ecb4e256f9859d54916770b45e86b0b101
Author: Richard Eisenberg <eir at cis.upenn.edu>
Date:   Mon Oct 14 17:39:48 2013 -0400

    Added test for #7667.


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

9cea38ecb4e256f9859d54916770b45e86b0b101
 tests/th/T7667.hs |    8 ++++++++
 tests/th/all.T    |    1 +
 2 files changed, 9 insertions(+)

diff --git a/tests/th/T7667.hs b/tests/th/T7667.hs
new file mode 100644
index 0000000..59287f1
--- /dev/null
+++ b/tests/th/T7667.hs
@@ -0,0 +1,8 @@
+{-# LANGUAGE TemplateHaskell, TypeOperators #-}
+
+module T7667 where
+
+import Language.Haskell.TH
+
+$( return [ TySynD (mkName "+") [PlainTV (mkName "a"), PlainTV (mkName "b")]
+                   (AppT (AppT (ConT ''Either) (VarT $ mkName "a")) (VarT $ mkName "b")) ] )
\ No newline at end of file
diff --git a/tests/th/all.T b/tests/th/all.T
index c1f8a9b..897c265 100644
--- a/tests/th/all.T
+++ b/tests/th/all.T
@@ -300,3 +300,4 @@ test('T4128', normal, compile, ['-v0'])
 test('T6062', normal, compile, ['-v0'])
 test('T4364', normal, compile, ['-v0'])
 test('T8412', normal, compile_fail, ['-v0'])
+test('T7667', normal, compile, ['-v0'])
\ No newline at end of file



More information about the ghc-commits mailing list