[commit: testsuite] master: Test Trac #7910 (c432fbc)

Simon Peyton Jones simonpj at microsoft.com
Wed May 15 15:15:27 CEST 2013


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

On branch  : master

https://github.com/ghc/testsuite/commit/c432fbce0e07542a02fab3f16d968656e119ec59

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

commit c432fbce0e07542a02fab3f16d968656e119ec59
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Wed May 15 10:19:21 2013 +0100

    Test Trac #7910

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

 tests/th/T7910.hs     |   16 ++++++++++++++++
 tests/th/T7910.stdout |    1 +
 tests/th/all.T        |    3 ++-
 3 files changed, 19 insertions(+), 1 deletions(-)

diff --git a/tests/th/T7910.hs b/tests/th/T7910.hs
new file mode 100644
index 0000000..d044365
--- /dev/null
+++ b/tests/th/T7910.hs
@@ -0,0 +1,16 @@
+{-# LANGUAGE ConstraintKinds #-}
+{-# LANGUAGE TemplateHaskell #-}
+module Main where
+
+import Language.Haskell.TH
+import Language.Haskell.TH.Syntax
+
+class C a
+instance C Int
+
+type D a = C a
+
+main = print $(
+  do isCInst <- isInstance ''C [ConT ''Int]
+     isDInst <- isInstance ''D [ConT ''Int]
+     lift (isCInst,isDInst))
diff --git a/tests/th/T7910.stdout b/tests/th/T7910.stdout
new file mode 100644
index 0000000..1fa0b54
--- /dev/null
+++ b/tests/th/T7910.stdout
@@ -0,0 +1 @@
+(True,True)
diff --git a/tests/th/all.T b/tests/th/all.T
index 5ff833e..ad1c4e9 100644
--- a/tests/th/all.T
+++ b/tests/th/all.T
@@ -273,4 +273,5 @@ test('T7532',
      ['T7532', '-v0 ' + config.ghc_th_way_flags])
 test('T2222', normal, compile, ['-v0'])
 test('T1849', normal, ghci_script, ['T1849.script'])
-test('T7681', normal, compile, ['-v0'])
\ No newline at end of file
+test('T7681', normal, compile, ['-v0'])
+test('T7910', normal, compile_and_run, ['-v0'])





More information about the ghc-commits mailing list