[Haskell-cafe] forkIO on multicore[MESSAGE NOT SCANNED]

Paul Keir pkeir at dcs.gla.ac.uk
Fri Dec 19 11:45:45 EST 2008


Thanks Luke, and everyone else. Ok, back to the drawing board.

Paul

 

 

From: Luke Palmer [mailto:lrpalmer at gmail.com] 
Sent: 19 December 2008 16:44
To: Paul Keir
Cc: haskell-cafe at haskell.org
Subject: Re: [Haskell-cafe] forkIO on multicore[MESSAGE NOT SCANNED]

 

On Fri, Dec 19, 2008 at 9:27 AM, Paul Keir <pkeir at dcs.gla.ac.uk> wrote:

	module Main where
	
	import Control.Concurrent
	
	fibs = 0 : 1 : zipWith (+) fibs (tail fibs)
	
	heavytask m = putMVar m (fibs !! 100000)


Oh, also, heavytask is not very heavy at all.  It just writes the thunk
(fibs !! 100000) into the MVar.  Not a single number is added in this
thread.

You probably meant to have the thread evaluate its argument _before_
writing it to the variable:

heavytask m = putMVar m $! (fibs !! 100000)

(Or more transparently)

heavytask m = let answer = fibs !! 100000 in answer `seq` putMVar m
answer

But as per my other comments, you will not see a speedup (in fact, you
will probably see some slowdown as two threads compete to compute the
same value).

Luke
 

	
	
	main = do ms <- sequence $ replicate 2 newEmptyMVar
	         mapM_ (forkIO . heavytask) $ tail ms
	         heavytask $ head ms
	         ms' <- mapM takeMVar ms
	         mapM_ print ms'
	
	Regards,
	Paul
	_______________________________________________
	Haskell-Cafe mailing list
	Haskell-Cafe at haskell.org
	http://www.haskell.org/mailman/listinfo/haskell-cafe

 

-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20081219/64a8c3ab/attachment-0001.htm


More information about the Haskell-Cafe mailing list