<html><head><meta http-equiv="Content-Type" content="text/html charset=utf-8"></head><body style="word-wrap: break-word; -webkit-nbsp-mode: space; -webkit-line-break: after-white-space;" class=""><div class=""><div class="">Atze,</div><div class=""><br class=""></div><div class="">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:</div><div class=""><br class=""></div><div class="">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.</div><div class=""><br class=""></div><div class="">As for what the code does, it measures distance every 10ms, integrates the stream, then stops when it reaches 1000.0.</div><div class=""><br class=""></div><div class="">integrateTelemetry :: EvStream (Double,Double) -> Double -> Behavior (Behavior (Double,Double))</div><div class="">integrateTelemetry stream startTime = foldEs update (0,startTime) stream where</div><div class="">  update (total, prevTime) (cur, curTime) = let diff = (curTime - prevTime) * cur </div><div class="">                                                    in (total + diff, curTime)</div><div class=""><br class=""></div><div class=""><br class=""></div><div class="">makeTimedStream :: ((a -> IO ()) -> IO ()) -> Int -> Now (EvStream a)</div><div class="">makeTimedStream conv delayMs =</div><div class="">  do  (res,f) <- callbackStream</div><div class="">      conn <- sync $ repeatedTimer (conv f) $ msDelay $ fromIntegral delayMs</div><div class="">      return res</div><div class=""><br class=""></div><div class="">createIRStream ::  SMBus.SMBus -> Now (EvStream (Double,Double))</div><div class="">createIRStream smbus =  </div><div class="">  do stream <- makeTimedStream (\f -> do  d <- getDistance smbus</div><div class="">                                          now <- getTime</div><div class="">                                          f (d,now)) 10</div><div class="">     return stream</div></div><div class=""><br class=""></div><div class=""> testFRP :: SMBus.SMBus -> Double -> Now (Event ())</div><div class=""><div class=""> testFRP smbus n =   do      stream <- createIRStream smbus</div><div class="">                                    now <- sync getTime</div><div class="">                                    b <- sample $ integrateTelemetry stream now</div><div class="">                                    enoughEv <- sample (Control.FRPNow.when (((> n) . fst) <$> b))</div><div class="">                                    let closeMessage i = "Current : " ++ show i</div><div class="">                                    let doneMessage i = "Done : " ++ show i</div><div class="">                                    let message = (closeMessage <$> b) `switch` (doneMessage <$> b <$ enoughEv)</div><div class="">                                    traceChanges "Message : " message</div><div class="">                                    return enoughEv</div></div><div class=""><br class=""></div><div class=""><br class=""></div><div class="">main =</div><div class=""><br class=""></div><div class=""><div class="">    initializeTime</div><div class="">    runNowMaster (testFRP smbus 1000.0)</div></div><div class=""><br class=""></div><div class=""><br class=""></div><br class=""><div><blockquote type="cite" class=""><div class="">On Aug 24, 2015, at 8:50 AM, Atze van der Ploeg <<a href="mailto:atzeus@gmail.com" class="">atzeus@gmail.com</a>> wrote:</div><br class="Apple-interchange-newline"><div class=""><div dir="ltr" class="">Hi Mike, cafe,<div class=""><br class=""></div><div class="">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.</div><div class=""><br class=""></div><div class="">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. </div><div class="">You can create a behavior that always give the integration of the values in the eventstream as follows:</div><div class=""><br class=""></div><div class="">integrate :: EvStream (Double,Double) -> Double -> Behavior (Behavior Double)</div><div class="">integrate stream startTime = foldEs update (0,startTime) stream where</div><div class="">  update (total, prevTime) (cur, curTime) = let diff = curTime - prevTime * cur </div><div class="">                                                                    in (total + diff, curTime)</div><div class=""><br class=""></div><div class="">Or use Control.FRPNow.Time.integrate :)</div><div class=""><br class=""></div><div class="">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? </div><div class=""><br class=""></div><div class="">Cheers,</div><div class=""><br class=""></div><div class="">Atze</div><div class=""><br class=""></div><div class=""><br class=""></div></div><div class="gmail_extra"><br class=""><div class="gmail_quote">2015-08-24 16:15 GMT+02:00 Michael Jones <span dir="ltr" class=""><<a href="mailto:mike@proclivis.com" target="_blank" class="">mike@proclivis.com</a>></span>:<br class=""><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex"><div style="word-wrap:break-word" class=""><div class=""><div class=""><div class=""><div class="">Atze,</div><div class=""><br class=""></div><div class="">I have a question about Streams.</div><div class=""><br class=""></div><div class="">In the Paper Impl the following code:</div><div class=""><br class=""></div><div class="">newtype Stream a = S { next :: B (E a) }</div></div><div class=""><br class=""></div><div class=""><div class="">catMaybesStream :: Stream (Maybe a) -> Stream a</div><div class="">catMaybesStream (S s) = S loop where</div><div class="">  loop = do  e <- s</div><div class="">             join <$> plan (nxt <$> e)</div><div class="">--  nxt :: Maybe a -> B (E a)</div><div class="">  nxt (Just a) = return (return a)</div><div class="">  nxt Nothing  = loop</div></div><div class=""><br class=""></div><div class="">Which I understand.</div><div class=""><br class=""></div><div class="">And in the library the following code:</div><div class=""><br class=""></div><div class="">newtype EvStream a = S { getEs :: Behavior (Event [a]) }</div></div><div class=""><br class=""></div><div class=""><br class=""></div><div class="">catMaybesEs :: EvStream (Maybe a) -> EvStream a</div><div class="">catMaybesEs s = S $ loop where</div><div class="">--  loop :: Behavior (Event [a])</div><div class="">  loop = do  e <- getEs s</div><div class="">             join <$> plan (nxt <$> e)</div><div class="">  nxt l = case  catMaybes l of</div><div class="">             [] -> loop</div><div class="">             l  -> return (return l)</div></div><div class=""><br class=""></div><div class="">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’.</div><div class=""><br class=""></div><div class="">But, catMaybeEs is written like the paper version, suggesting it is a recursive data structure arrays.</div><div class=""><br class=""></div><div class="">My goal is to write an integrator for a stream, such that the type signature is:</div><div class=""><br class=""></div><div class="">EvStream (Double,Double) -> EvStream (Double)</div><div class=""><br class=""></div><div class="">where the tuple is (data, time) and the result is (integratedData)</div><div class=""><br class=""></div><div class="">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.</div><div class=""><br class=""></div><div class="">Mike</div><div class=""><br class=""></div><br class=""><div class=""><blockquote type="cite" class=""><div class=""><div class="h5"><div class="">On Jul 15, 2015, at 7:25 AM, Atze van der Ploeg <<a href="mailto:atzeus@gmail.com" target="_blank" class="">atzeus@gmail.com</a>> wrote:</div><br class=""></div></div><div class=""><div class=""><div class="h5"><div dir="ltr" class=""><div style="margin:0px 0px 0.357142857142857em;padding:0px" class=""><font color="#4d5763" face="verdana, arial, helvetica, sans-serif" class=""><span style="font-size:14px;line-height:20px" class="">Dear Cafe,</span></font></div><div style="margin:0px 0px 0.357142857142857em;padding:0px" class=""><font color="#4d5763" face="verdana, arial, helvetica, sans-serif" class=""><span style="font-size:14px;line-height:20px" class="">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!" (<a href="https://www.reddit.com/r/haskell/comments/3ai7hl/principled_practical_frp_forget_the_past_change/" target="_blank" class="">https://www.reddit.com/r/haskell/comments/3ai7hl/principled_practical_frp_forget_the_past_change/</a>)</span></font></div><div style="margin:0px 0px 0.357142857142857em;padding:0px" class=""><font color="#4d5763" face="verdana, arial, helvetica, sans-serif" class=""><span style="font-size:14px;line-height:20px" class="">The main package: <a href="http://hackage.haskell.org/package/frpnow" target="_blank" class="">http://hackage.haskell.org/package/frpnow</a></span></font></div><div style="margin:0px 0px 0.357142857142857em;padding:0px" class=""><font color="#4d5763" face="verdana, arial, helvetica, sans-serif" class=""><span style="font-size:14px;line-height:20px" class="">Examples: <a href="https://github.com/atzeus/FRPNow/tree/master/Examples" target="_blank" class="">https://github.com/atzeus/FRPNow/tree/master/Examples</a></span></font></div><div style="margin:0px 0px 0.357142857142857em;padding:0px" class=""><font color="#4d5763" face="verdana, arial, helvetica, sans-serif" class=""><span style="font-size:14px;line-height:20px" class="">Gloss interoperability: <a href="http://hackage.haskell.org/package/frpnow-gloss" target="_blank" class="">http://hackage.haskell.org/package/frpnow-gloss</a></span></font></div><div style="margin:0px 0px 0.357142857142857em;padding:0px" class=""><font color="#4d5763" face="verdana, arial, helvetica, sans-serif" class=""><span style="font-size:14px;line-height:20px" class="">GTK interoperability: <a href="http://hackage.haskell.org/package/frpnow-gtk" target="_blank" class="">http://hackage.haskell.org/package/frpnow-gtk</a></span></font></div><div style="margin:0px 0px 0.357142857142857em;padding:0px" class=""><font color="#4d5763" face="verdana, arial, helvetica, sans-serif" class=""><span style="font-size:14px;line-height:20px" class="">(hackage doesn't like the newer GTK docs, so you can read the docs at <a href="http://www.cse.chalmers.se/~atze/frpnow-gtk/" target="_blank" class="">http://www.cse.chalmers.se/~atze/frpnow-gtk/</a> </span></font><span style="font-size:14px;line-height:20px;color:rgb(77,87,99);font-family:verdana,arial,helvetica,sans-serif" class="">)</span></div><div style="margin:0px 0px 0.357142857142857em;padding:0px" class=""><font color="#4d5763" face="verdana, arial, helvetica, sans-serif" class=""><span style="font-size:14px;line-height:20px" class=""><br class=""></span></font></div><div style="margin:0px 0px 0.357142857142857em;padding:0px" class=""><font color="#4d5763" face="verdana, arial, helvetica, sans-serif" class=""><span style="font-size:14px;line-height:20px" class="">Cheers,</span></font></div><div style="margin:0px 0px 0.357142857142857em;padding:0px" class=""><font color="#4d5763" face="verdana, arial, helvetica, sans-serif" class=""><span style="font-size:14px;line-height:20px" class=""><br class=""></span></font></div><div style="margin:0px 0px 0.357142857142857em;padding:0px" class=""><font color="#4d5763" face="verdana, arial, helvetica, sans-serif" class=""><span style="font-size:14px;line-height:20px" class="">Atze</span></font></div></div></div></div><span class="">
_______________________________________________<br class="">Haskell-Cafe mailing list<br class=""><a href="mailto:Haskell-Cafe@haskell.org" target="_blank" class="">Haskell-Cafe@haskell.org</a><br class=""><a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe" target="_blank" class="">http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe</a><br class=""></span></div></blockquote></div><br class=""></div></blockquote></div><br class=""></div>
</div></blockquote></div><br class=""></body></html>