[Haskell-cafe] Functional progr., images, laziness and all therest

Brian Hulley brianh at metamilk.com
Thu Jun 22 09:55:47 EDT 2006


Jerzy Karczmarczuk wrote:
> Brian Hulley wrote:
>> jerzy.karczmarczuk at info.unicaen.fr wrote:
>
>>> you may transform a recurrential equation yielding Y out of X:
>>> Y[n+1] = a*X[n+1] + b*Y[n]
>>> usually (imperatively) implemented as a loop, into a stream
>>> definition:
> ...
>> Can you explain how this transformation was accomplished?

> y  = (a*x0:yq)       -- Here I was in error, "a" missing
> yq = a*xq + b*y
>
> with, of course, a*xq meaning map(a*) xq; x+y meaning zipWith(*) x y
>
>                 y0 = a*x0
> Look yourself:  y1 = a*x1 + b*y0
>                 y2 = a*x2 + b*y1, etc. So, first, this is correct,
>                                   element by element.
>
> Don't tell me you have never seen the assembly of all non-negative
> integers as an infinite list thereof:
>
> integs = 0 : (integs + ones)   where ones = 1:ones
>
> it is quite similar (conceptually).

Thanks for the explanation.

>
> y IS NOT a longer list than yq, since co-recursive equations without
> limiting cases, apply only to *infinite* streams. Obviously, the
> consumer of such a stream will generate a finite segment only, but it
> is his/her/its problem, not that of the producer.

I still don't understand this point, since y = (a*x0 : yq) so surely by 
induction on the length of yq, y has 1 more element?

>
> 2. Are we speaking about assembly-style, imperative programming, or
>    about functional style? Please write your loop in Haskell or any
>    other fun. language, and share with us its elegance.

Starting with: Y[n+1] = a*X[n+1] + b*Y[n]

  filtr a b (x0:xs) = y0 : filtr' xs y0
     where
         y0 = a * x0
         filtr' (x_n1 : xs) y_n = y_n1 : filtr' xs y_n1
             where
                    y_n1 = a * x_n1 + b * y_n

In a sense I'm still using a lazy stream, but the difference is that I'm not 
making any use of the "evaluate once then store for next time" aspect of 
lazyness, so the above code could be translated directly to use the 
force/delay streams I mentioned before. Also, the original formula now 
appears directly in the definition of filtr' so it can be understood without 
an initiation into stream processing.

(Piotr - I see my original wording "imperative loop" was misleading - in the 
context of functional programming I tend to just use this to mean a simple 
recursive function)

>
> 3. Full disagreement. There is NOTHING obfuscated here, on the
>    contrary, the full semantics is in front of your eyes, it requires
>    only some reasoning in terms of infinite lists. See point (1).

The same could be said for all obfuscated code: it's always fully visible 
but just requires reasoning to understand it! :-) Still I suppose perhaps 
the word "obfuscated" was a bit strong and certainly with your explanation, 
which you mentioned as a prerequisite in answer to my point 1), I now 
understand your original code also, but not without making some effort.

Best regards,
Brian.

-- 
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.

http://www.metamilk.com 



More information about the Haskell-Cafe mailing list