Skip to content

Instantly share code, notes, and snippets.

@ali-abrar
Last active October 21, 2015 21:04
Show Gist options
  • Save ali-abrar/879c89b78ce296342664 to your computer and use it in GitHub Desktop.
Save ali-abrar/879c89b78ce296342664 to your computer and use it in GitHub Desktop.
Reflex.Dom List with Removable Elements
{-# LANGUAGE ScopedTypeVariables, RecursiveDo #-}
import Control.Monad
import Reflex.Dom
import qualified Data.Map as Map
import Data.Map (Map)
main :: IO ()
main = mainWidget test
test :: MonadWidget t m => m ()
test = do
let elements = Map.fromList $ zip [0::Int ..] ['a'..'z']
rec rs <- el "ul" $ listHoldWithKey elements removes $ \k v ->
el "li" $ button $ "Remove Node " ++ [v]
removes <- liftM (switch . current) $ mapDyn (leftmost . Map.elems . Map.mapWithKey (\k e -> fmap (const $ Map.singleton k Nothing) e)) rs
return ()
testListWithKey :: forall t m. MonadWidget t m => m ()
testListWithKey = do
let startingElements = Map.fromList $ zip [0::Int ..] ['a'..'z']
rec mapOfEvents :: Dynamic t (Map Int (Event t Int)) <- el "ul" $ listWithKey elements $ \k v -> do
btnClick <- el "li" $ button $ "Remove Node " ++ show k
return $ fmap (const k) btnClick -- Each list element returns Event t Int (where Int is the key)
listOfEvents :: Dynamic t [Event t Int] <- mapDyn Map.elems mapOfEvents -- Turn the Map of events into a list
dynamicMergedEvent :: Dynamic t (Event t Int) <- mapDyn leftmost listOfEvents -- Merge the list of events into a single event. See https://hackage.haskell.org/package/reflex-0.2/candidate/docs/Reflex-Class.html#v:leftmost
let mergedRemoveEvent :: Event t Int = switch (current dynamicMergedEvent) -- This event fires with the Int key of whichever "Remove Node" button you click. See https://hackage.haskell.org/package/reflex-0.2/candidate/docs/Reflex-Class.html#v:switch
elements <- foldDyn (\r es -> Map.delete r es) startingElements mergedRemoveEvent
return ()
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment