Hey I've been playing around with http://www.haskell.org/haskellwiki/Gtk2Hs/
Tutorials/TreeView and packing it up into a simple library.  I'm trying to 
make the list updatable however, and so far all of my attempts have failed :
(

See line 45 of my attachment please.
-- From http://www.haskell.org/haskellwiki/Gtk2Hs/Tutorials/TreeView

module Main where
--module SimpleListView where

import Graphics.UI.Gtk as GTK
import Control.Concurrent.MVar as MV

--{-
main :: IO ()
main = do
   initGUI       -- is start
   window <- windowNew
   (treeview,updateList) <- simpleListView "Subjects" ["Fred","Bob","Mary"] putStrLn
   containerAdd window treeview

   onDestroy window mainQuit
   widgetShowAll window
   updateList $ map show [1..10]
   mainGUI
   return ()---}

simpleListView :: String -> [String] -> (String -> IO()) -> IO (TreeView,([String]->IO()))
simpleListView title listItems onSelect = do

   list <- listStoreNew listItems
   listMVar <- MV.newMVar list
   treeview <- GTK.treeViewNewWithModel list
   GTK.treeViewSetHeadersVisible treeview True

           -- there should be a simpler way to render a list as the following!
   col <- GTK.treeViewColumnNew
   GTK.treeViewColumnSetTitle col title
   renderer <- GTK.cellRendererTextNew
   GTK.cellLayoutPackStart col renderer False
   GTK.cellLayoutSetAttributes col renderer list
           $ \ind -> [GTK.cellText := ind]
   GTK.treeViewAppendColumn treeview col

   tree <- GTK.treeViewGetSelection treeview
   GTK.treeSelectionSetMode tree  SelectionSingle
   GTK.onSelectionChanged tree (oneSelection listMVar tree onSelect)
   let updateList newListItems =
        do
   {-I tried two methods of clearing the list both are commented out here, and both return the same error SimpleListView: Prelude.head: empty list -}
             -- size <- GTK.listStoreGetSize list
             --                GTK.listStoreClear list
         _ <- MV.takeMVar listMVar
         putStrLn "1"
         newList <- listStoreNew newListItems
         putStrLn "2"
         GTK.cellLayoutSetAttributes col renderer newList
           $ \ind -> [GTK.cellText := ind]

         putStrLn "3"

         mapM_ (GTK.listStoreAppend list) newListItems
         putStrLn "4"
         GTK.treeViewSetModel treeview newList --This hangs
         putStrLn "5"
         MV.putMVar listMVar newList
         putStrLn "6"
             --                mapM_ (GTK.listStoreRemove list) [0..size-1]
   return (treeview,updateList)


oneSelection :: MV.MVar (GTK.ListStore String) -> GTK.TreeSelection -> (String -> IO ()) ->  IO ()
oneSelection listMVar tree onSelect = do
   list <- MV.takeMVar listMVar
   sel <- GTK.treeSelectionGetSelectedRows tree
   let s = head  (head sel)
   v <- GTK.listStoreGetValue list s
   onSelect v
   MV.putMVar listMVar list
------------------------------------------------------------------------------
Everyone hates slow websites. So do we.
Make your web apps faster with AppDynamics
Download AppDynamics Lite for free today:
http://p.sf.net/sfu/appdyn_d2d_nov
_______________________________________________
Gtk2hs-devel mailing list
Gtk2hs-devel@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/gtk2hs-devel

Reply via email to