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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/23ad5a9841b2e2935daf2fc35e534ad3f8232494

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

commit 23ad5a9841b2e2935daf2fc35e534ad3f8232494
Author: Simon Marlow <marlo...@gmail.com>
Date:   Mon Oct 29 10:46:47 2012 +0000

    add test for #7319

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

 tests/codeGen/should_run/T7319.hs     |   11 +++++++++++
 tests/codeGen/should_run/T7319.stderr |    5 +++++
 tests/codeGen/should_run/all.T        |    6 ++++++
 3 files changed, 22 insertions(+), 0 deletions(-)

diff --git a/tests/codeGen/should_run/T7319.hs 
b/tests/codeGen/should_run/T7319.hs
new file mode 100644
index 0000000..5159744
--- /dev/null
+++ b/tests/codeGen/should_run/T7319.hs
@@ -0,0 +1,11 @@
+{-# LANGUAGE BangPatterns, MagicHash #-}
+import Control.Exception
+import System.Environment
+import GHC.Exts
+
+main = do
+  args <- getArgs
+  foo args
+
+foo _ = let !e = toException (ErrorCall "test") in
+        raise# e
diff --git a/tests/codeGen/should_run/T7319.stderr 
b/tests/codeGen/should_run/T7319.stderr
new file mode 100644
index 0000000..4d3bc94
--- /dev/null
+++ b/tests/codeGen/should_run/T7319.stderr
@@ -0,0 +1,5 @@
+*** Exception (reporting due to +RTS -xc): (base:GHC.Exception.SomeException), 
stack trace: 
+  Main.foo,
+  called from Main.main,
+  called from Main.CAF
+T7319: test
diff --git a/tests/codeGen/should_run/all.T b/tests/codeGen/should_run/all.T
index cef3994..f2fbe43 100644
--- a/tests/codeGen/should_run/all.T
+++ b/tests/codeGen/should_run/all.T
@@ -94,3 +94,9 @@ test('setByteArray', normal, compile_and_run, [''])
 test('6146', normal, compile_and_run, [''])
 test('T5900', normal, compile_and_run, [''])
 test('T7163', normal, compile_and_run, [''])
+
+# Gives different results when optimised, so restrict to just one way
+test('T7319', [ extra_ways(['prof']), only_ways(['prof']), exit_code(1),
+                req_profiling,
+                extra_hc_opts('-fprof-auto'),
+                extra_run_opts('+RTS -xc') ], compile_and_run, [''])



_______________________________________________
Cvs-ghc mailing list
Cvs-ghc@haskell.org
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to