Re: [Haskell-cafe] Functional progr., images, laziness and all the rest

2006-06-22 Thread Jerzy Karczmarczuk

Brian Hulley wrote:

[EMAIL PROTECTED] 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?
I don't see how
yq = a * xq + b * y
relates to
   Y[n+1] = a*X[n+1] + b*Y[n]  -- (assuming the X[N+1] was a typo)

since y is a longer list than yq but Y[n] is an earlier element than 
Y[n+1], so it seems that the function is multiplying b by a later factor 
than it should.


Sure, y[n] is earlier, so defining the tail by the stream itself refers
an element to its predecessor. No problemo Baby, as used to say
Terminator 2, whose relevance to our problem is obvious, since he
also couldn't terminate him(it)self...

Let's write the stream construction once more. Starting with x=(x0:xq)
and parameters a and b, assuming that for n0 you take zero:

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).

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.



So:
1) Someone reading the code needs to do a lot of work to try to recover 
the original equation
2) Wouldn't an imperative loop, using the original equation directly, 
have made everything much simpler?

3) Therefore laziness has lead to obfuscated code.


1. Such codes are not meant to be thrown at an unprepared audience. Either
   the reader knows something about stream processing, or some introduction
   is necessary.

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.
   Please note that for stream-oriented applications, as the sound processing
   I mentioned, this n index has no meaning whatsoever, it just denotes
   a position within the stream. Index-less style is more compact, with less
   redundant entities.

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).

Thanks.

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


Re: [Haskell-cafe] Functional progr., images, laziness and all the rest

2006-06-22 Thread minh thu

hi !

2006/6/22, Brian Hulley [EMAIL PROTECTED]:
[snip]

So:
1) Someone reading the code needs to do a lot of work to try to recover the
original equation
2) Wouldn't an imperative loop, using the original equation directly, have
made everything much simpler?
3) Therefore laziness has lead to obfuscated code.


the way i see :
1/ but why do you call it 'original equation' ? the original thing is
expressed informaly in your head, then into a formula or an algorithm.
Here i find the first one-liner really readable. (although i think it
misses Y[0] = X[0]). But the loop is really readable too for
imperative enabled mind.
2/ for me, list or loop is quite the same thing (in this case)
(although loop is mor general since you can use the base index in
weird ways).
3/ see 1/ and 2/

Jerzy :
can you know a mean to express such computation but with elements
depending of time (in about the same way as languages as esterel)
(i.e. depending of IO)?
Paul Hudak uses a Channel in his book Haskell SOE .. but is there another way ?

thanks,
vo minh thu
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Functional progr., images, laziness and all the rest

