Re: [Haskell-cafe] Mapping over multiple values of a list at once?

For example, starting from
[4,3,2,6,7]
you need to find the averages of
4,3,2 and 3,2,6 and 2,6,7
resulting in
[3,4,5]
What is the most elegant way to do that? It's probably less elegant than tails, but very likely more efficient to keep track of running sums instead of summing the sublists over and over again.
import Data.Ratio nsums n xs = map (% n) $ scanl (+) (sum (take n xs)) $ zipWith (-) (drop n xs) xs Gergely -- http://www.fastmail.fm - The professional email service

How about this one? Should be pretty efficient.
let mavg n xs = let (sum -> seed,rest) = splitAt n xs in map (%n) .
scanl (\a (p,n) -> a+n-p) seed $ xs `zip` rest
2009/8/27 Patai Gergely
For example, starting from
[4,3,2,6,7]
you need to find the averages of
4,3,2 and 3,2,6 and 2,6,7
resulting in
[3,4,5]
What is the most elegant way to do that? It's probably less elegant than tails, but very likely more efficient to keep track of running sums instead of summing the sublists over and over again.
import Data.Ratio
nsums n xs = map (% n) $ scanl (+) (sum (take n xs)) $ zipWith (-) (drop n xs) xs
Gergely
-- http://www.fastmail.fm - The professional email service
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Eugene Kirpichov Web IR developer, market.yandex.ru

Or, when the list is infinite, turn it into a some neat but cryptic State computation: avgs = (:) <$> ((\d -> sum d `div` 3) <$> StateT (pure . splitAt 3)) <*> avgs test = evalState avgs [1,2..] -- Sebastiaan Visser On Aug 27, 2009, at 11:19 AM, Eugene Kirpichov wrote:
How about this one? Should be pretty efficient.
let mavg n xs = let (sum -> seed,rest) = splitAt n xs in map (%n) . scanl (\a (p,n) -> a+n-p) seed $ xs `zip` rest
2009/8/27 Patai Gergely
: For example, starting from
[4,3,2,6,7]
you need to find the averages of
4,3,2 and 3,2,6 and 2,6,7
resulting in
[3,4,5]
What is the most elegant way to do that? It's probably less elegant than tails, but very likely more efficient to keep track of running sums instead of summing the sublists over and over again.
import Data.Ratio
nsums n xs = map (% n) $ scanl (+) (sum (take n xs)) $ zipWith (-) (drop n xs) xs
Gergely

Hello Sebastiaan, Thursday, August 27, 2009, 3:49:48 PM, you wrote: you also need to replace (\d -> sum d `div` 3) with (`div` 3) . sum in order to keep Haskell spirit :)
Or, when the list is infinite, turn it into a some neat but cryptic State computation:
avgs = (:) <$> ((\d -> sum d `div` 3) <$> StateT (pure . splitAt 3)) <*> avgs
test = evalState avgs [1,2..]
-- Sebastiaan Visser
On Aug 27, 2009, at 11:19 AM, Eugene Kirpichov wrote:
How about this one? Should be pretty efficient.
let mavg n xs = let (sum -> seed,rest) = splitAt n xs in map (%n) . scanl (\a (p,n) -> a+n-p) seed $ xs `zip` rest
2009/8/27 Patai Gergely
: For example, starting from
[4,3,2,6,7]
you need to find the averages of
4,3,2 and 3,2,6 and 2,6,7
resulting in
[3,4,5]
What is the most elegant way to do that? It's probably less elegant than tails, but very likely more efficient to keep track of running sums instead of summing the sublists over and over again.
import Data.Ratio
nsums n xs = map (% n) $ scanl (+) (sum (take n xs)) $ zipWith (-) (drop n xs) xs
Gergely
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com
participants (4)
-
Bulat Ziganshin
-
Eugene Kirpichov
-
Patai Gergely
-
Sebastiaan Visser