[Haskell-cafe] GHC 6.10.1 multi-threaded broken?

Jeroen Baekelandt yrn001 at gmail.com
Sat Nov 29 07:49:48 EST 2008


Hi,

Since I upgraded from ghc 6.8.3 to 6.10.1, I noticed that my programs
do not run multi-threaded anymore. I tried simplifying my code, till I just
took one of the par/pseq demo's to verify if it wasn't my fault.

When I compile this code on 6.8.3 (both ubuntu and OS X), top shows something
like 180% CPU usage and the elapsed time is almost halved.
When compiled with 6.10.1, top shows max 100% and no speedup is noticable
at all. Sample run:

$ ghc --make -threaded paralleltest
$ time ./paralleltest +RTS -N1 -RTS
119201850

real	0m26.024s
user	0m25.494s
sys	0m0.220s

$ time ./paralleltest +RTS -N2 -RTS
119201850

real	0m25.770s
user	0m25.539s
sys	0m0.167s


I have the same on OS X and Ubuntu. I even compiled the Ubuntu ghc from source
myself and verified that GMP was used.

Any ideas?  

Thanks,

Jeroen


Here's the code:

module Main where

import Control.Parallel

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

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

parSumFibEuler :: Int -> Int -> Int
parSumFibEuler a b = f `par` (e `pseq` (e + f))
    where f = fib a
          e = sumEuler b

main = do
    print $ parSumFibEuler 40 7450





More information about the Haskell-Cafe mailing list