
Hello folks, Newbie question: how can I do something like the following? mixing IO and STM. module Test where import System.Random import Control.Concurrent import Control.Concurrent.STM test_Cubby = do tv <- newTVar 0 forkIO (producer tv) >> (consumer tv) where producer tv = do r <- randomRIO (1,10) atomically (do { v <- readTVar tv ; writeTVar tv (v+r) }) print ("insert " ++ show r) producer tv return () consumer tv = do r <- randomRIO (1,10) atomically (do { v <- readTVar tv ; if (v < r) then retry else writeTVar tv (v-r) }) print ("consume " ++ show r) consumer tv return () Thanks.

On 12/29/05, Quan Ta
Hello folks,
Newbie question: how can I do something like the following? mixing IO and STM.
module Test where
import System.Random import Control.Concurrent import Control.Concurrent.STM
test_Cubby = do
Change this:
tv <- newTVar 0
To this:
tv <- atomically (newTVar 0)
forkIO (producer tv) >> (consumer tv) where producer tv = do r <- randomRIO (1,10) atomically (do { v <- readTVar tv ; writeTVar tv (v+r) }) print ("insert " ++ show r) producer tv return () consumer tv = do r <- randomRIO (1,10) atomically (do { v <- readTVar tv ; if (v < r) then retry else writeTVar tv (v-r) }) print ("consume " ++ show r) consumer tv return ()
-- Friendly, Lemmih

test_Cubby = do tv <- newTVar 0
You've almost got it! But "newTVar 0" has type STM Tvar, and you're trying to use it in the IO monad. So just say "tv <- atomically (newTVar 0)" and you're set. Do notice that you'll see output like this: co"nisnusmeer t6 "6 " "c"oinnssuemret 61"" ""cionnsseurmte 95"" ""icnosnesrutm e2 "9 since the two threads are interleaved. -- Brian T. Sniffen bts@alum.mit.edu or brian.sniffen@gmail.com http://www.evenmere.org/~bts

On 12/29/05, Brian Sniffen
test_Cubby = do tv <- newTVar 0
You've almost got it! But "newTVar 0" has type STM Tvar, and you're trying to use it in the IO monad. So just say "tv <- atomically (newTVar 0)" and you're set. Do notice that you'll see output like this:
co"nisnusmeer t6 "6 " "c"oinnssuemret 61""
""cionnsseurmte 95""
""icnosnesrutm e2 "9
since the two threads are interleaved.
-- Brian T. Sniffen bts@alum.mit.edu or brian.sniffen@gmail.com http://www.evenmere.org/~bts
Thank you all for your help and comments ... module Main where import System.Random import Control.Concurrent import Control.Concurrent.STM forever act = act >> forever act test_Cubby = do tv <- atomically (newTVar 0) forkIO (forever $ producer tv) >> (forever $ consumer tv) where producer tv = do r <- randomRIO (1,10) atomically (do { v <- readTVar tv ; writeTVar tv (v+r) }) print ("insert " ++ show r) threadDelay r consumer tv = do r <- randomRIO (1,10) atomically (do { v <- readTVar tv ; if (v < r) then retry else writeTVar tv (v-r) }) print ("consume " ++ show r) threadDelay r I also slow it down a bit to get readable output ... thanks again. - Quan

Also, if you are trying to display a line that looks like insert 5 or consume 6 then consider using
putStrLn ("insert " ++ show r) putStrLn ("consume " ++ show r)
instead of
print ("insert " ++ show r) print ("consume " ++ show r)
to avoid printing out the extra quotation marks. The function print is defined in the prelude as
print :: Show a => a -> IO () print x = putStrLn (show x)
also, you could do:
putStrLn $ "insert " ++ show r
because the $ infix operator is just a tightly binding function application... you can think of it as a sort of left parenthesis that automatically adds a right parenthesis at the end of your expression. Jared.

Here's a version that provides clean output with no delays. It uses a single-entry mailbox (the TMVar "output") to ensure the processing doesn't run too far ahead of the log. module Test where import System.Random import Control.Concurrent import Control.Concurrent.STM test :: IO () test = do tv <- atomically (newTVar 0) output <- atomically (newTMVar "Log begins") forkIO (writer output) forkIO (producer tv output) consumer tv output write :: TMVar String -> String -> STM () write output message = putTMVar output message producer tv o = do r <- randomRIO (1,10) atomically $ do v <- readTVar tv writeTVar tv (v+r) write o ("insert " ++ show r) producer tv o return () consumer tv o = do r <- randomRIO (1,10) atomically $ do v <- readTVar tv if (v < r) then retry else writeTVar tv (v-r) write o ("consume " ++ show r) consumer tv o return () writer :: TMVar String -> IO () writer o = do msg <- atomically $ takeTMVar o putStrLn msg writer o
participants (4)
-
Brian Sniffen
-
Jared Updike
-
Lemmih
-
Quan Ta