[Haskell-cafe] Threading and Mullticore Computation
Don Stewart
dons at galois.com
Tue Mar 3 12:40:48 EST 2009
mwinter:
> Hi,
>
> I tried a get into concurrent Haskell using multiple cores. The program below
> creates 2 task in different threads, executes them, synchronizes the threads
> using MVar () and calculates the time needed.
>
> import System.CPUTime
> import Control.Concurrent
> import Control.Concurrent.MVar
>
> myTask1 = do
> return $! fac 60000
> print "Task1 done!"
> where fac 0 = 1
> fac n = n * fac (n-1)
>
> myTask2 = do
> return $! fac' 60000 1 1
> print "Task2 done!"
> where fac' n m p = if m>n then p else fac' n (m+1) (m*p)
>
> main = do
> mvar <- newEmptyMVar
> pico1 <- getCPUTime
> forkIO (myTask1 >> putMVar mvar ())
> myTask2
> takeMVar mvar
> pico2 <- getCPUTime
> print (pico2 - pico1)
>
>
> I compiled the code using
> $ ghc FirstFork.hs -threaded
> and executed it by
> $ main +RTS -N1 resp. $ main +RTS -N2
> I use GHC 6.8.3 on Vista with an Intel Dual Core processor. Instead of getting
> a speed up when using 2 cores I get as significant slow down, even though there
> is no sharing in my code above (at least none I am aware of. BTW, that was
> reason
> that I use 2 different local factorial functions). On my computer the 1-core
> version
> takes about 8.3sec and the 2-core version 12.8sec. When I increase the numbers
> from 60000 to 100000 the time difference gets even worse (30sec vs 51 sec). Can
> anybody give me an idea what I am doing wrong?
If you just want to check that your machine can do multicore, here's the
"hello world" I've been using:
import Control.Parallel
main = a `par` b `par` c `pseq` print (a + b + c)
where
a = ack 3 10
b = fac 42
c = fib 34
fac 0 = 1
fac n = n * fac (n-1)
ack 0 n = n+1
ack m 0 = ack (m-1) 1
ack m n = ack (m-1) (ack m (n-1))
fib 0 = 0
fib 1 = 1
fib n = fib (n-1) + fib (n-2)
To be run as:
$ ghc -O2 -threaded --make hello.hs
[1 of 1] Compiling Main ( hello.hs, hello.o )
Linking hello ...
$ time ./hello +RTS -N2
1405006117752879898543142606244511569936384005711076
./hello +RTS -N2 2.29s user 0.01s system 152% cpu 1.505 total
^^^^
-- Don
More information about the Haskell-Cafe
mailing list