Mon Oct 27 17:40:07 EDT 2008 Axe...@en...
* Add a demo for the combo box.
addfile ./demo/menu/ComboDemo.hs
hunk ./demo/menu/ComboDemo.hs 1
+module Main where
+
+import Graphics.UI.Gtk
+import Control.Concurrent.MVar
+import Control.Monad ( liftM )
+import Data.Maybe ( fromMaybe )
+import Data.List ( findIndex )
+
+
+main = do
+ initGUI
+
+ win <- windowNew
+ onDestroy win mainQuit [_$_]
+
+ (combo, store) <-
+ comboBoxEntryNewText id (words "ice-cream turkey pasta sandwich steak")
+ -- select the first item
+ comboBoxSetActive combo 0
+ [_$_]
+ -- Get the entry widget that the ComboBoxEntry uses.
+ (Just w) <- binGetChild combo
+ let entry = castToEntry w
+ [_$_]
+ -- Whenever the user has completed editing the text, append the new
+ -- text to the store unless it's already in there.
+ onEntryActivate entry $ do
+ str <- entryGetText entry
+ elems <- listStoreToList store
+ comboBoxSetActive combo (-1)
+ idx <- case (findIndex ((==) str) elems) of
+ Just idx -> return idx
+ Nothing -> listStoreAppend store str
+ comboBoxSetActive combo idx
+ return ()
+
+ containerAdd win combo
+ [_$_]
+ widgetShowAll win
+ mainGUI [_$_]
hunk ./demo/menu/Makefile 2
-PROG = menudemo [_$_]
-SOURCES = MenuDemo.hs
+PROGS = menudemo combodemo
+SOURCES = MenuDemo.hs ComboDemo.hs
hunk ./demo/menu/Makefile 5
-$(PROG) : $(SOURCES)
- $(HC) --make $< -o $@ $(HCFLAGS)
+all : $(PROGS)
+
+menudemo : MenuDemo.hs
+ $(HC_RULE)
+
+combodemo : ComboDemo.hs
+ $(HC_RULE)
+
+HC_RULE = $(HC) --make $< -o $@ $(HCFLAGS)
|