[commit: ghc] master: Test #9262 in th/T9262, and update other tests. (f688f03)

git at git.haskell.org git at git.haskell.org
Sun Nov 2 03:53:20 UTC 2014


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/f688f0377e13e0762d422ed3a83e74b5d39b5e13/ghc

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

commit f688f0377e13e0762d422ed3a83e74b5d39b5e13
Author: Richard Eisenberg <eir at cis.upenn.edu>
Date:   Tue Oct 21 09:12:34 2014 -0400

    Test #9262 in th/T9262, and update other tests.


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

f688f0377e13e0762d422ed3a83e74b5d39b5e13
 testsuite/tests/th/T6114.hs     | 13 ++++++-------
 testsuite/tests/th/T6114.stderr | 12 ------------
 testsuite/tests/th/T9262.hs     | 12 ++++++++++++
 testsuite/tests/th/T9262.stderr |  1 +
 testsuite/tests/th/all.T        |  3 ++-
 5 files changed, 21 insertions(+), 20 deletions(-)

diff --git a/testsuite/tests/th/T6114.hs b/testsuite/tests/th/T6114.hs
index bea852c..c5278e3 100644
--- a/testsuite/tests/th/T6114.hs
+++ b/testsuite/tests/th/T6114.hs
@@ -1,11 +1,10 @@
 {-# 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
-                )
+$(do
+   xName <- newName "x"
+   instanceType <- [t| $(varT xName) |]
+   _ <- reifyInstances ''Eq [instanceType]
+   return []
+  )
diff --git a/testsuite/tests/th/T6114.stderr b/testsuite/tests/th/T6114.stderr
deleted file mode 100644
index 917b56f..0000000
--- a/testsuite/tests/th/T6114.stderr
+++ /dev/null
@@ -1,12 +0,0 @@
-
-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 splice:
-      $(do { xName <- newName "x";
-             instanceType <- [t| $(varT xName) |];
-             _ <- reifyInstances ''Eq [instanceType];
-             .... })
diff --git a/testsuite/tests/th/T9262.hs b/testsuite/tests/th/T9262.hs
new file mode 100644
index 0000000..8a44603
--- /dev/null
+++ b/testsuite/tests/th/T9262.hs
@@ -0,0 +1,12 @@
+{-# LANGUAGE TemplateHaskell #-}
+
+module T9262 where
+
+import Language.Haskell.TH
+import Language.Haskell.TH.Ppr
+import System.IO
+
+$(do insts <- reifyInstances ''Eq [ListT `AppT` VarT (mkName "a")]
+     runIO $ putStrLn $ pprint insts
+     runIO $ hFlush stdout
+     return [] )
diff --git a/testsuite/tests/th/T9262.stderr b/testsuite/tests/th/T9262.stderr
new file mode 100644
index 0000000..efdf5e3
--- /dev/null
+++ b/testsuite/tests/th/T9262.stderr
@@ -0,0 +1 @@
+instance GHC.Classes.Eq a_0 => GHC.Classes.Eq ([a_0])
diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T
index 2981202..d3ae4e4 100644
--- a/testsuite/tests/th/all.T
+++ b/testsuite/tests/th/all.T
@@ -251,7 +251,7 @@ test('T5795', normal, compile_fail, ['-v0'])
 test('T6005', normal, compile, ['-v0'])
 test('T6005a', normal, compile, ['-v0'])
 test('T5737', normal, compile, ['-v0'])
-test('T6114', normal, compile_fail, ['-v0 -dsuppress-uniques'])
+test('T6114', normal, compile, ['-v0'])
 test('TH_StringPrimL', normal, compile_and_run, [''])
 test('T7064',
      extra_clean(['T7064a.hi', 'T7064a.o']),
@@ -329,5 +329,6 @@ test('T8954', normal, compile, ['-v0'])
 test('T8932', normal, compile_fail, ['-v0'])
 test('T8987', normal, compile_fail, ['-v0'])
 test('T7241', normal, compile_fail, ['-v0'])
+test('T9262', normal, compile, ['-v0'])
 test('T9199', normal, compile, ['-v0'])
 test('T9692', normal, compile, ['-v0'])



More information about the ghc-commits mailing list