[commit: testsuite] master: Add simple test for tryAtomicReadMVar. (e71dd63)
Edward Z. Yang
ezyang at MIT.EDU
Thu Jul 11 02:08:28 CEST 2013
Repository : ssh://darcs.haskell.org//srv/darcs/testsuite
On branch : master
https://github.com/ghc/testsuite/commit/e71dd63aa00b0702e5debea662c6e49f64f47974
>---------------------------------------------------------------
commit e71dd63aa00b0702e5debea662c6e49f64f47974
Author: Edward Z. Yang <ezyang at mit.edu>
Date: Wed Jul 10 13:37:20 2013 -0700
Add simple test for tryAtomicReadMVar.
Signed-off-by: Edward Z. Yang <ezyang at mit.edu>
>---------------------------------------------------------------
tests/concurrent/should_run/all.T | 1 +
tests/concurrent/should_run/tryAtomicReadMVar1.hs | 11 +++++++++++
2 files changed, 12 insertions(+), 0 deletions(-)
diff --git a/tests/concurrent/should_run/all.T b/tests/concurrent/should_run/all.T
index 5665764..1b729fa 100644
--- a/tests/concurrent/should_run/all.T
+++ b/tests/concurrent/should_run/all.T
@@ -77,6 +77,7 @@ test('T5866', exit_code(1), compile_and_run, [''])
test('atomicReadMVar1', normal, compile_and_run, [''])
test('atomicReadMVar2', normal, compile_and_run, [''])
test('atomicReadMVar3', normal, compile_and_run, [''])
+test('tryAtomicReadMVar1', normal, compile_and_run, [''])
# -----------------------------------------------------------------------------
# These tests we only do for a full run
diff --git a/tests/concurrent/should_run/tryAtomicReadMVar1.hs b/tests/concurrent/should_run/tryAtomicReadMVar1.hs
new file mode 100644
index 0000000..387dde3
--- /dev/null
+++ b/tests/concurrent/should_run/tryAtomicReadMVar1.hs
@@ -0,0 +1,11 @@
+module Main where
+
+import GHC.MVar
+import Control.Concurrent
+
+main = do
+ m <- newMVar (0 :: Int)
+ Just 0 <- tryAtomicReadMVar m
+ takeMVar m
+ Nothing <- tryAtomicReadMVar m
+ return ()
More information about the ghc-commits
mailing list