[commit: ghc] master: testsuite: Add test for #14028 (262bb95)
git at git.haskell.org
git at git.haskell.org
Fri Jul 28 16:37:20 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/262bb95f5e00eea783d3e756fe86d96839be45d7/ghc
>---------------------------------------------------------------
commit 262bb95f5e00eea783d3e756fe86d96839be45d7
Author: Ben Gamari <bgamari.foss at gmail.com>
Date: Fri Jul 28 11:44:20 2017 -0400
testsuite: Add test for #14028
Reviewers: austin
Subscribers: rwbarton, thomie
GHC Trac Issues: #14028
Differential Revision: https://phabricator.haskell.org/D3788
>---------------------------------------------------------------
262bb95f5e00eea783d3e756fe86d96839be45d7
testsuite/tests/quasiquotation/Makefile | 4 ++++
testsuite/tests/quasiquotation/T14028.hs | 8 ++++++++
testsuite/tests/quasiquotation/T14028C.c | 5 +++++
testsuite/tests/quasiquotation/T14028Quote.hs | 6 ++++++
testsuite/tests/quasiquotation/all.T | 4 ++++
5 files changed, 27 insertions(+)
diff --git a/testsuite/tests/quasiquotation/Makefile b/testsuite/tests/quasiquotation/Makefile
index 8e2e7e7..ebc91d2 100644
--- a/testsuite/tests/quasiquotation/Makefile
+++ b/testsuite/tests/quasiquotation/Makefile
@@ -9,3 +9,7 @@ T4150:
'$(TEST_HC)' $(TEST_HC_OPTS) -v0 -c T4150A.hs
-'$(TEST_HC)' $(TEST_HC_OPTS) -v0 -c T4150.hs
+T14028:
+ '$(TEST_HC)' $(TEST_HC_OPTS) T14028Quote.hs
+ '$(TEST_HC)' $(TEST_HC_OPTS) -c T14028C.c
+ '$(TEST_HC)' $(TEST_HC_OPTS) -fexternal-interpreter T14028 T14028C.o
diff --git a/testsuite/tests/quasiquotation/T14028.hs b/testsuite/tests/quasiquotation/T14028.hs
new file mode 100644
index 0000000..5313df6
--- /dev/null
+++ b/testsuite/tests/quasiquotation/T14028.hs
@@ -0,0 +1,8 @@
+{-# LANGUAGE QuasiQuotes #-}
+
+import T14028Quote
+
+s :: String
+s = [here|goes nothing|]
+
+main = putStrLn s
diff --git a/testsuite/tests/quasiquotation/T14028C.c b/testsuite/tests/quasiquotation/T14028C.c
new file mode 100644
index 0000000..0115013
--- /dev/null
+++ b/testsuite/tests/quasiquotation/T14028C.c
@@ -0,0 +1,5 @@
+#include <stdio.h>
+
+void hi() {
+ puts("Hello, World!");
+}
diff --git a/testsuite/tests/quasiquotation/T14028Quote.hs b/testsuite/tests/quasiquotation/T14028Quote.hs
new file mode 100644
index 0000000..01413ec
--- /dev/null
+++ b/testsuite/tests/quasiquotation/T14028Quote.hs
@@ -0,0 +1,6 @@
+module T14028Quote where
+import Language.Haskell.TH
+import Language.Haskell.TH.Quote
+
+here :: QuasiQuoter
+here = QuasiQuoter { quoteExp = litE . stringL }
diff --git a/testsuite/tests/quasiquotation/all.T b/testsuite/tests/quasiquotation/all.T
index 84d25f8..a10b8e4 100644
--- a/testsuite/tests/quasiquotation/all.T
+++ b/testsuite/tests/quasiquotation/all.T
@@ -6,3 +6,7 @@ test('T7918',
[req_interp, extra_run_opts('"' + config.libdir + '"'),
only_ways(config.ghc_th_way), unless(have_dynamic(), skip)],
compile_and_run, ['-package ghc ' + config.ghc_th_way_flags])
+test('T14028',
+ [req_interp, only_ways(config.ghc_th_way)],
+ run_command,
+ ['$MAKE -s --no-print-directory T14028'])
More information about the ghc-commits
mailing list