
Greetings, when using parMap (or parList and demanding) I see a curious pattern in CPU usage. Running "parMap rnf fib [1..100]" gives the following pattern of used CPUs: 4,3,2,1,4,3,2,1,... The fib function requires roughly two times the time if we go from fib(n) to fib(n+1), meaning that calculating the next element in the list always takes longer than the current. What I would like is a version of parMap that directly takes a free CPU and lets it calculate the next result, giving the usage pattern 4,4,4,4,... Below you find the simple Haskell program, which gives these results, please compile with "ghc --make -threaded -O2 Para.hs" and run on a machine with at least two cores and "./Para +RTS -N2" or better. I am not filing a bug yet as I would prefer to be told that I did it wrong and here is a better way: ... Thanks, Christian (Please assume that later on, "fib" will be replaced by something meaningful ;) # ghc --version # The Glorious Glasgow Haskell Compilation System, version 6.10.1 module Main where import Control.Parallel.Strategies -- parallel computation of fibonacci numbers in slow fib :: Int -> Int fib n | n < 1 = error "n < 1" | n == 1 = 1 | n == 2 = 1 | otherwise = fib (n-1) + fib(n-2) fibs = parMap rnf fib $ [1..100] -- fibs = let fs = map fib $ [1..100] in fs `demanding` (parList rnf fs) main = do mapM_ (putStrLn . show) $ zip [1..] fibs