Repository : ssh://darcs.haskell.org//srv/darcs/testsuite

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/452e0b74efdaee9efae9ac0e84627fc99de4bdcb

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

commit 452e0b74efdaee9efae9ac0e84627fc99de4bdcb
Author: Simon Peyton Jones <simo...@microsoft.com>
Date:   Tue Jun 5 11:42:04 2012 +0100

    Test Trac #6114

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

 tests/th/T6114.hs     |   11 +++++++++++
 tests/th/T6114.stderr |   17 +++++++++++++++++
 tests/th/all.T        |    1 +
 3 files changed, 29 insertions(+), 0 deletions(-)

diff --git a/tests/th/T6114.hs b/tests/th/T6114.hs
new file mode 100644
index 0000000..bea852c
--- /dev/null
+++ b/tests/th/T6114.hs
@@ -0,0 +1,11 @@
+{-# LANGUAGE TemplateHaskell #-}
+module T6114 where
+import Language.Haskell.TH
+import Control.Monad.Instances ()
+
+instanceVar = $(do
+                  xName <- newName "x"
+                  instanceType <- [t| $(varT xName) |]
+                  _ <- reifyInstances ''Eq [instanceType]
+                  undefined
+                )
diff --git a/tests/th/T6114.stderr b/tests/th/T6114.stderr
new file mode 100644
index 0000000..253c7c4
--- /dev/null
+++ b/tests/th/T6114.stderr
@@ -0,0 +1,17 @@
+
+T6114.hs:6:17:
+    The exact Name `x' is not in scope
+      Probable cause: you used a unique Template Haskell name (NameU), 
+      perhaps via newName, but did not bind it
+      If that's it, then -ddump-splices might be useful
+    In the argument of reifyInstances: GHC.Classes.Eq x_0
+    In the expression:
+      $(do { xName <- newName "x";
+             instanceType <- [t| $(varT xName) |];
+             _ <- reifyInstances ''Eq [instanceType];
+             .... })
+    In an equation for `instanceVar':
+        instanceVar
+          = $(do { xName <- newName "x";
+                   instanceType <- [t| $(varT xName) |];
+                   .... })
diff --git a/tests/th/all.T b/tests/th/all.T
index 19a29db..36aa3d0 100644
--- a/tests/th/all.T
+++ b/tests/th/all.T
@@ -243,3 +243,4 @@ test('T5976', normal, compile_fail, ['-v0'])
 test('T5795', normal, compile_fail, ['-v0'])
 test('T6005', normal, compile, ['-v0'])
 test('T6005a', normal, compile, ['-v0'])
+test('T6114', normal, compile_fail, ['-v0 -dsuppress-uniques'])



_______________________________________________
Cvs-ghc mailing list
Cvs-ghc@haskell.org
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to