Re: [Haskell-cafe] Performance question

Do you think it would be feasable to replace the GHC implementation of System.Random with something like System.Random.Mersenne?
Here is a variant that uses mersenne-random-pure64 and works less than 2x slower than C++:
- You don't need to compute samples count an extra time - You don't need to assemble double pairs from a list - Notice the strictness in randomDoublePairs: it doubled performance
{-# LANGUAGE BangPatterns #-}
import System.Random.Mersenne.Pure64 import System( getArgs ) import Data.List( foldl' )
isInCircle :: (Double,Double) -> Bool isInCircle (!x,!y) = sqrt (x*x + y*y) <= 1.0
accumulateHit :: Int -> (Double,Double) -> Int accumulateHit !hits pair = if isInCircle pair then hits + 1 else hits
monteCarloPi :: Int -> [(Double,Double)] -> Double monteCarloPi n xs = 4.0 * fromIntegral hits / fromIntegral n where hits = foldl' accumulateHit 0 . take n $ xs
randomDoublePairs g = let !(!x,!g') = randomDouble g !(!y,!g'') = randomDouble g' in (x,y):randomDoublePairs g''
main = do samples <- (read . head) `fmap` getArgs randomNumbers <- randomDoublePairs `fmap` newPureMT putStrLn . show $ monteCarloPi samples randomNumbers
jkff@*****:~/montecarlo$ time ./mc-hs 10000000 3.1417088
real 0m1.141s user 0m1.140s sys 0m0.000s jkff@*****:~/montecarlo$ time ./mc 10000000 10000000 3.14113
real 0m0.693s user 0m0.690s sys 0m0.000s
2009/2/26 Ben Lippmeier
: On 26/02/2009, at 9:27 PM, haskell@kudling.de wrote:
Currently i can only imagine to define a data type in order to use unboxed Ints instead of the accumulator tuple.
That would probably help a lot. It would also help to use two separate Double# parameters instead of the tuple.
The thing is that i don't see in the profile output yet what to improve. There are some allocations going on in "main", but i don't know what causes it.
The first thing I would do is replace your isInCircle :: (Floating a, Ord a) => (a,a) -> Bool with isInCircle :: (Double, Double) -> Bool
Can you point me to why that matters?
At the machine level, GHC treats the (Floating a, Ord a) as an extra argument to the function. This argument holds function pointers that tell
it
how to perform multiplication and <= for the unknown type 'a'. If you use Double instead of 'a', then it's more likely to use the actual machine op.
Ben.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Eugene Kirpichov Web IR developer, market.yandex.ru

I, personally, do, but I think that's more of a question to the GHC people :)
2009/2/26
Do you think it would be feasable to replace the GHC implementation of System.Random with something like System.Random.Mersenne?
Here is a variant that uses mersenne-random-pure64 and works less than 2x slower than C++:
- You don't need to compute samples count an extra time - You don't need to assemble double pairs from a list - Notice the strictness in randomDoublePairs: it doubled performance
{-# LANGUAGE BangPatterns #-}
import System.Random.Mersenne.Pure64 import System( getArgs ) import Data.List( foldl' )
isInCircle :: (Double,Double) -> Bool isInCircle (!x,!y) = sqrt (x*x + y*y) <= 1.0
accumulateHit :: Int -> (Double,Double) -> Int accumulateHit !hits pair = if isInCircle pair then hits + 1 else hits
monteCarloPi :: Int -> [(Double,Double)] -> Double monteCarloPi n xs = 4.0 * fromIntegral hits / fromIntegral n where hits = foldl' accumulateHit 0 . take n $ xs
randomDoublePairs g = let !(!x,!g') = randomDouble g !(!y,!g'') = randomDouble g' in (x,y):randomDoublePairs g''
main = do samples <- (read . head) `fmap` getArgs randomNumbers <- randomDoublePairs `fmap` newPureMT putStrLn . show $ monteCarloPi samples randomNumbers
jkff@*****:~/montecarlo$ time ./mc-hs 10000000 3.1417088
real 0m1.141s user 0m1.140s sys 0m0.000s jkff@*****:~/montecarlo$ time ./mc 10000000 10000000 3.14113
real 0m0.693s user 0m0.690s sys 0m0.000s
2009/2/26 Ben Lippmeier
: On 26/02/2009, at 9:27 PM, haskell@kudling.de wrote:
Currently i can only imagine to define a data type in order to use unboxed Ints instead of the accumulator tuple.
That would probably help a lot. It would also help to use two separate Double# parameters instead of the tuple.
The thing is that i don't see in the profile output yet what to improve. There are some allocations going on in "main", but i don't know what causes it.
The first thing I would do is replace your isInCircle :: (Floating a, Ord a) => (a,a) -> Bool with isInCircle :: (Double, Double) -> Bool
Can you point me to why that matters?
At the machine level, GHC treats the (Floating a, Ord a) as an extra argument to the function. This argument holds function pointers that tell
it
how to perform multiplication and <= for the unknown type 'a'. If you use Double instead of 'a', then it's more likely to use the actual machine op.
Ben.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Eugene Kirpichov Web IR developer, market.yandex.ru
Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Eugene Kirpichov Web IR developer, market.yandex.ru

haskell@kudling.de wrote:
Do you think it would be feasable to replace the GHC implementation of System.Random with something like System.Random.Mersenne?
There's a problem with using the Mersenne Twister: System.Random's interface has a split method: class RandomGen g where split :: g -> (g, g) The Mersenne Twister is good at producing a single stream of random numbers - in fact it works by generating a whole block of random numbers in one go, then consuming the block, and only then generating the next block. I have no idea how to implement a split method that produces independent streams. Even if I did, using split a lot would likely spoil the performance benefit of the generator. (System.Random.Mersenne.Pure64 provides a RandomGen instance for PureMT, but it cheats:) split = error "System.Random.Mersenne.Pure: unable to split the mersenne twister" Bertram

You can implement a reasonable split if you can fast-forward the generator.
There's no known method to fast-forward the MT, but other generators
like MRG32k3a can handle it.
-- Lennart
On Thu, Feb 26, 2009 at 12:08 PM, Bertram Felgenhauer
haskell@kudling.de wrote:
Do you think it would be feasable to replace the GHC implementation of System.Random with something like System.Random.Mersenne?
There's a problem with using the Mersenne Twister: System.Random's interface has a split method:
class RandomGen g where split :: g -> (g, g)
The Mersenne Twister is good at producing a single stream of random numbers - in fact it works by generating a whole block of random numbers in one go, then consuming the block, and only then generating the next block.
I have no idea how to implement a split method that produces independent streams. Even if I did, using split a lot would likely spoil the performance benefit of the generator.
(System.Random.Mersenne.Pure64 provides a RandomGen instance for PureMT, but it cheats:)
split = error "System.Random.Mersenne.Pure: unable to split the mersenne twister"
Bertram _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Thu, Feb 26, 2009 at 7:17 AM, Lennart Augustsson
You can implement a reasonable split if you can fast-forward the generator. There's no known method to fast-forward the MT, but other generators like MRG32k3a can handle it.
Are you aware of any existing (C/C++/Haskell) library implementing this algorithm? A cursory google search didn't turn anything up for me, aside from something implemented in Java, and another in Lisp. --Tracy

2009/2/26 Tracy Wadleigh
On Thu, Feb 26, 2009 at 7:17 AM, Lennart Augustsson
wrote: You can implement a reasonable split if you can fast-forward the generator. There's no known method to fast-forward the MT, but other generators like MRG32k3a can handle it.
Are you aware of any existing (C/C++/Haskell) library implementing this algorithm? A cursory google search didn't turn anything up for me, aside from something implemented in Java, and another in Lisp.
Maybe http://www.iro.umontreal.ca/~lecuyer/myftp/streams00/ ? -- Felipe.

Awesome, Felipe. Thanks.
--Tracy
On Thu, Feb 26, 2009 at 11:07 AM, Felipe Lessa
2009/2/26 Tracy Wadleigh
: On Thu, Feb 26, 2009 at 7:17 AM, Lennart Augustsson < lennart@augustsson.net> wrote:
You can implement a reasonable split if you can fast-forward the generator. There's no known method to fast-forward the MT, but other generators like MRG32k3a can handle it.
Are you aware of any existing (C/C++/Haskell) library implementing this algorithm? A cursory google search didn't turn anything up for me, aside from something implemented in Java, and another in Lisp.
Maybe http://www.iro.umontreal.ca/~lecuyer/myftp/streams00/http://www.iro.umontreal.ca/%7Elecuyer/myftp/streams00/?
-- Felipe.
participants (6)
-
Bertram Felgenhauer
-
Eugene Kirpichov
-
Felipe Lessa
-
haskell@kudling.de
-
Lennart Augustsson
-
Tracy Wadleigh