[commit: testsuite] master: Add test for #8186 (f3bef38)

git at git.haskell.org git at git.haskell.org
Wed Aug 28 05:07:06 CEST 2013


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

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

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

commit f3bef384968fca3ed3a9f9874d44bbdc7d8d3218
Author: Richard Eisenberg <eir at cis.upenn.edu>
Date:   Tue Aug 27 17:38:41 2013 -0400

    Add test for #8186


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

f3bef384968fca3ed3a9f9874d44bbdc7d8d3218
 tests/th/T8186.hs     |   11 +++++++++++
 tests/th/T8186.stdout |    3 +++
 tests/th/all.T        |    2 ++
 3 files changed, 16 insertions(+)

diff --git a/tests/th/T8186.hs b/tests/th/T8186.hs
new file mode 100644
index 0000000..1580a9c
--- /dev/null
+++ b/tests/th/T8186.hs
@@ -0,0 +1,11 @@
+{-# LANGUAGE TemplateHaskell, ParallelListComp #-}
+
+module Main where
+
+list = [ (x,y) | x <- [1..10], x `mod` 2 == 0 | y <- [2,6..50] ]
+
+list' = $( [| [ (x,y) | x <- [1..10], x `mod` 2 == 0 | y <- [2,6..50] ] |] )
+
+main = do putStrLn (show list)
+          putStrLn (show list')
+          putStrLn $ show (list == list')
\ No newline at end of file
diff --git a/tests/th/T8186.stdout b/tests/th/T8186.stdout
new file mode 100644
index 0000000..cd4aa8b
--- /dev/null
+++ b/tests/th/T8186.stdout
@@ -0,0 +1,3 @@
+[(2,2),(4,6),(6,10),(8,14),(10,18)]
+[(2,2),(4,6),(6,10),(8,14),(10,18)]
+True
diff --git a/tests/th/all.T b/tests/th/all.T
index fcb743f..455f45d 100644
--- a/tests/th/all.T
+++ b/tests/th/all.T
@@ -285,3 +285,5 @@ test('T8028',
 test('TH_Roles1', normal, compile_fail, ['-v0'])
 test('TH_Roles2', normal, compile, ['-v0 -ddump-tc'])
 test('TH_Roles3', normal, compile, ['-v0 -dsuppress-uniques'])
+
+test('T8186', normal, compile_and_run, ['-v0'])
\ No newline at end of file





More information about the ghc-commits mailing list