[vector] #45: fromList/sort performance problems
vector
vector at projects.haskell.org
Thu Oct 21 02:39:08 EDT 2010
#45: fromList/sort performance problems
-------------------+--------------------------------------------------------
Reporter: rl | Owner:
Type: defect | Status: new
Priority: major | Milestone: 0.8
Version: 0.7 | Keywords:
-------------------+--------------------------------------------------------
Reportedly, this is slow:
{{{
import Prelude hiding (sum)
import Data.Vector.Algorithms.Combinators (apply)
import Data.Vector.Algorithms.Intro (sort)
import Data.Vector.Unboxed (Vector, Unbox, fromList, sum)
vsort :: (Unbox a, Ord a) => [a] -> Vector a
vsort = apply sort . fromList
list :: [Int]
list = takeWhile (> 0) $ iterate (subtract 1) 10000000
main = do
print $ sum $ vsort list
}}}
And this is fast:
{{{
import Prelude hiding (sum)
import Control.Monad (zipWithM_)
import Data.Vector.Algorithms.Intro (sort)
import Data.Vector.Generic (create)
import Data.Vector.Unboxed (Vector, Unbox, sum)
import Data.Vector.Unboxed.Mutable (new, write)
vsort :: (Unbox a, Ord a) => [a] -> Vector a
vsort list = create $ do
v <- new (length list)
zipWithM_ (\i x -> write v i x) [0..] list
sort v
return v
list :: [Int]
list = takeWhile (> 0) $ iterate (subtract 1) 10000000
main = do
print $ sum $ vsort list
}}}
Also, boxed vector seem to kill performance here.
--
Ticket URL: <http://trac.haskell.org/vector/ticket/45>
vector <http://trac.haskell.org/vector>
Package vector
More information about the vector
mailing list