[commit: testsuite] master: Test for Trac #4135, comment 2 (7a318d7)
git at git.haskell.org
git at git.haskell.org
Wed Nov 6 10:40:24 UTC 2013
Repository : ssh://git@git.haskell.org/testsuite
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/7a318d7d3a1467251b3133c43f01c7372c32904e/testsuite
>---------------------------------------------------------------
commit 7a318d7d3a1467251b3133c43f01c7372c32904e
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Wed Nov 6 09:56:54 2013 +0000
Test for Trac #4135, comment 2
>---------------------------------------------------------------
7a318d7d3a1467251b3133c43f01c7372c32904e
tests/th/T4135a.hs | 15 +++++++++++++++
tests/th/all.T | 3 ++-
2 files changed, 17 insertions(+), 1 deletion(-)
diff --git a/tests/th/T4135a.hs b/tests/th/T4135a.hs
new file mode 100644
index 0000000..41549ca
--- /dev/null
+++ b/tests/th/T4135a.hs
@@ -0,0 +1,15 @@
+{-# LANGUAGE TemplateHaskell, MultiParamTypeClasses, TypeFamilies,
+ FlexibleInstances, OverlappingInstances #-}
+
+module T4135a where
+
+import Control.Monad
+import Language.Haskell.TH
+
+class Foo a where
+ type FooType a
+
+createInstance' :: Q Type -> Q Dec
+createInstance' t = liftM head [d|
+ instance Foo $t where
+ type FooType $t = String |]
diff --git a/tests/th/all.T b/tests/th/all.T
index 9b959fa..5428b9c 100644
--- a/tests/th/all.T
+++ b/tests/th/all.T
@@ -235,7 +235,8 @@ test('T5883', normal, compile, ['-v0 -dsuppress-uniques -ddump-splices'])
test('T5882', normal, compile, ['-v0'])
test('T5886', extra_clean(['T5886a.hi','T5886a.o']),
multimod_compile, ['T5886','-v0 ' + config.ghc_th_way_flags])
-test('T4135', normal, compile, ['-v0'])
+test('T4135', normal, compile, ['-v0'])
+test('T4135a', normal, compile, ['-v0'])
test('T5971', normal, compile_fail, ['-v0 -dsuppress-uniques'])
test('T5968', normal, compile, ['-v0'])
test('T5984', extra_clean(['T5984_Lib.hi', 'T5984_Lib.o']),
More information about the ghc-commits
mailing list