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

Reply via email to