Skip to content

Instantly share code, notes, and snippets.

@ali-abrar
Created July 28, 2015 19:01
Show Gist options
  • Save ali-abrar/ac0604f5a458e48aee62 to your computer and use it in GitHub Desktop.
Save ali-abrar/ac0604f5a458e48aee62 to your computer and use it in GitHub Desktop.
SO 30885883 - Why does this Reflex code result in Dynamics firing indefinitely with the same value?
-- http://stackoverflow.com/questions/30885883/why-does-this-reflex-code-result-in-dynamics-firing-indefinitely-with-the-same-v
{-# LANGUAGE RecursiveDo, ScopedTypeVariables #-}
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
:: 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)
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)
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment