Difference between revisions of "Gtk2Hs/Tutorials/TreeView"

From HaskellWiki
Jump to navigation Jump to search
m
m (Minor formatting changes)
 
Line 2: Line 2:
 
I shows a simple list with four names and after clicking on one it says which one you selected. i hope it is useful for others!
 
I shows a simple list with four names and after clicking on one it says which one you selected. i hope it is useful for others!
   
  +
<haskell>
 
module Main where
 
module Main where
   
Line 56: Line 57:
 
v <- Model.listStoreGetValue list s
 
v <- Model.listStoreGetValue list s
 
putStrLn $ "selected " ++ v
 
putStrLn $ "selected " ++ v
  +
</haskell>

Latest revision as of 00:46, 9 April 2021

I had much trouble with creating a simple selection from a list, lacking examples on the web i could find. Therefore i post here the solution I have working - it is not optimal and I would appreciate comments. I shows a simple list with four names and after clicking on one it says which one you selected. i hope it is useful for others!

 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

 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
               ]
    onDestroy window mainQuit
    widgetShowAll window
    mainGUI
    return ()

 oneSelection :: ListStore String -> Model.TreeSelection ->  IO ()
 oneSelection list tree = do
    sel <- Model.treeSelectionGetSelectedRows tree
    let s = head  (head sel)
    v <- Model.listStoreGetValue list s
    putStrLn $ "selected " ++ v