[Haskell-cafe] vector recycling

Roman Leshchinskiy rl at cse.unsw.edu.au
Sat Apr 17 02:19:08 EDT 2010


On 17/04/2010, at 13:32, Ben wrote:

> module Main where
> 
> import qualified Data.Vector.Generic as V
> import qualified Data.Vector.Unboxed as UV
> 
> type Vec = UV.Vector Double
> 
> axpy :: Double -> Vec -> Vec -> Vec
> axpy a x y = V.zipWith (+) (V.map (* a) x) y
> 
> sumVecs :: [(Double, Vec)] -> Vec
> sumVecs axs =
>    let (a, x) = head axs
>    in foldl adder (V.map (* a) x) (tail axs)
>        where adder :: Vec -> (Double, Vec) -> Vec
>              adder v1 (a, x) = axpy a x v1
> 
> how to i write this in a way which ensures recycling / fusion, e.g.
> in-place updates?

Unfortunately, recycling won't help you here. It is a purely local optimisation which doesn't work across function boundaries (inlining notwithstanding) and recursive calls. Your best bet is to use a mutable vector and do the fold in the ST monad.

That said, it would be quite possible to provide something like the following:

fold_inplace :: Vector v a => (v a -> b -> v a) -> v a -> [b] -> v a

This could use the recycling framework to safely do as much in-place as possible while still preserving a purely functional interface. I have to think about it. Really, this looks like just a poor man's substitute for linear types.

Roman




More information about the Haskell-Cafe mailing list