[Haskell-cafe] Why is boxed mutable array so slow?

Branimir Maksimovic bmaxa at hotmail.com
Sat Dec 1 17:09:05 CET 2012


I have made benchmark test inspired by http://lemire.me/blog/archives/2012/07/23/is-cc-worth-it/
What surprised me is that unboxed array is much faster than boxed array.Actually boxed array performance is on par with standard Haskell listwhich is very slow.All in all even unboxed array is about 10 times slower than Java version.I don't understand why is even unboxed array so slow.But! unboxed array consumes least amount of RAM.(warning, program consumes more than 3gb of ram)
 bmaxa at maxa:~/examples$ time ./Cumulboxed arraylast 262486571 seconds 4.972unboxed arraylast 262486571 seconds 0.776listlast 262486571 seconds 6.812
real    0m13.086suser    0m11.996ssys     0m1.080s
-------------------------------------------------------------------------{-# LANGUAGE CPP, BangPatterns #-}import System.CPUTimeimport Text.Printfimport Data.Array.IOimport Data.Array.Baseimport Data.Intimport Control.DeepSeqimport System.Mem
main :: IO()main = do	(newArray_ (0,n'-1) :: IO(A)) >>= test "boxed array" 	performGC	(newArray_ (0,n'-1) :: IO(B)) >>= test "unboxed array" 	performGC	begin <- getCPUTime	printf "list\nlast %d" $ last $ force $ take n' $ sum' data'	end <- getCPUTime	let diff = (fromIntegral (end - begin)) / (10^12)	printf " seconds %.3f\n" (diff::Double)
test s a = do	putStrLn s	begin <- getCPUTime	init' a	partial_sum a	end <- getCPUTime	let diff = (fromIntegral (end - begin)) / (10^12)	last <- readArray a (n'-1)	printf "last %d seconds %.3f\n" last (diff::Double)
n' :: Intn' = 50 * 1000 * 1000
type A = IOArray Int Int32type B = IOUArray Int Int32
init' a = do	(_,n) <- getBounds a	init a 0 n	where 		init a k n 			| k > n = return ()			| otherwise = do				let  !x = fromIntegral $ k + k `div` 3				unsafeWrite a k x				init a (k+1) n
partial_sum a = do				(_,n) <- getBounds a				k <- unsafeRead a 0				ps a 1 n k				where 					ps a i n s						| i > n = return ()						| otherwise = do							k <- unsafeRead a i							let !l = fromIntegral $ s + k							unsafeWrite a i l							ps a (i+1) n l
data' :: [Int32]data' = [k + k `div` 3 | k <- [0..] ]
sum' = scanl1 (+)
 		 	   		  
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20121201/96254ad1/attachment.htm>


More information about the Haskell-Cafe mailing list