reflex icon indicating copy to clipboard operation
reflex copied to clipboard

Performance problem and cyclic evaluation in fixIO.

Open wdanilo opened this issue 5 years ago • 4 comments

Hi! The following code draws 1000 checkboxes next to text fields. If a checkbox is selected, the text field shows the current mouse position. If it's unchecked, the text shows "-". All checkboxes are unchecked on the beginning.

{-# LANGUAGE OverloadedStrings #-}

import Prelude
import Reflex
import Reflex.Dom
import Data.Text (pack, unpack)
import Text.Read (readMaybe)
import Control.Applicative ((<*>), (<$>))
import GHCJS.DOM.EventM (mouseOffsetXY, EventM, event, mouseClientXY, uiPageXY, mouseButton, eventTarget)
import GHCJS.DOM.Types (IsUIEvent, IsElement)
import Control.Monad.IO.Class (MonadIO)

main :: IO ()
main = mainWidget $ mdo
  el "div" $ pure ()
  (elm, out) <- el' "div" $ do
    dynText relEvD
    flip mapM_ ([0..1000] :: [Int]) $ \_ -> do
      cb <- checkbox False def
      let vv = value cb
      let cv = current vv
      dynText ((\b a -> if b then a else "-") <$> vv <*> relEvD) 
      -- let ev2 = gate cv relEv
      -- evD <- holdDyn "-" ev2
      -- dynText evD
    
  relEv <- fmap (pack . show) <$> offsetMouseEvent elm Mousemove
  relEvD <- holdDyn "foo" relEv
  pure ()

offsetMouseEvent 
    :: (TriggerEvent tx m, IsUIEvent (EventType event), IsElement (RawElement el), MonadIO m) 
    => Element er el t -> EventName event -> m (Event tx (Int, Int))
offsetMouseEvent elm ev = wrapDomEvent (_element_raw elm) (elementOnEventName ev) uiPageXY

There is a huge performance problem with the code – even if we do not select any checkbox (so all text boxes show just "-") the performance of the app is low. When inspecting the JS Performance tab in Chrome we can discover that a lot of function calls are performed in every frame in JS. I suspect that the cause it the line dynText ((\b a -> if b then a else "-") <$> vv <*> relEvD), because Reflex is not provided with an information that it should eval the lambda only on change of the vv event, so the evaluation happens when the relEvD event is triggered (on every mouse move).

If that's the correct way of thinking, then everything works OK so far. The problem appears when trying to properly optimize the logic. I assume that the gate function could be used exactly for the described purpose. Unfortunately, when replacing the line dynText ((\b a -> if b then a else "-") <$> vv <*> relEvD) with the commented 3 lines in the code, the compiled application throws runtime error of cyclic evaluation in fixIO, which does not make sense to me. What's interesting, uncommenting only the line let ev2 = gate cv relEv causes the runtime error, which makes it even more bizarre, as let bindings should rather not affect the runtime logic of the app.

There are 2 questions involved in this issue:

  • Why the runtime error appears and how the end user is able to discover the cause (are there any debug tools for that)?
  • If the gate function would not provide me with the expected performance (disabling all computations unless the checkbox is checked), what would be the correct way of expressing this behavior in Reflex? My real use case is a bit more complicated – I've got up to a million lines on the screen and I want the user to click and drag on any end of the line to move it. Only after clicking on the end of the line, the line should follow the mouse, while all other lines should just stay in place without any additional computations.

wdanilo avatar May 03 '19 00:05 wdanilo

I can't reproduce your problem with any recent Obelisk (neither master nor develop). Maybe you just stumbled upon a bug that is already fixed?

To answer your questions:

1: Not that I am aware of. Usually they can be found pretty quickly though, by disabling/enabling code sections. 2: The code seems to work fine for me with gate.

eskimor avatar May 03 '19 10:05 eskimor

In general when you have cycles which should in fact work, what usually helps is delay 0 on the opposing event to "break" the loop. Usually something in the code is too strict in that case and I would rather fix that, but that is not always feasible (e.g. some deep library code, which you don't have the time to fix right now.)

eskimor avatar May 03 '19 10:05 eskimor

Hi!

There is a huge performance problem with the code – even if we do not select any checkbox (so all text boxes show just "-") the performance of the app is low.

You have a dynText relEvD at the top that shows the current mouse position regardless of whether anything is selected. That alone will generate lots of DOM events followed by lots of corresponding reflex events followed by lots of DOM updates and redraws of the text element and can cause high CPU. The browser can generate the events at a really high rate for something like mousemove. I haven't checked but I'd expect pure JS to exhibit a similar problem, maybe to a smaller degree at first.

So I guess the question really is: if we remove the top dynText relEvD and nothing is selected then how to avoid high cpu while moving the mouse?

AFAIK using gate will not stop the flood of mousemove events as reflex will still consider the input event to be used. However, you could try switching the event between never and the actual mousemove. Maybe something like so:

main2 :: (MonadWidget t m) => m ()
main2 = mdo
  (elm, _) <- el' "div" $ do
    forM_ ([0..1000] :: [Int]) $ \_ -> do
      cb <- checkbox False def
      let dEv = ffor (value cb) $ \case
                  True -> relEv
                  False -> never
      evD <- holdDyn "-" $ switch $ current dEv
      dynText evD
      pure ()

  relEv <- fmap (T.pack . show) <$> offsetMouseEvent elm Mousemove
  pure ()

Now reflex should notice the mousemove event is unused and not process it. Of course when anything is selected you're back to high CPU and I don't think anything can be done about that unless you throttle the input event (how?). Others could probably offer a more in depth explanation.

Like @eskimor I haven't been able to reproduce the runtime error.

mulderr avatar May 03 '19 13:05 mulderr

throttle the input event

Indeed: http://hackage.haskell.org/package/reflex-0.6.1/docs/Reflex-Time.html#v:throttle Something like evD <- holdDyn "-" <=< throttle someTime $ switch $ current dEv might help

alexfmpe avatar May 03 '19 13:05 alexfmpe