[Haskell-cafe] MVar and Par ..

Mozhgan Kabiri mozhgan_kch at hotmail.com
Tue Dec 16 06:13:08 EST 2008


Hi ..Hmm .. maybe I explained it badly.For example I want my two processor to do two tasks while they are sharing a variable . Is it not parallelism ? We don't need MVar, as well ? I completely misunderstood !MozhganDate: Tue, 16 Dec 2008 04:03:59 -0700From: lrpalmer at gmail.comTo: mozhgan_kch at hotmail.comSubject: Re: [Haskell-cafe] MVar and Par ..CC: haskell-cafe at haskell.org2008/12/16 Mozhgan Kabiri <mozhgan_kch at hotmail.com>





Hi ..

Hope you are doing well . I've just joined this group. 
Recently, I am  struggling to do some simple experiment with haskell language about parallelism and wrong answers that we can get while using a shared variable .
I tried to write a simple program, for example calculationg 'n=n+1' few times.And then I tried to do it in parallel by using 'par' and 'pseq' . The aim was to get the wrong answer because we have to share a variable here,and without using 'MVar' function we will get the wrong answer for the calculation .
This is fortunately impossible.  par can never change the semantics of a program; it just says "compute this in parallel now because we might need it later", as opposed to just computing it later when it is demanded.  Because Haskell is referentially transparent, the answer it will get now vs. later will always be the same.
Race conditions cannot happen with par.  Perhaps you want to experiment with concurrency rather than parallelism (this is the realm in which MVars lie).  In that case, look at the function forkIO, which spawns a new thread, and the MVar operations.
Luke

I don't know how to write it in parallel in order to get a wrong answer when we don't use MVar,because we have a shared variable here. I read about MVars as well,but also I don't know how to combine MVar and Par together to get the program to work.
I wrote this :
module Main where

f :: Int -> Int -> Int
f i n = g 1 i n
  where g x i n | x <= i = g (x+1) i (n+1)
                | otherwise = n

main :: IO ()
main =
  do putStrLn "starting..."
     let r = f 10 5
     putStrLn (show r)
     putStrLn "finished"
I want to make to work in parallel by using 'Par'.And also use MVar for this simple example to work.
All of the example about MVar are a little bit complicated and I couldn't figure it that how can I write one,the same !
Can any one help me with this ? I want a simple example that I can feel the need of MVar when I run my program in parallel and while I am using a shared variable.
Regards;
Mozhgan
Get news, entertainment and everything you care about at Live.com. Check it out!

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe at haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

_________________________________________________________________
Invite your mail contacts to join your friends list with Windows Live Spaces. It's easy!
http://spaces.live.com/spacesapi.aspx?wx_action=create&wx_url=/friends.aspx&mkt=en-us
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20081216/0e94cd5d/attachment.htm


More information about the Haskell-Cafe mailing list