[commit: ghc] ghc-8.0: testsuite: Add test for #12993 (1181bb5)

git at git.haskell.org git at git.haskell.org
Sun Dec 18 21:26:44 UTC 2016


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

On branch  : ghc-8.0
Link       : http://ghc.haskell.org/trac/ghc/changeset/1181bb580ad01d56fb1b624dc6787cafb553293e/ghc

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

commit 1181bb580ad01d56fb1b624dc6787cafb553293e
Author: Ben Gamari <ben at smart-cactus.org>
Date:   Fri Dec 16 16:47:45 2016 -0500

    testsuite: Add test for #12993
    
    (cherry picked from commit 54706738cd452717c7ec1a91927c3941c8037c7b)


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

1181bb580ad01d56fb1b624dc6787cafb553293e
 testsuite/tests/th/T12993.hs     | 4 ++++
 testsuite/tests/th/T12993_Lib.hs | 4 ++++
 testsuite/tests/th/all.T         | 1 +
 3 files changed, 9 insertions(+)

diff --git a/testsuite/tests/th/T12993.hs b/testsuite/tests/th/T12993.hs
new file mode 100644
index 0000000..6082669
--- /dev/null
+++ b/testsuite/tests/th/T12993.hs
@@ -0,0 +1,4 @@
+{-# LANGUAGE TemplateHaskell #-}
+module T12993 where
+import T12993_Lib
+f = $(q)
diff --git a/testsuite/tests/th/T12993_Lib.hs b/testsuite/tests/th/T12993_Lib.hs
new file mode 100644
index 0000000..441b783
--- /dev/null
+++ b/testsuite/tests/th/T12993_Lib.hs
@@ -0,0 +1,4 @@
+{-# LANGUAGE TemplateHaskell #-}
+module T12993_Lib (q) where
+data X = X { x :: Int }
+q = [|x|]
diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T
index 773b360..0e24b48 100644
--- a/testsuite/tests/th/all.T
+++ b/testsuite/tests/th/all.T
@@ -421,3 +421,4 @@ test('T12411', normal, compile_fail, [''])
 test('T12788', extra_clean(['T12788_Lib.hi', 'T12788_Lib.o']),
                multimod_compile_fail,
                ['T12788.hs', '-v0 ' + config.ghc_th_way_flags])
+test('T12993', normal, multimod_compile, ['T12993.hs', '-v0'])



More information about the ghc-commits mailing list