为什么此 Reflex 代码会导致 Dynamics 以相同的值无限期地触发?

Why does this Reflex code result in Dynamics firing indefinitely with the same value?

这个小程序的目的是显示三个按钮,第三个按钮的标签最初是“0”,之后是最后点击按钮的索引。目前按钮的数量和其他按钮的标签是不变的。

当我用 ghcjs 编译这个自包含文件并在浏览器中加载 Main.jsexe/index.html 时,我可以看到两个 traceDyns 在循环中触发,两者总是有值0. 据我所知,在单击按钮之前不会发生任何事情,因为 _el_clicked 为系统的其余部分提供信息。

此外,请注意我使用 mapDyn (fst . head . Map.toList) 来提取所选按钮的索引 - 我不确定这是正确的,但无论哪种方式我都不知道是什么原因导致无限循环。

{-# LANGUAGE RecursiveDo #-}

module Main where

import Reflex
import Reflex.Dom

import qualified Data.Map as Map

dynButton
  :: MonadWidget t m
  => Dynamic t String
  -> m (Event t ())
dynButton s = do
  (e, _) <- el' "button" $ dynText s
  return $ _el_clicked e

-- widget that takes dynamic list of strings
-- and displays a button for each, returning
-- an event of chosen button's index
listChoiceWidget
  :: MonadWidget t m
  => Dynamic t [String]
  -> m (Event t Int)
listChoiceWidget choices = el "div" $ do
  asMap <- mapDyn (Map.fromList . zip [(0::Int)..]) choices
  evs <- listWithKey asMap (\_ s -> dynButton s)
  k <- mapDyn (fst . head . Map.toList) evs
  return $ updated (traceDyn "k" k)

options :: MonadWidget t m => Dynamic t Int -> m (Dynamic t [String])
options foo = do
  mapDyn (\x -> ["a", "b", show x]) foo

main :: IO ()
main = mainWidget $ el "div" $ do
  rec n <- listChoiceWidget o
      o <- options foo
      foo <- holdDyn 0 n
  display (traceDyn "foo" foo)

您的 listChoiceWidget 代码似乎丢弃了由 dynButton 构造的点击事件。

listWithKeyreturnsm (Dynamic t (Map k a))。在您的例子中,键的类型为 Int,值为 Event t ()(由 dynButton 生成)。

这一行:

k <- mapDyn (fst . head . Map.toList) evs

您正在将 Dynamic t (Map Int (Event t ())) 变成 Dynamic t Int,但至关重要的是,当点击事件触发时您并没有这样做。此行映射到 evs 并生成一个 Dynamic,它始终包含 Ints 到 Events 映射中的第一个键,无论事件是否已触发。它将始终是包含 Int 0 的 Dynamic。

您看到循环的原因是:

  1. main 将初始值为 0 的 foo 送入 options
  2. 构建了新的选项
  3. listChoiceWidget 收到新选项并更新列表
  4. 生成的事件整数映射的第一个键已更新
  5. foolistChoiceWidget
  6. 接收密钥更新事件
  7. 返回第 2 步无限循环

您需要某种方法来确定最后一个按钮单击事件,而不是从 Map 中检索第一个键。您的地图已包含显示的每个按钮的点击事件。现在这些事件的类型是 Event t (),但您真正需要的是 Event t Int,这样当事件触发时您可以知道它来自哪个按钮。

evs' <- mapDyn (Map.mapWithKey (\k e -> fmap (const k) e)) evs

evs' 具有类型 Dynamic t (Map Int (Event t Int))。接下来我们需要一些方法来组合我们的事件,以便我们有一个事件会随着最近单击的按钮的键而触发。

dynEv <- mapDyn (leftmost . Map.elems . Map.mapWithKey (\k e -> fmap (const k) e)) evs

dynEv 现在的类型是 Dynamic t (Event t Int)。 Map 的键已经被烘焙到事件中,所以我们不再需要它们了。 Map.elems 将我们的事件地图变成事件列表,leftmost 允许您将事件列表合并为一个事件。

来自 docsleftmost:"Create a new Event that occurs if at least one of the Events in the list occurs. If multiple occur at the same time they are folded from the left with the given function."

最后,我们需要将您的 Dynamic t (Event t Int) 转换为 Event t Int。我们将使用 switch,它需要一个 Behavior t (Event t a) 和 returns 一个 Event t a。因此,下一行将导致 Event t Int.

switch (current dynEv)

current 提取 DynamicBehaviorswitch 创建 "an Event that will occur whenever the currently-selected input Event occurs."

这是修改后的 listChoiceWidget 代码。我已经包含了内联类型注释,因此您需要启用 ScopedTypeVariables 语言扩展来编译此代码(或者您可以删除注释)。

listChoiceWidget
  :: forall t m. MonadWidget t m
  => Dynamic t [String]
  -> m (Event t Int)
listChoiceWidget choices = el "div" $ do
  asMap <- mapDyn (Map.fromList . zip [(0::Int)..]) choices
  evs :: Dynamic t (Map.Map Int (Event t ())) <- listWithKey asMap (\_ s -> dynButton s)
  dynEv :: Dynamic t (Event t Int) <- mapDyn (leftmost . Map.elems . Map.mapWithKey (\k e -> fmap (const k) e)) evs
  return $ switch (current dynEv)

Here's a gist of the complete file.