[Haskell-cafe] Sliding windows for streaming

MarLinn monkleyon at gmail.com
Sun Jun 7 02:46:45 UTC 2020


Hi David,

this problem reminds me a lot of a whole bunch of functions in OpenCV, 
the image manipulation library. Applying a function on every possible 
window of a specific size is one of the core tools in image analysis, 
either as a moving 1D-function applied to every row, or as a moving 
2D-function on the whole image. So you might find a lot of inspiration 
there. Note that the applied function is called a "kernel" in that area.

I haven't looked at the library in some time, but here are a few 
thoughts from what I remember:

First of all, thinking about the end of the stream is a good idea. But 
what about the start of the stream? If the end of the stream can have 
non-full windows, why shouldn't the first window have exactly one 
element, the second have two, and so on until the window size is 
reached? Or something completely different?

Now the most general idea for start and end of the stream would be to 
let the user decide. In OpenCV, there are several standard methods to 
handle image borders: cut all non-full windows (like you do at the start 
of the stream right now), repeat the value at the border to fill the 
gaps, take the min/max/average of the last full window to fill the gaps 
etc. Why not let the user provide two functions (Seq a → Seq a → Maybe 
(Seq a)). The first argument is the first/last "full" sequence, the 
second one is the non-full sequence to be filled, and the result is 
either a sequence of up to window-size or Nothing to represent that the 
result is to be cut. Let the user provide a record with these functions 
as settings, provide several reasonable defaults, and there you go.

So in essence, what I'm suggesting is something like

	data WindowingSettings a x m = WindowingSettings
	    { windowStartHandler :: Seq a -> Seq a -> m (Maybe (Seq a))
	    , windowEndHandler   :: Seq a -> Seq a -> m (Maybe (Seq a))
	    , windowFunction     :: a -> m x
	    }

	slidingWindowWith
	    :: (Monad m, Semigroup x)
	    => WindowingSettings a x m
	    -> Int
	    -> Stream (Of a) m b
	    -> Stream (Of x) m b

I would also suggest offering a version where windowFunction is 
basically id. Why? Several of the most useful tools want to apply their 
function to the whole window each time, for example to calculate a 
weighted average or for edge/blob detection. But they also need 
reasonable border handling. So their implementation might look something 
like

	weightedAverage weigh size
		= fmap (average . weigh)
		. slidingWindowWith (bothEndsWith interpolateLinear) size

Of course a (Seq a) is a Semigroup, so if the user wants a full (Seq a) 
they could always rebuild it inside windowFunction. But why make that 
extra difficult.

In fact id could be the default impelentation because WindowingSettings 
should make a decent Functor. So a moving maximum might look something like

	slidingWindowMax size = slidingWindowWith (Max <$> repeatBorders) size

Of course these cents still have some rough edges to iron out. For 
example, I'm coming from the user side, so I have no idea what's even 
possible on the inside. But I hope they are of use anyway.

Cheers,
MarLinn

On 06/06/2020 23.32, David Feuer wrote:
> I'm looking for a bit of help with a library design choice.
>
> The streaming package currently offers a slidingWindow function
> converting a stream into a stream of fixed-size windows of that
> stream[1]:
>
>      slidingWindow
>        :: Monad m
>        => Int  -- Window size
>        -> Stream (Of a) m b
>        -> Stream (Of (Seq a)) m b
>
> This is based directly on a similar function in conduit. Using a rough
> translation into the world of lists, we have
>
>      slidingWindow 3 "abcdef" = ["abc","bcd","cde","def"]
>
> The awkward case where the stream is shorter than the window is
> handled by potentially producing a short sequence at the end:
>
>      slidingWindow 3 "ab" = ["ab"]
>      slidingWindow 3 "" = [""]
>
> I recently merged a pull request that adds variations on sliding
> window maxima and minima using what's apparently a "folklore"
> algorithm. For example
>
>      slidingWindowMax 3 "abcbab" = "abcccb"
>
> This is basically like
>
>      slidingWindowMax k = map maximum . slidingWindow k
>
> except that an empty stream doesn't yield anything, to avoid undefined values.
>
> The big advantage of these specialized functions is that rather than
> having to take a maximum over a sequence of length `k` at each step,
> they only do a constant (amortized) amount of work at each step. Nice!
> But not very general. Suppose we want to take a moving average of some
> sort, like an arithmetic mean, geometric mean, harmonic mean, or
> median? That thought leads quite naturally to a data structure: a
> queue holding elements of some arbitrary *semigroup* that efficiently
> keeps track of the sum of all the elements in the queue[2].
>
> While the choice of *data structure* is moderately obvious, the choice
> of *sliding window function* is less so. The tricky bit is, again,
> what happens when the stream is too short for the window. If you work
> in the Sum semigroup and divide the results by the window size to get
> a moving average, then a too-short stream will give a (single) result
> that's completely wrong! Oof. What would be the most useful way to
> deal with this? The streams in `streaming` give us the option of
> producing a distinguished "return" value that comes after all the
> yields. Would it make sense to *return* the incomplete sum, and the
> number of elements that went into it, instead of *yielding* it into
> the result stream? That seems flexible, but maybe a tad annoying. What
> do y'all think?
>
> [1] https://hackage.haskell.org/package/streaming-0.2.3.0/docs/Streaming-Prelude.html#v:slidingWindow
>
> [2] See the AnnotatedQueue in
> https://github.com/haskell-streaming/streaming/pull/99/files which
> basically modifies Okasaki's implicit queues using some of the basic
> ideas that appear in Hinze-Paterson 2–3 trees.
> _______________________________________________
> Haskell-Cafe mailing list
> To (un)subscribe, modify options or view archives go to:
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
> Only members subscribed via the mailman list are allowed to post.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20200607/5359d959/attachment.html>


More information about the Haskell-Cafe mailing list