Parallel forkOS does not work on ubuntu

Hoang Truong hoangta at comp.nus.edu.sg
Tue Dec 9 07:47:53 EST 2008


Hi Simon,
I tried with forkIO and added another dowork functions but the result is the
same: only one core is used, three other cores are idle. Do you have any
other suggestions? Is there anything I should take care when installing GHC?

I also did try the Wombat.hs from the tutorial, but only one core is used
and the times are almost the same.

seq sum: 119201850
seq time: 20.959932 seconds.
par sum: 119201850
par time: 20.959547 seconds.

--------
import System.Time
import Control.Parallel

fib :: Int -> Int
fib 0 = 0
fib 1 = 1
fib n = fib (n-1) + fib (n-2)

secDiff :: ClockTime -> ClockTime -> Float
secDiff (TOD secs1 psecs1) (TOD secs2 psecs2) =
fromInteger (psecs2 - psecs1) / 1e12 + fromInteger (secs2 - secs1)

mkList :: Int -> [Int]
mkList n = [1..n-1]

relprime :: Int -> Int -> Bool
relprime x y = gcd x y == 1

euler :: Int -> Int
euler n = length (filter (relprime n) (mkList n))

sumEuler :: Int -> Int
sumEuler = sum . (map euler) . mkList

sumFibEuler:: Int -> Int -> Int
sumFibEuler a b = fib a + sumEuler b

parSumFibEuler a b = f `par` (e `pseq` (e+ f))
where
f = fib a
e = sumEuler b

r1 :: Int
r1 = sumFibEuler 40 7450

r2 :: Int
r2 = parSumFibEuler 40 7450


main :: IO ()
main =
do
t0 <- getClockTime
pseq r1 (return())
t1 <- getClockTime
putStrLn ("seq sum: " ++ show r1)
putStrLn ("seq time: " ++ show (secDiff t0 t1) ++ " seconds.")
t0 <- getClockTime
pseq r2 (return())
t1 <- getClockTime
putStrLn ("par sum: " ++ show r2)
putStrLn ("par time: " ++ show (secDiff t0 t1) ++ " seconds.")
-----

Many thanks,

Hoang


On Tue, Dec 9, 2008 at 7:26 PM, Simon Marlow <marlowsd at gmail.com> wrote:

> Hoang Truong wrote:
>
>> Hello everybody,
>>
>> I am following "A Tutorial on Parallel and Concurrent Programming in
>> Haskell" and I have a problem with making Haskell to use my multi-cores
>> (Core 2 Quad  CPU).
>> The Haskel version I used is GHC 6.10.1, for Haskell 98. I compile my
>> below program with command: ghc --make -threaded -debug thread0.hs, and run
>> with: thread0 +RTS -N4 while watching the cpu usage on another terminal (by:
>> mpstat -P ALL 1 100), but the program uses only one core of my Ubuntu Linux.
>>
>> Do any of you know why or has any suggestions? Below is my program:
>>
>
> Why do people still insist on using forkOS?  You don't need forkOS unless
> you need to call C libraries that use thread-local state.  Otherwise, it
> will just reduce your performance compared to forkIO.  Admittedly the
> documentation for forkOS has been misleading in the past, but I think the
> current version is pretty clear:
>
>
> http://www.haskell.org/ghc/docs/latest/html/libraries/base/Control-Concurrent.html#v%3AforkOS
>
>  import Control.Concurrent
>> import Control.Concurrent.MVar
>>
>> fib :: Int -> Int
>> fib 0 = 0
>> fib 1 = 1
>> fib n = fib (n-1) + fib (n-2)
>>
>> dowork =
>> putStrLn ("fib 35 = " ++ (show (fib 35)))
>>
>
> Perhaps you were expecting "fib 35" to be repeatedly executed each time you
> call dowork?  Laziness means it only gets evaluated once.
>
> Cheers,
>        Simon
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/glasgow-haskell-users/attachments/20081209/1382174b/attachment-0001.htm


More information about the Glasgow-haskell-users mailing list