haskellwxwidgetsfrpreactive-banana

Reactive Banana: Alternate buttons events


I am trying for the first time to use Reactive Banana (WX) to display a text like "Pressed button One", "Pressed button Two", etc. on top of five buttons:

{-# LANGUAGE ScopedTypeVariables #-}

import Graphics.UI.WX hiding (Event)
import Reactive.Banana
import Reactive.Banana.WX

data Buttons = One | Two | Three | Four | Five deriving (Show)

main :: IO ()
main = start $ do
  f      <- frame [text := “Five Buttons“]
  bone   <- button f [text := “One”]
  btwo   <- button f [text := “Two”]
  bthree <- button f [text := “Three”]
  bfour  <- button f [text := “Four”]
  bfive  <- button f [text := “Five”]
  out    <- staticText f []

  set f [layout := margin 10 $
          column 5 [row 5 [widget bone, widget btwo, widget bthree, widget bfour, widget bfive],
                    grid 5 5 [[label “Output:” , widget out]
                              ]]]

  let networkDescription :: forall t. Frameworks t => Moment t ()
      networkDescription = do
        eone   <- event0 bone   command
        etwo   <- event0 btwo   command
        ethree <- event0 bthree command
        efour  <- event0 bfour  command
        efive  <- event0 bfive  command

        let
          somethinghere::Behaviour t Buttons
          somethinghere = ....
        sink out [text :== "Pressed button " ++ show <$> somethinghere]

  network <- compile networkDescription    
  actuate network

The code is just the main skeleton. What I am not able to do at the moment is filling up the somethinghere method. As said, if for example the button "One" is pressed, then somethinghere should return referring to Buttons ADT data One and so on. I tried with accumB and unionWith but I don't think I am getting right the mechanism. Any help?


Solution

  • I believe you want something like:

    let eChangeSelection :: Event t Buttons
        eChangeSelection = unions
            [ One <$ eone
            , Two <$ etwo
            , Three <$ ethree
            , Four <$ efour
            , Five <$ efive
            ]
    
        -- Your `somethinghere`:
        bSelection :: Behavior t Buttons
        bSelection = stepper One eChangeSelection
    

    bSelection represents the currently selected button, and eChangeSelection is the stream of updates to it. unions merges the five event streams, and (<$) tags each individual stream with the appropriate value. Note that I arbitrarily picked One as the initial selection value; you might prefer doing something different (e.g. using a Behavior t (Maybe Buttons) so that it is possible to not have a button selected).