Are non-blocking heavy computations in Reflex possible?

Hello everyone,

I’m using reflex with Obelisk and hit a roadblock. My application is doing some intensive (pure) calculations that end up blocking the UI.

Here’s a simplified example:

performanceQuirk :: MonadWidget t m => m ()
performanceQuirk = divClass "flex flex-col gap-2" $ mdo
  (heavyButton,_) <- elAttr' "button" ("class" =: "btn btn-primary") $ text "Heavy Computation"

  let heavyClick = Loading <$ domEvent Click heavyButton

  heavyComputationFinished <- performEvent $ ffor heavyClick $ \_ -> do
    Computed <$> liftIO veryHeavyComputation

  stateD <- holdDyn Initial (leftmost [heavyClick, heavyComputationFinished, quickClick])
  
  (quickButton,_) <- elAttr' "button" ("class" =: "btn btn-primary") $ text "Instant Computation"

  let quickClick = Computed (quickComputation "123") <$ domEvent Click quickButton

  divClass "alert" $
    dyn_ $ ffor stateD $ \case
      Initial -> text "Initial"
      Loading -> divClass "loading loading-spinner loading-sm" blank
      Computed x -> text $ "Computed " <> tshow x

veryHeavyComputation :: IO Text
veryHeavyComputation = do
  threadDelay $ 5000 * 1000
  pure "Heavy Computation"

quickComputation :: Text -> Text
quickComputation t = do
  "Quick Computation: " <> t

data PerformanceTestState =
  Initial |
  Loading |
  Computed Text

The current behavior is:

After clicking the Heavy Computation button, clicking the Instant Computation one does nothing. Eventually, after the heavy one completes, the instant one will override the UI.

What I’m hoping to achieve is while the heavy computation is running I should be able to click the Instant Computation button and see the UI update immediately. Then after the heavy one completes, it should update it again.

Is this even possible?

Use performEventAsync to build an Event which fires when the work finishes. You will need to forkIO the background thread yourself, per the Haddocks.

3 Likes

Thank you!

For the record, this is a working example:

performanceQuirk :: MonadWidget t m => m ()
performanceQuirk = divClass "flex flex-col gap-2" $ mdo
  (heavyButton, _) <- elAttr' "button" ("class" =: "btn btn-primary") $ text "Heavy Computation"

  let heavyClick = Loading <$ domEvent Click heavyButton

  heavyComputationFinished <- performEventAsync $
    ffor heavyClick $ \_ callback -> do
      liftIO . void . async $ do
        veryHeavyComputation
          >>= callback . Computed

  let stateUpdated = leftmost [heavyClick, heavyComputationFinished, quickClick]

  stateD <- holdDyn Initial stateUpdated

  (quickButton, _) <- elAttr' "button" ("class" =: "btn btn-primary") $ text "Instant Computation"

  let quickClick = Computed (quickComputation "123") <$ domEvent Click quickButton

  divClass "alert" $
    dyn_ $
      ffor stateD $ \case
        Initial -> text "Initial"
        Loading -> divClass "loading loading-spinner loading-sm" blank
        Computed x -> text $ "Computed " <> tshow x

veryHeavyComputation :: IO Text
veryHeavyComputation = do
  threadDelay $ 1000 * 1000
  pure "Heavy Computation"

quickComputation :: Text -> Text
quickComputation t = do
  "Quick Computation: " <> t

data PerformanceTestState
  = Initial
  | Loading
  | Computed Text
2 Likes

I was replying in a rush; thanks for filling in the details.