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

On branch  : master
Link       : 
http://ghc.haskell.org/trac/ghc/changeset/7a76405a81a718f7b1c72d4b9f7d7883abc1b77b/testsuite

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

commit 7a76405a81a718f7b1c72d4b9f7d7883abc1b77b
Author: Krzysztof Gogolewski <krz.gogolew...@gmail.com>
Date:   Sat Oct 5 17:23:59 2013 +0200

    Test #8412


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

7a76405a81a718f7b1c72d4b9f7d7883abc1b77b
 tests/th/{T5971.hs => T8412.hs} |    3 +--
 tests/th/T8412.stderr           |    6 ++++++
 2 files changed, 7 insertions(+), 2 deletions(-)

diff --git a/tests/th/T5971.hs b/tests/th/T8412.hs
similarity index 56%
copy from tests/th/T5971.hs
copy to tests/th/T8412.hs
index bca58ea..074bb50 100644
--- a/tests/th/T5971.hs
+++ b/tests/th/T8412.hs
@@ -1,6 +1,5 @@
 {-# LANGUAGE TemplateHaskell #-}
-module T5971 where
 
 import Language.Haskell.TH
 
-_ = $(newName "x" >>= varE)
+type T = $(return $ LitT $ NumTyLit (-1))
diff --git a/tests/th/T8412.stderr b/tests/th/T8412.stderr
new file mode 100644
index 0000000..21d43e4
--- /dev/null
+++ b/tests/th/T8412.stderr
@@ -0,0 +1,6 @@
+
+T8412.hs:5:12:
+    Illegal literal in type (type literals must not be negative): -1
+    In the result of the splice:
+      $(return $ LitT $ NumTyLit (- 1))
+    To see what the splice expanded to, use -ddump-splices

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

Reply via email to