[commit: ghc] wip/rae: Test #9738 in th/T9738 (56de19b)
git at git.haskell.org
git at git.haskell.org
Fri Oct 31 17:36:44 UTC 2014
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/rae
Link : http://ghc.haskell.org/trac/ghc/changeset/56de19b2930d067d338dcf4e8cb254be73d3b640/ghc
>---------------------------------------------------------------
commit 56de19b2930d067d338dcf4e8cb254be73d3b640
Author: Richard Eisenberg <eir at cis.upenn.edu>
Date: Tue Oct 28 14:53:59 2014 -0400
Test #9738 in th/T9738
>---------------------------------------------------------------
56de19b2930d067d338dcf4e8cb254be73d3b640
testsuite/tests/th/T9738.hs | 16 ++++++++++++++++
testsuite/tests/th/T9738.stderr | 1 +
testsuite/tests/th/all.T | 1 +
3 files changed, 18 insertions(+)
diff --git a/testsuite/tests/th/T9738.hs b/testsuite/tests/th/T9738.hs
new file mode 100644
index 0000000..7c5f020
--- /dev/null
+++ b/testsuite/tests/th/T9738.hs
@@ -0,0 +1,16 @@
+{-# LANGUAGE TemplateHaskell #-}
+
+module T9738 where
+
+import System.IO
+import Language.Haskell.TH
+
+data Foo = MkFoo
+
+$( do decs <- [d| {-# ANN type Foo "hi" #-}
+ {-# ANN MkFoo "there" #-}
+ {-# ANN module "Charley" #-}
+ |]
+ runIO $ print decs
+ runIO $ hFlush stdout
+ return [] )
diff --git a/testsuite/tests/th/T9738.stderr b/testsuite/tests/th/T9738.stderr
new file mode 100644
index 0000000..e4b97cb
--- /dev/null
+++ b/testsuite/tests/th/T9738.stderr
@@ -0,0 +1 @@
+[PragmaD (AnnP (TypeAnnotation T9738.Foo) (LitE (StringL "hi"))),PragmaD (AnnP (ValueAnnotation T9738.MkFoo) (LitE (StringL "there"))),PragmaD (AnnP ModuleAnnotation (LitE (StringL "Charley")))]
diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T
index 3c108a7..4409571 100644
--- a/testsuite/tests/th/all.T
+++ b/testsuite/tests/th/all.T
@@ -334,3 +334,4 @@ test('T9199', normal, compile, ['-v0'])
test('T9692', normal, compile, ['-v0'])
test('T8953', normal, compile, ['-v0'])
test('T9084', normal, compile_fail, ['-v0'])
+test('T9738', normal, compile, ['-v0'])
More information about the ghc-commits
mailing list