[Haskell-cafe] Re: A problem with par and modules boundaries...

John Lato jwlato at gmail.com
Fri May 22 10:51:18 EDT 2009


Hi Mario,

It looks like the parallelize function is getting inlined when it's in
the same file, but not when it's in a separate file.

Adding a {-# INLINE parallelize #-} pragma to the module with
parallelize recovers all the performance for me.

You could probably see exactly what's happening in more detail by
going through the Core output.

John Lato

> Message: 23
> Date: Thu, 21 May 2009 22:59:51 -0400
> From: Mario Bla?evi? <mblazevic at stilo.com>
> Subject: [Haskell-cafe] A problem with par and modules boundaries...
> To: <haskell-cafe at haskell.org>
> Message-ID: <.1242961191 at magma.ca>
> Content-Type: text/plain; charset="utf-8"
>
> I'll cut to the chase. The short program below works perfectly: when I compile it
> with -O2 -threaded and run with +RTS -N2 command-line options, I get a nearly 50%
> real-time improvement:
>
> $ time ./primes-test +RTS -N2
> 5001
>
> real    0m9.307s
> user    0m16.581s
> sys     0m0.200s
>
> However, if I move the `parallelize' definition into another module and import
> that module, the performance is completely lost:
>
> $ time ./primes-test +RTS -N2
> 5001
>
> real    0m15.282s
> user    0m15.165s
> sys     0m0.080s
>
> I'm confused. I know that `par` must be able work across modules boundaries,
> because Control.Parallel.Strategies is a module and presumably it works. What am
> I doing wrong?
>
>
>> module Main where
>>
>> import Control.Parallel
>> import Data.List (find)
>> import Data.Maybe (maybe)
>>
>> --import Parallelizable
>> parallelize a b = a `par` (b `pseq` (a, b))
>>
>> test :: Integer -> Integer -> Integer
>> test n1 n2 = let (p1, p2) = parallelize
>>                                (product $ factors $ product [1..n1])
>>                                (product $ factors $ product [1..n2])
>>              in p2 `div` p1
>>
>> factors n = maybe [n] (\k-> (k : factors (n `div` k)))
>>                   (find (\k-> n `mod` k == 0) [2 .. n - 1])
>>
>> main = print (test 5000 5001)
>


More information about the Haskell-Cafe mailing list