
Dear Cafe, We have released the (nearly) first version of FRPNow, the functional reactive programming library based on the ICFP 2015 paper "Principled Practical FRP: Forget the Past, Change the Future, FRPNow!" ( https://www.reddit.com/r/haskell/comments/3ai7hl/principled_practical_frp_fo... ) The main package: http://hackage.haskell.org/package/frpnow Examples: https://github.com/atzeus/FRPNow/tree/master/Examples Gloss interoperability: http://hackage.haskell.org/package/frpnow-gloss GTK interoperability: http://hackage.haskell.org/package/frpnow-gtk (hackage doesn't like the newer GTK docs, so you can read the docs at http://www.cse.chalmers.se/~atze/frpnow-gtk/ ) Cheers, Atze

Congrats on the release! Can't wait to have a play with this - am curious
how it compares to reactive-banana.
- ocharles
On Wed, Jul 15, 2015 at 2:25 PM Atze van der Ploeg
Dear Cafe,
We have released the (nearly) first version of FRPNow, the functional reactive programming library based on the ICFP 2015 paper "Principled Practical FRP: Forget the Past, Change the Future, FRPNow!" ( https://www.reddit.com/r/haskell/comments/3ai7hl/principled_practical_frp_fo... )
The main package: http://hackage.haskell.org/package/frpnow
Examples: https://github.com/atzeus/FRPNow/tree/master/Examples
Gloss interoperability: http://hackage.haskell.org/package/frpnow-gloss
GTK interoperability: http://hackage.haskell.org/package/frpnow-gtk
(hackage doesn't like the newer GTK docs, so you can read the docs at http://www.cse.chalmers.se/~atze/frpnow-gtk/ )
Cheers,
Atze _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

Atze, I have a question about Streams. In the Paper Impl the following code: newtype Stream a = S { next :: B (E a) } catMaybesStream :: Stream (Maybe a) -> Stream a catMaybesStream (S s) = S loop where loop = do e <- s join <$> plan (nxt <$> e) -- nxt :: Maybe a -> B (E a) nxt (Just a) = return (return a) nxt Nothing = loop Which I understand. And in the library the following code: newtype EvStream a = S { getEs :: Behavior (Event [a]) } catMaybesEs :: EvStream (Maybe a) -> EvStream a catMaybesEs s = S $ loop where -- loop :: Behavior (Event [a]) loop = do e <- getEs s join <$> plan (nxt <$> e) nxt l = case catMaybes l of [] -> loop l -> return (return l) I assume the new type EvStream the intent is for the stream of ‘a’ to be an array rather than a recursive data structure, based on the name ‘getEs’. But, catMaybeEs is written like the paper version, suggesting it is a recursive data structure arrays. My goal is to write an integrator for a stream, such that the type signature is: EvStream (Double,Double) -> EvStream (Double) where the tuple is (data, time) and the result is (integratedData) and I modeled the function catMaybeEs, but it is not working. So I want to understand the general way to handle the stream in catMaybesEs. Mike
On Jul 15, 2015, at 7:25 AM, Atze van der Ploeg
wrote: Dear Cafe, We have released the (nearly) first version of FRPNow, the functional reactive programming library based on the ICFP 2015 paper "Principled Practical FRP: Forget the Past, Change the Future, FRPNow!" (https://www.reddit.com/r/haskell/comments/3ai7hl/principled_practical_frp_fo... https://www.reddit.com/r/haskell/comments/3ai7hl/principled_practical_frp_fo...) The main package: http://hackage.haskell.org/package/frpnow http://hackage.haskell.org/package/frpnow Examples: https://github.com/atzeus/FRPNow/tree/master/Examples https://github.com/atzeus/FRPNow/tree/master/Examples Gloss interoperability: http://hackage.haskell.org/package/frpnow-gloss http://hackage.haskell.org/package/frpnow-gloss GTK interoperability: http://hackage.haskell.org/package/frpnow-gtk http://hackage.haskell.org/package/frpnow-gtk (hackage doesn't like the newer GTK docs, so you can read the docs at http://www.cse.chalmers.se/~atze/frpnow-gtk/ http://www.cse.chalmers.se/~atze/frpnow-gtk/ )
Cheers,
Atze _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

Hi Mike, cafe,
The implementation in the library is essentially the same as in the paper,
but B (E [a]) instead of B (E a) allows multiple simultaneous events,
whereas the implementation in the paper does not. The result is B (E [a]),
where the list is the list of all results in the event stream which occur
at that point. Like the implementation in the paper, the behavior switches
as soon as the next event occurs.
I'm a bit unclear on your question, neither implementation is recursive. If
you want to use event streams it's best not to look at their
implementation, which is tricky, but just use the combinators that are
available.
You can create a behavior that always give the integration of the values in
the eventstream as follows:
integrate :: EvStream (Double,Double) -> Double -> Behavior (Behavior
Double)
integrate stream startTime = foldEs update (0,startTime) stream where
update (total, prevTime) (cur, curTime) = let diff = curTime - prevTime *
cur
in
(total + diff, curTime)
Or use Control.FRPNow.Time.integrate :)
The result will give a Behavior (Behavior Double), because the result
depends on when we start integrating to prevent the space leak. Does that
answer your question?
Cheers,
Atze
2015-08-24 16:15 GMT+02:00 Michael Jones
Atze,
I have a question about Streams.
In the Paper Impl the following code:
newtype Stream a = S { next :: B (E a) }
catMaybesStream :: Stream (Maybe a) -> Stream a catMaybesStream (S s) = S loop where loop = do e <- s join <$> plan (nxt <$> e) -- nxt :: Maybe a -> B (E a) nxt (Just a) = return (return a) nxt Nothing = loop
Which I understand.
And in the library the following code:
newtype EvStream a = S { getEs :: Behavior (Event [a]) }
catMaybesEs :: EvStream (Maybe a) -> EvStream a catMaybesEs s = S $ loop where -- loop :: Behavior (Event [a]) loop = do e <- getEs s join <$> plan (nxt <$> e) nxt l = case catMaybes l of [] -> loop l -> return (return l)
I assume the new type EvStream the intent is for the stream of ‘a’ to be an array rather than a recursive data structure, based on the name ‘getEs’.
But, catMaybeEs is written like the paper version, suggesting it is a recursive data structure arrays.
My goal is to write an integrator for a stream, such that the type signature is:
EvStream (Double,Double) -> EvStream (Double)
where the tuple is (data, time) and the result is (integratedData)
and I modeled the function catMaybeEs, but it is not working. So I want to understand the general way to handle the stream in catMaybesEs.
Mike
On Jul 15, 2015, at 7:25 AM, Atze van der Ploeg
wrote: Dear Cafe, We have released the (nearly) first version of FRPNow, the functional reactive programming library based on the ICFP 2015 paper "Principled Practical FRP: Forget the Past, Change the Future, FRPNow!" ( https://www.reddit.com/r/haskell/comments/3ai7hl/principled_practical_frp_fo... ) The main package: http://hackage.haskell.org/package/frpnow Examples: https://github.com/atzeus/FRPNow/tree/master/Examples Gloss interoperability: http://hackage.haskell.org/package/frpnow-gloss GTK interoperability: http://hackage.haskell.org/package/frpnow-gtk (hackage doesn't like the newer GTK docs, so you can read the docs at http://www.cse.chalmers.se/~atze/frpnow-gtk/ )
Cheers,
Atze _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

Atze, Ah, now it is more clear what the intended representation is. Let me address the point about recursion, which reflects more or less my difficulty understanding how a stream produces values in time. Referencing the paper version: newtype Stream a = S { next :: B (E a) } catMaybesStream :: Stream (Maybe a) -> Stream a catMaybesStream (S s) = S loop where loop = do e <- s join <$> plan (nxt <$> e) -- nxt :: Maybe a -> B (E a) nxt (Just a) = return (return a) nxt Nothing = loop loop references nxt, and nxt references loop, hence my use of the word ‘recursion’. But perhaps saying ‘data’ is incorrect. My intuition says that the ‘a’ in B (E a) must be a Stream for the ‘recursion’ to work. What then really twists my mind up is ‘e <-s’ getting the next value n times. I’m not an expert in how Haskell evaluates these expressions, but I really would like to understand how that works, because my old ‘imperative’ mind is in need of an upgrade. Mike
On Aug 24, 2015, at 8:50 AM, Atze van der Ploeg
wrote: Hi Mike, cafe,
The implementation in the library is essentially the same as in the paper, but B (E [a]) instead of B (E a) allows multiple simultaneous events, whereas the implementation in the paper does not. The result is B (E [a]), where the list is the list of all results in the event stream which occur at that point. Like the implementation in the paper, the behavior switches as soon as the next event occurs.
I'm a bit unclear on your question, neither implementation is recursive. If you want to use event streams it's best not to look at their implementation, which is tricky, but just use the combinators that are available. You can create a behavior that always give the integration of the values in the eventstream as follows:
integrate :: EvStream (Double,Double) -> Double -> Behavior (Behavior Double) integrate stream startTime = foldEs update (0,startTime) stream where update (total, prevTime) (cur, curTime) = let diff = curTime - prevTime * cur in (total + diff, curTime)
Or use Control.FRPNow.Time.integrate :)
The result will give a Behavior (Behavior Double), because the result depends on when we start integrating to prevent the space leak. Does that answer your question?
Cheers,
Atze
2015-08-24 16:15 GMT+02:00 Michael Jones
mailto:mike@proclivis.com>: Atze, I have a question about Streams.
In the Paper Impl the following code:
newtype Stream a = S { next :: B (E a) }
catMaybesStream :: Stream (Maybe a) -> Stream a catMaybesStream (S s) = S loop where loop = do e <- s join <$> plan (nxt <$> e) -- nxt :: Maybe a -> B (E a) nxt (Just a) = return (return a) nxt Nothing = loop
Which I understand.
And in the library the following code:
newtype EvStream a = S { getEs :: Behavior (Event [a]) }
catMaybesEs :: EvStream (Maybe a) -> EvStream a catMaybesEs s = S $ loop where -- loop :: Behavior (Event [a]) loop = do e <- getEs s join <$> plan (nxt <$> e) nxt l = case catMaybes l of [] -> loop l -> return (return l)
I assume the new type EvStream the intent is for the stream of ‘a’ to be an array rather than a recursive data structure, based on the name ‘getEs’.
But, catMaybeEs is written like the paper version, suggesting it is a recursive data structure arrays.
My goal is to write an integrator for a stream, such that the type signature is:
EvStream (Double,Double) -> EvStream (Double)
where the tuple is (data, time) and the result is (integratedData)
and I modeled the function catMaybeEs, but it is not working. So I want to understand the general way to handle the stream in catMaybesEs.
Mike
On Jul 15, 2015, at 7:25 AM, Atze van der Ploeg
mailto:atzeus@gmail.com> wrote: Dear Cafe, We have released the (nearly) first version of FRPNow, the functional reactive programming library based on the ICFP 2015 paper "Principled Practical FRP: Forget the Past, Change the Future, FRPNow!" (https://www.reddit.com/r/haskell/comments/3ai7hl/principled_practical_frp_fo... https://www.reddit.com/r/haskell/comments/3ai7hl/principled_practical_frp_fo...) The main package: http://hackage.haskell.org/package/frpnow http://hackage.haskell.org/package/frpnow Examples: https://github.com/atzeus/FRPNow/tree/master/Examples https://github.com/atzeus/FRPNow/tree/master/Examples Gloss interoperability: http://hackage.haskell.org/package/frpnow-gloss http://hackage.haskell.org/package/frpnow-gloss GTK interoperability: http://hackage.haskell.org/package/frpnow-gtk http://hackage.haskell.org/package/frpnow-gtk (hackage doesn't like the newer GTK docs, so you can read the docs at http://www.cse.chalmers.se/~atze/frpnow-gtk/ http://www.cse.chalmers.se/~atze/frpnow-gtk/ )
Cheers,
Atze _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org mailto:Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

This is the magic of the implementation, as well as Haskell. Very funky
indeed. The paper describes it, but I must admit it is all pretty tricky :)
2015-08-24 17:01 GMT+02:00 Michael Jones
Atze,
Ah, now it is more clear what the intended representation is.
Let me address the point about recursion, which reflects more or less my difficulty understanding how a stream produces values in time.
Referencing the paper version:
newtype Stream a = S { next :: B (E a) }
catMaybesStream :: Stream (Maybe a) -> Stream a catMaybesStream (S s) = S loop where loop = do e <- s join <$> plan (nxt <$> e) -- nxt :: Maybe a -> B (E a) nxt (Just a) = return (return a) nxt Nothing = loop
loop references nxt, and nxt references loop, hence my use of the word ‘recursion’. But perhaps saying ‘data’ is incorrect. My intuition says that the ‘a’ in B (E a) must be a Stream for the ‘recursion’ to work. What then really twists my mind up is ‘e <-s’ getting the next value n times. I’m not an expert in how Haskell evaluates these expressions, but I really would like to understand how that works, because my old ‘imperative’ mind is in need of an upgrade.
Mike
On Aug 24, 2015, at 8:50 AM, Atze van der Ploeg
wrote: Hi Mike, cafe,
The implementation in the library is essentially the same as in the paper, but B (E [a]) instead of B (E a) allows multiple simultaneous events, whereas the implementation in the paper does not. The result is B (E [a]), where the list is the list of all results in the event stream which occur at that point. Like the implementation in the paper, the behavior switches as soon as the next event occurs.
I'm a bit unclear on your question, neither implementation is recursive. If you want to use event streams it's best not to look at their implementation, which is tricky, but just use the combinators that are available. You can create a behavior that always give the integration of the values in the eventstream as follows:
integrate :: EvStream (Double,Double) -> Double -> Behavior (Behavior Double) integrate stream startTime = foldEs update (0,startTime) stream where update (total, prevTime) (cur, curTime) = let diff = curTime - prevTime * cur in (total + diff, curTime)
Or use Control.FRPNow.Time.integrate :)
The result will give a Behavior (Behavior Double), because the result depends on when we start integrating to prevent the space leak. Does that answer your question?
Cheers,
Atze
2015-08-24 16:15 GMT+02:00 Michael Jones
: Atze,
I have a question about Streams.
In the Paper Impl the following code:
newtype Stream a = S { next :: B (E a) }
catMaybesStream :: Stream (Maybe a) -> Stream a catMaybesStream (S s) = S loop where loop = do e <- s join <$> plan (nxt <$> e) -- nxt :: Maybe a -> B (E a) nxt (Just a) = return (return a) nxt Nothing = loop
Which I understand.
And in the library the following code:
newtype EvStream a = S { getEs :: Behavior (Event [a]) }
catMaybesEs :: EvStream (Maybe a) -> EvStream a catMaybesEs s = S $ loop where -- loop :: Behavior (Event [a]) loop = do e <- getEs s join <$> plan (nxt <$> e) nxt l = case catMaybes l of [] -> loop l -> return (return l)
I assume the new type EvStream the intent is for the stream of ‘a’ to be an array rather than a recursive data structure, based on the name ‘getEs’.
But, catMaybeEs is written like the paper version, suggesting it is a recursive data structure arrays.
My goal is to write an integrator for a stream, such that the type signature is:
EvStream (Double,Double) -> EvStream (Double)
where the tuple is (data, time) and the result is (integratedData)
and I modeled the function catMaybeEs, but it is not working. So I want to understand the general way to handle the stream in catMaybesEs.
Mike
On Jul 15, 2015, at 7:25 AM, Atze van der Ploeg
wrote: Dear Cafe, We have released the (nearly) first version of FRPNow, the functional reactive programming library based on the ICFP 2015 paper "Principled Practical FRP: Forget the Past, Change the Future, FRPNow!" ( https://www.reddit.com/r/haskell/comments/3ai7hl/principled_practical_frp_fo... ) The main package: http://hackage.haskell.org/package/frpnow Examples: https://github.com/atzeus/FRPNow/tree/master/Examples Gloss interoperability: http://hackage.haskell.org/package/frpnow-gloss GTK interoperability: http://hackage.haskell.org/package/frpnow-gtk (hackage doesn't like the newer GTK docs, so you can read the docs at http://www.cse.chalmers.se/~atze/frpnow-gtk/ )
Cheers,
Atze _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

Atze, Will the magic be revealed during your presentation next week? I guess I better take the paper on the plane and read it 3 more times before I get there :-) Mike
On Aug 24, 2015, at 9:08 AM, Atze van der Ploeg
wrote: This is the magic of the implementation, as well as Haskell. Very funky indeed. The paper describes it, but I must admit it is all pretty tricky :)
2015-08-24 17:01 GMT+02:00 Michael Jones
mailto:mike@proclivis.com>: Atze, Ah, now it is more clear what the intended representation is.
Let me address the point about recursion, which reflects more or less my difficulty understanding how a stream produces values in time.
Referencing the paper version:
newtype Stream a = S { next :: B (E a) }
catMaybesStream :: Stream (Maybe a) -> Stream a catMaybesStream (S s) = S loop where loop = do e <- s join <$> plan (nxt <$> e) -- nxt :: Maybe a -> B (E a) nxt (Just a) = return (return a) nxt Nothing = loop
loop references nxt, and nxt references loop, hence my use of the word ‘recursion’. But perhaps saying ‘data’ is incorrect. My intuition says that the ‘a’ in B (E a) must be a Stream for the ‘recursion’ to work. What then really twists my mind up is ‘e <-s’ getting the next value n times. I’m not an expert in how Haskell evaluates these expressions, but I really would like to understand how that works, because my old ‘imperative’ mind is in need of an upgrade.
Mike
On Aug 24, 2015, at 8:50 AM, Atze van der Ploeg
mailto:atzeus@gmail.com> wrote: Hi Mike, cafe,
The implementation in the library is essentially the same as in the paper, but B (E [a]) instead of B (E a) allows multiple simultaneous events, whereas the implementation in the paper does not. The result is B (E [a]), where the list is the list of all results in the event stream which occur at that point. Like the implementation in the paper, the behavior switches as soon as the next event occurs.
I'm a bit unclear on your question, neither implementation is recursive. If you want to use event streams it's best not to look at their implementation, which is tricky, but just use the combinators that are available. You can create a behavior that always give the integration of the values in the eventstream as follows:
integrate :: EvStream (Double,Double) -> Double -> Behavior (Behavior Double) integrate stream startTime = foldEs update (0,startTime) stream where update (total, prevTime) (cur, curTime) = let diff = curTime - prevTime * cur in (total + diff, curTime)
Or use Control.FRPNow.Time.integrate :)
The result will give a Behavior (Behavior Double), because the result depends on when we start integrating to prevent the space leak. Does that answer your question?
Cheers,
Atze
2015-08-24 16:15 GMT+02:00 Michael Jones
mailto:mike@proclivis.com>: Atze, I have a question about Streams.
In the Paper Impl the following code:
newtype Stream a = S { next :: B (E a) }
catMaybesStream :: Stream (Maybe a) -> Stream a catMaybesStream (S s) = S loop where loop = do e <- s join <$> plan (nxt <$> e) -- nxt :: Maybe a -> B (E a) nxt (Just a) = return (return a) nxt Nothing = loop
Which I understand.
And in the library the following code:
newtype EvStream a = S { getEs :: Behavior (Event [a]) }
catMaybesEs :: EvStream (Maybe a) -> EvStream a catMaybesEs s = S $ loop where -- loop :: Behavior (Event [a]) loop = do e <- getEs s join <$> plan (nxt <$> e) nxt l = case catMaybes l of [] -> loop l -> return (return l)
I assume the new type EvStream the intent is for the stream of ‘a’ to be an array rather than a recursive data structure, based on the name ‘getEs’.
But, catMaybeEs is written like the paper version, suggesting it is a recursive data structure arrays.
My goal is to write an integrator for a stream, such that the type signature is:
EvStream (Double,Double) -> EvStream (Double)
where the tuple is (data, time) and the result is (integratedData)
and I modeled the function catMaybeEs, but it is not working. So I want to understand the general way to handle the stream in catMaybesEs.
Mike
On Jul 15, 2015, at 7:25 AM, Atze van der Ploeg
mailto:atzeus@gmail.com> wrote: Dear Cafe, We have released the (nearly) first version of FRPNow, the functional reactive programming library based on the ICFP 2015 paper "Principled Practical FRP: Forget the Past, Change the Future, FRPNow!" (https://www.reddit.com/r/haskell/comments/3ai7hl/principled_practical_frp_fo... https://www.reddit.com/r/haskell/comments/3ai7hl/principled_practical_frp_fo...) The main package: http://hackage.haskell.org/package/frpnow http://hackage.haskell.org/package/frpnow Examples: https://github.com/atzeus/FRPNow/tree/master/Examples https://github.com/atzeus/FRPNow/tree/master/Examples Gloss interoperability: http://hackage.haskell.org/package/frpnow-gloss http://hackage.haskell.org/package/frpnow-gloss GTK interoperability: http://hackage.haskell.org/package/frpnow-gtk http://hackage.haskell.org/package/frpnow-gtk (hackage doesn't like the newer GTK docs, so you can read the docs at http://www.cse.chalmers.se/~atze/frpnow-gtk/ http://www.cse.chalmers.se/~atze/frpnow-gtk/ )
Cheers,
Atze _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org mailto:Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

Sadly, the presentation is only 20 minutes long, including questions, so I
have no time to talk about the implementation at all :(
However, I'd be happy to answer any questions you have in person, as well
as via mail :)
Cheers,
Atze
2015-08-24 17:14 GMT+02:00 Michael Jones
Atze,
Will the magic be revealed during your presentation next week? I guess I better take the paper on the plane and read it 3 more times before I get there :-)
Mike
On Aug 24, 2015, at 9:08 AM, Atze van der Ploeg
wrote: This is the magic of the implementation, as well as Haskell. Very funky indeed. The paper describes it, but I must admit it is all pretty tricky :)
2015-08-24 17:01 GMT+02:00 Michael Jones
: Atze,
Ah, now it is more clear what the intended representation is.
Let me address the point about recursion, which reflects more or less my difficulty understanding how a stream produces values in time.
Referencing the paper version:
newtype Stream a = S { next :: B (E a) }
catMaybesStream :: Stream (Maybe a) -> Stream a catMaybesStream (S s) = S loop where loop = do e <- s join <$> plan (nxt <$> e) -- nxt :: Maybe a -> B (E a) nxt (Just a) = return (return a) nxt Nothing = loop
loop references nxt, and nxt references loop, hence my use of the word ‘recursion’. But perhaps saying ‘data’ is incorrect. My intuition says that the ‘a’ in B (E a) must be a Stream for the ‘recursion’ to work. What then really twists my mind up is ‘e <-s’ getting the next value n times. I’m not an expert in how Haskell evaluates these expressions, but I really would like to understand how that works, because my old ‘imperative’ mind is in need of an upgrade.
Mike
On Aug 24, 2015, at 8:50 AM, Atze van der Ploeg
wrote: Hi Mike, cafe,
The implementation in the library is essentially the same as in the paper, but B (E [a]) instead of B (E a) allows multiple simultaneous events, whereas the implementation in the paper does not. The result is B (E [a]), where the list is the list of all results in the event stream which occur at that point. Like the implementation in the paper, the behavior switches as soon as the next event occurs.
I'm a bit unclear on your question, neither implementation is recursive. If you want to use event streams it's best not to look at their implementation, which is tricky, but just use the combinators that are available. You can create a behavior that always give the integration of the values in the eventstream as follows:
integrate :: EvStream (Double,Double) -> Double -> Behavior (Behavior Double) integrate stream startTime = foldEs update (0,startTime) stream where update (total, prevTime) (cur, curTime) = let diff = curTime - prevTime * cur in (total + diff, curTime)
Or use Control.FRPNow.Time.integrate :)
The result will give a Behavior (Behavior Double), because the result depends on when we start integrating to prevent the space leak. Does that answer your question?
Cheers,
Atze
2015-08-24 16:15 GMT+02:00 Michael Jones
: Atze,
I have a question about Streams.
In the Paper Impl the following code:
newtype Stream a = S { next :: B (E a) }
catMaybesStream :: Stream (Maybe a) -> Stream a catMaybesStream (S s) = S loop where loop = do e <- s join <$> plan (nxt <$> e) -- nxt :: Maybe a -> B (E a) nxt (Just a) = return (return a) nxt Nothing = loop
Which I understand.
And in the library the following code:
newtype EvStream a = S { getEs :: Behavior (Event [a]) }
catMaybesEs :: EvStream (Maybe a) -> EvStream a catMaybesEs s = S $ loop where -- loop :: Behavior (Event [a]) loop = do e <- getEs s join <$> plan (nxt <$> e) nxt l = case catMaybes l of [] -> loop l -> return (return l)
I assume the new type EvStream the intent is for the stream of ‘a’ to be an array rather than a recursive data structure, based on the name ‘getEs’.
But, catMaybeEs is written like the paper version, suggesting it is a recursive data structure arrays.
My goal is to write an integrator for a stream, such that the type signature is:
EvStream (Double,Double) -> EvStream (Double)
where the tuple is (data, time) and the result is (integratedData)
and I modeled the function catMaybeEs, but it is not working. So I want to understand the general way to handle the stream in catMaybesEs.
Mike
On Jul 15, 2015, at 7:25 AM, Atze van der Ploeg
wrote: Dear Cafe, We have released the (nearly) first version of FRPNow, the functional reactive programming library based on the ICFP 2015 paper "Principled Practical FRP: Forget the Past, Change the Future, FRPNow!" ( https://www.reddit.com/r/haskell/comments/3ai7hl/principled_practical_frp_fo... ) The main package: http://hackage.haskell.org/package/frpnow Examples: https://github.com/atzeus/FRPNow/tree/master/Examples Gloss interoperability: http://hackage.haskell.org/package/frpnow-gloss GTK interoperability: http://hackage.haskell.org/package/frpnow-gtk (hackage doesn't like the newer GTK docs, so you can read the docs at http://www.cse.chalmers.se/~atze/frpnow-gtk/ )
Cheers,
Atze _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

Atze, On why I did not use Control.FRPNow.Time.integrate. Wrt code below, which is a bit contrived, in that I don’t really need to integrate sensor data, but if I can, I can then use the same concept for other algorithms, such as filtering and control: The idea was to make sure that time of any sensor reading was as near as possible to the actual measurement. Assuming there are many streams running in parallel in an application, taking the time with the measurement (in same sync evaluation) was assumed to be more accurate than taking it code that consumes the stream and processes the data, after the event from the sync evaluation. Also, if a stream is treated like a pipe and filter, the time can be passed along for later processing stages. As for what the code does, it measures distance every 10ms, integrates the stream, then stops when it reaches 1000.0. integrateTelemetry :: EvStream (Double,Double) -> Double -> Behavior (Behavior (Double,Double)) integrateTelemetry stream startTime = foldEs update (0,startTime) stream where update (total, prevTime) (cur, curTime) = let diff = (curTime - prevTime) * cur in (total + diff, curTime) makeTimedStream :: ((a -> IO ()) -> IO ()) -> Int -> Now (EvStream a) makeTimedStream conv delayMs = do (res,f) <- callbackStream conn <- sync $ repeatedTimer (conv f) $ msDelay $ fromIntegral delayMs return res createIRStream :: SMBus.SMBus -> Now (EvStream (Double,Double)) createIRStream smbus = do stream <- makeTimedStream (\f -> do d <- getDistance smbus now <- getTime f (d,now)) 10 return stream testFRP :: SMBus.SMBus -> Double -> Now (Event ()) testFRP smbus n = do stream <- createIRStream smbus now <- sync getTime b <- sample $ integrateTelemetry stream now enoughEv <- sample (Control.FRPNow.when (((> n) . fst) <$> b)) let closeMessage i = "Current : " ++ show i let doneMessage i = "Done : " ++ show i let message = (closeMessage <$> b) `switch` (doneMessage <$> b <$ enoughEv) traceChanges "Message : " message return enoughEv main = initializeTime runNowMaster (testFRP smbus 1000.0)
On Aug 24, 2015, at 8:50 AM, Atze van der Ploeg
wrote: Hi Mike, cafe,
The implementation in the library is essentially the same as in the paper, but B (E [a]) instead of B (E a) allows multiple simultaneous events, whereas the implementation in the paper does not. The result is B (E [a]), where the list is the list of all results in the event stream which occur at that point. Like the implementation in the paper, the behavior switches as soon as the next event occurs.
I'm a bit unclear on your question, neither implementation is recursive. If you want to use event streams it's best not to look at their implementation, which is tricky, but just use the combinators that are available. You can create a behavior that always give the integration of the values in the eventstream as follows:
integrate :: EvStream (Double,Double) -> Double -> Behavior (Behavior Double) integrate stream startTime = foldEs update (0,startTime) stream where update (total, prevTime) (cur, curTime) = let diff = curTime - prevTime * cur in (total + diff, curTime)
Or use Control.FRPNow.Time.integrate :)
The result will give a Behavior (Behavior Double), because the result depends on when we start integrating to prevent the space leak. Does that answer your question?
Cheers,
Atze
2015-08-24 16:15 GMT+02:00 Michael Jones
mailto:mike@proclivis.com>: Atze, I have a question about Streams.
In the Paper Impl the following code:
newtype Stream a = S { next :: B (E a) }
catMaybesStream :: Stream (Maybe a) -> Stream a catMaybesStream (S s) = S loop where loop = do e <- s join <$> plan (nxt <$> e) -- nxt :: Maybe a -> B (E a) nxt (Just a) = return (return a) nxt Nothing = loop
Which I understand.
And in the library the following code:
newtype EvStream a = S { getEs :: Behavior (Event [a]) }
catMaybesEs :: EvStream (Maybe a) -> EvStream a catMaybesEs s = S $ loop where -- loop :: Behavior (Event [a]) loop = do e <- getEs s join <$> plan (nxt <$> e) nxt l = case catMaybes l of [] -> loop l -> return (return l)
I assume the new type EvStream the intent is for the stream of ‘a’ to be an array rather than a recursive data structure, based on the name ‘getEs’.
But, catMaybeEs is written like the paper version, suggesting it is a recursive data structure arrays.
My goal is to write an integrator for a stream, such that the type signature is:
EvStream (Double,Double) -> EvStream (Double)
where the tuple is (data, time) and the result is (integratedData)
and I modeled the function catMaybeEs, but it is not working. So I want to understand the general way to handle the stream in catMaybesEs.
Mike
On Jul 15, 2015, at 7:25 AM, Atze van der Ploeg
mailto:atzeus@gmail.com> wrote: Dear Cafe, We have released the (nearly) first version of FRPNow, the functional reactive programming library based on the ICFP 2015 paper "Principled Practical FRP: Forget the Past, Change the Future, FRPNow!" (https://www.reddit.com/r/haskell/comments/3ai7hl/principled_practical_frp_fo... https://www.reddit.com/r/haskell/comments/3ai7hl/principled_practical_frp_fo...) The main package: http://hackage.haskell.org/package/frpnow http://hackage.haskell.org/package/frpnow Examples: https://github.com/atzeus/FRPNow/tree/master/Examples https://github.com/atzeus/FRPNow/tree/master/Examples Gloss interoperability: http://hackage.haskell.org/package/frpnow-gloss http://hackage.haskell.org/package/frpnow-gloss GTK interoperability: http://hackage.haskell.org/package/frpnow-gtk http://hackage.haskell.org/package/frpnow-gtk (hackage doesn't like the newer GTK docs, so you can read the docs at http://www.cse.chalmers.se/~atze/frpnow-gtk/ http://www.cse.chalmers.se/~atze/frpnow-gtk/ )
Cheers,
Atze _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org mailto:Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

The implementation in the library is essentially the same as in the paper, but B (E [a]) instead of B (E a) allows multiple simultaneous events, whereas the implementation in the paper does not. The result is B (E [a]), where the list is the list of all results in the event stream which occur at that point. Like the implementation in the paper, the behavior switches as soon as the next event occurs.
It looks like ‘merge’ will take two streams in, one stream out, such that if the input streams have a simultaneous event, they get put into the same array [a]. nextAll seems to get all the events, and next takes the head, and the remainder is lost. Perhaps with some trick they can be separated back into individual streams. Given this, it seems the array is more about merging and splitting streams so that things that happen at the same time do not have to be forced into some arbitrary order. But, suppose you have a synchronous system of measurements, such that you want to intentionally put simultaneous events into a stream? Say the events are: Sensor 1 Meas (E1) Sensor 2 Meas (E2) Sensor 3 Meas (E3) and we can assume they are measured at the same time (one async call), so they are time correlated. We may then want to filter them as a pair, etc. Or there may be logic that if two events that occur at the same time and are in some relation, it triggers a new event E4 as an output. Or we might combine measurements into estimates, like in an estimator with multiple sensors, etc. Your probably guessing I’m a hardware guy :-) Now we could tuple them, and that would work fine, and merge would work fine, but then the events must be of a fixed number. Suppose some events are sampled at different times, so we might want events in the stream to look like: [E1, E2, E3] [E1, E3] [E1, E2, E3] [E1, E3] And say we want to generate the stream with callbackStream, so that one callback call sends the events, and they are put into the list as simultaneous. Now, I am guessing the answer is going to be that this is an abuse of the design intent, and perhaps the tuple could just be a tuple of Maybes, and that in most systems, the number of simultaneous events is fixed, etc. But in systems where sensors can be added or subtracted, and where the type of events are somewhat arbitrary or there may be optional redundency, I can imagine that adding an arbitrary number of events into a stream and having processing that can examine the contents of the stream and adjust to what is present might be nice. Do you have any advice on how to insert events into the stream simultaneously, and ways to split a stream into parallel streams, etc. Mike
participants (3)
-
Atze van der Ploeg
-
Michael Jones
-
Oliver Charles