2006-06-22 Thread Udo Stenzel
[EMAIL PROTECTED] wrote:
 apparently - Clean has better handling of strictness
 issues [saying at the same time that he/she doesn't use Clean...]

Uhm... well... and does it?  From what I've heard, Clean has the same
mechanism as Haskell, which is the 'seq' primitive.  Clean just adds
some syntactic sugar to make functions strict in some arguments.  If
that's the only difference, I'm quite happy with the False-guard idiom
(and may be even more happy with !-patterns).

 And here apparently I am one of rare people  - I am not proud of it,
 rather quite sad, who defends laziness as an *algorithmisation tool*,
 which makes it easy and elegant to construct co-recursive codes. Circular
 programs, run-away infinite streams, hidden backtracking etc. 

And don't forget the Most Unreliable Method to Compute Pi!  That would
be plain impossible without lazy evaluation.  (Nice blend of humor and
insight in that paper, by the way.)

 
 In this context, I found Clean more helpful than Haskell, for ONE reason.
 Clean has a primitive datatype: unboxed, spine-lazy but head-strict lists.

If I understand correctly, you'd get the same in GHC by defining

* data IntList = Nil | Cons I# IntList

though it is monomorphic, and you'd get the same semantics from

* data List a = Nil | Cons !a (List a)

Now it is polymorphic and it may even get unpacked.


Udo.
-- 
If your life was a horse, you'd have to shoot it.


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


Re: [Haskell-cafe] Functional progr., images, laziness and all the rest

2006-06-22 Thread Jerzy Karczmarczuk

minh thu wrote:

/about the stream algorithms, lazy style/


can you know a mean to express such computation but with elements
depending of time (in about the same way as languages as esterel)
(i.e. depending of IO)?
Paul Hudak uses a Channel in his book Haskell SOE .. but is there 
another way ?


Frankly, I don't see it well. The co-recursive, lazy constructions are
based on the fact that it is the consumer who unrolls the list and
forces the reduction. So, the unevaluated closures should contain
somehow the latent data, or rather refer to them. Synchronous processing
is another story, here the producer is really active.

Esterel until the version 4 demanded that all 'circuits' which handled
the data flows be *acyclic*; now it is more flexible, so you can do a lot
of own-tail-eating snakes with it, but differently.

I believe that ways of producing intricate streams by such languages or
Lustre are somehow based on continuation mechanisms. The paper on Esterel,
etc. :   ftp://ftp-sop.inria.fr/esterel/pub/papers/foundations.pdf

gives you an example in Lustre
X[n+1] = U[n+1]*sin(X[n] + S[n+1]-S[n])
S[n+1] = cos(S[n]+U[n+1]

in a form remarkably analogous as I did:

node Control(U:float) returns X:float
  var S:float
  let
X = 0.0 - (U*sin(pre(X)+S-pre(S));
S = 1.0 - cos(pre(S)+U);
  tel

So, I would say that this is obviously a live domain. The language Signal
can oversample, and produce output faster than the input, but I have
never followed the details.

Perhaps some YamPa-ladins who read this list could shed some light on the
reactive stream processing?
They use Arrows, a generalization (and twist, not compatible) of Monads, so
there is obviously *some* relation to continuations here... But I am a
Perfect Non-Specialist.


Jerzy Karczmarczuk


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


Re: [Haskell-cafe] Functional progr., images, laziness and all the rest

2006-06-22 Thread Ross Paterson
On Thu, Jun 22, 2006 at 01:24:32PM +0200, Jerzy Karczmarczuk wrote:
 I believe that ways of producing intricate streams by such languages or
 Lustre are somehow based on continuation mechanisms. The paper on Esterel,
 etc. :   ftp://ftp-sop.inria.fr/esterel/pub/papers/foundations.pdf
 
 gives you an example in Lustre
 X[n+1] = U[n+1]*sin(X[n] + S[n+1]-S[n])
 S[n+1] = cos(S[n]+U[n+1]
 
 in a form remarkably analogous as I did:
 
 node Control(U:float) returns X:float
   var S:float
   let
 X = 0.0 - (U*sin(pre(X)+S-pre(S));
 S = 1.0 - cos(pre(S)+U);
   tel

For comparison, here's a version using arrows (except that the U stream
is shifted forward, so its first value is used):

class ArrowLoop a = ArrowCircuit a where
delay :: b - a b b

control :: ArrowCircuit a = a Float Float
control = proc u - do
rec let x' = u * sin (x + s' - s)
s' = cos (s * u)
x - delay 0 - x'
s - delay 1 - s'
returnA - x

One can plug in various implementations of ArrowCircuit.  For stream
processors, delay is just cons, and the computation is equivalent to
the infinite list version.  Another implementation uses continuations.

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


Re: [Haskell-cafe] Functional progr., images, laziness and all the rest

2006-06-21 Thread Brian Hulley

[EMAIL PROTECTED] wrote:
[snip]

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:
filtr a b x@(x0:xq) = y where
y  = (x0:yq)
yq = a*xq + b*y


Can you explain how this transformation was accomplished?
I don't see how
yq = a * xq + b * y
relates to
   Y[n+1] = a*X[n+1] + b*Y[n]  -- (assuming the X[N+1] was a typo)

since y is a longer list than yq but Y[n] is an earlier element than Y[n+1], 
so it seems that the function is multiplying b by a later factor than it 
should.


So:
1) Someone reading the code needs to do a lot of work to try to recover the 
original equation
2) Wouldn't an imperative loop, using the original equation directly, have 
made everything much simpler?

3) Therefore laziness has lead to obfuscated code.



with (*) and (+) conveniently overloaded (or replaced by specific
obvious ops).

In such a way you can program in 2 - 6 lines some quite exquisite
musical instruments (for example the Karplus-Strong guitar, or a
flute), construct the reverberation filters, make ever-rising
Shepard/Risset paradoxical sounds, etc. etc. With laziness it is a
sheer pleasure and fun, without - a pain. If you wish, find my PADL talk 
on it...


In this context, I found Clean more helpful than Haskell, for ONE
reason. Clean has a primitive datatype: unboxed, spine-lazy but
head-strict lists. The co-recursion works, as the construction of the
tail is postponed, but there is no pollution of the space by thunks -
unevaluated list *elements*.
This I really do miss in Haskell... But perhaps I simply don't know
how to obtain a similar behaviour?


If you only needed the head-strict aspect, something like

data HSList a = Empty | Cons !a (HSList a)

(GHC also has unboxed types so perhaps something like data HSList = Empty | 
Cons Double# HSList but see the restrictions on their use at 
http://www.haskell.org/ghc/docs/latest/html/users_guide/primitives.html )


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 


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