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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/ccedf63de0bbb1789f96117adb6f4f81868f9f40

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

commit ccedf63de0bbb1789f96117adb6f4f81868f9f40
Author: Simon Marlow <[email protected]>
Date:   Tue Nov 15 11:54:35 2011 +0000

    add test for #5626

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

 tests/codeGen/should_run/5626.hs     |   11 +++++++++++
 tests/codeGen/should_run/5626.stderr |    1 +
 tests/codeGen/should_run/all.T       |    1 +
 3 files changed, 13 insertions(+), 0 deletions(-)

diff --git a/tests/codeGen/should_run/5626.hs b/tests/codeGen/should_run/5626.hs
new file mode 100644
index 0000000..93afcf7
--- /dev/null
+++ b/tests/codeGen/should_run/5626.hs
@@ -0,0 +1,11 @@
+module Main where
+
+wrap x = [x]!!0
+
+f :: [Int] -> a
+f a = foldr (\b -> \c -> c) (undefined ()) (a ++ a) 0
+
+main = do
+  print $ (f [] :: String)
+  print $ wrap $ (f [] :: Int)
+  print $ wrap $ (f [] :: (Int, Int, Int, Int))
diff --git a/tests/codeGen/should_run/5626.stderr 
b/tests/codeGen/should_run/5626.stderr
new file mode 100644
index 0000000..7cab83d
--- /dev/null
+++ b/tests/codeGen/should_run/5626.stderr
@@ -0,0 +1 @@
+5626: Prelude.undefined
diff --git a/tests/codeGen/should_run/all.T b/tests/codeGen/should_run/all.T
index 5640245..fcaf11b 100644
--- a/tests/codeGen/should_run/all.T
+++ b/tests/codeGen/should_run/all.T
@@ -86,3 +86,4 @@ test('4441', normal, compile_and_run, [''])
 test('5149', omit_ways(['ghci']), multi_compile_and_run,
                  ['5149', [('5149_cmm.cmm', '')], ''])
 test('5129', normal, compile_and_run, [''])
+test('5626', exit_code(1), compile_and_run, [''])



_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to