Re: [Haskell-cafe] Help to create a function to calculate a n element moving average ??

2010-09-29 Thread Henning Thielemann
S. Doaitse Swierstra schrieb:
 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 _   _ []  = []

Moving average can be interpreted as convolution (*):
[1/n,1/n,1/n,...,1/n] * xs

You may drop the first (n-1) values, since they average over initial
padding zeros.

Convolution is associative and you can decompose the first operand into
simpler parts:

1/n · [1,1,1,...] * [1,0,0,,0,0,-1] * xs
 = 1/n · integrate ([1,0,0,,0,0,-1] * xs)

Convolution is commutative, thus you could also write
 = 1/n · [1,0,0,,0,0,-1] * integrate xs
 but then integration of xs will yield unbounded values and thus higher
rounding errors.

This yields:

movingAverage :: Int - [Float] - [Float]
movingAverage n =
   drop (n-1) .
   map (/ fromIntegral n) .
   scanl1 (+) .
   (\xs - zipWith (-) xs (replicate n 0 ++ xs))

This should be the same as the implementation above, but maybe a bit
nicer. :-)

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


Re: [Haskell-cafe] Help to create a function to calculate a n element moving average ??

2010-09-29 Thread S. Doaitse Swierstra

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


Re: [Haskell-cafe] Help to create a function to calculate a n element moving average ??

2010-09-28 Thread S. Doaitse Swierstra
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


On 28 sep 2010, at 03:40, Richard O'Keefe wrote:

 
 On 27/09/2010, at 5:20 AM, rgowka1 wrote:
 
 Type signature would be Int - [Double] - [(Double,Double)]
 
 Any thoughts or ideas on how to calculate a n-element moving average
 of a list of Doubles?
 
 Let's say [1..10]::[Double]
 
 what is the function to calculate the average of the 3 elements?
 
 [(1,0),(2,0),(3,2),(4,3)] :: [(Double,Double)]
 
 moving_average3 (xs0 @ (_ : (xs1 @ (_ : xs2 =
  zipWith3 (\x y z - (x+y+z)/3) xs0 xs1 xs2
 
 *Main moving_average3 [1..10]
 [2.0,3.0,4.0,5.0,6.0,7.0,8.0,9.0]
 
 The result is two elements shorter than the original, but that
 _is_ the definition of moving average after all.
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] Help to create a function to calculate a n element moving average ??

2010-09-27 Thread Richard O'Keefe

On 27/09/2010, at 5:20 AM, rgowka1 wrote:

 Type signature would be Int - [Double] - [(Double,Double)]
 
 Any thoughts or ideas on how to calculate a n-element moving average
 of a list of Doubles?
 
 Let's say [1..10]::[Double]
 
 what is the function to calculate the average of the 3 elements?
 
 [(1,0),(2,0),(3,2),(4,3)] :: [(Double,Double)]

 moving_average3 (xs0 @ (_ : (xs1 @ (_ : xs2 =
   zipWith3 (\x y z - (x+y+z)/3) xs0 xs1 xs2

*Main moving_average3 [1..10]
[2.0,3.0,4.0,5.0,6.0,7.0,8.0,9.0]

The result is two elements shorter than the original, but that
_is_ the definition of moving average after all.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Help to create a function to calculate a n element moving average ??

2010-09-26 Thread rgowka1
Type signature would be Int - [Double] - [(Double,Double)]

Any thoughts or ideas on how to calculate a n-element moving average
of a list of Doubles?

Let's say [1..10]::[Double]

what is the function to calculate the average of the 3 elements?

[(1,0),(2,0),(3,2),(4,3)] :: [(Double,Double)]

(1,0) the average is zero as the length is less than 3

(2,0) the average is zero as the length is less than 3

(3,2) the average is (1+2+3)/3 = 2

(4,3) the average is (2+3+4)/3 = 9
..
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Help to create a function to calculate a n element moving average ??

2010-09-26 Thread Serguey Zefirov
2010/9/26 rgowka1 rgow...@gmail.com:
 Type signature would be Int - [Double] - [(Double,Double)]

 Any thoughts or ideas on how to calculate a n-element moving average
 of a list of Doubles?

 Let's say [1..10]::[Double]

 what is the function to calculate the average of the 3 elements?

 [(1,0),(2,0),(3,2),(4,3)] :: [(Double,Double)]

 (1,0) the average is zero as the length is less than 3

 (2,0) the average is zero as the length is less than 3

 (3,2) the average is (1+2+3)/3 = 2

 (4,3) the average is (2+3+4)/3 = 9

movingAverage n xs = map (/n) $ sums n xs

sums 1 xs = xs
sums n xx@(x:xs) = zipWith (+) xx (sums (n-1) xs)

Tests:
*Main movingAverage 1 [1..10]
[1.0,2.0,3.0,4.0,5.0,6.0,7.0,8.0,9.0,10.0]
*Main movingAverage 2 [1..10]
[1.5,2.5,3.5,4.5,5.5,6.5,7.5,8.5,9.5]
*Main movingAverage 3 [1..10]
[2.0,3.0,4.0,5.0,6.0,7.0,8.0,9.0]
*Main movingAverage 4 [1..10]
[2.5,3.5,4.5,5.5,6.5,7.5,8.5]

Is it right? ;)

It is more interesting to create movingAverage in CPS/iteratees style.
That way you'll have solid interface with IO world and you can freely
alternate between reading moving averages and waiting for another
ticket. No magic usafeInterleaveIO, hGetContents, etc, will be
required.

I did this once for my friend's pet project in Erlang, we jointly
developed a whole library of operators over time series - sums,
averages, etc. It is simple and fun. ;)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe