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
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)
>
On 12/29/05, Brian Sniffen <[EMAIL PROTECTED]> wrote:
> test_Cubby => do> tv <- newTVar 0You've almost got it! But "newTVar 0" has type STM Tvar, and you'retrying 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 likethis
> 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""
On 12/29/05, Quan Ta <[EMAIL PROTECTED]> wrote:
> 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:
>
Hello folks,
Newbie question: how can I do something like the following? mixing IO and STM.
module Test whereimport System.Random
import Control.Concurrentimport Control.Concurrent.STM
test_Cubby = do
tv <- newTVar 0
forkIO (producer tv) >> (consumer tv) where
producer tv = do r <-