[Haskell-cafe] Vector sort poor performance

Alexander Pakhomov ker0sin at ya.ru
Thu Aug 21 00:24:05 UTC 2014


Hi!

I've got dramatically low sort performamce: about 2 us of time and 5 kB of allocation
for unpacked vector of 4 (four) Double.

Code:
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

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
    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 
[1 of 1] Compiling Main             ( sort.hs, sort.o )
Linking sort ...
-4.999949999e9

real    0m0.189s
user    0m0.184s
sys     0m0.000s

Does anybody know what's going on?


More information about the Haskell-Cafe mailing list