On 29 sep 2010, at 00:58, o...@cs.otago.ac.nz wrote:

>> Avoiding repeated additions:
>> 
>> movingAverage :: Int -> [Float] -> [Float]
>> movingAverage n l = runSums (sum . take n $l) l (drop n l)
>>     where n'     = fromIntegral n
>>           runSums sum (h:hs) (t:ts) = sum / n' : runSums (sum-h+t) hs ts
>>           runSums _   _     []      = []
>> 
>> Doaitse
> 
> I very very carefully avoided doing any such thing in my example code.
> For each output result, my code does two additions and one division.
> Yours does one addition, one subtraction, and one division, for the
> required case n = 3.  The way I formulated it, each calculation is
> independent.  The way you've formulated it, the error in one
> calculation accumulates into the next.  NOT a good idea.

If this an issue then:

module MovingAverage where

movingAverage :: [Float] -> [Float]
movingAverage (x:y:l) = movingAverage' x y l
    where movingAverage' x y (z:zs) = (x+y+z)/3:movingAverage' y z zs
          movingAverage' _ _ _      = []
movingAverage _       = []


has far fewer pattern matches,

 Doaitse


> 
> 

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to