[Haskell-cafe] [ANN] frpnow-0.12

Michael Jones mike at proclivis.com
Mon Aug 24 14:15:50 UTC 2015


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/ <https://www.reddit.com/r/haskell/comments/3ai7hl/principled_practical_frp_forget_the_past_change/>)
> 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 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/e12d365d/attachment.html>


More information about the Haskell-Cafe mailing list