[Haskell-cafe] Performance question

Eugene Kirpichov ekirpichov at gmail.com
Thu Feb 26 06:36:26 EST 2009


I, personally, do, but I think that's more of a question to the GHC people :)

2009/2/26  <haskell at kudling.de>:
> 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 <Ben.Lippmeier at anu.edu.au>:
>>>
>>> On 26/02/2009, at 9:27 PM, haskell at 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 at haskell.org
>>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>>
>>
>>
>>
>>--
>>Eugene Kirpichov
>>Web IR developer, market.yandex.ru
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



-- 
Eugene Kirpichov
Web IR developer, market.yandex.ru


More information about the Haskell-Cafe mailing list