[Haskell-beginners] Simple Moving Average of a list of real numbers

Michael Orlitzky michael at orlitzky.com
Tue Nov 26 17:11:56 UTC 2013


On 11/25/2013 10:28 AM, Alexandr M wrote:
> Hello !
> 
> Could anybody explain me how to calculate simple moving average of a list ?
> 
> I have found several examples in internet but I completely don't
> understand how it works.
> 
> Basically it's necessary to iterate over the list of real numbers and
> calculate average values over last n items in the list.
> 
> I just can't imagine how to do it without loops.

When you need to know the position of something in a list, one easy way
to get it is to "zip" the original list with another list of
"positions", [1,2,3,...]. Then when you're processing the list, you're
not just dealing with some element somewhere in the list, you have the
ordered pair (item, position) which you probably know what to do with.

Inline below is some code that uses this idea along with a "scan"
(similar to a fold) to accomplish the moving average. Here it is in action:

  Prelude> :l moving_average.hs
  [1 of 1] Compiling Main             ( moving_average.hs, interpreted )
  Ok, modules loaded: Main.
  *Main> let samples = [1,2,3,4,5] :: [Double]
  *Main> let mavg = moving_average samples
  *Main> print mavg
  [(1.0,1.0),(1.5,2.0),(2.0,3.0),(2.5,4.0),(3.0,5.0)]

If you only want the averages (and not the positions), the positions are
easy to drop:

  *Main> print $ map fst mavg
  [1.0,1.5,2.0,2.5,3.0]

Code below. I've tried to avoid line wrapping, but buyer beware.


module Main
where

-- | Create a list whose nth entry is a pair containing the average of
--   the first n elements of the given samples, along with the
--   position n. We use a "scan" to do this; a scan is like a fold
--   except it keeps track of the intermediate values and not just the
--   final one.
--
--   We can use this to our advantage; the nth average is just (n-1)
--   times the previous average, added to the current item, and then
--   divided by n. So we will thread a pair, (average, position),
--   through the list computing each average from the previous one as
--   we go.
--
--   The result should be a list of all averages we generated along
--   the way. If you want to drop the positions from the result, you
--   can simply call `map fst` on it.
--
moving_average :: (Fractional a) => [a] -> [(a,a)]
moving_average [] = []
moving_average samples =
  -- scanl1 uses the first entry of samples_pos as the first entry in
  -- the result. Since we don't need to do any averaging of the first
  -- item (it gets divided by one), this is what we want.
  scanl1 average samples_pos
  where
    -- The indices we'll use for the positions in the list. We use
    -- fromIntegral on all of them because we want to be able to
    -- divide by them, so they need to be converted to something
    -- Fractional (GHC will figure it out).
    positions = map fromIntegral [1..]

    -- The list samples_pos contains the original samples "zipped" with
    -- their position in the list. The entries of samples_pos should be
    -- pairs (x,y) where x was te original entry in the list, and y
    -- was its position. This lets us know which number we need to
    -- divide by for the average
    samples_pos = zip samples positions

    -- This is the function that does the work. It takes the previous
    -- (average, position) pair and the new (value, position) pair and
    -- uses them to generate the new (average, position).
    average :: (Fractional b) => (b,b) -> (b,b) -> (b,b)
    average (prev_avg, prev_pos) (sample, pos) =
      (new_avg, pos)
      where
        prev_sum = prev_avg * prev_pos
        new_avg = (prev_sum + sample) / pos



More information about the Beginners mailing list