File: CellLayout.chs

package info (click to toggle)
haskell-gtk 0.11.0-5
  • links: PTS, VCS
  • area: main
  • in suites: squeeze
  • size: 2,920 kB
  • ctags: 82
  • sloc: haskell: 1,929; ansic: 714; sh: 5; makefile: 3
file content (310 lines) | stat: -rw-r--r-- 11,950 bytes parent folder | download
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
{-# LANGUAGE CPP #-}
-- -*-haskell-*-
--  GIMP Toolkit (GTK) Interface CellLayout
--
--  Author : Axel Simon
--
--  Created: 23 January 2006
--
--  Copyright (C) 2006 Axel Simon
--
--  This library is free software; you can redistribute it and/or
--  modify it under the terms of the GNU Lesser General Public
--  License as published by the Free Software Foundation; either
--  version 2.1 of the License, or (at your option) any later version.
--
--  This library is distributed in the hope that it will be useful,
--  but WITHOUT ANY WARRANTY; without even the implied warranty of
--  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
--  Lesser General Public License for more details.
--
-- TODO: the following varargs functions were not bound
--   gtk_cell_layout_set_attributes
--
-- |
-- Maintainer  : gtk2hs-users@lists.sourceforge.net
-- Stability   : provisional
-- Portability : portable (depends on GHC)
--
-- An interface for packing cells
--
-- * Module available since Gtk+ version 2.4
--
module Graphics.UI.Gtk.ModelView.CellLayout (
-- * Detail
-- 
-- | 'CellLayout' is an interface which is implemented by all objects which
-- provide a 'TreeViewColumn' API for packing cells, setting attributes and data funcs.

-- * Class Hierarchy
-- |
-- @
-- |  Interface CellLayout
-- |   +----'TreeViewColumn'
-- |   +----'CellView'
-- |   +----'IconView'
-- |   +----'EntryCompletion'
-- |   +----'ComboBox'
-- |   +----'ComboBoxEntry'
-- @

#if GTK_CHECK_VERSION(2,4,0)
-- * Types
  CellLayoutClass,
  toCellLayout,

-- * Methods
  cellLayoutPackStart,
  cellLayoutPackEnd,
  cellLayoutReorder,
  cellLayoutClear,
  cellLayoutClearAttributes,
#if GTK_CHECK_VERSION(2,12,0)
  cellLayoutGetCells,
#endif
  cellLayoutAddColumnAttribute,
  cellLayoutSetAttributes,
  cellLayoutSetAttributeFunc,
#endif
  ) where

import System.Glib.FFI
import System.Glib.GList
import System.Glib.Attributes
import System.Glib.GObject (destroyFunPtr)
import System.Glib.GType
{#import Graphics.UI.Gtk.Types#}
{#import Graphics.UI.Gtk.ModelView.Types#}
{#import Graphics.UI.Gtk.ModelView.TreeModel#}
{#import Graphics.UI.Gtk.ModelView.CustomStore#} (treeModelGetRow)

{# context lib="gtk" prefix="gtk" #}

#if GTK_CHECK_VERSION(2,4,0)

#if GTK_CHECK_VERSION(2,6,0)
instance CellLayoutClass CellView
instance CellLayoutClass IconView
#endif

instance CellLayoutClass EntryCompletion
instance CellLayoutClass TreeViewColumn
instance CellLayoutClass ComboBox
instance CellLayoutClass ComboBoxEntry

--------------------
-- Methods

-- | Packs the @cell@ into the beginning of the cell layout. If @expand@ is
-- @False@, then the @cell@ is allocated no more space than it needs. Any
-- unused space is divided evenly between cells for which @expand@ is @True@.
--
-- Note that reusing the same cell renderer is not supported.
--
cellLayoutPackStart :: (CellLayoutClass self, CellRendererClass cell) => self
 -> cell  -- ^ @cell@ - A 'CellRenderer'.
 -> Bool  -- ^ @expand@ - @True@ if @cell@ is to be given extra space
          -- allocated to @cellLayout@.
 -> IO ()
cellLayoutPackStart self cell expand =
  {# call gtk_cell_layout_pack_start #}
    (toCellLayout self)
    (toCellRenderer cell)
    (fromBool expand)

-- | Adds the @cell@ to the end of @cellLayout@. If @expand@ is @False@, then
-- the @cell@ is allocated no more space than it needs. Any unused space is
-- divided evenly between cells for which @expand@ is @True@.
--
-- Note that reusing the same cell renderer is not supported.
--
cellLayoutPackEnd :: (CellLayoutClass self, CellRendererClass cell) => self
 -> cell  -- ^ @cell@ - A 'CellRenderer'.
 -> Bool  -- ^ @expand@ - @True@ if @cell@ is to be given extra space
          -- allocated to @cellLayout@.
 -> IO ()
cellLayoutPackEnd self cell expand =
  {# call gtk_cell_layout_pack_end #}
    (toCellLayout self)
    (toCellRenderer cell)
    (fromBool expand)

-- | Re-inserts @cell@ at @position@. Note that @cell@ has already to be
-- packed into @cellLayout@ for this to function properly.
--
cellLayoutReorder :: (CellLayoutClass self, CellRendererClass cell) => self
 -> cell  -- ^ @cell@ - A 'CellRenderer' to reorder.
 -> Int   -- ^ @position@ - New position to insert @cell@ at.
 -> IO ()
cellLayoutReorder self cell position =
  {# call gtk_cell_layout_reorder #}
    (toCellLayout self)
    (toCellRenderer cell)
    (fromIntegral position)

-- | Remove all renderers from the cell layout.
--
cellLayoutClear :: CellLayoutClass self => self -> IO ()
cellLayoutClear self =
  {# call gtk_cell_layout_clear #}
    (toCellLayout self)

#if GTK_CHECK_VERSION(2,12,0)
-- | Returns the cell renderers which have been added to @cellLayout@.
--
-- * Available since Gtk+ version 2.12
--
cellLayoutGetCells :: CellLayoutClass self => self
 -> IO [CellRenderer] -- ^ returns a list of cell renderers
cellLayoutGetCells self =
  {# call gtk_cell_layout_get_cells #}
    (toCellLayout self)
  >>= fromGList
  >>= mapM (makeNewGObject mkCellRenderer . return)
#endif

-- | Adds an attribute mapping to the renderer @cell@. The @column@ is
-- the 'ColumnId' of the model to get a value from, and the @attribute@ is the
-- parameter on @cell@ to be set from the value. So for example if column 2 of
-- the model contains strings, you could have the \"text\" attribute of a
-- 'CellRendererText' get its values from column 2.
--
cellLayoutAddColumnAttribute :: (CellLayoutClass self, CellRendererClass cell) => self
 -> cell   -- ^ @cell@ - A 'CellRenderer'.
 -> ReadWriteAttr cell a v  -- ^ @attribute@ - An attribute of a renderer.
 -> ColumnId row v    -- ^ @column@ - The virtual column of the model from which to 
                      -- retrieve the attribute.
 -> IO ()
cellLayoutAddColumnAttribute self cell attr column =
  withCString (show attr) $ \attributePtr ->
  {# call gtk_cell_layout_add_attribute #}
    (toCellLayout self)
    (toCellRenderer cell)
    attributePtr
    (fromIntegral (columnIdToNumber column))


-- | Specify how a row of the @model@ defines the
-- attributes of the 'CellRenderer' @cell@. This is a convenience wrapper
-- around 'cellLayoutSetAttributeFunc' in that it sets the cells of the @cell@
-- with the data retrieved from the model.
--
-- * Note on using 'Graphics.UI.Gtk.ModelView.TreeModelSort.TreeModelSort' and
-- 'Graphics.UI.Gtk.ModelView.TreeModelFilter.TreeModelFilter': These two models
-- wrap another model, the so-called child model, instead of storing their own
-- data. This raises the problem that the data of cell renderers must be set
-- using the child model, while the 'TreeIter's that the view works with refer to
-- the model that encapsulates the child model. For convenience, this function
-- transparently translates an iterator to the child model before extracting the
-- data using e.g. 'Graphics.UI.Gtk.TreeModel.TreeModelSort.treeModelSortConvertIterToChildIter'.
-- Hence, it is possible to install the encapsulating model in the view and to
-- pass the child model to this function.
--
cellLayoutSetAttributes :: (CellLayoutClass self,
			     CellRendererClass cell,
			     TreeModelClass (model row),
			     TypedTreeModelClass model)
 => self
 -> cell   -- ^ @cell@ - A 'CellRenderer'.
 -> model row -- ^ @model@ - A model containing rows of type @row@.
 -> (row -> [AttrOp cell]) -- ^ Function to set attributes on the cell renderer.
 -> IO ()
cellLayoutSetAttributes self cell model attributes = 
  cellLayoutSetAttributeFunc self cell model $ \iter -> do
    row <- treeModelGetRow model iter
    set cell (attributes row)

-- | Install a function that looks up a row in the model and sets the
-- attributes of the 'CellRenderer' @cell@ using the row's content.
--
cellLayoutSetAttributeFunc :: (CellLayoutClass self,
			       CellRendererClass cell,
			       TreeModelClass model)
 => self
 -> cell   -- ^ @cell@ - A 'CellRenderer'.
 -> model  -- ^ @model@ - A model from which to draw data.
 -> (TreeIter -> IO ()) -- ^ Function to set attributes on the cell renderer.
 -> IO ()
cellLayoutSetAttributeFunc self cell model func = do
  fPtr <- mkSetAttributeFunc $ \_ cellPtr' modelPtr' iterPtr _ -> do
    iter <- convertIterFromParentToChildModel iterPtr modelPtr' 
      (toTreeModel model)
    let (CellRenderer cellPtr) = toCellRenderer cell
    if unsafeForeignPtrToPtr cellPtr  /= cellPtr' then
      error ("cellLayoutSetAttributeFunc: attempt to set attributes of "++
	     "a different CellRenderer.")
      else func iter
  {#call gtk_cell_layout_set_cell_data_func #} (toCellLayout self)
    (toCellRenderer cell) fPtr (castFunPtrToPtr fPtr) destroyFunPtr

{#pointer CellLayoutDataFunc#}

foreign import ccall "wrapper" mkSetAttributeFunc ::
  (Ptr CellLayout -> Ptr CellRenderer -> Ptr TreeModel -> Ptr TreeIter ->
   Ptr () -> IO ()) -> IO CellLayoutDataFunc

-- Given a 'TreeModelFilter' or a 'TreeModelSort' and a 'TreeIter', get the
-- child model of these models and convert the iter to an iter of the child
-- model. This is an ugly internal function that is needed for some widgets
-- which pass iterators to the callback function of set_cell_data_func that
-- refer to some internal TreeModelFilter models that they create around the
-- user model. This is a bug but since C programs mostly use the columns
-- rather than the cell_layout way to extract attributes, this bug does not
-- show up in many programs. Reported in the case of EntryCompletion as bug
-- \#551202.
--
convertIterFromParentToChildModel ::
     Ptr TreeIter -- ^ the iterator
  -> Ptr TreeModel -- ^ the model that we got from the all back
  -> TreeModel -- ^ the model that we actually want
  -> IO TreeIter
convertIterFromParentToChildModel iterPtr parentModelPtr childModel =
  let (TreeModel modelFPtr) = childModel
      modelPtr = unsafeForeignPtrToPtr modelFPtr in
  if modelPtr==parentModelPtr then peek iterPtr else
  if typeInstanceIsA (castPtr parentModelPtr) gTypeTreeModelFilter then
    alloca $ \childIterPtr -> do
      treeModelFilterConvertIterToChildIter parentModelPtr childIterPtr iterPtr
      childPtr <- treeModelFilterGetModel parentModelPtr
      if childPtr==modelPtr then peek childIterPtr else
        convertIterFromParentToChildModel childIterPtr childPtr childModel
  else if typeInstanceIsA (castPtr parentModelPtr) gTypeTreeModelSort then
    alloca $ \childIterPtr -> do
      treeModelSortConvertIterToChildIter parentModelPtr childIterPtr iterPtr
      childPtr <- treeModelSortGetModel parentModelPtr
      if childPtr==modelPtr then peek childIterPtr else
        convertIterFromParentToChildModel childIterPtr childPtr childModel
  else do
    iter <- peek iterPtr
    error ("CellLayout: don't know how to convert iter "++show  iter++
           " from model "++show parentModelPtr++" to model "++
           show modelPtr++". Is it possible that you are setting the "++
           "attributes of a CellRenderer using a different model than "++
           "that which was set in the view?")

foreign import ccall unsafe "gtk_tree_model_filter_get_model"
  treeModelFilterGetModel :: Ptr TreeModel -> IO (Ptr TreeModel)

foreign import ccall safe "gtk_tree_model_filter_convert_iter_to_child_iter"
  treeModelFilterConvertIterToChildIter :: Ptr TreeModel -> Ptr TreeIter ->
    Ptr TreeIter -> IO () 

foreign import ccall unsafe "gtk_tree_model_sort_get_model"
  treeModelSortGetModel :: Ptr TreeModel -> IO (Ptr TreeModel)
  
foreign import ccall safe "gtk_tree_model_sort_convert_iter_to_child_iter"
  treeModelSortConvertIterToChildIter :: Ptr TreeModel -> Ptr TreeIter ->
    Ptr TreeIter -> IO () 

-- | Clears all existing attributes previously set with
-- 'cellLayoutSetAttributes'.
--
cellLayoutClearAttributes :: (CellLayoutClass self, CellRendererClass cell) => self
 -> cell  -- ^ @cell@ - A 'CellRenderer' to clear the attribute mapping on.
 -> IO ()
cellLayoutClearAttributes self cell =
  {# call gtk_cell_layout_clear_attributes #}
    (toCellLayout self)
    (toCellRenderer cell)

#endif