Code Monkey home page Code Monkey logo

Comments (4)

ocharles avatar ocharles commented on August 17, 2024

I also note that if I don't have reactimate $ print <$> b' <@ onPrint then I don't get a sampling message at all. This surprises me, because [Note LatchStrictness] states that all latches (and thus I would expect all Behaviors) should be in WHNF at the end of network evaluation - but that doesn't seem to actually be happening.

from reactive-banana.

ocharles avatar ocharles commented on August 17, 2024

A smaller repro:

{-# language BlockArguments #-}

module Main where

import Data.Functor
import Debug.Trace
import Reactive.Banana
import Reactive.Banana.Frameworks

main :: IO ()
main = do
  (onChangeCheckbox, changeCheckbox) <- newAddHandler

  actuate =<< compile do
    onToggle <- fromAddHandler onChangeCheckbox
    checked  <- stepper False onToggle

    let b1 = traceShowId <$> pure "1"
    let b' = liftA2 (,) checked b1

    reactimate $ return () <$ b' <@ onToggle

  changeCheckbox True
  changeCheckbox False
  changeCheckbox True

Note that changing b1 to be b1 = pure $ traceShowId "1" there is no problem. Also, changing b' to be let b' = traceShowId <$> pure 1 <* checked also doesn't have a problem. It seems to be something specific about having a separate b1 binding that uses fmap.

I also tried let b' = b1 <* checked and this also doesn't have the problem

from reactive-banana.

ocharles avatar ocharles commented on August 17, 2024

Another weird point: let b' = liftA2 (,) b1 checked does not have a problem, but let b' = liftA2 (,) checked b1 does. So the order here seems to matter. Probably need to get into core at this point.

from reactive-banana.

mitchellwrosen avatar mitchellwrosen commented on August 17, 2024

I made some progress on understanding this one.

Here's a rough diagram of a slightly simplified version of Ollie's example.
Screen Shot 2023-02-26 at 11 10 20 AM

The black text are latches, with nodes in the tree being <*> pointing at the left and right side.

The red arrow shows an onToggle event coming in and affecting the value of the checked latch directly.

We need to calculate the value of the entire latch (the root of the tree), so we will go down depth-first, getting each latch's value, per the definition of applyL and cachedLatch:

applyL :: Latch (a -> b) -> Latch a -> Latch b
applyL lf lx = cachedLatch
({-# SCC applyL #-} getValueL lf <*> getValueL lx)

, _evalL = do
Latch{..} <- liftIO $ Ref.read latch
-- calculate current value (lazy!) with timestamp
(a,time) <- RW.listen eval
liftIO $ if time <= _seenL
then return _valueL -- return old value
else do -- update value
let _seenL = time
let _valueL = a
a `seq` Ref.put latch (Latch {..})
return a

So, say the event occurs at time t=5. When evaluating the whole latch, after getting to the checked child, we'll write t=5 to the evaluation context, since it was directly updated by the event. (The EvalL monad is WriterT Time IO; the time indicates the latest time that this evaluation is recent as of).

Then, later nodes in the tree (such as our traceShowId <$> pure "1", which we expect to be unaffected by the onToggle event and thus not recomputed, enter the same evaluation logic

(a,time) <- RW.listen eval
liftIO $ if time <= _seenL
then return _valueL -- return old value
else do -- update value
let _seenL = time
let _valueL = a
a `seq` Ref.put latch (Latch {..})
return a

only in a context where t=5 is already written to the EvalL context. We'll therefore hit the else-branch which corresponds to recomputing this value rather than using what's cached.

from reactive-banana.

Related Issues (20)

Recommend Projects

  • React photo React

    A declarative, efficient, and flexible JavaScript library for building user interfaces.

  • Vue.js photo Vue.js

    🖖 Vue.js is a progressive, incrementally-adoptable JavaScript framework for building UI on the web.

  • Typescript photo Typescript

    TypeScript is a superset of JavaScript that compiles to clean JavaScript output.

  • TensorFlow photo TensorFlow

    An Open Source Machine Learning Framework for Everyone

  • Django photo Django

    The Web framework for perfectionists with deadlines.

  • D3 photo D3

    Bring data to life with SVG, Canvas and HTML. 📊📈🎉

Recommend Topics

  • javascript

    JavaScript (JS) is a lightweight interpreted programming language with first-class functions.

  • web

    Some thing interesting about web. New door for the world.

  • server

    A server is a program made to process requests and deliver data to clients.

  • Machine learning

    Machine learning is a way of modeling and interpreting data that allows a piece of software to respond intelligently.

  • Game

    Some thing interesting about game, make everyone happy.

Recommend Org

  • Facebook photo Facebook

    We are working to build community through open source technology. NB: members must have two-factor auth.

  • Microsoft photo Microsoft

    Open source projects and samples from Microsoft.

  • Google photo Google

    Google ❤️ Open Source for everyone.

  • D3 photo D3

    Data-Driven Documents codes.