Search code examples
user-interfacehaskellgladeright-clickgtk2hs

capturing right-click event on treeview row [haskell gtk2hs]


I have searched thoroughly (at least I believe so) and I didn't find any answer for my problem, so I'd like to ask you for help. I'm trying to determine when a user right-clicks a row in my treeView (list of users) and then show a pop-up window with options to edit and delete them.

Here's how my app looks so far

Here's the code that generates the treeView:

import Graphics.UI.Gtk
import System.Glib.Signals (on)
import Graphics.UI.Gtk.Glade
import Graphics.UI.Gtk.ModelView as New
import SzuDB

data GUI = GUI {
                mainWindow :: Window,
                --Buttony
                dodajUczBt :: Button,
                cancelAddUczBt :: Button,
                zapiszUczBtn :: Button,
                --TreeView
                listaUczView :: TreeView,
                -- Dialogi
                dodajUzDialog :: Dialog,
                -- Entry
                nImie :: Entry,
                nNazwisko :: Entry,
                nWiek :: SpinButton,
                lblLiczbaUcz :: Label

               }

-- Różne listy

data ListStores = ListStores { uczestnicy :: ListStore Uczestnik }


main = do
        initGUI

        dbh <- connect "szu.db"

        gui <- loadGlade "szu.glade" dbh

        -- lapiemy uzytkownikow
        uczestnicy <- getAllUsers dbh

        labelSetText (lblLiczbaUcz gui) $ "Liczba uczestników: "++ show (length uczestnicy)

        listaUczestnikow <- New.listStoreNew uczestnicy
        New.treeViewSetModel (listaUczView gui) listaUczestnikow
        wyswietlUczestnikow (listaUczView gui) listaUczestnikow

        let liststore = ListStores $ listaUczestnikow

        loadGUIEvents gui dbh liststore


        widgetShowAll (mainWindow gui)
        mainGUI

--      loadGlade etc.

wyswietlUczestnikow view uczestnik = do
      New.treeViewSetHeadersVisible view True

      -- add a couple columns
      renderer1 <- New.cellRendererTextNew
      col1 <- New.treeViewColumnNew
      New.treeViewColumnPackStart col1 renderer1 True
      New.cellLayoutSetAttributes col1 renderer1 uczestnik $ \row -> [ New.cellText := imie row ]
      New.treeViewColumnSetTitle col1 "Imię"
      New.treeViewAppendColumn view col1

      renderer2 <- New.cellRendererTextNew
      col2 <- New.treeViewColumnNew
      New.treeViewColumnPackStart col2 renderer2 True
      New.cellLayoutSetAttributes col2 renderer2 uczestnik $ \row -> [ New.cellText := nazwisko row ]
      New.treeViewColumnSetTitle col2 "Nazwisko"
      New.treeViewAppendColumn view col2

      renderer3 <- New.cellRendererTextNew
      col3 <- New.treeViewColumnNew
      New.treeViewColumnPackStart col3 renderer3 True
      New.cellLayoutSetAttributes col3 renderer3 uczestnik $ \row -> [ New.cellText := show (wiek row) ]
      New.treeViewColumnSetTitle col3 "Wiek"
      New.treeViewAppendColumn view col3

--
-- ladujemy wydarzenia
--

-- loadGuiEvents etc.

I have already tried to use the example at http://www.muitovar.com/gtk2hs/chap7-2.html but it resulted in compile error (it said that eventButton is used with one argument while it requires none).

Any help would be greatly appreciated :) Cheers


Solution

  • Okay it seems I'm going be the first one to find answer for my own question :)

    (1) First of all the example at http://www.muitovar.com/gtk2hs/chap7-2.html didn't work for me because you have two eventButton functions in gtk2hs and you have to use the one from Graphics.UI.Gtk.Gdk.Events. So you have to add at the beginning of the file:

    import Graphics.UI.Gtk.Gdk.Events as Ev
    

    and then add Ev. prefix to eventButton, RightButton and eventSent. It'll work now :)

    (2) How to respond to right clicks on treeView row:

    Having solved the aforementioned problem I stumbled upon this example, where it's shown how to respond to selecting a row in treeView. So I mixed those two solutions and came up with something like this (most of the code comes from the treeview example with some of my tweaks):

    module Main where
    
     {- an example how to select from a list
       not satisfactory yet:
           - there should be a simpler way to render a simple list
           - i could not convert the model i got back to a list 
               from which to get the value
    
           - the interface offers a great number of functions 
               and it is very difficult to find which ones are 
               really needed for simple tasks
      -}
    
    import Graphics.UI.Gtk
    import Graphics.UI.Gtk.ModelView as Model
    import Graphics.UI.Gtk.Gdk.Events as Ev
    
    main :: IO ()
    main = do
       initGUI       -- is start
       window <- windowNew
    
       list <- listStoreNew ["Vince", "Jhen", "Chris", "Sharon"]
    
       treeview <- Model.treeViewNewWithModel list
       Model.treeViewSetHeadersVisible treeview True
    
               -- there should be a simpler way to render a list as the following!
       col <- Model.treeViewColumnNew
       Model.treeViewColumnSetTitle col "colTitle"
       renderer <- Model.cellRendererTextNew
       Model.cellLayoutPackStart col renderer False
       Model.cellLayoutSetAttributes col renderer list
               $ \ind -> [Model.cellText := ind]
       Model.treeViewAppendColumn treeview col
    
       --tree <- Model.treeViewGetSelection treeview
       --Model.treeSelectionSetMode tree  SelectionSingle
       --Model.onSelectionChanged tree (oneSelection list tree)
    
       set window [ windowDefaultWidth := 100
                   , windowDefaultHeight := 200
                   , containerChild := treeview
                  ]
    
       -- here comes the right-click popup       
    
       eda <- actionNew "EDA" "Edit" Nothing Nothing
       pra <- actionNew "PRA" "Process" Nothing Nothing
       rma <- actionNew "RMA" "Remove" Nothing Nothing
       saa <- actionNew "SAA" "Save" Nothing Nothing
    
       agr <- actionGroupNew "AGR1" 
       mapM_ (actionGroupAddAction agr) [eda,pra,rma,saa]
    
       uiman <- uiManagerNew
       uiManagerAddUiFromString uiman uiDecl
       uiManagerInsertActionGroup uiman agr 0
    
       maybePopup <- uiManagerGetWidget uiman "/ui/popup"
       let pop = case maybePopup of 
                (Just x) -> x
                Nothing -> error "Cannot get popup from string"
    
       onButtonPress treeview (\x -> if (Ev.eventButton x) == Ev.RightButton
                                     then do 
                                   menuPopup (castToMenu pop) Nothing
                                   return (Ev.eventSent x)
                                     else return (Ev.eventSent x))
    
       mapM_ (prAct treeview list) [eda,pra,rma,saa]    
    
    
       onDestroy window mainQuit
       widgetShowAll window
       mainGUI
       return ()
    
    uiDecl = "<ui> \
    \          <popup>\
    \            <menuitem action=\"EDA\" />\
    \            <menuitem action=\"PRA\" />\
    \            <menuitem action=\"RMA\" />\
    \            <separator />\
    \            <menuitem action=\"SAA\" />\
    \          </popup>\
    \        </ui>"   
    
    -- Handle the right-click. You can write a function that'll respond to various 
    -- actions, like for example: handleAction "EDA" = do something, etc.    
    
    prAct treeview list a = onActionActivate a $ do 
            name <- actionGetName a
                -- getting the selected row
    
            tree <- Model.treeViewGetSelection treeview
    
            -- you can also use treeSelectionGetSelected to get the Iter object
                -- and then convert it to Int by using listStoreIterToIndex and so get
                -- the ListStore item at given index
    
              sel <- Model.treeSelectionGetSelectedRows tree
            let s = head  (head sel)
            v <- Model.listStoreGetValue list s
            putStrLn ("Action Name: " ++ name ++ " | Item: " ++ v)
    

    I hope it'll be helpful for someone :)

    Cheers