[commit: ghc] wip/rae: Test #9084 in th/T9084. (8155cc4)
git at git.haskell.org
git at git.haskell.org
Fri Oct 31 17:36:41 UTC 2014
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/rae
Link : http://ghc.haskell.org/trac/ghc/changeset/8155cc4581ac313f7b73f887a87dbe6bf02956e5/ghc
>---------------------------------------------------------------
commit 8155cc4581ac313f7b73f887a87dbe6bf02956e5
Author: Richard Eisenberg <eir at cis.upenn.edu>
Date: Tue Oct 28 13:10:11 2014 -0400
Test #9084 in th/T9084.
The patch includes errors for a whole host of pragmas. But, these
are generated one at a time, and it doesn't seem like a good idea
to add gobs of test-cases here.
>---------------------------------------------------------------
8155cc4581ac313f7b73f887a87dbe6bf02956e5
testsuite/tests/th/T9084.hs | 10 ++++++++++
testsuite/tests/th/T9084.stderr | 2 ++
testsuite/tests/th/all.T | 1 +
3 files changed, 13 insertions(+)
diff --git a/testsuite/tests/th/T9084.hs b/testsuite/tests/th/T9084.hs
new file mode 100644
index 0000000..6b1fe0d
--- /dev/null
+++ b/testsuite/tests/th/T9084.hs
@@ -0,0 +1,10 @@
+{-# LANGUAGE TemplateHaskell #-}
+
+module T9084 where
+
+$([d|
+ class C a where
+ meth :: a -> a
+ meth = undefined -- give a (silly) default
+ {-# MINIMAL meth #-}
+ |])
diff --git a/testsuite/tests/th/T9084.stderr b/testsuite/tests/th/T9084.stderr
new file mode 100644
index 0000000..ad90d1b
--- /dev/null
+++ b/testsuite/tests/th/T9084.stderr
@@ -0,0 +1,2 @@
+
+T9084.hs:5:3: MINIMAL pragmas not (yet) handled by Template Haskell
diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T
index 28ae4fb..d6aaa84 100644
--- a/testsuite/tests/th/all.T
+++ b/testsuite/tests/th/all.T
@@ -333,3 +333,4 @@ test('T9262', normal, compile, ['-v0'])
test('T9199', normal, compile, ['-v0'])
test('T9692', normal, compile, ['-v0'])
test('T8953', normal, compile, ['-v0'])
+test('T9084', normal, compile_fail, ['-v0'])
More information about the ghc-commits
mailing list