This is my solution in Haskell:
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE OverloadedStrings #-}
import Data.String
import Graphics.UI.Gtk
import qualified Data.Map as Map
import qualified Data.Text as T
import Data.Maybe
import qualified Graphics.UI.Gtk.Gdk.Pixbuf as Pixbuf
import Control.Monad
colorsRawL = [(0,0,0),(254,26,89),(255,0,0),(0,255,0),(0,0,255),(255,255,0),(0,255,255),(255,0,255),(192,192,192),(128,128,128),(128,0,0),(128,128,0),(0,128,0),(128,0,128),(0,128,128),(0,0,128)]
manufacturers = [("Sony"::String), ("LG"::String), ("Panasonic"::String), ("Toshiba"::String), ("Nokia"::String), ("Samsung"::String)]
data ListElement = ListElement { name :: String , selected::Pixbuf }
getManufacturers::IO[ListElement]
getManufacturers = mapM (\x -> do
pbn <- Pixbuf.pixbufNew ColorspaceRgb False 8 16 16
Pixbuf.pixbufFill pbn 255 255 255 1
let el = ListElement x pbn
return el
) manufacturers
pixBufListS::IO [(String,Pixbuf)]
pixBufListS = mapM (\(r,g,b)-> do
pbn <- Pixbuf.pixbufNew ColorspaceRgb False 8 16 16
Pixbuf.pixbufFill pbn r g b 1
let name::String = ("Color ("++(show r)++" "++(show g)++" "++(show b)++ ")")
return (name,pbn)
) colorsRawL
getMap::IO (Map.Map String Pixbuf)
getMap = do
list <- pixBufListS
let mp = Map.fromList list
return mp
main :: IO ()
main = do
initGUI
window <- windowNew
fixed <- fixedNew
pixList <-pixBufListS
manus <- getManufacturers
lststoreManus::(ListStore ListElement) <- listStoreNew manus
treeview <- treeViewNew
treeViewSetModel treeview lststoreManus
treeViewSetHeadersVisible treeview True
colName <- treeViewColumnNew
imgCol <- treeViewColumnNew
colCombo <- treeViewColumnNew
treeViewColumnSetTitle imgCol ("Image column"::T.Text )
treeViewColumnSetTitle colName ("String column"::T.Text )
treeViewColumnSetTitle colCombo ("Combo"::T.Text )
iconRenderer <- cellRendererPixbufNew
renderer1 <- cellRendererTextNew
comboRenderer <- cellRendererComboNew
cellLayoutPackStart imgCol iconRenderer True
cellLayoutPackStart colName renderer1 True
cellLayoutPackStart colCombo comboRenderer True
cellLayoutSetAttributes imgCol iconRenderer lststoreManus $ (\ListElement { selected = t } -> [cellPixbuf := t])
cellLayoutSetAttributes colName renderer1 lststoreManus $ \row -> [ cellText := name row ]
cellLayoutSetAttributeFunc colCombo comboRenderer lststoreManus $
(\iter -> do (tmodel, colid) <- comboTextModel
(ListElement a b) <- treeModelGetRow lststoreManus iter
set comboRenderer [ cellVisible := True
, cellComboTextModel := (tmodel, colid)
, cellTextEditable := True
, cellComboHasEntry := False
, cellText := ("Choose pixbuf"::String)])
treeViewAppendColumn treeview colName
treeViewAppendColumn treeview imgCol
treeViewAppendColumn treeview colCombo
_ <- on comboRenderer editingStarted $ \widget treepath -> do
case treepath of
[k] -> do
let comboPix::ComboBox = castToComboBox widget
lststorerep::(ListStore (String,Pixbuf)) <- listStoreNew pixList
customStoreSetColumn lststorerep (makeColumnIdString 0) fst
customStoreSetColumn lststorerep (makeColumnIdPixbuf 1) snd
comboBoxSetModel comboPix (Just lststorerep)
rendertxt <- cellRendererTextNew
renderpic <- cellRendererPixbufNew
cellLayoutPackStart comboPix rendertxt False
cellLayoutPackStart comboPix renderpic True
cellLayoutAddColumnAttribute comboPix renderpic cellPixbuf $ makeColumnIdPixbuf 1
_ <- on comboRenderer edited $ \_treePath newStringValue -> do
case _treePath of
[k] -> do
(ListElement a b) <- listStoreGetValue lststoreManus k
myMap <- getMap
let finded = fromJust ( Map.lookup newStringValue myMap )
let toStore = ListElement a finded
listStoreSetValue lststoreManus k toStore
putStrLn $ "new value: " ++ newStringValue
fixedPut fixed treeview (10,10)
widgetSetSizeRequest treeview 500 100
containerAdd window fixed
onDestroy window mainQuit
windowSetDefaultSize window 600 500
windowSetPosition window WinPosCenter
widgetShowAll window
mainGUI
comboTextModel = do store <- listStoreNew []
let column = makeColumnIdString 0 :: ColumnId String String
return (store, column)
{-
dependencies :
- base >= 4.7 && < 5
- gtk
- text
- containers
-}
