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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/676cd5733831f13279139dc05820ac1c9b8f3b9a

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

commit 676cd5733831f13279139dc05820ac1c9b8f3b9a
Author: Simon Marlow <[email protected]>
Date:   Thu Aug 23 09:46:31 2012 +0100

    modify to use TVar instead of QSemN (which has gone)

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

 tests/stm053.hs |   17 ++++++++---------
 1 files changed, 8 insertions(+), 9 deletions(-)

diff --git a/tests/stm053.hs b/tests/stm053.hs
index 12bcc24..b6af5db 100644
--- a/tests/stm053.hs
+++ b/tests/stm053.hs
@@ -1,4 +1,3 @@
-{-# OPTIONS_GHC -fglasgow-exts #-}
 -- !!! test threadDelay, Random, and QSemN.
 
 -- Variation of conc023, testing STM timeouts instead of IO
@@ -7,18 +6,18 @@ import System.Random
 import Control.Concurrent
 import Control.Exception
 import Control.Concurrent.STM
+import Control.Monad
 
 n = 5000  -- no. of threads
 m = 3000  -- maximum delay
 
 main = do
-   s <- newQSemN n
-   is <- sequence (take n (repeat (getStdRandom (randomR (1,m)))))
+   s <- newTVarIO 0
+   is <- replicateM n (getStdRandom (randomR (1,m)))
    mapM (fork_sleep s) is
-   waitQSemN s n
+   atomically $ do i <- readTVar s; check (i == n)
    where
-       fork_sleep :: QSemN -> Int -> IO ThreadId
-       fork_sleep s i = forkIO (do waitQSemN s 1
-                                   t <- registerDelay (i*1000)
-                                   atomically $ (readTVar t >>= check)
-                                   signalQSemN s 1)
+        fork_sleep :: TVar Int -> Int -> IO ThreadId
+        fork_sleep s i = forkIO $ do
+             t <- registerDelay (i*1000)
+             atomically $ do readTVar t >>= check; modifyTVar s (+1)



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

Reply via email to