The intent of this small program is to show three buttons, with the third button's label initially being "0" and afterwards being the index of the last-clicked button. For now the number of buttons and the labels of the other buttons are constant.
When I compile this self-contained file with ghcjs and load Main.jsexe/index.html in the browser, I can see the two traceDyns firing in a loop, both always having the value 0. As far as I understand, nothing should happen until a button is clicked, because the _el_clicked feeds the rest of the system.
Also, note that I'm using mapDyn (fst . head . Map.toList)
in order to extract the index of the selected button - I'm not sure this is correct, but either way I don't know what causes the infinite looping.
{-# 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)