thomashoneyman/purescript-halogen-hooks

Sequential state updates don't cause hook re-execution.

frabbit opened this issue · 15 comments

Hi @thomashoneyman,

first of all thx for this great project, it's really nice to have hooks for halogen.

It seems that I ran into a huge problem with sequential state updates. It seems that a hook is only interpreted once, this is a problem if you have state updates which are triggered by state updates. The following code demonstrates the problem (sorry if it's too much noise):

module Halogen.Hooks.Conditional where

import Prelude

import Data.Maybe (Maybe(..))
import Data.Newtype (class Newtype)
import Data.Tuple.Nested ((/\), type (/\))
import Effect.Aff (Milliseconds(..), delay)
import Effect.Aff.Class (class MonadAff, liftAff)
import Effect.Class (liftEffect)
import Effect.Class.Console (log)
import Effect.Random (randomInt)
import Effect.Unsafe (unsafePerformEffect)
import Halogen (Component)
import Halogen.HTML as HH
import Halogen.HTML.Events as HE
import Halogen.Hooks (Hook, UseEffect, UseState, useLifecycleEffect)
import Halogen.Hooks as Hooks

newtype UseConditional hooks = UseConditional (UseEffect (UseState (Boolean) hooks))
derive instance newtypeUseConditional :: Newtype (UseConditional hooks) _

useConditional :: forall slots output m . MonadAff m => Boolean -> Hook slots output m UseConditional (Boolean)
useConditional opt = Hooks.wrap Hooks.do
  -- unique id to understand which hook execution is called by useEffect
  id <- Hooks.pure $ show $ unsafePerformEffect $ randomInt 0 10000
  Hooks.pure $ unsafePerformEffect $ liftEffect $ log $ "runConditional(" <> id <> "): " <> (show opt)
  state /\ stateToken <- Hooks.useState false
  useMyEffect stateToken id state { opt }
  Hooks.pure state
  where
    useMyEffect stateToken id state deps@{ opt : opt' } = Hooks.captures deps Hooks.useTickEffect do
      liftEffect $ log $ "CHANGE HANDLER TRIGGERED(" <> id <> "): " <> (show deps) <> ": " <> (show state) <> ":" <> (show opt')
      Hooks.put stateToken opt'
      pure Nothing

newtype UseConditionalTest hooks = UseConditionalTest (UseConditional (UseEffect (UseState (Boolean) hooks)))
derive instance newtypeUseConditionalTest :: Newtype (UseConditionalTest hooks) _

useConditionalTest :: forall slots output m . MonadAff m => Hook slots output m UseConditionalTest (Boolean)
useConditionalTest = Hooks.wrap Hooks.do
  state /\ stateToken <- Hooks.useState false
  useLifecycleEffect do
    Hooks.put stateToken true
    pure Nothing
  val <- useConditional state
  Hooks.pure val

component :: forall query input output m. MonadAff m => Component HTML query input output m
component = Hooks.component $ \_ -> Hooks.do
  count /\ countToken <- Hooks.useState 0
  val <- useConditionalTest
  Hooks.pure do
    HH.div_
      [
        HH.text $ "count: " <> (show count)
      , HH.br_
      , HH.text $ "val: " <> (show val)
      , HH.br_
      , HH.button [HE.onClick (\_ -> handleClick countToken count)] [HH.text "trigger count change" ]
      ]

  where
    handleClick countToken count = Just do
      Hooks.put countToken (count + 1)

The problem is that the effect handler in useConditional is not updated and not called a second time after the input variable opt has changed. Clicking the trigger count change button forces the execution of the lost call.

I was able to fix this issue by changing the runUseHookFn inside of component to

runUseHookFn
  :: forall hooks q i ps o m
   . InterpretHookReason
  -> (i -> Hooked ps o m Unit hooks (H.ComponentHTML (HookM ps o m Unit) ps m))
  -> H.HalogenM (HookState q i ps o m) (HookM ps o m Unit) ps o m Unit
runUseHookFn reason hookFn = do
  interpretUseHookFn reason hookFn
  { evalQueue } <- getState
  sequence_ evalQueue
  modifyState_ _ { evalQueue = [] }

  -- Consider state updates triggered by state updates
  repeat reason evalQueue
  where
  repeat Finalize evalQueue = pure unit
  repeat Queued evalQueue = pure unit -- not sure about this one, maybe this should be recursive too 
  repeat _ evalQueue = do -- don't call Initialize twice
    if (Array.length evalQueue) > 0 then runUseHookFn Step hookFn else pure unit

I was really just digging around in the source, so i have no idea if this is a good solution and what side effects it causes. But it triggers the interpretation of the current hook as long as the interpretation generates new items in evalQueue. I have no idea if this is too expensive, maybe there is a smarter way to do this.

Regarding the repeated hook execution in general, i think that react hooks work in a similar way.

This is the output before the change to runUseHookFn:

runConditional(3080): false
runConditional(653): true
CHANGE HANDLER TRIGGERED(3080): { opt: false }: false:false
runConditional(6754): true

This is the output after the change to runUseHookFn:

runConditional(5513): false
runConditional(434): true
CHANGE HANDLER TRIGGERED(5513): { opt: false }: false:false
runConditional(3605): true
runConditional(6510): true
CHANGE HANDLER TRIGGERED(6510): { opt: true }: false:true
runConditional(6724): true
runConditional(1650): true

@frabbit Putting this into my own words, let me redescribe your problem to ensure I'm understanding your question.

First, you have a useConditional hook that will trigger some handler (e.g. logging content to the console) when the argument passed into that hook (i.e. opt) changes. Since that hook uses the useTickEffect internally, it will always run the handler for the first time.

Second, your are are using useConditionalTest to attempt to trigger that handler function a second time (and every time thereafter) by

  1. using a state value that gets passed into the useConditional hook
  2. immediately changing the state value after the useState hook but before the useLifecycleEffect hook

The problem is that the useLifecycleEffect hook inside the useConditionalTest hook does not trigger the "useConditional's 'log to console'" handler a second time. You have found that clicking on the button will cause it to trigger find, but that's not what you're trying to do. While you could use runHookFn, you are hoping for something cleaner.

Here's my question. Does this 'bug' go away if you reorder your hooks, so that the useLifecycleEffect hook runs after the useConditional hook in your definition for useConditionalTest? In other words, reimplementing it like so:

useConditionalTest :: forall slots output m . MonadAff m => Hook slots output m UseConditionalTest (Boolean)
useConditionalTest = Hooks.wrap Hooks.do
  state /\ stateToken <- Hooks.useState false

  -- run the `useConditional` hook 
  -- before the `useLifecycleEffect hook
  val <- useConditional state
  useLifecycleEffect do
    Hooks.put stateToken true
    pure Nothing
  Hooks.pure val

Hey @JordanMartinez ,

actually it's the other way around. The second hook should do something based on a condition. A more real world example would be something like this:

do
  maybeConfig <- useLoadConfig "http://myapp/config.json"
  appData <- useLoadApplicationData maybeConfig

the second hook should load the application data only when config is a Just. That's what i mean with sequential or dependent state updates.

This is a corresponding react example: https://stackblitz.com/edit/react-ze3hnw

@frabbit Thanks for catching this!

I took a brief review of the code. The relevant sections include evalHookM, which interprets HookM code into HalogenM, and interpretUseHookFn, which evaluates the hooks.

The function to evaluate hooks is passed to evalHookM as an argument, called runHooks, and this function is called after any state update:

interpretHalogenHook :: HookF ps o m ~> H.HalogenM (HookState q i ps o m) (HookM ps o m Unit) ps o m
interpretHalogenHook = case _ of
Modify (StateToken token) f reply -> do
state <- getState
let v = f (unsafeGetCell token state.stateCells.queue)
putState $ state { stateCells { queue = unsafeSetCell token v state.stateCells.queue } }
runHooks
pure (reply v)

Because of this runHooks argument (which is the interpretUseHookFn function applied to some arguments of its own), Hooks will be re-evaluated after every state update. For example, this code will evaluate useState twice on click:

Hooks.do
  state /\ stateToken <- useState 0
  let onClick = Hooks.modify_ stateToken (_ + 5) *> Hooks.modify_ stateToken (_ + 10)
  Hooks.pure $ HH.div [ HE.onClick \_ -> Just onClick ] [ HH.text $ show state ]

However, there's a catch: evaluating an effect hook is not the same as executing the effect it contains. Instead, when you evaluate an effect hook, the effect it describes is put into a queue, and only after all the hooks have been evaluated does this queue get executed.

You can see that in action by looking at interpretUseHookFn, specifically where it reaches the UseEffect constructor:

UseEffect mbMemos act a -> do
case reason of
Initialize -> do
for_ mbMemos \memos -> do
modifyState_ \st ->
st { effectCells { queue = Array.snoc st.effectCells.queue memos } }
let
eval = do
mbFinalizer <- evalHookM (interpretUseHookFn Queued hookFn) act
for_ mbFinalizer \finalizer ->
modifyState_ \st ->
st { finalizerQueue = Array.snoc st.finalizerQueue finalizer }
modifyState_ \st -> st { evalQueue = Array.snoc st.evalQueue eval }
Queued ->
pure unit
Step -> do
for_ mbMemos \memos -> do
{ effectCells: { index, queue } } <- getState
let
newQueue = unsafeSetCell index memos queue
nextIndex = if index + 1 < Array.length queue then index + 1 else 0
memos' :: { old :: MemoValuesImpl, new :: MemoValuesImpl }
memos' =
{ old: fromMemoValues (unsafeGetCell index queue)
, new: fromMemoValues memos
}
modifyState_ _ { effectCells = { index: nextIndex, queue: newQueue } }
when (Object.isEmpty memos'.new.memos || not memos'.new.eq memos'.old.memos memos'.new.memos) do
let eval = void $ evalHookM (interpretUseHookFn Queued hookFn) act
modifyState_ \st -> st { evalQueue = Array.snoc st.evalQueue eval }

So to summarize what happens when Hooks are evaluated:

  1. interpretUseHookFn is called, which evaluates all the hooks. This may be triggered by an event like initialization, or by the function being called directly (as evalHookM does).
  2. Hooks are interpreted one at a time, each time updating some internal state and (possibly) returning some value, which the user will see. For example, useState will return the current value in state to the user. use*Effect doesn't return anything to the user; it only updates internal Hook state by adding the effect to evalQueue.
  3. interpretUseHookFn completes, so hook evaluation is over. Now, evalQueue runs, performing all the effects that need to happen on this render.

The problem you noticed is that the effects in evalQueue may themselves update state, which should cause the effects to run again. But instead they just run once.

This struck me as odd because we do call runHooks after any state update, in evalHookM. So why aren't effects re-run?

I think the problem is this line:

let eval = void $ evalHookM (interpretUseHookFn Queued hookFn) act

it provides a runHooks function to evalHookM that will not re-run effects. So if a state update happens in an effect written in useLifecycleEffect or useTickEffect, then these effects won't be re-run after the state update.

You mentioned updating runUseHookFn as a possibility, but I don't think that's quite correct. What if effects are added to the queue which don't perform state updates? That shouldn't re-trigger anything. It should strictly be done on state updates, in evalHookM, via the interpretUseHookFn function.

This is definitely a bug, and thank you @frabbit for catching it!

I'll need to test updating that line to make sure it doesn't introduce any undesirable behavior, but I believe that should fix this issue.

I'm pretty sure this issue is actually preventing my useEvent implementation that now allows unsubscriptions from working.

Given the below code...

component :: H.Component HH.HTML (Const Void) Unit Unit Aff
component = Hooks.component \_ -> Hooks.do
  state /\ tState <- useState 0

  Hooks.captures { state } useTickEffect do
    liftEffect $ log $ "run tick effect"
    pure $ Just do
      liftEffect $ log $ "clean up tick effect"

  Hooks.pure $
    HH.div_
      [ HH.button
        [ HE.onClick \_ -> Just do
          Hooks.modify_ tState \s -> s + 1
        ]
        [ HH.text "Click to change the state value, which will trigger \
                  \the useTickEffect."
        ]
      ]

... shouldn't the console's output look like this if I click the button 3 times?

-- initial run
run tick effect
-- 1st click
clean up tick effect
run tick effect
-- 2nd click
clean up tick effect
run tick effect
-- 3rd click
clean up tick effect
run tick effect
-- when component is disposed of
clean up tick effect

@JordanMartinez yes, that's right, that's the behavior you should see. I will finally have some time open in my schedule tomorrow to work on this, and I'm anticipating putting up a fix for you and @frabbit to take a look at by tomorrow night. Thanks for the small example!

In your case, the effect is being run on every tick, but the finalizer is not; this is separate but related to @frabbit's issue.

You mentioned updating runUseHookFn as a possibility, but I don't think that's quite correct. What if effects are added to the queue which don't perform state updates? That shouldn't re-trigger anything. It should strictly be done on state updates, in evalHookM, via the interpretUseHookFn function.

I'll need to test updating that line to make sure it doesn't introduce any undesirable behavior, but I believe that should fix this issue.

Using the work I did in #12, I tried changing interpretUseHookFn to runUseHookFn and it produces an infinite loop.

I think I've figured this out. Thomas might have a better idea as to WHY the above infinite loop occurs.

I would guess that runUseHookFn is the correct step to take, but the bug is caused by how that function is implemented:

{ evalQueue } <- getState
  sequence_ evalQueue
  modifyState_ _ { evalQueue = [] }

In this situation, we don't clear out the evalQueue until after all of its effects have been run. However, what happens if one of those effects is to call runHookFn? Then you'll get an infinite loop. So, I tried clearing out the eval queue before running the effects:

{ evalQueue } <- getState
  modifyState_ _ { evalQueue = [] }
  sequence_ evalQueue

That stops the infinite loop I was getting initially (again, I'm using the code from #12), but it still doesn't fix the problem. So, I think the fix is:

  • find all places where the code is used like that and update it to clear the evalQueue before running its effects
  • use @frabbit's "loop until no more evals exist" idea in its implementation somewhere.

Quick update on this: I want to make sure this issue can be understood, resolved, and not re-introduced. With that in mind I've been putting together tests that capture this problem, so you can write a spec like this:

stateHook :: Spec Unit
stateHook = describe "useState" do
  it "initializes to the proper initial state value" do
    ref <- initDriver

    Tuple { count } events <- evalTestM ref $ runWriterT do
      evalTestHook Initialize useStateCount

    -- The state should properly initialize
    count `shouldEqual` 0
    events `shouldEqual` [ RunHooks Initialize, Render ]

  it "updates state" do
    ref <- initDriver

    Tuple count events <- evalTestM ref $ runWriterT do
      { increment } <- evalTestHook Initialize useStateCount

      let runHooks = void $ evalTestHook Step useStateCount

      -- increment twice
      evalTestHookM runHooks increment *> evalTestHookM runHooks increment

      { count } <- evalTestHook Finalize useStateCount
      pure count

    -- The final state of the Hook should reflect the number of times it has
    -- been incremented.
    count `shouldEqual` 2
    events `shouldEqual`
      [ -- initializer
        RunHooks Initialize
      , Render

        -- state updates x2
      , ModifyState
      , RunHooks Step
      , Render
      , ModifyState
      , RunHooks Step
      , Render

        -- finalizer
      , RunHooks Finalize
      ]

which I can add to continuous integration for this repository to verify further internal improvements and tweaks succeed. Ideally some of this can be transformed into property tests as well.

I've added a failing useLifecycleEffect test to cover the issue you reported in this ticket, @frabbit, but I haven't yet had time to implement and test fixes. Working on it, though!

@frabbit I took your code and inlined all the hooks to get this:

module Test.Manual.Conditional where

import Prelude

import Data.Maybe (Maybe(..))
import Data.Newtype (class Newtype)
import Data.Tuple.Nested ((/\), type (/\))
import Effect (Effect)
import Effect.Aff (Milliseconds(..), delay)
import Effect.Aff.Class (class MonadAff, liftAff)
import Effect.Class (liftEffect)
import Effect.Class.Console (log)
import Effect.Random (randomInt)
import Effect.Unsafe (unsafePerformEffect)
import Halogen (Component)
import Halogen.Aff (awaitBody, runHalogenAff)
import Halogen.HTML as HH
import Halogen.HTML.Events as HE
import Halogen.Hooks (Hook, UseEffect, UseState, useLifecycleEffect)
import Halogen.Hooks as Hooks
import Halogen.VDom.Driver (runUI)

main :: Effect Unit
main = runHalogenAff do
  body <- awaitBody
  runUI component unit body

component :: forall query input output m. MonadAff m => Component HH.HTML query input output m
component = Hooks.component $ \_ -> Hooks.do
  count /\ countToken <- Hooks.useState 0
  state1 /\ stateToken1 <- Hooks.useState false
  useLifecycleEffect do
    Hooks.put stateToken1 true
    pure Nothing
  -- unique id to understand which hook execution is called by useEffect
  id <- Hooks.pure $ show $ unsafePerformEffect $ randomInt 0 10000
  Hooks.pure $ unsafePerformEffect $ liftEffect $ log $ "runConditional(" <> id <> "): " <> (show state1)
  state2 /\ stateToken2 <- Hooks.useState false
  useMyEffect stateToken2 id state2 { state1 }
  Hooks.pure do
    HH.div_
      [
        HH.text $ "count: " <> (show count)
      , HH.br_
      , HH.text $ "val: " <> (show state2)
      , HH.br_
      , HH.button [HE.onClick (\_ -> handleClick countToken count)] [HH.text "trigger count change" ]
      ]

  where
    useMyEffect stateToken2 id state2 deps@{ state1 : state1' } = Hooks.captures deps Hooks.useTickEffect do
      liftEffect $ log $ "CHANGE HANDLER TRIGGERED(" <> id <> "): " <> (show deps) <> ": " <> (show state2) <> ":" <> (show state1')
      Hooks.put stateToken2 state1'
      pure Nothing

    handleClick countToken count = Just do
      Hooks.put countToken (count + 1)

Now, if we follow the logic behind this code, I believe we'll see why this bug occurs:

  1. count and state1 are initialized
  2. the lifecycle effect is enqueued in evalQueue
  3. state2 is initialized
  4. the tick effect is enqueued in evalQueue
  5. now that all hooks have been interpreted, we run the effects in the evalQueue. The lifecycle effect gets run, which reevaluates all hooks.
    1. count remains unchanged
    2. state1 gets changed
    3. lifecycle effect is not rerun
    4. state2 is unchanged
    5. tick effect's finalizer effect and normal effect are both NOT enqueued because the interpret reason was Queued, not Step.
  6. the tick effect gets run for the first time, which prints the initial 'change handler triggered' message

We expect a step 7 where the tick effect runs its finalizer (if any) and its normal effects since the dependencies were changed in step 5. These effects should have been enqueued in step 5.5, but weren't.

So, why weren't they enqueued? It's because the Initialize step for a lifecycle effect re-runs the hooks via the Queued reason. Thus, when we get to the tick effect, it does nothing. So, theoretically, if we changed this reason to Step, it should work, right?

Wrong. In this situation, the tick effect hasn't been initialized yet. Therefore, the effectCells queue does not have any mbMemos /\ finalizer elements yet. So, if we did use Step there, we would get a runtime error due to calling unsafeGetCell index effectCells.queue, which will return undefined.

So, I think the issue is that we are not enqueueing another Step interpretation, which would cause the hook to recheck its memos. However, I just tried something like that and it's still not working.

It's also way too late and my brain is fumbling at this point.

I believe I've figured out a fix to this bug. See this commit. I get the same output that @frabbit expected above when he used runUseHookFn. I'll submit a PR shortly so it's easier to see what I did in full.

However, this fix raises another question. If the finalizer for a useTickEffect (A) modifies state that is the dependency for another useTickEffect (B). How should the effects be run?

  1. A finalizer
  2. A initializer
  3. B finalizer
  4. B initializer

Or

  1. A finalizer
  2. B finalizer
  3. B initializer
  4. A initializer

The fix I linked above does the first approach, but I'm guessing we will want the second one...?

I think it's acceptable that an effect's cleanup and re-run be considered a unit -- a cycle that is performed after each render. Which is to say that for any render after the initial render the pair of effect cleanup, effect body should be considered one; if the cleanup happens to affect the memo of another effect, that effect can be evaluated once the first effect's body evaluates again.

We also don't want to render in between cleaning up an effect from a previous render and re-running it for the current render.

With that in mind, this sequence of events is fine:

  1. A cleanup (changes memo of B), body
  2. (because memo changed) B cleanup, body

@frabbit This was fixed in #20 and is available in release 0.2.0

@thomashoneyman @JordanMartinez thx a lot, i will give it a try when i'm back on my side project.