[vector] #32: Performance of concatMap and O2/Odph
vector
vector at projects.haskell.org
Sun Aug 22 09:20:12 EDT 2010
#32: Performance of concatMap and O2/Odph
--------------------+-------------------------------------------------------
Reporter: choener | Owner:
Type: defect | Status: new
Priority: minor | Milestone:
Version: 0.6 | Keywords:
--------------------+-------------------------------------------------------
This one is fun, I get slowdowns of up to 10.000x which is especially nice
in code that is called often ;-) (why exactly, I do not know yet, it
should be more like x5 - 10x)
-Odph adversely effects runtime performance here!
The code below differs only in the "makes it slow" line.
{{{
module Main where
import qualified Data.Vector.Unboxed as VU
import Criterion.Main
iL = 4
jL = 100
good :: Int -> Int -> VU.Vector (Int,Int)
good i j = {-# CORE "good" #-}
VU.map (\(k,l) -> (k-l,l)) $
VU.concatMap (
\d -> VU.map (\d' -> (d,d'))
$ VU.enumFromN 3 (d-5)) -- for each distance, all possible
left/right combinations
$ VU.enumFromN 8 (min 23 (j-i-13)) -- diagonal distance or number of
unpaired nucleotides -2.
{-# INLINE good #-}
bad :: Int -> Int -> VU.Vector (Int,Int)
bad i j = {-# CORE "bad" #-}
VU.map (\(k,l) -> (i+k,j-l)) $ -- this part makes it slow!
VU.map (\(k,l) -> (k-l,l)) $
VU.concatMap (
\d -> VU.map (\d' -> (d,d'))
$ VU.enumFromN 3 (d-5)) -- for each distance, all possible
left/right combinations
$ VU.enumFromN 8 (min 23 (j-i-13)) -- diagonal distance or number of
unpaired nucleotides -2.
{-# INLINE bad #-}
main = defaultMain
[ bench "good" $ whnf (\j -> VU.sum $ VU.map (\(k,l) -> k+l) $ good iL
j) jL
, bench "bad" $ whnf (\j -> VU.sum $ VU.map (\(k,l) -> k+l) $ bad iL j)
jL
]
}}}
--
Ticket URL: <http://trac.haskell.org/vector/ticket/32>
vector <http://trac.haskell.org/vector>
Package vector
More information about the vector
mailing list