[Haskell-cafe] Vector sort poor performance

Alexander Pakhomov ker0sin at ya.ru
Thu Aug 21 10:20:38 UTC 2014


1) The problem is not a measurement. The whole foo function a bottleneck in my program.
2) Change Vector.Algorithms.Intro.sort to List.sort improves performance 2-3x, remove sort improves performance 30x
C++ is 30x faster on this task. That's strange, because using Vector.Mutable.Unboxed should provide good performance.
And C++ spends all time in vector allocation. With on stack dynamic array it is 400 times faster.
3) Anyway Criterion measurement is 1.6 us (different machine)

Measurement code is:

import Data.List
import Control.Monad
import Control.Monad.ST
import qualified Data.Vector.Unboxed as V
import qualified Data.Vector.Unboxed.Mutable as MV
import qualified Data.Vector.Algorithms.Intro as Intro
import Data.IORef
import Criterion.Main

arr = V.fromList ([1,2] :: [Double])
foo x = V.head q
    where
        q = runST $ do
            res <- V.unsafeThaw $ V.concat
                [ V.map (\e -> e + x) arr
                , V.map (\e -> e - x) arr]
            Intro.sort res
            V.unsafeFreeze res

main = do
    ref <- newIORef 0
    defaultMain [
        bgroup "sort" [ bench "10" $ whnf foo 10]]


21.08.2014, 09:01, "Felipe Lessa" <felipe.lessa at gmail.com>:
> On 20-08-2014 21:24, Alexander Pakhomov wrote:
>>      ref <- newIORef 0
>>      forM_ [0..100000] $! \i -> do
>>          modifyIORef' ref (+(foo $ fromInteger i)) -- for foo not to optimize out
>>      readIORef ref >>= print
>>
>>  ghc -O2 sort.hs && time ./sort
>
> My first recommendation is to use criterion.  It will get you a way
> better idea of the timing needed for your function, specially since it
> does not do much work.
>
> Cheers,
>
> --
> Felipe.
>
> ,
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe


More information about the Haskell-Cafe mailing list