[vector] #96: forM_ in unboxed module generates temporary vector
vector
vector at projects.haskell.org
Fri Jun 7 02:48:46 BST 2013
#96: forM_ in unboxed module generates temporary vector
--------------------+-------------------------------------------------------
Reporter: sanketr | Owner:
Type: defect | Status: new
Priority: major | Milestone:
Version: 0.7 | Keywords:
--------------------+-------------------------------------------------------
I discovered this when debugging some performance issues.
Data.Vector.Unboxed.forM_ generates temporary vector in each iteration,
and copies contents to it which causes slowdown in the code that use it
for a mutating loop.
I think the example code below reproduces it - in the core, newByteArray
seems to be generated for forM_:
{{{
{-# LANGUAGE BangPatterns #-}
import Data.Vector.Unboxed.Mutable as MU
import Data.Vector.Unboxed as U hiding (mapM_)
import Control.Monad.ST as ST
import Control.Monad.Primitive (PrimState)
import Data.Int
type MVI1 s = MVector (PrimState (ST s)) Int
gridWalk :: MVI1 s -> Int -> ST s ()
gridWalk fp !k = do
{-#SCC cmp #-} MU.unsafeWrite fp k k
{-#INLINE gridWalk #-}
findSnakes :: Vector Int32 -> Vector Int32 -> MVI1 s -> Int -> Int ->
(Int -> Int -> Int) -> ST s ()
findSnakes a b fp !k !ct !op = U.forM_ (U.fromList [0..ct-1]) (\x ->
gridWalk fp (op k x))
{-#INLINE findSnakes #-}
f :: Vector Int32 -> Vector Int32 -> Int
f a b = runST $ do
fp <- new 10
findSnakes a b fp (0) 10 (+)
return 5
{-#INLINABLE f #-}
main = print $ f (U.fromList [0]) (U.fromList [0])
}}}
In the optimized core, this is seen (create new vector, and copy the
contents there):
{{{
$j =
\ (x1 :: Int#) ->
case newByteArray# (*# x1 4) (sc1 `cast` ...)
of _ { (# ipv, ipv1 #) ->
case (copyMutableByteArray# sc4 (*# sc2 4) ipv1 0 (*#
sc3 4) ipv)
`cast` ...
}}}
I had to work around this issue of temporary generation by writing a loop
myself.
Tested with GHC 7.6.1, vector 0.10
--
Ticket URL: <http://trac.haskell.org/vector/ticket/96>
vector <http://trac.haskell.org/vector>
Package vector
More information about the vector
mailing list