[commit: testsuite] master: Add tests for new TH #4124, #4128, #4170, #4364, #6062 (e595c81)

git at git.haskell.org git
Sat Oct 5 17:10:41 UTC 2013


Repository : ssh://git at git.haskell.org/testsuite

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

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

commit e595c81ee0951f17d34b918123dfa7711710fe89
Author: Krzysztof Gogolewski <krz.gogolewski at gmail.com>
Date:   Sat Oct 5 19:08:09 2013 +0200

    Add tests for new TH #4124, #4128, #4170, #4364, #6062


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

e595c81ee0951f17d34b918123dfa7711710fe89
 tests/th/T4124.hs |    6 ++++++
 tests/th/T4128.hs |    7 +++++++
 tests/th/T4170.hs |   13 +++++++++++++
 tests/th/T4364.hs |    7 +++++++
 tests/th/T6062.hs |    3 +++
 tests/th/all.T    |    7 +++++++
 6 files changed, 43 insertions(+)

diff --git a/tests/th/T4124.hs b/tests/th/T4124.hs
new file mode 100644
index 0000000..a3dddda
--- /dev/null
+++ b/tests/th/T4124.hs
@@ -0,0 +1,6 @@
+{-# LANGUAGE TemplateHaskell #-}
+module T4124 where
+
+class Storable a where
+data X = X
+[d| instance Storable $( [t| X |] ) where |]
diff --git a/tests/th/T4128.hs b/tests/th/T4128.hs
new file mode 100644
index 0000000..961ba4c
--- /dev/null
+++ b/tests/th/T4128.hs
@@ -0,0 +1,7 @@
+{-# LANGUAGE TemplateHaskell #-}
+module T4128 where
+
+import Language.Haskell.TH
+class C a where
+data X = X
+fmap return $ instanceD (cxt []) [t| C $(conT ''X) |] []
diff --git a/tests/th/T4170.hs b/tests/th/T4170.hs
new file mode 100644
index 0000000..87ccad6
--- /dev/null
+++ b/tests/th/T4170.hs
@@ -0,0 +1,13 @@
+{-# LANGUAGE TemplateHaskell #-}
+module T4170 where
+
+import Language.Haskell.TH
+
+class LOL a
+
+lol :: Q [Dec]
+lol = [d|
+    instance LOL Int
+    |]
+
+instance LOL Int
diff --git a/tests/th/T4364.hs b/tests/th/T4364.hs
new file mode 100644
index 0000000..1278c2a
--- /dev/null
+++ b/tests/th/T4364.hs
@@ -0,0 +1,7 @@
+{-# LANGUAGE TemplateHaskell #-}
+module T4364 where
+
+data Z
+
+type N0 = $( [t| Z |] )
+type N1 = $( [t| Z |] )
diff --git a/tests/th/T6062.hs b/tests/th/T6062.hs
new file mode 100644
index 0000000..330b3f2
--- /dev/null
+++ b/tests/th/T6062.hs
@@ -0,0 +1,3 @@
+{-# LANGUAGE TemplateHaskell #-}
+module T6062 where
+x = [| False True |]
diff --git a/tests/th/all.T b/tests/th/all.T
index 9b9b730..5c0315f 100644
--- a/tests/th/all.T
+++ b/tests/th/all.T
@@ -293,3 +293,10 @@ test('T8333',
      normal,
      run_command,
      ['$MAKE -s --no-print-directory T8333'])
+
+test('T4170', normal, compile, ['-v0'])
+test('T4124', normal, compile, ['-v0'])
+test('T4128', normal, compile, ['-v0'])
+test('T6062', normal, compile, ['-v0'])
+test('T4364', normal, compile, ['-v0'])
+




More information about the ghc-commits mailing list