[commit: ghc] wip/rae: Test #7484 in th/T7484 (89b963f)
git at git.haskell.org
git at git.haskell.org
Tue Nov 4 16:36:37 UTC 2014
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/rae
Link : http://ghc.haskell.org/trac/ghc/changeset/89b963f2ec7e116ea34632fec54b174bfbd111ff/ghc
>---------------------------------------------------------------
commit 89b963f2ec7e116ea34632fec54b174bfbd111ff
Author: Richard Eisenberg <eir at cis.upenn.edu>
Date: Mon Nov 3 15:33:51 2014 -0500
Test #7484 in th/T7484
>---------------------------------------------------------------
89b963f2ec7e116ea34632fec54b174bfbd111ff
testsuite/tests/th/T7484.hs | 7 +++++++
testsuite/tests/th/T7484.stderr | 4 ++++
testsuite/tests/th/all.T | 1 +
3 files changed, 12 insertions(+)
diff --git a/testsuite/tests/th/T7484.hs b/testsuite/tests/th/T7484.hs
new file mode 100644
index 0000000..b1a9cba
--- /dev/null
+++ b/testsuite/tests/th/T7484.hs
@@ -0,0 +1,7 @@
+{-# LANGUAGE TemplateHaskell #-}
+
+module T7484 where
+
+import Language.Haskell.TH
+
+$( return [ ValD (VarP (mkName "a ")) (NormalB (LitE (IntegerL 5))) [] ] )
diff --git a/testsuite/tests/th/T7484.stderr b/testsuite/tests/th/T7484.stderr
new file mode 100644
index 0000000..3ffe123
--- /dev/null
+++ b/testsuite/tests/th/T7484.stderr
@@ -0,0 +1,4 @@
+
+T7484.hs:7:4:
+ Illegal variable name: ‘a ’
+ When splicing a TH declaration: a = 5
diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T
index bb8734e..db41e19 100644
--- a/testsuite/tests/th/all.T
+++ b/testsuite/tests/th/all.T
@@ -338,3 +338,4 @@ test('T9738', normal, compile, ['-v0'])
test('T9081', normal, compile, ['-v0'])
test('T9066', normal, compile, ['-v0'])
test('T9209', normal, compile_fail, ['-v0'])
+test('T7484', expect_broken(7484), compile_fail, ['-v0'])
More information about the ghc-commits
mailing list