[Haskell-cafe] How to improve the zipwith's performance

julian zhangjun.julian at gmail.com
Fri Aug 15 02:07:29 UTC 2014


Dear 

The runnable code is blow

import Data.Clustering.Hierarchical
import qualified Data.Vector.Primitive as DV
import System.Random
import Control.Monad


main = do
    vectorList <- genTestdata
    let cluster = dendrogram SingleLinkage vectorList getVectorDistance  
    putStrLn $ show cluster

genZero x 
    | x<5 = x
    |otherwise = 0

genVector::IO (DV.Vector Int)
genVector = do
    listRandom <- mapM (\x -> randomRIO (1,30) ) [1..20]
    let intOut = DV.fromList $ map genZero listRandom
    return intOut

genTestdata = do 
    r <- sequence  $ map (\x -> liftM (\y -> (x,y)) genVector) [1..1000]
    return r

getExp2 v1 v2 = d*d
    where
        d = v1 - v2

getExp v1 v2
    | v1 == v2 = 0
    | otherwise = getExp2 v1 v2

tfoldl  d = DV.foldl1' (+) d

changeDataType:: Int -> Double
changeDataType d = fromIntegral d

getVectorDistance::(a,DV.Vector Int)->(a, DV.Vector Int )->Double
getVectorDistance v1 v2 = fromIntegral $ tfoldl dat
    where
        l1 = snd v1
        l2 = snd v2
        dat = DV.zipWith getExp l1 l2

发自我的 iPhone

> 在 2014年8月15日,上午4:25,Felipe Lessa <felipe.lessa at gmail.com> 写道:
> 
> Hey, Jun Zhang!
> 
> It would be nice if you provided a full runnable example so that someone
> may tinker with it testing different approaches.
> 
> As it stands, I don't have any suggestions of how you could extract more
> performance.
> 
> 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