[Haskell-cafe] TMVar's are great but fail under ghc 6.10.1 windows

Sterling Clover s.clover at gmail.com
Mon Mar 30 22:54:42 EDT 2009


Is it possible to rewrite this without unsafeIOToSTM? unsafeIOToSTM  
is insanely unsafe, and can cause otherwise working STM code to do  
unpredictable and terrible things to the runtime.

Cheers,
Sterl.

On Mar 30, 2009, at 4:27 PM, Alberto G. Corona wrote:

> Control.Concurrent.STM.TMVar's  combine the best of MVars and TVars:
>
> -Unlike TVars, they permit blocking/early retry when the TMVar is  
> being used by other process, so that complete processes are not  
> retried at the end when happens that the TVars have been modified  
> in the meantime.
>
> - Unlike MVars, they have no deadlocks, specially when a process is  
> trying to adquire exclusive access to more than one TMVar.
>
> however, It happens that fails in my windows box with ghc 6.10.1  ,  
> single core
>
> here is the code and the results:
>
>
> -----------begin code:
>
> module Main where
>
> import Control.Concurrent.STM
>
> import Control.Concurrent
> import System.IO.Unsafe
> import GHC.Conc
>
>
>
> mtxs=  unsafePerformIO $ mapM newTMVarIO $ take 5 $ repeat  0
>
> proc i= atomically $ do
>  unsafeIOToSTM $ putStr $ "init of process "++ show i++"\n"
>  xs<- mapM takeTMVar mtxs
>
>  mapM (\(mtx,x) ->putTMVar mtx (x+1)) $  zip mtxs xs
>
>  xs' <- mapM readTMVar mtxs
>  unsafeIOToSTM $ putStr $ "End of processs "++show i ++ " result= "+ 
> + show xs'++"\n"
>
>
>
> main=do
> mapM (forkIO . proc) [1..5]
> threadDelay 100000000
>
> -------------end code
>
> the rigth result must be (occasionally with some "init of process  
> x" repeated)
>
> init of process 1
> init of process 2
> End of processs 1 result= [1,1,1,1,1]
> init of process 2                                       -- retried
> End of processs 2 result= [2,2,2,2,2]
> init of process 3
> End of processs 3 result= [3,3,3,3,3]
> init of process 4
> End of processs 4 result= [4,4,4,4,4]
> init of process 5
> End of processs 5 result= [5,5,5,5,5]
>
>
> under windows the program produces strange results for example
>
> init of process 1
> init of process 2
> init of process 3
> init of process 4
> init of process 5
> End of processs 1 result= [1,1,1,1,1]
> End of processs 2 result= [1,1,1,1,1]
> (deadlock)
>
> or this other:
>
> init of process 1
> init of process 2
> init of process 3
> init of process 4
> init of process 5
> End of processs 1 result= [1,1,1,1,1]
> End of processs 2 result= [1,1,1,1,1]
> init of process 3
> init of process 4
> init of process 5
> init of process 2
> End of processs 4 result= [2,2,2,2,2]
> End of processs 3 result= [2,2,2,2,2]
> End of processs 5 result= [2,2,2,2,2]
> End of processs 2 result= [2,2,2,2,2]
> init of process 3
> init of process 5
> init of process 2
> End of processs 3 result= [3,3,3,3,3]
> End of processs 5 result= [3,3,3,3,3]
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe



More information about the Haskell-Cafe mailing list