[commit: testsuite] master: Test Trac #8499 (a019503)
git at git.haskell.org
git at git.haskell.org
Wed Nov 6 08:33:38 UTC 2013
Repository : ssh://git@git.haskell.org/testsuite
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/a019503ea3651241fa5d71fd1cdf7c8da8dbbf3a/testsuite
>---------------------------------------------------------------
commit a019503ea3651241fa5d71fd1cdf7c8da8dbbf3a
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Wed Nov 6 08:33:25 2013 +0000
Test Trac #8499
>---------------------------------------------------------------
a019503ea3651241fa5d71fd1cdf7c8da8dbbf3a
tests/th/T8499.hs | 12 ++++++++++++
tests/th/all.T | 1 +
2 files changed, 13 insertions(+)
diff --git a/tests/th/T8499.hs b/tests/th/T8499.hs
new file mode 100644
index 0000000..353bb9f
--- /dev/null
+++ b/tests/th/T8499.hs
@@ -0,0 +1,12 @@
+{-# LANGUAGE TemplateHaskell, PolyKinds, DataKinds #-}
+{-# OPTIONS_GHC -Wall #-}
+
+module T8499 where
+
+import Language.Haskell.TH
+
+$( do TyConI (DataD _ _ [PlainTV tvb_a] _ _) <- reify ''Maybe
+ my_a <- newName "a"
+ return [TySynD (mkName "SMaybe")
+ [KindedTV my_a (AppT (ConT ''Maybe) (VarT tvb_a))]
+ (TupleT 0)] )
diff --git a/tests/th/all.T b/tests/th/all.T
index e38297f..55c5a93 100644
--- a/tests/th/all.T
+++ b/tests/th/all.T
@@ -303,3 +303,4 @@ test('T8412', normal, compile_fail, ['-v0'])
test('T7667', normal, compile, ['-v0'])
test('T7667a', normal, compile_fail, ['-v0'])
test('T8455', normal, compile, ['-v0'])
+test('T8499', normal, compile, ['-v0'])
More information about the ghc-commits
mailing list