[Haskell-cafe] [ANN] frpnow-0.12

Atze van der Ploeg atzeus at gmail.com
Mon Aug 24 15:08:55 UTC 2015


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 <mike at 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 <atzeus at 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 <mike at 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 <atzeus at 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_forget_the_past_change/
>> )
>> 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 at haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
>>
>>
>>
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20150824/aa071b19/attachment.html>


More information about the Haskell-Cafe mailing list