Repository : ssh://darcs.haskell.org//srv/darcs/packages/base

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/78ba99dbc668fa0439095333657c91d3cabb317e

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

commit 78ba99dbc668fa0439095333657c91d3cabb317e
Author: Ian Lynagh <[email protected]>
Date:   Sat Nov 19 23:53:35 2011 +0000

    Move ioref001 to base/tests

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

 tests/all.T           |    6 ++++++
 tests/ioref001.hs     |    9 +++++++++
 tests/ioref001.stdout |    1 +
 3 files changed, 16 insertions(+), 0 deletions(-)

diff --git a/tests/all.T b/tests/all.T
index b96722a..c7f9e7f 100644
--- a/tests/all.T
+++ b/tests/all.T
@@ -24,3 +24,9 @@ test('take001', extra_run_opts('1'), compile_and_run, [''])
 test('genericNegative001', extra_run_opts('-1'), compile_and_run, [''])
 test('ix001', normal, compile_and_run, [''])
 
+# need to add -K64m to the compiler opts, so that GHCi gets it too
+test('ioref001',
+     [skip_if_fast,extra_run_opts('+RTS -K64m -RTS')],
+     compile_and_run,
+     ['+RTS -K64m -RTS'])
+
diff --git a/tests/ioref001.hs b/tests/ioref001.hs
new file mode 100644
index 0000000..837b82e
--- /dev/null
+++ b/tests/ioref001.hs
@@ -0,0 +1,9 @@
+
+module Main where
+
+import Data.IORef
+
+loop r 0 = return ()
+loop r c = loop r (c-1) >> writeIORef r 42
+
+main = newIORef 0 >>= \r -> loop r 1000000 >> putStrLn "done"
diff --git a/tests/ioref001.stdout b/tests/ioref001.stdout
new file mode 100644
index 0000000..19f86f4
--- /dev/null
+++ b/tests/ioref001.stdout
@@ -0,0 +1 @@
+done



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

Reply via email to