[Haskell-cafe] FRP, integration and differential equations.

Peter Verswyvelen bugfact at gmail.com
Tue Apr 21 07:34:29 EDT 2009


BTW, a bit of topic, your recent work on causal commutative arrows and CCA
compiler seems very promising. Any news on that? Seems that it could
drastically speedup Yampa.
On Tue, Apr 21, 2009 at 1:32 PM, Peter Verswyvelen <bugfact at gmail.com>wrote:

> Hey thanks for the Adam-Bashford tip, didn't know that one yet (although I
> used similar techniques in the past, didn't know it had a name :-)
>
> Well, solving the ODE is usually the task of a dedicated physics engine.
> But IMHO with FRP we try to reuse small building blocks so we get very
> modular systems; a big physics black box seems to be against this principle?
>
> On Tue, Apr 21, 2009 at 1:24 PM, Paul L <ninegua at gmail.com> wrote:
>
>> Adam-Bashford method can be easily implemented to replace Euler's. But
>> to really get higher accuracy, one may need variable time steps and
>> perhaps even back tracking, which is an interesting topic on its own.
>> But my question is, is FRP really the right setting in which to
>> explore a highly accurate ODE solver?
>>
>>
>> On 4/21/09, Peter Verswyvelen <bugfact at gmail.com> wrote:
>> > Well, the current FRP systems don't accurately solve this, since they
>> just
>> > use an Euler integrator, as do many games. As long as the time steps are
>> > tiny enough this usually works good enough. But I wouldn't use these
>> FRPs
>> > to
>> > guide an expensive robot or spaceship at high precision :-)
>> >
>> >
>> > On Tue, Apr 21, 2009 at 11:48 AM, jean-christophe mincke <
>> > jeanchristophe.mincke at gmail.com> wrote:
>> >
>> >> Paul,
>> >>
>> >> Thank you for your reply.
>> >>
>> >> Integration is a tool to solve a some ODEs but ot all of them. Suppose
>> >> all
>> >> we have is a paper and a pencil and we need to symbolically solve:
>> >>
>> >>
>> >>
>> >> /
>> >> t
>> >> de(t)/dt = f(t)  -> the solution is given by e(t) = |      f(t) dt +
>> >> e(t0)
>> >>
>> /
>> >> t0
>> >>
>> >> de(t)/dt = f(e(t), t) -> A simple integral cannot solve it, we need to
>> >> use
>> >> the dedicated technique appropriate to this type of ODE.
>> >>
>> >>
>> >> Thus, if the intention of the expression
>> >>
>> >>    e = integrate *something *
>> >>
>> >> is "I absolutely want to integrate *something* using some integration
>> >> scheme", I am not convinced that this solution properly covers the
>> second
>> >> case above.
>> >>
>> >> However if its the meaning is "I want to solve the ODE : de(t)/dt =*
>> >> something* " I would be pleased if the system should be clever enough
>> to
>> >> analyse the *something expression* and to apply or propose the most
>> >> appropriate numerical method.
>> >>
>> >> Since the two kinds of ODEs require 2 specific methematical solutions,
>> I
>> >> do
>> >> not find suprising that this fact is also reflected in a program.
>> >>
>> >> I have not the same experience as some poster/authors but I am curious
>> >> about the way the current FRPs are able to accurately solve the most
>> >> simple
>> >> ODE:
>> >>
>> >>     de(t)/dt = e
>> >>
>> >> All I have seen/read seems to use the Euler method. I am really
>> >> interested
>> >> in knowing whether anybody has implemented a higher order method?
>> >>
>> >> Regards
>> >>
>> >> J-C
>> >>
>> >>
>> >> On Tue, Apr 21, 2009 at 5:03 AM, Paul L <ninegua at gmail.com> wrote:
>> >>
>> >>> Trying to give different semantics to the same declarative definition
>> >>> based
>> >>> on whether it's recursively defined or not seems rather hack-ish,
>> >>> although
>> >>> I can understand what you are coming from from an implementation
>> angle.
>> >>>
>> >>> Mathematically an integral operator has only one semantics regardless
>> >>> of what's put in front of it or inside. If our implementation can't
>> >>> match
>> >>> this
>> >>> simplicity, then we got a problem!
>> >>>
>> >>> The arrow FRP gets rid of the leak problem and maintains a single
>> >>> definition
>> >>> of integral by using a restricted form of recursion - the loop
>> operator.
>> >>> If you'd rather prefer having signals as first class objects, similar
>> >>> technique
>> >>> existed in synchronous languages [1], i.e., by using a special rec
>> >>> primitive.
>> >>>
>> >>> Disclaimer: I was the co-author of the leak paper [2].
>> >>>
>> >>> [1] A co-iterative characterization of synchronous stream functions, P
>> >>> Caspi, M Pouzet.
>> >>> [2] Plugging a space leak with an arrow, H. Liu, P. Hudak
>> >>>
>> >>> --
>> >>> Regards,
>> >>> Paul Liu
>> >>>
>> >>> Yale Haskell Group
>> >>> http://www.haskell.org/yale
>> >>>
>> >>> On 4/20/09, jean-christophe mincke <jeanchristophe.mincke at gmail.com>
>> >>> wrote:
>> >>> > In a post in the *Elerea, another FRP library *thread*,* Peter
>> >>> Verswyvelen
>> >>> > wrote:
>> >>> >
>> >>> > *>I think it would be nice if we could make a "reactive benchmark"
>> or
>> >>> > something: some tiny examples that capture the essence of reactive
>> >>> systems,
>> >>> > and a way to compare each solution's >pros and cons.* *
>> >>> > *
>> >>> > *>For example the "plugging a space leak with an arrow" papers
>> reduces
>> >>> the
>> >>> > recursive signal problem to
>> >>> > *
>> >>> > *
>> >>> > *
>> >>> > *>e = integral 1 e*
>> >>> > *
>> >>> > *
>> >>> >  *>Maybe the Nlift problem is a good example for dynamic
>> collections,
>> >>> but I
>> >>> > guess we'll need more examples.*
>> >>> > *
>> >>> > *
>> >>> > *>The reason why I'm talking about examples and not semantics is
>> >>> > because
>> >>> the
>> >>> > latter seems to be pretty hard to get right for FRP?*
>> >>> >
>> >>> > I would like to come back to this exemple. I am trying to write a
>> >>> > small
>> >>> FRP
>> >>> > in F# (which is a strict language, a clone of Ocaml) and I also came
>> >>> across
>> >>> > space and/or time leak. But maybe not for the same reasons...
>> >>> >
>> >>> > Thinking about these problems and after some trials and errors, I
>> came
>> >>> to
>> >>> > the following conclusions:
>> >>> >
>> >>> > I believe that writing the expression
>> >>> >
>> >>> >       e = integral 1 *something*
>> >>> >
>> >>> >       where e is a Behavior (thus depends on a continuous time).
>> >>> >
>> >>> > has really two different meanings.
>> >>> >
>> >>> > 1. if *something *is independent of e, what the above expression
>> means
>> >>> is
>> >>> > the classical integration of a time dependent function between t0
>> and
>> >>> t1.
>> >>> > Several numerical methods are available to compute this integral
>> and,
>> >>> > as
>> >>> far
>> >>> > as I know, they need to compute *something *at t0, t1 and, possibly,
>> >>> > at
>> >>> > intermediate times. In this case, *something *can be a Behavior.
>> >>> >
>> >>> > 2. If *something *depends directly or indirectly of e then we are
>> >>> > faced
>> >>> with
>> >>> > a first order differential equation of the form:
>> >>> >
>> >>> >        de/dt = *something*(e,t)
>> >>> >
>> >>> >     where de/dt is the time derivative of e and  *something*(e,t)
>> >>> indicates
>> >>> > that *something* depends, without loss of generality, on both e and
>> t.
>> >>> >
>> >>> > There exist specific methods to numerically solve differential
>> >>> > equations
>> >>> > between t0 and t1. Some of them only require the knowledge of e at
>> t0
>> >>> (the
>> >>> > Euler method), some others needs  to compute *something *from
>> >>> intermediate
>> >>> > times (in [t0, t1[ ) *and *estimates of e at those intermediary
>> times.
>> >>> >
>> >>> > 3. *something *depends (only) on one or more events that, in turns,
>> >>> > are
>> >>> > computed from e. This case seems to be the same as the first one
>> where
>> >>> the
>> >>> > integrand can be decomposed into a before-event integrand and an
>> >>> after-event
>> >>> > integrand (if any event has been triggered). Both integrands being
>> >>> > independent from e. But I have not completely investigated this case
>> >>>  yet...
>> >>> >
>> >>> > Coming back to my FRP, which is based on residual behaviors, I use a
>> >>> > specific solution for each case.
>> >>> >
>> >>> > Solution to case 1 causes no problem and is similar to what is done
>> in
>> >>> > classical FRP (Euler method, without recursively defined behaviors).
>> >>> Once
>> >>> > again as far as I know...
>> >>> >
>> >>> > The second case has two solutions:
>> >>> > 1. the 'integrate' function is replaced by a function 'solve' which
>> >>> > has
>> >>> the
>> >>> > following signature
>> >>> >
>> >>> >        solve :: a -> (Behavior a -> Behavior a) -> Behavior a
>> >>> >
>> >>> >       In fact,  *something*(e,t) is represented by an integrand
>> >>> > function
>> >>> > from behavior to behavior, this function is called by the
>> >>> > integration           method. The integration method is then free to
>> >>> pass
>> >>> > estimates of e, as constant behaviors, to the integrand function.
>> >>> >
>> >>> >       The drawbacks of this solution are:
>> >>> >       - To avoid space/time leaks, it cannot be done without side
>> >>> effects
>> >>> > (to be honest, I have not been able to  find a solution without
>> >>> > assignement). However these side effects are not visible from
>> outside
>> >>> > of
>> >>> the
>> >>> > solve function. ..
>> >>> >       - If behaviors are defined within the integrand function, they
>> >>> > are
>> >>> not
>> >>> > accessible from outside of this integrand function.
>> >>> >
>> >>> > 2. Introduce constructions that looks like to signal functions.
>> >>> >
>> >>> >       solve :: a -> SF a a -> Behavior a
>> >>> >
>> >>> >    where a SF is able to react to events and may manage an internal
>> >>> state.
>> >>> >    This solution solves the two above problems but make the FRP a
>> bit
>> >>> more
>> >>> > complex.
>> >>> >
>> >>> >
>> >>> > Today, I tend to prefer the first solution, but what is important,
>> in
>> >>> > my
>> >>> > opinion, is to recognize the fact that
>> >>> >
>> >>> >     e = integral 1 *something*
>> >>> >
>> >>> > really addresses two different problems (integration and solving of
>> >>> > differential equations) and each problem should have their own
>> >>> > solution.
>> >>> >
>> >>> > The consequences are :
>> >>> >
>> >>> >    1. There is no longer any need for my FRP to be able to define a
>> >>> Behavior
>> >>> >    recursively. That is a good news for this is quite tricky in F#.
>> >>> >    Consequently, there is no need to introduce delays.
>> >>> >    2. Higher order methods for solving of diff. equations can be
>> used
>> >>> (i.e.
>> >>> >    Runge-Kutta). That is also good news for this was one of my main
>> >>> > goal
>> >>> in
>> >>> >    doing the exercice of writing a FRP.
>> >>> >
>> >>> > Regards,
>> >>> >
>> >>> > J-C
>> >>> >
>> >>>
>> >>
>> >>
>> >> _______________________________________________
>> >> Haskell-Cafe mailing list
>> >> Haskell-Cafe at haskell.org
>> >> http://www.haskell.org/mailman/listinfo/haskell-cafe
>> >>
>> >>
>> >
>>
>>
>> --
>> Regards,
>> Paul Liu
>>
>> Yale Haskell Group
>> http://www.haskell.org/yale
>>
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20090421/7fd9038c/attachment.htm


More information about the Haskell-Cafe mailing list