reactive-banana icon indicating copy to clipboard operation
reactive-banana copied to clipboard

Consider unifying `valueB` and `valueBLater`

Open HeinrichApfelmus opened this issue 8 years ago • 12 comments

The functions

valueB :: Behavior a -> Moment a
valueBLater :: Behavior a -> Moment a

are somewhat redundant. Unfortunately, the distinction seems necessary, because the two variants differ when it comes to recursion: The result value of valueB is available immediately, while the result value of valueBLater is | until the end of the Moment.

Maybe there is a way to unify them again?

HeinrichApfelmus avatar Sep 14 '15 13:09 HeinrichApfelmus

I'm confused with this difference, why is this necessary? What is the difference in the model? Is this due implementation details?

atzeus avatar Dec 31 '15 10:12 atzeus

The two combinators are indistinguishable in the model implementation. Unfortunately, I have found it necessary to distinguish them in the efficient implementation. This is because the IO type constructor is not a good MonadFix instance.

The following code demonstrates the issue. If we want to use the result for IO right away, then valueB is the right choice (testA1 vs testA2). If we want to use the result with value recursion, then valueBLater is the right choice (testB1 vs testB2). I have not been able to find an implementation that works in both cases.

    {-# LANGUAGE RecursiveDo #-}
    module TestValueB where
    import Reactive.Banana
    import Reactive.Banana.Frameworks

    testMoment :: MomentIO a -> IO a
    testMoment m = fmap from $
        interpretFrameworks (\e -> m >>= \x -> return (x <$ e)) [Just ()]
        where from [Just x] = x

    testA1, testA2, testB1, testB2 :: MomentIO Int

    -- works
    testA1 = do
        b <- stepper 0 never
        x <- valueB b
        liftIO $ print x
        return x

    -- fails, throws exception
    testA2 = do
        b <- stepper 0 never
        x <- valueBLater b
        liftIO $ print x
        return x

    -- fails, does not terminate
    testB1 = mdo
        x <- valueB b
        b <- stepper 0 never
        return x

    -- works
    testB2 = mdo
        x <- valueBLater b
        b <- stepper 0 never
        return x

HeinrichApfelmus avatar Jan 01 '16 16:01 HeinrichApfelmus

I see. Is there any documentation how your implementation works? On Jan 1, 2016 5:30 PM, "Heinrich Apfelmus" [email protected] wrote:

The two combinators are indistinguishable in the model implementation. Unfortunately, I have found it necessary to distinguish them in the efficient implementation. This is because the IO type constructor is not a good MonadFix instance.

The following code demonstrates the issue. If we want to use the result for IO right away, then valueB is the right choice (testA1 vs testA2). If we want to use the result with value recursion, then valueBLater is the right choice (testB1 vs testB2). I have not been able to find an implementation that works in both cases.

{-# LANGUAGE RecursiveDo #-}
module TestValueB where
import Reactive.Banana
import Reactive.Banana.Frameworks

testMoment :: MomentIO a -> IO a
testMoment m = fmap from $
    interpretFrameworks (\e -> m >>= \x -> return (x <$ e)) [Just ()]
    where from [Just x] = x

testA1, testA2, testB1, testB2 :: MomentIO Int

-- works
testA1 = do
    b <- stepper 0 never
    x <- valueB b
    liftIO $ print x
    return x

-- fails, throws exception
testA2 = do
    b <- stepper 0 never
    x <- valueBLater b
    liftIO $ print x
    return x

-- fails, does not terminate
testB1 = mdo
    x <- valueB b
    b <- stepper 0 never
    return x

-- works
testB2 = mdo
    x <- valueBLater b
    b <- stepper 0 never
    return x

— Reply to this email directly or view it on GitHub https://github.com/HeinrichApfelmus/reactive-banana/issues/108#issuecomment-168315014 .

atzeus avatar Jan 01 '16 16:01 atzeus

I presume that valueBLater does not immediately get the value, but creates a mutable cell which is filled in at the end of the moment with the correct value, and that forcing the value before the end of the moment is an error.

Would it work if you take this behavior, but add that forcing the value (before the end of the moment) also causes it to observe the value?

I.e. the observation is done at most at the end of the moment, but earlier if the value is forced?

atzeus avatar Jan 01 '16 16:01 atzeus

I presume that valueBLater does not immediately get the value, but creates a mutable cell which is filled in at the end of the moment with the correct value, and that forcing the value before the end of the moment is an error.

Yes, pretty much. In order to return an actual value, some IO actions have to happen. In particular, the argument Behavior has to be "built" and inserted into the graph. In the case of valueBLater, these IO actions are deferred to until the end of the current Moment, as you presumed correctly.

Would it work if you take this behavior, but add that forcing the value (before the end of the moment) also causes it to observe the value?

In principle, that should be possible, but I found it hard to write code that does this. The main difficulty is that in order to get the actual values, some IO actions have to be performed. But the value is pure, so something along the lines of unsafeInterleaveIO needs to be used. Unfortunately, these IO actions may trigger "building" the argument Behavior, which in turn may trigger other calls to valueB. When using unsafeInterleaveIO, all of this happens outside the normal ordering of IO actions, and I have no idea how to ensure correctness / atomicity in this case, where we have nested, interleaving, and potentially recursive actions.

That's why I've implemented a solution that is "good enough" and opened an issue. :smile:

HeinrichApfelmus avatar Jan 02 '16 15:01 HeinrichApfelmus

I'm a bit confused. Would this work (in pseudocode)?

valueB b = scheduleForceAtEndOfMoment m >> return m where
  m = unsafePerformIO $ readValueOf b

This gives bottom if value is forced before the behavior is defined, but this is consistent with the semantics, I think.

atzeus avatar Jan 02 '16 15:01 atzeus

Yes, in principle, this would work. However, executing readValueOf b may in turn make calls to scheduleForceAtEndOfMoment, perhaps even recursively, depending on how the Behavior b came to be in the first place.

Essentially, I would have to write a thing that can

  1. Schedule IO actions to be run later
  2. Handle recursion, i.e. an IO action may schedule itself, but it will not be run twice.
  3. Nesting: Allow scheduled IO actions to schedule other IO actions to be run at the same end of the moment (i.e. right now)
  4. Can do all that from within unsafePerformIO.

I have not attempted to tackle the fourth point, because it seems very difficult to me, with little benefit.

HeinrichApfelmus avatar Jan 02 '16 20:01 HeinrichApfelmus

I don't understand why readValueOf b might make calls to scheduleForceAtEndOfMoment. I assumed readValueOf b is just reading some mutable cell (which might change in the start of the next moment, but not before that).

Can you give an example where readValueOf b causes calls scheduleForceAtEndOfMoment (or something else)?

atzeus avatar Jan 02 '16 20:01 atzeus

Also what do you mean with this?

... This is because the IO type constructor is not a good MonadFix instance.

atzeus avatar Jan 03 '16 11:01 atzeus

Can you give an example where readValueOf b causes calls scheduleForceAtEndOfMoment (or something else)?

Essentially, the trouble is that the Behavior b is not simply a cell, rather it is itself an action, which happens in a special monad Reactive.Banana.Internal.Combinators.Moment, which is a transformer stack on top of IO. For instance, the definition of applyB looks like this (e.g. in commit 429ae4cd29262ab24eea69346e5a486725ee55e7):

type Moment     = ReaderT EventNetwork Prim.Build
type Behavior a = Cached Moment (Latch a, Pulse ())

applyB  = liftCached2 $ \(~(l1,p1)) (~(l2,p2)) -> liftBuild $ do
    p3 <- Prim.unionWithP const p1 p2
    let l3 = Prim.applyL l1 l2
    return (l3,p3)

Essentially, it says that Behavior is built from a pair of primitive types Latch and Pulse. The Pulse keeps track of when the Behavior changes, so that we can offer an efficient changes function for binding to external UI libraries.

Latch and Pulse can only be "created" from within the Build monad. For instance, "creation" for a Latch means that we call newIORef to create the cell that holds the value of the latch, but also other things, like dependency information.

Now, what applyB does is it caches the creation, so that we get observable sharing. In pseudocode, it looks something like this:

    applyB bf bx = unsafePerformIO $ do
        sharingDetector <- newIORef
        return $ do
            maybeCreatedAlready <- liftIO $ readIORef sharingDetector
            case maybeCreatedAlready of
                Just (latch, pulse) -> return (latch, pulse)
                Nothing             -> do
                    (l1,p1) <- bf
                    (l2,p2) <- bx

                    -- the following lines call
                    -- scheduleForceAtEndOfMoment
                    p3 <- Prim.unionWithP const p1 p2
                    let l3 = Prim.applyL l1 l2

                    liftIO $ writeIORef maybeCreatedAlready $ Just (l3,p3)
                    return (l3,p3)

The point is that new pulses and latches can only be created at the end of the Moment, so the lines indicated by a comment call scheduleForceAtEndOfMoment.

Now, I'm not saying that unifying these two is wholly impossible. I think it is possible. But with my current setup, it's far from easy. Ultimately, the problem is that a Behavior is more than just an IORef that contains the current value, but also other things.

... This is because the IO type constructor is not a good MonadFix instance.

What I was referring to is that the class instance MonadFix IO does not satisfy all the laws I want, though I have to admit that I'm not entirely clear on which laws these are. In any case, here is one recursive example in several different monads. For some monads, it terminates, but for some it doesn't, and this is bad for the issue at hand.

{-# LANGUAGE RecursiveDo #-}
import Control.Monad.Trans.State.Lazy
import Data.Functor.Identity

-- does not terminate
testIO :: IO ()
testIO = mdo
    Just _ <- return b
    b <- return (Just 'a')
    return ()

-- terminates
testRecState :: ()
testRecState = runIdentity . fmap fst . flip runStateT (0::Int) $ mdo
    Just _ <- return b
    b <- return (Just 'a')
    return ()

-- does not terminate
testRecStateTIO :: IO ()
testRecStateTIO = fmap fst . flip runStateT (0::Int) $ mdo
    Just _ <- return b
    b <- return (Just 'a')
    return ()

(Just for reference, the articles that introduce MonadFix, in particular "Recursive Monadic Bindings", can be found on Levent Erkök's website.)

HeinrichApfelmus avatar Jan 04 '16 00:01 HeinrichApfelmus

Thanks, I see now why it's hard in this setup. On Jan 4, 2016 1:00 AM, "Heinrich Apfelmus" [email protected] wrote:

Can you give an example where readValueOf b causes calls scheduleForceAtEndOfMoment (or something else)?

Essentially, the trouble is that the Behavior b is not simply a cell, rather it is itself an action, which happens in a special monad Reactive.Banana.Internal.Combinators.Moment, which is a transformer stack on top of IO. For instance, the definition of applyB looks like this (e.g. in commit 429ae4c https://github.com/HeinrichApfelmus/reactive-banana/commit/429ae4cd29262ab24eea69346e5a486725ee55e7 ):

type Moment = ReaderT EventNetwork Prim.Buildtype Behavior a = Cached Moment (Latch a, Pulse ())

applyB = liftCached2 $ (~(l1,p1)) (~(l2,p2)) -> liftBuild $ do p3 <- Prim.unionWithP const p1 p2 let l3 = Prim.applyL l1 l2 return (l3,p3)

Essentially, it says that Behavior is built from a pair of primitive types Latch and Pulse. The Pulse keeps track of when the Behavior changes, so that we can offer an efficient changes function for binding to external UI libraries.

Latch and Pulse can only be "created" from within the Build monad. For instance, "creation" for a Latch means that we call newIORef to create the cell that holds the value of the latch.

Now, what applyB does is it caches the creation, so that we get observable sharing. In pseudocode, it looks something like this:

applyB bf bx = unsafePerformIO $ do
    sharingDetector <- newIORef
    return $ do
        maybeCreatedAlready <- liftIO $ readIORef sharingDetector
        case maybeCreatedAlready of
            Just (latch, pulse) -> return (latch, pulse)
            Nothing             -> do
                (l1,p1) <- bf
                (l2,p2) <- bx

                -- the following lines call
                -- scheduleForceAtEndOfMoment
                p3 <- Prim.unionWithP const p1 p2
                let l3 = Prim.applyL l1 l2

                liftIO $ writeIORef maybeCreatedAlready $ Just (l3,p3)
                return (l3,p3)

The point is that new pulses and latches can only be created at the end of the Moment, so the lines indicated by a comment call scheduleForceAtEndOfMoment.

Now, I'm not saying that unifying these two is wholly impossible. I think it is possible. But with my current setup, it's far from easy. Ultimately, the problem is that a Behavior is more than just an IORef that contains the current value, but also other things.

... This is because the IO type constructor is not a good MonadFix instance.

What I was referring to is that the class instance MonadFix IO does not satisfy all the laws I want, though I have to admit that I'm not entirely clear on which laws these are. In any case, here is one recursive example in several different monads. For some monads, it terminates, but for some it doesn't, and this is bad for the issue at hand.

{-# LANGUAGE RecursiveDo #-}import Control.Monad.Trans.State.Lazyimport Data.Functor.Identity -- does not terminatetestIO :: IO () testIO = mdo Just _ <- return b b <- return (Just 'a') return () -- terminatestestRecState :: () testRecState = runIdentity . fmap fst . flip runStateT (0::Int) $ mdo Just _ <- return b b <- return (Just 'a') return () -- does not terminatetestRecStateTIO :: IO () testRecStateTIO = fmap fst . flip runStateT (0::Int) $ mdo Just _ <- return b b <- return (Just 'a') return ()

(Just for reference, the articles that introduce MonadFix, in particular "Recursive Monadic Bindings", can be found on Levent Erkök's website https://sites.google.com/site/leventerkok/.)

— Reply to this email directly or view it on GitHub https://github.com/HeinrichApfelmus/reactive-banana/issues/108#issuecomment-168556525 .

atzeus avatar Jan 04 '16 07:01 atzeus

Note that

main :: IO ()
main = mdo
  ~(Just _) <- return b
  b <- return (Just 'a')
  return ()

does terminate, so it seems to be related to the strictness of IO. Doesn't really change anything though, but gets us a bit more of an insight into what's going on!

ocharles avatar Feb 10 '16 16:02 ocharles