Search code examples
haskellthreepenny-gui

Monad: [UI Element] vs [Element]


In the following code sample i tried to create a box with a number of select elements and combine their selection into a list of values using behaviors. (code compiles/runs in ghci with just threepenny-gui)

{-# LANGUAGE RecursiveDo #-}
module Threepenny.Gui where

import Prelude hiding (lookup)
import Control.Monad
import Data.List
import Data.Traversable
import Data.Maybe
import Data.Monoid
import qualified Data.Map as Map
import qualified Data.Set as Set

import qualified Graphics.UI.Threepenny as UI
import Graphics.UI.Threepenny.Core hiding (delete)

{-----------------------------------------------------------------------------
    (#) Reverse function application: flip $
    (#+) Append DOM elements as children to given element: parent #+ children
    (#.) Returns UI Element with CSS class changed to second parameter
------------------------------------------------------------------------------}
gui :: IO ()
gui = startGUI defaultConfig setup

fixedTextarea = UI.textarea # set style [("resize", "none"), ("height", "14px"), ("width", "500px")]

combinedBeh :: MonadIO m => [Element] -> m (Behavior ([Maybe Int]))
combinedBeh sl = sequenceA <$> sequence blist
  where blist  = fmap (stepper Nothing . UI.selectionChange ) sl

selectDivWrong :: UI (Element, Behavior [Maybe Int])
selectDivWrong = do 
  let select options = UI.select 
        # set style [("display","inline-block"), ("width", "150px"), ("margin", "0px 0px 4px 0px")]
        #+ fmap (\x -> UI.option # set UI.text (show x)) options
      selectionList :: [UI Element]
      selectionList = replicate 6 $ select [0, 1, 2, 3, 4, 5]

  selectionList' <- (sequence selectionList :: UI [Element])
  bSelectionList <- combinedBeh selectionList'
  mainBox        <- UI.mkElement "selectDiv"
    # set style [("display","inline-block"), ("background-color", "#333344"),
     ("height", "200px"), ("width", "150px"), ("padding", "1px")] --
    #+ (selectionList) -- unsequenced list of UI elements. The behavior (bSelectionList) should have all the info it needs though(?).
-- why does (#+) not have the same UI info as bSelectionList ?

  return (mainBox, bSelectionList)

selectDivCorrect :: UI (Element, Behavior [Maybe Int])
selectDivCorrect = do 
  let select options = UI.select 
        # set style [("display","inline-block"), ("width", "150px"), ("margin", "0px 0px 4px 0px")]
        #+ fmap (\x -> UI.option # set UI.text (show x)) options
      selectionList :: [UI Element]
      selectionList = replicate 6 $ select [0, 1, 2, 3, 4, 5]

  selectionList' <- (sequence selectionList :: UI [Element])
  bSelectionList <- combinedBeh selectionList'
  mainBox        <- UI.mkElement "selectDiv"
    # set style [("display","inline-block"), ("background-color", "#333344"),
     ("height", "200px"), ("width", "150px"), ("padding", "1px")] --
    #+ (fmap pure selectionList')

  return (mainBox, bSelectionList)

setup :: Window -> UI ()
setup window = void $ mdo
  (sDiv1, bSDiv) <- selectDivWrong
  text1   <- fixedTextarea # sink UI.text (show <$> bSDiv) 

  (sDiv2, bSDiv2) <- selectDivCorrect
  text2   <- fixedTextarea # sink UI.text (show <$> bSDiv2) 


  getBody window 
    #+ [grid
        [ [element sDiv1]
        , [element text1]
        , [element sDiv2]
        , [element text2]
        ]]  
    # set style [("background-color", "#eeeeee")]

Initially i wanted to use selectDivWrong but figured out that i need to modify it to selectDivCorrect. My problem is that i don't understand why there is a functional difference. in both cases selectionList contains all elements that need to be added and bSelectionList combines all behaviors. I'm not sure how UI handles all the state and events (and i haven't used monads/applicatives a whole lot yet), but i suspect that in the correct version the combined UI context is added to the 'top level' and thus passed to (#+) (or UI.mkElement ?), but remains unused in the list of UI Elements in the wrong version.

I'm still not sure if i'm missing anything, though. I'd really like to be sure and find an explanation that helps identify this sort of issue in the future, since i basically found the solution via trial and error. (also feel free to rename the question...)


Solution

  • They key point is that the type UI Element denotes a (monadic) action that creates/manipulates/returns a thing, whereas the type Element denotes the thing itself. Sometimes, the former creates a new thing, sometimes it returns an old thing.

    In your case, selectionList :: [UI Element] is a list of actions that create a thing (each).

    In the wrong version, you first use sequence to execute all the actions in sequence, but then you also pass it the list to the #+ combinator, which internally executes all the actions in sequence as well. Hence, the actions are executed twice, so each element is created twice.

    In the correct version, you use sequence to execute all the actions in sequence and retain the corresponding new things (Element) in the list selectionList'. All elements have been created once, and then you simply pass them to whatever comes next. The combinator pure builds an action that simply returns an existing thing, that's it works.


    In the end, the type of #+ may be a bit confusing, it would be more transparent if it accepted a list [Element] instead of a list [UI Element]. The latter reduces syntactic noise, though, as it reduces the need to name individual elements.