How to force React Hooks re-render a JSX?

I have a modal dialog that allows to “edit” something from the parent component. Now, I want this “something” to always be fetched from the parent component. This seems to be a no-brainer, because when parent changes data, that causes the modal to re-render with new data.

But the real problem is when the parent wasn’t changed, and a user modified some data, then dismissed the dialog. In this case the dialog caches the modified data, so the next time it pops up, the modified data is shown instead of the actual data from the parent.

So, how to can I make sure that every time a modal window pops up it’s re-rendered anew?

Steps to reproduce

  1. Given this src/Main.purs that just implements a modal dialog with a <textarea>

    module Main where
    
    import Prelude
    
    import Data.Maybe (Maybe(..))
    import Data.Nullable (Nullable, null)
    import Effect (Effect)
    import Effect.Class.Console (log)
    import Effect.Exception (throw)
    import Effect.Uncurried (runEffectFn1)
    import React.Basic.DOM (css)
    import React.Basic.DOM as R
    import React.Basic.DOM.Client (createRoot, renderRoot)
    import React.Basic.DOM.Events as RE
    import React.Basic.Events as RE
    import React.Basic.Hooks (Component, JSX, Ref, component, readRefMaybe)
    import React.Basic.Hooks as React
    import Unsafe.Coerce (unsafeCoerce)
    import Web.DOM.Internal.Types (Node)
    import Web.DOM.NonElementParentNode (getElementById)
    import Web.Event.Event (Event)
    import Web.HTML (window)
    import Web.HTML.HTMLDocument (toNonElementParentNode)
    import Web.HTML.Window (document)
    import FFI (closeDialogIfItsTarget, showModal)
    
    type RefNode = Ref (Nullable Node)
    
    main :: Effect Unit
    main = do
      doc <- document =<< window
      root <- getElementById "root" $ toNonElementParentNode doc
      case root of
        Nothing -> throw "Could not find root."
        Just container -> do
          reactRoot <- createRoot container
          app <- mkApp
          renderRoot reactRoot (app {})
    
    mkApp :: Component {}
    mkApp = do
      component "Test" \_ -> React.do
        modalRef :: RefNode <- React.useRef null
        pure $
          R.div_ [ modalDialog modalRef [R.textarea {defaultValue: "hello!"}]
                 , R.button { onClick: RE.handler_ $ applyToReactRef modalRef showModal
                            , children: [R.text "Launch modal"]}
                 ]
    
    applyToReactRef :: RefNode -> (Node -> Effect Unit) -> Effect Unit
    applyToReactRef mbRef f = readRefMaybe mbRef >>= case _ of
            Nothing -> log "Error: null node"
            Just ref -> f ref
    
    modalDialog :: RefNode -> Array JSX -> JSX
    modalDialog dialogRef children =
      let
        closeOnClick :: Event -> Effect Unit
        closeOnClick ev = applyToReactRef dialogRef (closeDialogIfItsTarget ev)
      -- The oddness with styles is to make sure that clicking outside the dialog will
      -- close it. Source
      -- https://stackoverflow.com/questions/25864259/how-to-close-the-new-html-dialog-tag-by-clicking-on-its-backdrop
      in
       R.dialog { style: css {padding: "0"}
                , onClick: RE.handler RE.nativeEvent closeOnClick
                , ref: dialogRef
                , children:
                  [ R.form
                    { style: css {padding: "1rem"}
                    , method: "dialog"
                    , children
                    }
                  ]
                }
    

    and this FFI.purs

    module FFI where
    
    import Prelude
    import Effect (Effect)
    import Web.DOM.Node (Node)
    import Web.Event.Event (Event)
    
    foreign import showModal :: Node -> Effect Unit
    foreign import closeDialogIfItsTarget :: Event -> Node -> Effect Unit
    

    and FFI.js

    export const closeDialogIfItsTarget = function(mouseEvent) {
        return function (dialogRef) {
            return function () {
                if (mouseEvent.target === dialogRef)
                    dialogRef.close();
            }
        };
    };
    
    export const showModal = function(dialogRef) {
        return function () {
            dialogRef.showModal();
        };
    };
    
  2. Compile the code and open the modal by clicking the button

  3. Change the text in the text area

  4. Dismiss the dialog

  5. Re-open the dialog again

Expected

The textarea should contain original text hello!

Actual

The textarea would contain whatever text you changed

1 Like

You could reset the <form> whenever the <dialog> closes. Something like this

module App where

import Prelude

import Data.Maybe (Maybe(..))
import Data.Nullable as Nullable
import Effect (Effect)
import React.Basic.DOM as DOM
import React.Basic.Events as Events
import React.Basic.Hooks (Component)
import React.Basic.Hooks as Hooks
import Web.DOM (Node)
import Web.DOM.Node as Node
import Web.Event.EventTarget as EventTarget
import Web.HTML.Event.EventTypes as EventTypes
import Web.HTML.HTMLFormElement as HTMLFormElement

foreign import showModal :: Node -> Effect Unit

mkApp :: Component Unit
mkApp = do
  Hooks.component "App" \_ -> Hooks.do
    dialogRef <- Hooks.useRef Nullable.null
    formRef <- Hooks.useRef Nullable.null

    let
      handleOpenDialog = Events.handler_ do
        maybeDialog <- Hooks.readRefMaybe dialogRef
        case maybeDialog of
          Just dialog -> showModal dialog
          Nothing -> mempty

    Hooks.useEffectOnce do
      maybeDialog <- Hooks.readRefMaybe dialogRef
      case maybeDialog of
        Just dialog -> do
          let eventTarget = Node.toEventTarget dialog
          listener <-
            EventTarget.eventListener \_ -> do
              maybeForm <- Hooks.readRefMaybe formRef
              case maybeForm >>= HTMLFormElement.fromNode of
                Just form -> HTMLFormElement.reset form
                Nothing -> mempty

          EventTarget.addEventListener EventTypes.close listener true eventTarget
          pure (EventTarget.removeEventListener EventTypes.close listener true eventTarget)

        Nothing -> mempty

    pure
      ( DOM.div_
          [ DOM.button
              { onClick: handleOpenDialog
              , children: [ DOM.text "Open dialog" ]
              }
          , DOM.dialog
              { ref: dialogRef
              , children:
                  [ DOM.form
                      { ref: formRef
                      , children:
                          [ DOM.textarea_ []
                          , DOM.button
                              { formMethod: "dialog"
                              , children: [ DOM.text "Submit" ]
                              }
                          ]
                      }
                  ]
              }
          ]
      )

If you wanted the close handler to be in FFI, as in your original snippet, then you could pass the formRef through there instead.

2 Likes

I see, so, like, using a form and resetting it explicitly. Thank you

1 Like

I just noticed, it also seems like the React lib forgot to implement onClose event (which is why I guess you’re using this “addEventListener”). I sent a fix

So, while the PR adding the onClick event wasn’t merged, I tried your code with EventTarget and co, but found it too involved and complicated. There’s lots of code in useEffectOnce that may be avoided. (I also presume it should be useEffect, because the …Once version would be executed just once, and when it will happen the dialogRef wasn’t assigned yet, so the mempty branch should get executed instead of the assignment).

Instead I figured it’s way simpler to re-declare dialog creation with the onClose event added, like:

-- A `dialog` JSX that allows to pass onClose field that is missing in the React
-- dialog. A fix was sent
-- https://github.com/purescript-react/purescript-react-basic-dom/pull/55
dialogRaw :: ∀ attrs. Record attrs -> JSX
dialogRaw = React.element (unsafeCoerce (unsafePerformEffect (R.unsafeCreateDOMComponent "dialog")))

Full implementation for the original code (barring the reset FFI):

module Main where

import Prelude

import Data.Maybe (Maybe(..))
import Data.Nullable (Nullable, null)
import Data.Tuple (Tuple(..))
import Data.Tuple.Nested ((/\))
import Effect (Effect)
import Effect.Class.Console (log)
import Effect.Exception (throw)
import Effect.Unsafe (unsafePerformEffect)
import FFI (closeDialogIfItsTarget, showModal, formReset)
import React.Basic.DOM (css)
import React.Basic.DOM as R
import React.Basic.DOM.Client (createRoot, renderRoot)
import React.Basic.DOM.Events as RE
import React.Basic.Events as RE
import React.Basic.Hooks (Component, JSX, Ref, component, readRefMaybe)
import React.Basic.Hooks as React
import Unsafe.Coerce (unsafeCoerce)
import Web.DOM.Internal.Types (Node)
import Web.DOM.NonElementParentNode (getElementById)
import Web.Event.Event (Event)
import Web.HTML (window)
import Web.HTML.HTMLDocument (toNonElementParentNode)
import Web.HTML.Window (document)

type RefNode = Ref (Nullable Node)

-- A `dialog` JSX that allows to pass fields that are missing in the React dialog
dialogRaw :: ∀ attrs. Record attrs -> JSX
dialogRaw = React.element (unsafeCoerce (unsafePerformEffect (R.unsafeCreateDOMComponent "dialog")))

main :: Effect Unit
main = do
  doc <- document =<< window
  root <- getElementById "root" $ toNonElementParentNode doc
  case root of
    Nothing -> throw "Could not find root."
    Just container -> do
      reactRoot <- createRoot container
      app <- mkApp
      renderRoot reactRoot (app {})

mkApp :: Component {}
mkApp = do
  modalDialog <- mkModalDialog
  component "Test" \_ -> React.do
    modalRef :: RefNode <- React.useRef null
    pure $
      R.div_ [ modalDialog $ modalRef /\ [R.textarea {defaultValue: "hello!"}]
             , R.button { onClick: RE.handler_ $ applyToReactRef modalRef showModal
                        , children: [R.text "Launch modal"]}
             ]

applyToReactRef :: RefNode -> (Node -> Effect Unit) -> Effect Unit
applyToReactRef mbRef f = readRefMaybe mbRef >>= case _ of
        Nothing -> log "Error: null node"
        Just ref -> f ref

-- | A dialog window. NOTE: this dialog impelemnts a form, and you're not allowed to
-- | embed a form into a form.
mkModalDialog :: React.Component (Tuple RefNode (Array JSX))
mkModalDialog =
  React.component "modalDialog" \(Tuple dialogRef children) -> React.do
    formRef :: RefNode <- React.useRef null
    let
      closeOnClick :: Event -> Effect Unit
      closeOnClick = applyToReactRef dialogRef <<< closeDialogIfItsTarget
      resetFormOnClose :: Effect Unit
      resetFormOnClose = applyToReactRef formRef formReset
    -- The oddness with styles is to make sure that clicking outside the dialog will
    -- close it. Source
    -- https://stackoverflow.com/questions/25864259/how-to-close-the-new-html-dialog-tag-by-clicking-on-its-backdrop
    -- TODO: paths handling has to be separated to its own component for better modal
    -- dialog reuse and logic incapsulation
    pure $
     dialogRaw { style: css {padding: "0"}
               , onClick: RE.handler RE.nativeEvent closeOnClick
               , onClose: RE.handler_ resetFormOnClose
               , ref: dialogRef
               , children:
                 [ R.form
                   { style: css {padding: "1rem"}
                   , method: "dialog"
                   , children
                   , ref: formRef
                   }
                 ]
               }

useEffect runs after render, so dialogRef will be assigned. See this simplified example: https://codesandbox.io/p/sandbox/d2jvyc

1 Like