[Haskell-cafe] vector recycling

Jason Dagit dagit at codersbase.com
Sat Apr 17 01:51:30 EDT 2010


On Fri, Apr 16, 2010 at 8:32 PM, Ben <midfield at gmail.com> wrote:

> hello --
>
> this is mostly a question for roman, or don, i guess.  suppose i have
> a list of similarly-sized vectors, and i want to add them up (possibly
> with coefficients), to yield a result vector.  something like
>
> 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?
>

One thing you can always do is check what the optimizer produces.  Don wrote
ghc-core (on hackage) specifically for this task.  You should also try with
-Odph, when -O2 isn't giving you the results you need.

Hopefully Don or Roman can give you tips on exploiting fusion when the
optimizer doesn't do the right thing.

Jason
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20100417/fc3940dc/attachment.html


More information about the Haskell-Cafe mailing list