[Haskell-cafe] forkIO on multicore

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


Hi all,

I'm seeing no performance increase with a simple coarse-grained
2-thread code using Control.Concurrent. I compile with:

>  hc conc.hs -o conc --make -threaded

and I run with

>  time ./conc +RTS -N2

But using either "-N1" or "-N2", the program runs in about 1.8secs.
(I'd prefer a longer running thread task, but my fib function
currently runs out of memory).

Anyway, my program is below, and I'm using GHC version 6.8.2 on
a 2-core Pentium D. Can anyone help?

module Main where

import Control.Concurrent

fibs = 0 : 1 : zipWith (+) fibs (tail fibs)

heavytask m = putMVar m (fibs !! 100000)

main = do ms <- sequence $ replicate 2 newEmptyMVar
          mapM_ (forkIO . heavytask) $ tail ms
          heavytask $ head ms
          ms' <- mapM takeMVar ms
          mapM_ print ms'

Regards,
Paul


More information about the Haskell-Cafe mailing list