[commit: testsuite] master: Add test T8028 (e2ad30b)
Richard Eisenberg
eir at cis.upenn.edu
Tue Jul 2 22:27:02 CEST 2013
Repository : ssh://darcs.haskell.org//srv/darcs/testsuite
On branch : master
https://github.com/ghc/testsuite/commit/e2ad30bfec27b8c12b7af2479e3bdaa24ac7e13a
>---------------------------------------------------------------
commit e2ad30bfec27b8c12b7af2479e3bdaa24ac7e13a
Author: Richard Eisenberg <eir at cis.upenn.edu>
Date: Mon Jul 1 21:58:07 2013 +0100
Add test T8028
>---------------------------------------------------------------
tests/th/T8028.hs | 7 +++++++
tests/th/T8028.stderr | 4 ++++
tests/th/T8028a.hs | 6 ++++++
tests/th/all.T | 7 ++++++-
4 files changed, 23 insertions(+), 1 deletions(-)
diff --git a/tests/th/T8028.hs b/tests/th/T8028.hs
new file mode 100644
index 0000000..fec993a
--- /dev/null
+++ b/tests/th/T8028.hs
@@ -0,0 +1,7 @@
+{-# LANGUAGE TemplateHaskell #-}
+
+module T8028 where
+
+import T8028a
+
+$(x)
\ No newline at end of file
diff --git a/tests/th/T8028.stderr b/tests/th/T8028.stderr
new file mode 100644
index 0000000..20cf1c7
--- /dev/null
+++ b/tests/th/T8028.stderr
@@ -0,0 +1,4 @@
+
+T8028.hs:7:3:
+ Illegal empty closed type family
+ When splicing a TH declaration: type family F_0 where
diff --git a/tests/th/T8028a.hs b/tests/th/T8028a.hs
new file mode 100644
index 0000000..928a96e
--- /dev/null
+++ b/tests/th/T8028a.hs
@@ -0,0 +1,6 @@
+module T8028a where
+
+import Language.Haskell.TH
+
+x = do n <- newName "F"
+ return [ClosedTypeFamilyD n [] Nothing []]
diff --git a/tests/th/all.T b/tests/th/all.T
index c6407c4..73d60af 100644
--- a/tests/th/all.T
+++ b/tests/th/all.T
@@ -275,4 +275,9 @@ test('T7681', normal, compile, ['-v0'])
test('T7910', normal, compile_and_run, ['-v0'])
test('ClosedFam1', normal, compile, ['-dsuppress-uniques -v0'])
-test('ClosedFam2', normal, compile, ['-v0'])
\ No newline at end of file
+test('ClosedFam2', normal, compile, ['-v0'])
+
+test('T8028',
+ extra_clean(['T8028a.hi', 'T8028a.o']),
+ multimod_compile_fail,
+ ['T8028', '-v0 ' + config.ghc_th_way_flags])
More information about the ghc-commits
mailing list