1{-# LANGUAGE CPP #-}
2-- -*-haskell-*-
3--  GIMP Toolkit (GTK) Widget TreeView
4--
5--  Author : Axel Simon
6--
7--  Created: 9 May 2001
8--
9--  Copyright (C) 2001-2005 Axel Simon
10--
11--  This library is free software; you can redistribute it and/or
12--  modify it under the terms of the GNU Lesser General Public
13--  License as published by the Free Software Foundation; either
14--  version 2.1 of the License, or (at your option) any later version.
15--
16--  This library is distributed in the hope that it will be useful,
17--  but WITHOUT ANY WARRANTY; without even the implied warranty of
18--  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
19--  Lesser General Public License for more details.
20--
21-- TODO
22--
23-- gtk_tree_view_get_bin_window is to compare the GDK window from incoming
24--   events. We don't marshal that window parameter, so this function is not
25--   bound either.
26--
27-- The following functions related to drag and drop:
28--   treeViewSetDragDestRow, treeViewGetDragDestRow, treeViewGetDestRowAtPos
29-- these seem to be useful only in cases when the user wants to implement
30-- drag and drop himself rather than use the widget's implementation. I
31-- think this would be a bad idea in the first place.
32--
33-- get_search_equal_func is missing: proper memory management is impossible
34--
35-- gtk_tree_view_set_destroy_count_func is not meant to be useful
36--
37-- expand-collapse-cursor-row needs to be bound if it is useful to expand
38--   and collapse rows in a user-defined manner. Would only work on Gtk 2.2
39--   and higher since the return parameter changed
40--
41-- move_cursor, select_all, select_cursor_parent, select_cursor_row
42--   toggle_cursor_row, unselect_all are not bound.
43--   These functions are only useful to change the widgets
44--   behaviour for these actions. Everything else can be done with
45--   cursor_changed and columns_changed
46--
47-- set_scroll_adjustment makes sense if the user monitors the scroll bars
48--   and the scroll bars can be replaced anytime (the latter is odd)
49--
50-- |
51-- Maintainer  : gtk2hs-users@lists.sourceforge.net
52-- Stability   : provisional
53-- Portability : portable (depends on GHC)
54--
55-- A widget for displaying both trees and lists.
56--
57module Graphics.UI.Gtk.ModelView.TreeView (
58-- * Description
59--
60-- | Widget that displays any object that implements the 'TreeModel'
61-- interface.
62--
63-- The widget supports scrolling natively. This implies that pixel
64-- coordinates can be given in two formats: relative to the current view's
65-- upper left corner or relative to the whole list's coordinates. The former
66-- are called widget coordinates while the letter are called tree
67-- coordinates.
68
69-- * Class Hierarchy
70-- |
71-- @
72-- |  'GObject'
73-- |   +----'Object'
74-- |         +----'Widget'
75-- |               +----'Container'
76-- |                     +----TreeView
77-- @
78
79-- * Types
80  TreeView,
81  TreeViewClass,
82  castToTreeView, gTypeTreeView,
83  toTreeView,
84  Point,
85  DragAction(..),
86#if GTK_CHECK_VERSION(2,10,0)
87  TreeViewGridLines(..),
88#endif
89
90-- * Constructors
91  treeViewNew,
92  treeViewNewWithModel,
93
94-- * Methods
95  treeViewGetModel,
96  treeViewSetModel,
97  treeViewGetSelection,
98  treeViewGetHAdjustment,
99  treeViewSetHAdjustment,
100  treeViewGetVAdjustment,
101  treeViewSetVAdjustment,
102  treeViewGetHeadersVisible,
103  treeViewSetHeadersVisible,
104  treeViewColumnsAutosize,
105  treeViewSetHeadersClickable,
106  treeViewGetRulesHint,
107  treeViewSetRulesHint,
108  treeViewAppendColumn,
109  treeViewRemoveColumn,
110  treeViewInsertColumn,
111  treeViewGetColumn,
112  treeViewGetColumns,
113  treeViewMoveColumnAfter,
114  treeViewMoveColumnFirst,
115  treeViewSetExpanderColumn,
116  treeViewGetExpanderColumn,
117  treeViewSetColumnDragFunction,
118  treeViewScrollToPoint,
119  treeViewScrollToCell,
120  treeViewSetCursor,
121#if GTK_CHECK_VERSION(2,2,0)
122  treeViewSetCursorOnCell,
123#endif
124  treeViewGetCursor,
125  treeViewRowActivated,
126  treeViewExpandAll,
127  treeViewCollapseAll,
128#if GTK_CHECK_VERSION(2,2,0)
129  treeViewExpandToPath,
130#endif
131  treeViewExpandRow,
132  treeViewCollapseRow,
133  treeViewMapExpandedRows,
134  treeViewRowExpanded,
135  treeViewGetReorderable,
136  treeViewSetReorderable,
137  treeViewGetPathAtPos,
138  treeViewGetCellArea,
139  treeViewGetBackgroundArea,
140  treeViewGetVisibleRect,
141#if GTK_CHECK_VERSION(2,12,0)
142  treeViewConvertBinWindowToTreeCoords,
143  treeViewConvertBinWindowToWidgetCoords,
144  treeViewConvertTreeToBinWindowCoords,
145  treeViewConvertTreeToWidgetCoords,
146  treeViewConvertWidgetToBinWindowCoords,
147  treeViewConvertWidgetToTreeCoords,
148#endif
149#if GTK_MAJOR_VERSION < 3
150  treeViewCreateRowDragIcon,
151#endif
152  treeViewGetEnableSearch,
153  treeViewSetEnableSearch,
154  treeViewGetSearchColumn,
155  treeViewSetSearchColumn,
156  treeViewSetSearchEqualFunc,
157#if GTK_CHECK_VERSION(2,6,0)
158  treeViewGetFixedHeightMode,
159  treeViewSetFixedHeightMode,
160  treeViewGetHoverSelection,
161  treeViewSetHoverSelection,
162  treeViewGetHoverExpand,
163  treeViewSetHoverExpand,
164#if GTK_CHECK_VERSION(2,10,0)
165  treeViewGetHeadersClickable,
166#endif
167#endif
168#if GTK_CHECK_VERSION(2,8,0)
169  treeViewGetVisibleRange,
170#endif
171#if GTK_CHECK_VERSION(2,10,0)
172  treeViewEnableModelDragDest,
173  treeViewEnableModelDragSource,
174  treeViewUnsetRowsDragSource,
175  treeViewUnsetRowsDragDest,
176  treeViewGetSearchEntry,
177  treeViewSetSearchEntry,
178#endif
179#if GTK_CHECK_VERSION(2,6,0)
180  treeViewSetRowSeparatorFunc,
181#if GTK_CHECK_VERSION(2,10,0)
182  treeViewGetRubberBanding,
183  treeViewSetRubberBanding,
184  treeViewGetEnableTreeLines,
185  treeViewSetEnableTreeLines,
186  treeViewGetGridLines,
187  treeViewSetGridLines,
188#endif
189#endif
190#if GTK_CHECK_VERSION(2,12,0)
191  treeViewSetTooltipRow,
192  treeViewSetTooltipCell,
193  treeViewGetTooltipContext,
194#endif
195
196-- * Attributes
197  treeViewModel,
198  treeViewHAdjustment,
199  treeViewVAdjustment,
200  treeViewHeadersVisible,
201  treeViewHeadersClickable,
202  treeViewExpanderColumn,
203  treeViewReorderable,
204  treeViewRulesHint,
205  treeViewEnableSearch,
206  treeViewSearchColumn,
207#if GTK_CHECK_VERSION(2,4,0)
208  treeViewFixedHeightMode,
209#if GTK_CHECK_VERSION(2,6,0)
210  treeViewHoverSelection,
211  treeViewHoverExpand,
212#endif
213#endif
214  treeViewShowExpanders,
215  treeViewLevelIndentation,
216  treeViewRubberBanding,
217#if GTK_CHECK_VERSION(2,10,0)
218  treeViewEnableGridLines,
219#endif
220  treeViewEnableTreeLines,
221#if GTK_CHECK_VERSION(2,10,0)
222  treeViewGridLines,
223  treeViewSearchEntry,
224#endif
225#if GTK_CHECK_VERSION(2,12,0)
226  treeViewTooltipColumn,
227#endif
228
229-- * Signals
230  columnsChanged,
231  cursorChanged,
232  rowCollapsed,
233  rowExpanded,
234  rowActivated,
235  testCollapseRow,
236  testExpandRow,
237
238-- * Deprecated
239#ifndef DISABLE_DEPRECATED
240#if GTK_MAJOR_VERSION < 3
241  treeViewWidgetToTreeCoords,
242  treeViewTreeToWidgetCoords,
243#endif
244  onColumnsChanged,
245  afterColumnsChanged,
246  onCursorChanged,
247  afterCursorChanged,
248  onRowActivated,
249  afterRowActivated,
250  onRowCollapsed,
251  afterRowCollapsed,
252  onRowExpanded,
253  afterRowExpanded,
254  onStartInteractiveSearch,
255  afterStartInteractiveSearch,
256  onTestCollapseRow,
257  afterTestCollapseRow,
258  onTestExpandRow,
259  afterTestExpandRow
260#endif
261  ) where
262
263import Control.Monad    (liftM,)
264import Data.Maybe       (fromMaybe)
265
266import System.Glib.FFI
267import System.Glib.UTFString
268import System.Glib.GList                (fromGList)
269import System.Glib.Flags
270import System.Glib.Attributes
271import System.Glib.Properties
272import Graphics.UI.Gtk.Gdk.Enums        (DragAction(..))
273import Graphics.UI.Gtk.Gdk.Events       (Modifier(..))
274import Graphics.UI.Gtk.General.Structs  (Point, Rectangle)
275import Graphics.UI.Gtk.Abstract.Object  (makeNewObject)
276{#import Graphics.UI.Gtk.Types#}
277{#import Graphics.UI.Gtk.Signals#}
278import Graphics.UI.Gtk.ModelView.TreeModel (columnIdToNumber,
279                                            makeColumnIdString)
280{#import Graphics.UI.Gtk.ModelView.Types#}
281{#import Graphics.UI.Gtk.General.DNDTypes#}     (TargetList(..))
282
283{# context lib="gtk" prefix="gtk" #}
284
285--------------------
286-- Constructors
287
288-- | Creates a new 'TreeView' widget.
289--
290treeViewNew :: IO TreeView
291treeViewNew =
292  makeNewObject mkTreeView $
293  liftM (castPtr :: Ptr Widget -> Ptr TreeView) $
294  {# call tree_view_new #}
295
296-- | Create a new 'TreeView'
297-- widget with @model@ as the storage model.
298--
299treeViewNewWithModel :: TreeModelClass model => model -> IO TreeView
300treeViewNewWithModel model =
301  makeNewObject mkTreeView $
302  liftM (castPtr :: Ptr Widget -> Ptr TreeView) $
303  {# call tree_view_new_with_model #}
304    (toTreeModel model)
305
306--------------------
307-- Methods
308
309-- | Returns the model that supplies the data for
310-- this 'TreeView'. Returns @Nothing@ if the model is unset.
311--
312treeViewGetModel :: TreeViewClass self => self -> IO (Maybe TreeModel)
313treeViewGetModel self =
314  maybeNull (makeNewGObject mkTreeModel) $
315  {# call unsafe tree_view_get_model #}
316    (toTreeView self)
317
318-- | Set the 'TreeModel' for the current View.
319--
320treeViewSetModel :: (TreeViewClass self, TreeModelClass model) => self
321 -> Maybe model
322 -> IO ()
323treeViewSetModel self model =
324  {# call tree_view_set_model #}
325    (toTreeView self)
326    (maybe (TreeModel nullForeignPtr) toTreeModel model)
327
328-- | Retrieve a 'TreeSelection' that
329-- holds the current selected nodes of the View.
330--
331treeViewGetSelection :: TreeViewClass self => self -> IO TreeSelection
332treeViewGetSelection self =
333  makeNewGObject mkTreeSelection $
334  {# call unsafe tree_view_get_selection #}
335    (toTreeView self)
336
337-- | Gets the 'Adjustment' currently being used for the horizontal aspect.
338--
339treeViewGetHAdjustment :: TreeViewClass self => self -> IO (Maybe Adjustment)
340treeViewGetHAdjustment self =
341  maybeNull (makeNewObject mkAdjustment) $
342  {# call unsafe tree_view_get_hadjustment #}
343    (toTreeView self)
344
345-- | Sets the 'Adjustment' for the current horizontal aspect.
346--
347treeViewSetHAdjustment :: TreeViewClass self => self
348 -> Maybe Adjustment -- ^ @adjustment@ - The 'Adjustment' to set, or @Nothing@
349 -> IO ()
350treeViewSetHAdjustment self adjustment =
351  {# call tree_view_set_hadjustment #}
352    (toTreeView self)
353    (fromMaybe (Adjustment nullForeignPtr) adjustment)
354
355-- | Gets the 'Adjustment' currently being used for the vertical aspect.
356--
357treeViewGetVAdjustment :: TreeViewClass self => self -> IO (Maybe Adjustment)
358treeViewGetVAdjustment self =
359  maybeNull (makeNewObject mkAdjustment) $
360  {# call unsafe tree_view_get_vadjustment #}
361    (toTreeView self)
362
363-- | Sets the 'Adjustment' for the current vertical aspect.
364--
365treeViewSetVAdjustment :: TreeViewClass self => self
366 -> Maybe Adjustment -- ^ @adjustment@ - The 'Adjustment' to set, or @Nothing@
367 -> IO ()
368treeViewSetVAdjustment self adjustment =
369  {# call tree_view_set_vadjustment #}
370    (toTreeView self)
371    (fromMaybe (Adjustment nullForeignPtr) adjustment)
372
373-- | Query if the column headers are visible.
374--
375treeViewGetHeadersVisible :: TreeViewClass self => self -> IO Bool
376treeViewGetHeadersVisible self =
377  liftM toBool $
378  {# call unsafe tree_view_get_headers_visible #}
379    (toTreeView self)
380
381-- | Set the visibility state of the column headers.
382--
383treeViewSetHeadersVisible :: TreeViewClass self => self -> Bool -> IO ()
384treeViewSetHeadersVisible self headersVisible =
385  {# call tree_view_set_headers_visible #}
386    (toTreeView self)
387    (fromBool headersVisible)
388
389-- | Resize the columns to their optimal size.
390--
391treeViewColumnsAutosize :: TreeViewClass self => self -> IO ()
392treeViewColumnsAutosize self =
393  {# call tree_view_columns_autosize #}
394    (toTreeView self)
395
396-- | Set wether the columns headers are sensitive to mouse clicks.
397--
398treeViewSetHeadersClickable :: TreeViewClass self => self -> Bool -> IO ()
399treeViewSetHeadersClickable self setting =
400  {# call tree_view_set_headers_clickable #}
401    (toTreeView self)
402    (fromBool setting)
403
404-- | Query if visual aid for wide columns is turned on.
405--
406treeViewGetRulesHint :: TreeViewClass self => self -> IO Bool
407treeViewGetRulesHint self =
408  liftM toBool $
409  {# call unsafe tree_view_get_rules_hint #}
410    (toTreeView self)
411
412-- | This function tells Gtk+ that the user interface for your application
413-- requires users to read across tree rows and associate cells with one
414-- another. By default, Gtk+ will then render the tree with alternating row
415-- colors. Do /not/ use it just because you prefer the appearance of the ruled
416-- tree; that's a question for the theme. Some themes will draw tree rows in
417-- alternating colors even when rules are turned off, and users who prefer that
418-- appearance all the time can choose those themes. You should call this
419-- function only as a /semantic/ hint to the theme engine that your tree makes
420-- alternating colors useful from a functional standpoint (since it has lots of
421-- columns, generally).
422--
423treeViewSetRulesHint :: TreeViewClass self => self -> Bool -> IO ()
424treeViewSetRulesHint self setting =
425  {# call tree_view_set_rules_hint #}
426    (toTreeView self)
427    (fromBool setting)
428
429-- | Append a new column to the 'TreeView'. Returns the new number of columns.
430--
431treeViewAppendColumn :: TreeViewClass self => self -> TreeViewColumn -> IO Int
432treeViewAppendColumn self column =
433  liftM fromIntegral $
434  {# call tree_view_append_column #}
435    (toTreeView self)
436    column
437
438-- | Remove column @tvc@ from the 'TreeView'
439-- widget. The number of remaining columns is returned.
440--
441treeViewRemoveColumn :: TreeViewClass self => self -> TreeViewColumn -> IO Int
442treeViewRemoveColumn self column =
443  liftM fromIntegral $
444  {# call tree_view_remove_column #}
445    (toTreeView self)
446    column
447
448-- | Inserts column @tvc@ into the
449-- 'TreeView' widget at the position @pos@. Returns the number of
450-- columns after insertion. Specify -1 for @pos@ to insert the column
451-- at the end.
452--
453treeViewInsertColumn :: TreeViewClass self => self
454 -> TreeViewColumn
455 -> Int
456 -> IO Int
457treeViewInsertColumn self column position =
458  liftM fromIntegral $
459  {# call tree_view_insert_column #}
460    (toTreeView self)
461    column
462    (fromIntegral position)
463
464-- | Retrieve a 'TreeViewColumn'.
465--
466-- * Retrieve the @pos@ th columns of
467--   'TreeView'. If the index is out of range Nothing is returned.
468--
469treeViewGetColumn :: TreeViewClass self => self -> Int -> IO (Maybe TreeViewColumn)
470treeViewGetColumn self pos = do
471  tvcPtr <- {# call unsafe tree_view_get_column #} (toTreeView self)
472    (fromIntegral pos)
473  if tvcPtr==nullPtr then return Nothing else
474    liftM Just $ makeNewObject mkTreeViewColumn (return tvcPtr)
475
476-- | Return all 'TreeViewColumn's in this 'TreeView'.
477--
478treeViewGetColumns :: TreeViewClass self => self -> IO [TreeViewColumn]
479treeViewGetColumns self = do
480  colsList <- {# call unsafe tree_view_get_columns #} (toTreeView self)
481  colsPtr <- fromGList colsList
482  mapM (makeNewObject mkTreeViewColumn) (map return colsPtr)
483
484-- | Move a specific column.
485--
486-- * Use 'treeViewMoveColumnToFront' if you want to move the column
487--   to the left end of the 'TreeView'.
488--
489treeViewMoveColumnAfter :: TreeViewClass self => self
490 -> TreeViewColumn
491 -> TreeViewColumn
492 -> IO ()
493treeViewMoveColumnAfter self column baseColumn =
494  {# call tree_view_move_column_after #}
495    (toTreeView self)
496    column
497    baseColumn
498
499-- | Move a specific column.
500--
501-- * Use 'treeViewMoveColumnAfter' if you want to move the column
502--   somewhere else than to the leftmost position.
503--
504treeViewMoveColumnFirst :: TreeViewClass self => self -> TreeViewColumn -> IO ()
505treeViewMoveColumnFirst self which =
506  {# call tree_view_move_column_after #}
507    (toTreeView self)
508    which
509    (TreeViewColumn nullForeignPtr)
510
511-- | Set location of hierarchy controls.
512--
513-- * Sets the column to draw the expander arrow at. If @col@
514--   is @Nothing@, then the expander arrow is always at the first
515--   visible column.
516--
517-- If you do not want expander arrow to appear in your tree, set the
518-- expander column to a hidden column.
519--
520treeViewSetExpanderColumn :: TreeViewClass self => self
521 -> Maybe TreeViewColumn
522 -> IO ()
523treeViewSetExpanderColumn self column =
524  {# call unsafe tree_view_set_expander_column #}
525    (toTreeView self)
526    (fromMaybe (TreeViewColumn nullForeignPtr) column)
527
528-- | Get location of hierarchy controls.
529--
530-- * Gets the column to draw the expander arrow at. If @col@
531--   is @Nothing@, then the expander arrow is always at the first
532--   visible column.
533--
534treeViewGetExpanderColumn :: TreeViewClass self => self
535 -> IO TreeViewColumn
536treeViewGetExpanderColumn self =
537  makeNewObject mkTreeViewColumn $
538  {# call unsafe tree_view_get_expander_column #}
539    (toTreeView self)
540
541-- | Specify where a column may be dropped.
542--
543-- * Sets a user function for determining where a column may be dropped when
544--   dragged.  This function is called on every column pair in turn at the
545--   beginning of a column drag to determine where a drop can take place.
546--
547-- * The callback function take the 'TreeViewColumn' to be moved, the
548--   second and third arguments are the columns on the left and right side
549--   of the new location. At most one of them might be @Nothing@
550--   which indicates that the column is about to be dropped at the left or
551--   right end of the 'TreeView'.
552--
553-- * The predicate @pred@ should return @True@ if it is ok
554--   to insert the column at this place.
555--
556-- * Use @Nothing@ for the predicate if columns can be inserted
557--   anywhere.
558--
559treeViewSetColumnDragFunction :: TreeViewClass self => self
560 -> Maybe (TreeViewColumn
561        -> Maybe TreeViewColumn
562        -> Maybe TreeViewColumn
563        -> IO Bool)
564 -> IO ()
565treeViewSetColumnDragFunction self Nothing =
566  {# call tree_view_set_column_drag_function #} (toTreeView self)
567    nullFunPtr nullPtr nullFunPtr
568treeViewSetColumnDragFunction self (Just pred) = do
569  fPtr <- mkTreeViewColumnDropFunc $ \_ target prev next _ -> do
570    target' <- makeNewObject mkTreeViewColumn (return target)
571    prev' <- if prev==nullPtr then return Nothing else liftM Just $
572      makeNewObject mkTreeViewColumn (return prev)
573    next' <- if next==nullPtr then return Nothing else liftM Just $
574      makeNewObject mkTreeViewColumn (return next)
575    res <- pred target' prev' next'
576    return (fromBool res)
577  {# call tree_view_set_column_drag_function #}
578    (toTreeView self)
579    fPtr
580    (castFunPtrToPtr fPtr) destroyFunPtr
581
582{#pointer TreeViewColumnDropFunc#}
583
584foreign import ccall "wrapper" mkTreeViewColumnDropFunc ::
585  (Ptr TreeView -> Ptr TreeViewColumn -> Ptr TreeViewColumn -> Ptr TreeViewColumn ->
586  Ptr () -> IO {#type gboolean#}) -> IO TreeViewColumnDropFunc
587
588-- | Scroll to a coordinate.
589--
590-- * Scrolls the tree view such that the top-left corner of the
591--   visible area is @treeX@, @treeY@, where @treeX@
592--   and @treeY@ are specified in tree window coordinates.
593--   The 'TreeView' must be realized before this function is
594--   called.  If it isn't, you probably want to use
595--   'treeViewScrollToCell'.
596--
597treeViewScrollToPoint :: TreeViewClass self => self
598 -> Int
599 -> Int
600 -> IO ()
601treeViewScrollToPoint self treeX treeY =
602  {# call tree_view_scroll_to_point #}
603    (toTreeView self)
604    (fromIntegral treeX)
605    (fromIntegral treeY)
606
607-- | Scroll to a cell.
608--
609-- Moves the alignments of tree_view to the position specified by mbColumn and mbPath.
610-- If mbColumn is Nothing, then no horizontal scrolling occurs. Likewise, if mbPath
611-- is Nothing no vertical scrolling occurs. At a minimum, one of mbColumn or mbPath
612-- need to be provided. @rowAlign@ determines where the row is placed, and
613-- @colAlign@ determines where column is placed. Both are expected to be between
614-- 0.0 and 1.0. 0.0 means left/top alignment, 1.0 means right/bottom alignment,
615-- 0.5 means center.
616--
617-- If Nothing is passed instead of @rowAlign@ and @colAlign@, then the tree does
618-- the minimum amount of work to scroll the cell onto the screen. This means
619-- that the cell will be scrolled to the edge closest to its current position.
620-- If the cell is currently visible on the screen, nothing is done.
621--
622-- This function only works if the model is set, and path is a valid row on
623-- the model. If the model changes before the tree_view is realized, the
624-- centered path will be modified to reflect this change.
625--
626treeViewScrollToCell :: TreeViewClass self => self
627 -> Maybe TreePath
628 -> Maybe TreeViewColumn
629 -> Maybe (Float, Float)
630 -> IO ()
631treeViewScrollToCell self mbPath mbColumn (Just (rowAlign, colAlign)) =
632  maybeWithTreePath mbPath $ \path ->
633  {# call tree_view_scroll_to_cell #}
634    (toTreeView self)
635    path
636    (maybe (TreeViewColumn nullForeignPtr) toTreeViewColumn mbColumn)
637    1
638    (realToFrac rowAlign)
639    (realToFrac colAlign)
640treeViewScrollToCell self mbPath mbColumn Nothing =
641  maybeWithTreePath mbPath $ \path ->
642  {# call tree_view_scroll_to_cell #}
643    (toTreeView self)
644    path
645    (maybe (TreeViewColumn nullForeignPtr) toTreeViewColumn mbColumn)
646    0
647    0.0
648    0.0
649
650-- | Selects a specific row.
651--
652-- * Sets the current keyboard focus to be at @path@, and
653--   selects it.  This is useful when you want to focus the user\'s
654--   attention on a particular row.  If @focusColumn@ is given,
655--   then the input focus is given to the column specified by
656--   it. Additionally, if @focusColumn@ is specified, and
657--   @startEditing@ is @True@,
658--   then editing will be started in the
659--   specified cell.  This function is often followed by a
660--   'widgetGrabFocus' to the 'TreeView' in order
661--   to give keyboard focus to the widget.
662--
663treeViewSetCursor :: TreeViewClass self => self
664 -> TreePath
665 -> (Maybe (TreeViewColumn, Bool))
666 -> IO ()
667treeViewSetCursor self path Nothing =
668  withTreePath path $ \path ->
669  {# call tree_view_set_cursor #}
670    (toTreeView self)
671    path
672    (TreeViewColumn nullForeignPtr)
673    (fromBool False)
674treeViewSetCursor self path (Just (focusColumn, startEditing)) =
675  withTreePath path $ \path ->
676  {# call tree_view_set_cursor #}
677    (toTreeView self)
678    path
679    focusColumn
680    (fromBool startEditing)
681
682#if GTK_CHECK_VERSION(2,2,0)
683-- | Selects a cell in a specific row.
684--
685-- * Similar to 'treeViewSetCursor' but allows a column to
686--   containt several 'CellRenderer's.
687--
688-- * Only available in Gtk 2.2 and higher.
689--
690treeViewSetCursorOnCell :: (TreeViewClass self, CellRendererClass focusCell) => self
691 -> TreePath
692 -> TreeViewColumn
693 -> focusCell
694 -> Bool
695 -> IO ()
696treeViewSetCursorOnCell self path focusColumn focusCell startEditing =
697  withTreePath path $ \path ->
698  {# call tree_view_set_cursor_on_cell #}
699    (toTreeView self)
700    path
701    focusColumn
702    (toCellRenderer focusCell)
703    (fromBool startEditing)
704#endif
705
706-- | Retrieves the position of the focus.
707--
708-- * Returns a pair @(path, column)@.If the cursor is not currently
709--   set, @path@ will be @[]@. If no column is currently
710--   selected, @column@ will be @Nothing@.
711--
712treeViewGetCursor :: TreeViewClass self => self
713 -> IO (TreePath, Maybe TreeViewColumn)
714treeViewGetCursor self =
715  alloca $ \tpPtrPtr -> alloca $ \tvcPtrPtr -> do
716  {# call unsafe tree_view_get_cursor #}
717    (toTreeView self)
718    (castPtr tpPtrPtr)
719    (castPtr tvcPtrPtr)
720  tpPtr <- peek tpPtrPtr
721  tvcPtr <- peek tvcPtrPtr
722  tp <- fromTreePath tpPtr
723  tvc <- if tvcPtr==nullPtr then return Nothing else liftM Just $
724    makeNewObject mkTreeViewColumn (return tvcPtr)
725  return (tp,tvc)
726
727-- | Emit the activated signal on a cell.
728--
729treeViewRowActivated :: TreeViewClass self => self
730 -> TreePath
731 -> TreeViewColumn
732 -> IO ()
733treeViewRowActivated self path column =
734  withTreePath path $ \path ->
735  {# call tree_view_row_activated #}
736    (toTreeView self)
737    path
738    column
739
740-- | Recursively expands all nodes in the tree view.
741--
742treeViewExpandAll :: TreeViewClass self => self -> IO ()
743treeViewExpandAll self =
744  {# call tree_view_expand_all #}
745    (toTreeView self)
746
747-- | Recursively collapses all visible, expanded nodes in the tree view.
748--
749treeViewCollapseAll :: TreeViewClass self => self -> IO ()
750treeViewCollapseAll self =
751  {# call tree_view_collapse_all #}
752    (toTreeView self)
753
754#if GTK_CHECK_VERSION(2,2,0)
755-- | Make a certain path visible.
756--
757-- * This will expand all parent rows of @tp@ as necessary.
758--
759-- * Only available in Gtk 2.2 and higher.
760--
761treeViewExpandToPath :: TreeViewClass self => self -> TreePath -> IO ()
762treeViewExpandToPath self path =
763  withTreePath path $ \path ->
764  {# call tree_view_expand_to_path #}
765    (toTreeView self)
766    path
767#endif
768
769-- | Opens the row so its children are visible.
770--
771treeViewExpandRow :: TreeViewClass self => self
772 -> TreePath -- ^ @path@ - path to a row
773 -> Bool     -- ^ @openAll@ - whether to recursively expand, or just expand
774             -- immediate children
775 -> IO Bool  -- ^ returns @True@ if the row existed and had children
776treeViewExpandRow self path openAll =
777  liftM toBool $
778  withTreePath path $ \path ->
779  {# call tree_view_expand_row #}
780    (toTreeView self)
781    path
782    (fromBool openAll)
783
784-- | Collapses a row (hides its child rows, if they exist).
785--
786treeViewCollapseRow :: TreeViewClass self => self
787 -> TreePath -- ^ @path@ - path to a row in the tree view
788 -> IO Bool  -- ^ returns @True@ if the row was collapsed.
789treeViewCollapseRow self path =
790  liftM toBool $
791  withTreePath path $ \path ->
792  {# call tree_view_collapse_row #}
793    (toTreeView self)
794    path
795
796-- | Call function for every expaned row.
797--
798treeViewMapExpandedRows :: TreeViewClass self => self
799 -> (TreePath -> IO ())
800 -> IO ()
801treeViewMapExpandedRows self func = do
802  fPtr <- mkTreeViewMappingFunc $ \_ tpPtr _ -> fromTreePath tpPtr >>= func
803  {# call tree_view_map_expanded_rows #}
804    (toTreeView self)
805    fPtr
806    nullPtr
807  freeHaskellFunPtr fPtr
808
809{#pointer TreeViewMappingFunc#}
810
811foreign import ccall "wrapper" mkTreeViewMappingFunc ::
812  (Ptr TreeView -> Ptr NativeTreePath -> Ptr () -> IO ()) ->
813  IO TreeViewMappingFunc
814
815-- | Check if row is expanded.
816--
817treeViewRowExpanded :: TreeViewClass self => self
818 -> TreePath -- ^ @path@ - A 'TreePath' to test expansion state.
819 -> IO Bool  -- ^ returns @True@ if @path@ is expanded.
820treeViewRowExpanded self path =
821  liftM toBool $
822  withTreePath path $ \path ->
823  {# call unsafe tree_view_row_expanded #}
824    (toTreeView self)
825    path
826
827-- | Query if rows can be moved around.
828--
829-- * See 'treeViewSetReorderable'.
830--
831treeViewGetReorderable :: TreeViewClass self => self -> IO Bool
832treeViewGetReorderable self =
833  liftM toBool $
834  {# call unsafe tree_view_get_reorderable #}
835    (toTreeView self)
836
837-- | Check if rows can be moved around.
838--
839-- * Set whether the user can use drag and drop (DND) to reorder the rows in
840--   the store. This works on both 'TreeStore' and 'ListStore' models. If @ro@
841--   is @True@, then the user can reorder the model by dragging and dropping
842--   rows.  The developer can listen to these changes by connecting to the
843--   model's signals. If you need to control which rows may be dragged or
844--   where rows may be dropped, you can override the
845--   'Graphics.UI.Gtk.ModelView.CustomStore.treeDragSourceRowDraggable'
846--   function in the default DND implementation of the model.
847--
848treeViewSetReorderable :: TreeViewClass self => self
849 -> Bool
850 -> IO ()
851treeViewSetReorderable self reorderable =
852  {# call tree_view_set_reorderable #}
853    (toTreeView self)
854    (fromBool reorderable)
855
856-- | Map a pixel to the specific cell.
857--
858-- * Finds the path at the 'Point' @(x, y)@. The
859--   coordinates @x@ and @y@ are relative to the top left
860--   corner of the 'TreeView' drawing window. As such, coordinates
861--   in a mouse click event can be used directly to determine the cell
862--   which the user clicked on. This function is useful to realize
863--   popup menus.
864--
865-- * The returned point is the input point relative to the cell's upper
866--   left corner. The whole 'TreeView' is divided between all cells.
867--   The returned point is relative to the rectangle this cell occupies
868--   within the 'TreeView'.
869--
870treeViewGetPathAtPos :: TreeViewClass self => self
871 -> Point
872 -> IO (Maybe (TreePath, TreeViewColumn, Point))
873treeViewGetPathAtPos self (x,y) =
874  alloca $ \tpPtrPtr ->
875  alloca $ \tvcPtrPtr ->
876  alloca $ \xPtr ->
877  alloca $ \yPtr -> do
878    res <- liftM toBool $
879      {# call unsafe tree_view_get_path_at_pos #}
880      (toTreeView self)
881      (fromIntegral x)
882      (fromIntegral y)
883      (castPtr tpPtrPtr)
884      (castPtr tvcPtrPtr)
885      xPtr
886      yPtr
887    tpPtr <- peek tpPtrPtr
888    tvcPtr <- peek tvcPtrPtr
889    xCell <- peek xPtr
890    yCell <- peek yPtr
891    if not res then return Nothing else do
892      tp <- fromTreePath tpPtr
893      tvc <- makeNewObject mkTreeViewColumn (return tvcPtr)
894      return (Just (tp,tvc,(fromIntegral xCell, fromIntegral yCell)))
895
896-- | Retrieve the smallest bounding box of a cell.
897--
898-- * Fills the bounding rectangle in tree window coordinates for the
899--   cell at the row specified by @tp@ and the column specified by
900--   @tvc@.
901--   If @path@ is @Nothing@ or points to a path not
902--   currently displayed, the @y@ and @height@ fields of
903--   the 'Rectangle' will be filled with @0@. The sum of
904--   all cell rectangles does not cover the entire tree; there are extra
905--   pixels in between rows, for example.
906--
907treeViewGetCellArea :: TreeViewClass self => self
908 -> Maybe TreePath
909 -> TreeViewColumn
910 -> IO Rectangle
911treeViewGetCellArea self Nothing tvc =
912  alloca $ \rPtr ->
913  {# call unsafe tree_view_get_cell_area #}
914    (toTreeView self)
915    (NativeTreePath nullPtr)
916    tvc
917    (castPtr (rPtr :: Ptr Rectangle))
918    >> peek rPtr
919treeViewGetCellArea self (Just tp) tvc =
920  withTreePath tp $ \tp ->
921  alloca $ \rPtr -> do
922  {# call unsafe tree_view_get_cell_area #}
923    (toTreeView self)
924    tp
925    tvc
926    (castPtr (rPtr :: Ptr Rectangle))
927    >> peek rPtr
928
929-- | Retrieve the largest bounding box of a cell.
930--
931-- * Fills the bounding rectangle in tree window coordinates for the
932--   cell at the row specified by @tp@ and the column specified by
933--   @tvc@.
934--   If @path@ is @Nothing@ or points to a path not
935--   currently displayed, the @y@ and @height@ fields of
936--   the 'Rectangle' will be filled with @0@. The background
937--   areas tile the widget's area to cover the entire tree window
938--   (except for the area used for header buttons). Contrast this with
939--   'treeViewGetCellArea'.
940--
941treeViewGetBackgroundArea :: TreeViewClass self => self
942 -> Maybe TreePath
943 -> TreeViewColumn
944 -> IO Rectangle
945treeViewGetBackgroundArea self Nothing tvc =
946  alloca $ \rPtr ->
947  {# call unsafe tree_view_get_background_area #}
948    (toTreeView self)
949    (NativeTreePath nullPtr)
950    tvc
951    (castPtr (rPtr :: Ptr Rectangle))
952  >> peek rPtr
953treeViewGetBackgroundArea self (Just tp) tvc =
954  withTreePath tp $ \tp -> alloca $ \rPtr ->
955  {# call unsafe tree_view_get_background_area #}
956    (toTreeView self)
957    tp
958    tvc
959    (castPtr (rPtr :: Ptr Rectangle))
960  >> peek rPtr
961
962-- | Retrieve the currently visible area.
963--
964-- * The returned rectangle gives the visible part of the tree in tree
965--   coordinates.
966--
967treeViewGetVisibleRect :: TreeViewClass self => self -> IO Rectangle
968treeViewGetVisibleRect self =
969  alloca $ \rPtr -> do
970  {# call unsafe tree_view_get_visible_rect #}
971    (toTreeView self)
972    (castPtr (rPtr :: Ptr Rectangle))
973  peek rPtr
974
975#ifndef DISABLE_DEPRECATED
976#if GTK_MAJOR_VERSION < 3
977-- | 'treeViewTreeToWidgetCoords' has been deprecated since version 2.12 and should not be used in
978-- newly-written code. Due to historial reasons the name of this function is incorrect. For converting
979-- bin window coordinates to coordinates relative to bin window, please see
980-- 'treeViewConvertBinWindowToWidgetCoords'.
981--
982-- Converts tree coordinates (coordinates in full scrollable area of the tree) to bin window
983-- coordinates.
984--
985-- Removed in Gtk3.
986treeViewTreeToWidgetCoords :: TreeViewClass self => self
987 -> Point    -- ^ @(tx, ty)@ - tree X and Y coordinates
988 -> IO Point -- ^ @(wx, wy)@ returns widget X and Y coordinates
989treeViewTreeToWidgetCoords self (tx, ty) =
990  alloca $ \wxPtr ->
991  alloca $ \wyPtr -> do
992  {# call unsafe tree_view_tree_to_widget_coords #}
993    (toTreeView self)
994    (fromIntegral tx)
995    (fromIntegral ty)
996    wxPtr
997    wyPtr
998  wx <- peek wxPtr
999  wy <- peek wyPtr
1000  return (fromIntegral wx, fromIntegral wy)
1001
1002-- | 'treeViewWidgetToTreeCoords' has been deprecated since version 2.12 and should not be used in
1003-- newly-written code. Due to historial reasons the name of this function is incorrect. For converting
1004-- coordinates relative to the widget to bin window coordinates, please see
1005-- 'treeViewConvertWidgetToBinWindowCoords'.
1006--
1007-- Converts bin window coordinates to coordinates for the tree (the full scrollable area of the tree).
1008--
1009-- Removed in Gtk3.
1010treeViewWidgetToTreeCoords :: TreeViewClass self => self
1011 -> Point    -- ^ @(wx, wy)@ - widget X and Y coordinates
1012 -> IO Point -- ^ @(tx, ty)@ returns tree X and Y coordinates
1013treeViewWidgetToTreeCoords self (wx, wy) =
1014  alloca $ \txPtr ->
1015  alloca $ \tyPtr -> do
1016  {# call unsafe tree_view_widget_to_tree_coords #}
1017    (toTreeView self)
1018    (fromIntegral wx)
1019    (fromIntegral wy)
1020    txPtr
1021    tyPtr
1022  tx <- peek txPtr
1023  ty <- peek tyPtr
1024  return (fromIntegral tx, fromIntegral ty)
1025#endif
1026#endif
1027
1028#if GTK_CHECK_VERSION(2,12,0)
1029-- | Converts bin window coordinates to coordinates for the tree (the full scrollable area of the tree).
1030treeViewConvertBinWindowToTreeCoords :: TreeViewClass self => self
1031 -> Point -- ^ @(bx, by)@ - bin window X and Y coordinates
1032 -> IO Point -- ^ @(tx, ty)@ returns tree X and Y coordinates
1033treeViewConvertBinWindowToTreeCoords self (bx, by) =
1034  alloca $ \txPtr ->
1035  alloca $ \tyPtr -> do
1036  {# call unsafe tree_view_convert_bin_window_to_tree_coords #}
1037    (toTreeView self)
1038    (fromIntegral bx)
1039    (fromIntegral by)
1040    txPtr
1041    tyPtr
1042  tx <- peek txPtr
1043  ty <- peek tyPtr
1044  return (fromIntegral tx, fromIntegral ty)
1045
1046-- | Converts bin window coordinates (see 'treeViewGetBinWindow' to widget relative coordinates.
1047treeViewConvertBinWindowToWidgetCoords :: TreeViewClass self => self
1048 -> Point -- ^ @(bx, by)@ - bin window X and Y coordinates
1049 -> IO Point -- ^ @(wx, wy)@ returns widget X and Y coordinates
1050treeViewConvertBinWindowToWidgetCoords self (bx, by) =
1051  alloca $ \wxPtr ->
1052  alloca $ \wyPtr -> do
1053  {# call unsafe tree_view_convert_bin_window_to_widget_coords #}
1054    (toTreeView self)
1055    (fromIntegral bx)
1056    (fromIntegral by)
1057    wxPtr
1058    wyPtr
1059  wx <- peek wxPtr
1060  wy <- peek wyPtr
1061  return (fromIntegral wx, fromIntegral wy)
1062
1063-- | Converts tree coordinates (coordinates in full scrollable area of the tree) to bin window
1064-- coordinates.
1065treeViewConvertTreeToBinWindowCoords :: TreeViewClass self => self
1066 -> Point -- ^ @(tx, ty)@ - tree X and Y coordinates
1067 -> IO Point -- ^ @(bx, by)@ returns bin window X and Y coordinates
1068treeViewConvertTreeToBinWindowCoords self (tx, ty) =
1069  alloca $ \bxPtr ->
1070  alloca $ \byPtr -> do
1071  {# call unsafe tree_view_convert_tree_to_bin_window_coords #}
1072    (toTreeView self)
1073    (fromIntegral tx)
1074    (fromIntegral ty)
1075    bxPtr
1076    byPtr
1077  bx <- peek bxPtr
1078  by <- peek byPtr
1079  return (fromIntegral bx, fromIntegral by)
1080
1081-- | Converts tree coordinates (coordinates in full scrollable area of the tree) to widget coordinates.
1082treeViewConvertTreeToWidgetCoords :: TreeViewClass self => self
1083 -> Point -- ^ @(tx, ty)@ - tree X and Y coordinates
1084 -> IO Point -- ^ @(wx, wy)@ returns widget X and Y coordinates
1085treeViewConvertTreeToWidgetCoords self (wx, wy) =
1086  alloca $ \bxPtr ->
1087  alloca $ \byPtr -> do
1088  {# call unsafe tree_view_convert_tree_to_widget_coords #}
1089    (toTreeView self)
1090    (fromIntegral wx)
1091    (fromIntegral wy)
1092    bxPtr
1093    byPtr
1094  bx <- peek bxPtr
1095  by <- peek byPtr
1096  return (fromIntegral bx, fromIntegral by)
1097
1098-- | Converts widget coordinates to coordinates for the window (see 'treeViewGetBinWindow' ).
1099treeViewConvertWidgetToBinWindowCoords :: TreeViewClass self => self
1100 -> Point -- ^ @(wx, wy)@ - widget X and Y coordinates
1101 -> IO Point -- ^ @(bx, by)@ returns bin window X and Y coordinates
1102treeViewConvertWidgetToBinWindowCoords self (wx, wy) =
1103  alloca $ \bxPtr ->
1104  alloca $ \byPtr -> do
1105  {# call unsafe tree_view_convert_widget_to_bin_window_coords #}
1106    (toTreeView self)
1107    (fromIntegral wx)
1108    (fromIntegral wy)
1109    bxPtr
1110    byPtr
1111  bx <- peek bxPtr
1112  by <- peek byPtr
1113  return (fromIntegral bx, fromIntegral by)
1114
1115-- | Converts widget coordinates to coordinates for the tree (the full scrollable area of the tree).
1116treeViewConvertWidgetToTreeCoords :: TreeViewClass self => self
1117 -> Point -- ^ @(wx, wy)@ - bin window X and Y coordinates
1118 -> IO Point -- ^ @(tx, ty)@ returns tree X and Y coordinates
1119treeViewConvertWidgetToTreeCoords self (wx, wy) =
1120  alloca $ \txPtr ->
1121  alloca $ \tyPtr -> do
1122  {# call unsafe tree_view_convert_widget_to_tree_coords #}
1123    (toTreeView self)
1124    (fromIntegral wx)
1125    (fromIntegral wy)
1126    txPtr
1127    tyPtr
1128  tx <- peek txPtr
1129  ty <- peek tyPtr
1130  return (fromIntegral tx, fromIntegral ty)
1131#endif
1132
1133#if GTK_MAJOR_VERSION < 3
1134-- | Creates a 'Pixmap' representation of the row at the given path. This image
1135-- can be used for a drag icon.
1136--
1137-- Removed in Gtk3.
1138treeViewCreateRowDragIcon :: TreeViewClass self => self
1139 -> TreePath
1140 -> IO Pixmap
1141treeViewCreateRowDragIcon self path =
1142  wrapNewGObject mkPixmap $
1143  withTreePath path $ \path ->
1144  {# call unsafe tree_view_create_row_drag_icon #}
1145    (toTreeView self)
1146    path
1147#endif
1148
1149-- | Returns whether or not the tree allows to start interactive searching by
1150-- typing in text.
1151--
1152-- * If enabled, the user can type in text which will set the cursor to
1153--   the first matching entry.
1154--
1155treeViewGetEnableSearch :: TreeViewClass self => self -> IO Bool
1156treeViewGetEnableSearch self =
1157  liftM toBool $
1158  {# call unsafe tree_view_get_enable_search #}
1159    (toTreeView self)
1160
1161-- | If this is set, then the user can type in text to search
1162-- through the tree interactively (this is sometimes called \"typeahead
1163-- find\").
1164--
1165-- Note that even if this is @False@, the user can still initiate a search
1166-- using the \"start-interactive-search\" key binding. In any case,
1167-- a predicate that compares a row of the model with the text the user
1168-- has typed must be set using 'treeViewSetSearchEqualFunc'.
1169--
1170treeViewSetEnableSearch :: TreeViewClass self => self -> Bool -> IO ()
1171treeViewSetEnableSearch self enableSearch =
1172  {# call tree_view_set_enable_search #}
1173    (toTreeView self)
1174    (fromBool enableSearch)
1175
1176-- %hash c:ecc5 d:bed6
1177-- | Gets the column searched on by the interactive search code.
1178--
1179treeViewGetSearchColumn :: (TreeViewClass self, GlibString string) => self
1180 -> IO (ColumnId row string) -- ^ returns the column the interactive search code searches in.
1181treeViewGetSearchColumn self =
1182  liftM (makeColumnIdString . fromIntegral) $
1183  {# call unsafe tree_view_get_search_column #}
1184    (toTreeView self)
1185
1186-- %hash c:d0d0
1187-- | Sets @column@ as the column where the interactive search code should
1188-- search in.
1189--
1190-- If the sort column is set, users can use the \"start-interactive-search\"
1191-- key binding to bring up search popup. The enable-search property controls
1192-- whether simply typing text will also start an interactive search.
1193--
1194-- Note that @column@ refers to a column of the model. Furthermore, the
1195-- search column is not used if a comparison function is set, see
1196-- 'treeViewSetSearchEqualFunc'.
1197--
1198treeViewSetSearchColumn :: (TreeViewClass self, GlibString string) => self
1199 -> (ColumnId row string) -- ^ @column@ - the column of the model to search in, or -1 to disable
1200        -- searching
1201 -> IO ()
1202treeViewSetSearchColumn self column =
1203  {# call tree_view_set_search_column #}
1204    (toTreeView self)
1205    (fromIntegral (columnIdToNumber column))
1206
1207
1208-- | Set the predicate to test for equality.
1209--
1210-- * The predicate must returns @True@ if the text entered by the user
1211--   and the row of the model match. Calling this function will overwrite
1212--   the 'treeViewSearchColumn' (which isn't used anyway when a comparison
1213--   function is installed).
1214--
1215treeViewSetSearchEqualFunc :: (TreeViewClass self, GlibString string) => self
1216 -> Maybe (string -> TreeIter -> IO Bool)
1217 -> IO ()
1218treeViewSetSearchEqualFunc self (Just pred) = do
1219  fPtr <- mkTreeViewSearchEqualFunc (\_ _ keyPtr iterPtr _ -> do
1220    key <- peekUTFString keyPtr
1221    iter <- peek iterPtr
1222    liftM (fromBool . not) $ pred key iter)
1223  {# call tree_view_set_search_equal_func #} (toTreeView self) fPtr
1224    (castFunPtrToPtr fPtr) destroyFunPtr
1225  {# call tree_view_set_search_column #} (toTreeView self) 0
1226treeViewSetSearchEqualFunc self Nothing = do
1227  {# call tree_view_set_search_equal_func #} (toTreeView self)
1228    nullFunPtr nullPtr nullFunPtr
1229  {# call tree_view_set_search_column #} (toTreeView self) (-1)
1230
1231{#pointer TreeViewSearchEqualFunc#}
1232
1233foreign import ccall "wrapper" mkTreeViewSearchEqualFunc ::
1234  (Ptr TreeModel -> {#type gint#} -> CString -> Ptr TreeIter -> Ptr () ->
1235   IO {#type gboolean#}) -> IO TreeViewSearchEqualFunc
1236
1237-- helper to marshal native tree paths to TreePaths
1238readNTP :: Ptr TreePath -> IO TreePath
1239readNTP ptr = peekTreePath (castPtr ptr)
1240
1241#if GTK_CHECK_VERSION(2,6,0)
1242-- | Returns whether fixed height mode is turned on for the tree view.
1243--
1244-- * Available since Gtk+ version 2.6
1245--
1246treeViewGetFixedHeightMode :: TreeViewClass self => self
1247 -> IO Bool -- ^ returns @True@ if the tree view is in fixed height mode
1248treeViewGetFixedHeightMode self =
1249  liftM toBool $
1250  {# call gtk_tree_view_get_fixed_height_mode #}
1251    (toTreeView self)
1252
1253-- | Enables or disables the fixed height mode of the tree view. Fixed height
1254-- mode speeds up 'TreeView' by assuming that all rows have the same height.
1255-- Only enable this option if all rows are the same height and all columns are
1256-- of type 'TreeViewColumnFixed'.
1257--
1258-- * Available since Gtk+ version 2.6
1259--
1260treeViewSetFixedHeightMode :: TreeViewClass self => self
1261 -> Bool  -- ^ @enable@ - @True@ to enable fixed height mode
1262 -> IO ()
1263treeViewSetFixedHeightMode self enable =
1264  {# call gtk_tree_view_set_fixed_height_mode #}
1265    (toTreeView self)
1266    (fromBool enable)
1267
1268-- | Returns whether hover selection mode is turned on for @treeView@.
1269--
1270-- * Available since Gtk+ version 2.6
1271--
1272treeViewGetHoverSelection :: TreeViewClass self => self
1273 -> IO Bool -- ^ returns @True@ if the tree view is in hover selection mode
1274treeViewGetHoverSelection self =
1275  liftM toBool $
1276  {# call gtk_tree_view_get_hover_selection #}
1277    (toTreeView self)
1278
1279-- | Enables of disables the hover selection mode of the tree view. Hover
1280-- selection makes the selected row follow the pointer. Currently, this works
1281-- only for the selection modes 'SelectionSingle' and 'SelectionBrowse'.
1282--
1283-- * Available since Gtk+ version 2.6
1284--
1285treeViewSetHoverSelection :: TreeViewClass self => self
1286 -> Bool  -- ^ @hover@ - @True@ to enable hover selection mode
1287 -> IO ()
1288treeViewSetHoverSelection self hover =
1289  {# call gtk_tree_view_set_hover_selection #}
1290    (toTreeView self)
1291    (fromBool hover)
1292
1293-- | Returns whether hover expansion mode is turned on for the tree view.
1294--
1295-- * Available since Gtk+ version 2.6
1296--
1297treeViewGetHoverExpand :: TreeViewClass self => self
1298 -> IO Bool -- ^ returns @True@ if the tree view is in hover expansion mode
1299treeViewGetHoverExpand self =
1300  liftM toBool $
1301  {# call gtk_tree_view_get_hover_expand #}
1302    (toTreeView self)
1303
1304-- | Enables of disables the hover expansion mode of the tree view. Hover
1305-- expansion makes rows expand or collaps if the pointer moves over them.
1306--
1307-- * Available since Gtk+ version 2.6
1308--
1309treeViewSetHoverExpand :: TreeViewClass self => self
1310 -> Bool  -- ^ @expand@ - @True@ to enable hover selection mode
1311 -> IO ()
1312treeViewSetHoverExpand self expand =
1313  {# call gtk_tree_view_set_hover_expand #}
1314    (toTreeView self)
1315    (fromBool expand)
1316#endif
1317
1318
1319#if GTK_CHECK_VERSION(2,10,0)
1320-- %hash c:88cb d:65c9
1321-- | Returns whether all header columns are clickable.
1322--
1323-- * Available since Gtk+ version 2.10
1324--
1325treeViewGetHeadersClickable :: TreeViewClass self => self
1326 -> IO Bool -- ^ returns @True@ if all header columns are clickable, otherwise
1327            -- @False@
1328treeViewGetHeadersClickable self =
1329  liftM toBool $
1330  {# call gtk_tree_view_get_headers_clickable #}
1331    (toTreeView self)
1332#endif
1333
1334#if GTK_CHECK_VERSION(2,8,0)
1335-- %hash c:1d81 d:3587
1336-- | Return the first and last visible path.
1337-- Note that there may be invisible paths in between.
1338--
1339-- * Available since Gtk+ version 2.8
1340--
1341treeViewGetVisibleRange :: TreeViewClass self => self
1342 -> IO (TreePath, TreePath)     -- ^ the first and the last node that is visible
1343treeViewGetVisibleRange self  = alloca $ \startPtr -> alloca $ \endPtr -> do
1344  valid <- liftM toBool $
1345    {# call gtk_tree_view_get_visible_range #}
1346    (toTreeView self) (castPtr startPtr) (castPtr endPtr)
1347  if not valid then return ([],[]) else do
1348    startTPPtr <- peek startPtr
1349    endTPPtr <- peek endPtr
1350    startPath <- fromTreePath startTPPtr
1351    endPath <- fromTreePath endTPPtr
1352    return (startPath, endPath)
1353
1354#endif
1355
1356#if GTK_CHECK_VERSION(2,10,0)
1357-- %hash c:61e1 d:3a0a
1358-- | Turns @treeView@ into a drop destination for automatic DND.
1359--
1360treeViewEnableModelDragDest :: TreeViewClass self => self
1361  -> TargetList                -- ^ @targets@ - the list of targets that the
1362                               -- the view will support
1363  -> [DragAction]              -- ^ @actions@ - flags denoting the possible actions
1364                               -- for a drop into this widget
1365  -> IO ()
1366treeViewEnableModelDragDest self targets actions =
1367  alloca $ \nTargetsPtr -> do
1368  tlPtr <- {#call unsafe gtk_target_table_new_from_list#} targets nTargetsPtr
1369  nTargets <- peek nTargetsPtr
1370  {# call gtk_tree_view_enable_model_drag_dest #}
1371    (toTreeView self)
1372    tlPtr
1373    nTargets
1374    ((fromIntegral . fromFlags) actions)
1375  {#call unsafe gtk_target_table_free#} tlPtr nTargets
1376
1377-- %hash c:1df9 d:622
1378-- | Turns @treeView@ into a drag source for automatic DND.
1379--
1380treeViewEnableModelDragSource :: TreeViewClass self => self
1381 -> [Modifier]                -- ^ @startButtonMask@ - Mask of allowed buttons
1382                              -- to start drag
1383 -> TargetList                -- ^ @targets@ - the list of targets that the
1384                              -- the view will support
1385 -> [DragAction]              -- ^ @actions@ - flags denoting the possible actions
1386                              -- for a drag from this widget
1387 -> IO ()
1388treeViewEnableModelDragSource self startButtonMask targets actions =
1389  alloca $ \nTargetsPtr -> do
1390  tlPtr <- {#call unsafe gtk_target_table_new_from_list#} targets nTargetsPtr
1391  nTargets <- peek nTargetsPtr
1392  {# call gtk_tree_view_enable_model_drag_source #}
1393    (toTreeView self)
1394    ((fromIntegral . fromFlags) startButtonMask)
1395    tlPtr
1396    nTargets
1397    ((fromIntegral . fromFlags) actions)
1398  {#call unsafe gtk_target_table_free#} tlPtr nTargets
1399
1400-- %hash c:5201 d:f3be
1401-- | Undoes the effect of 'treeViewEnableModelDragSource'.
1402--
1403treeViewUnsetRowsDragSource :: TreeViewClass self => self -> IO ()
1404treeViewUnsetRowsDragSource self =
1405  {# call gtk_tree_view_unset_rows_drag_source #}
1406    (toTreeView self)
1407
1408-- %hash c:e31e d:323d
1409-- | Undoes the effect of 'treeViewEnableModelDragDest'.
1410--
1411treeViewUnsetRowsDragDest :: TreeViewClass self => self -> IO ()
1412treeViewUnsetRowsDragDest self =
1413  {# call gtk_tree_view_unset_rows_drag_dest #}
1414    (toTreeView self)
1415
1416-- %hash c:3355 d:3bbe
1417-- | Returns the 'Entry' which is currently in use as interactive search entry
1418-- for @treeView@. In case the built-in entry is being used, @Nothing@ will be
1419-- returned.
1420--
1421-- * Available since Gtk+ version 2.10
1422--
1423treeViewGetSearchEntry :: TreeViewClass self => self
1424 -> IO (Maybe Entry) -- ^ returns the entry currently in use as search entry.
1425treeViewGetSearchEntry self = do
1426  ePtr <- {# call gtk_tree_view_get_search_entry #}
1427    (toTreeView self)
1428  if ePtr==nullPtr then return Nothing else liftM Just $
1429    makeNewObject mkEntry (return ePtr)
1430
1431-- %hash c:5e11 d:8ec5
1432-- | Sets the entry which the interactive search code will use for this
1433-- @treeView@. This is useful when you want to provide a search entry in our
1434-- interface at all time at a fixed position. Passing @Nothing@ for @entry@
1435-- will make the interactive search code use the built-in popup entry again.
1436--
1437-- * Available since Gtk+ version 2.10
1438--
1439treeViewSetSearchEntry :: (TreeViewClass self, EntryClass entry) => self
1440 -> (Maybe entry)
1441          -- ^ @entry@ - the entry the interactive search code of @treeView@
1442          -- should use or @Nothing@
1443 -> IO ()
1444treeViewSetSearchEntry self (Just entry) =
1445  {# call gtk_tree_view_set_search_entry #}
1446    (toTreeView self)
1447    (toEntry entry)
1448treeViewSetSearchEntry self Nothing =
1449  {# call gtk_tree_view_set_search_entry #}
1450    (toTreeView self)
1451    (Entry nullForeignPtr)
1452#endif
1453
1454#if GTK_CHECK_VERSION(2,6,0)
1455-- %hash c:6326 d:a050
1456-- | Sets the row separator function, which is used to determine whether a row
1457-- should be drawn as a separator. If the row separator function is @Nothing@,
1458-- no separators are drawn. This is the default value.
1459--
1460-- * Available since Gtk+ version 2.6
1461--
1462treeViewSetRowSeparatorFunc :: TreeViewClass self => self
1463 -> Maybe (TreeIter -> IO Bool)     -- ^ @func@ - a callback function that
1464                                    -- returns @True@ if the given row of
1465                                    -- the model should be drawn as separator
1466 -> IO ()
1467treeViewSetRowSeparatorFunc self Nothing =
1468  {# call gtk_tree_view_set_row_separator_func #}
1469    (toTreeView self) nullFunPtr nullPtr nullFunPtr
1470treeViewSetRowSeparatorFunc self (Just func) = do
1471  funcPtr <- mkTreeViewRowSeparatorFunc $ \_ tiPtr _ -> do
1472    ti <- peekTreeIter tiPtr
1473    liftM fromBool $ func ti
1474  {# call gtk_tree_view_set_row_separator_func #}
1475    (toTreeView self) funcPtr (castFunPtrToPtr funcPtr) destroyFunPtr
1476
1477{#pointer TreeViewRowSeparatorFunc #}
1478
1479foreign import ccall "wrapper" mkTreeViewRowSeparatorFunc ::
1480  (Ptr TreeModel -> Ptr TreeIter -> Ptr () -> IO {#type gboolean#}) ->
1481  IO TreeViewRowSeparatorFunc
1482
1483#if GTK_CHECK_VERSION(2,10,0)
1484-- %hash c:778a d:eacd
1485-- | Returns whether rubber banding is turned on for @treeView@. If the
1486-- selection mode is 'SelectionMultiple', rubber banding will allow the user to
1487-- select multiple rows by dragging the mouse.
1488--
1489-- * Available since Gtk+ version 2.10
1490--
1491treeViewGetRubberBanding :: TreeViewClass self => self
1492 -> IO Bool -- ^ returns @True@ if rubber banding in @treeView@ is enabled.
1493treeViewGetRubberBanding self =
1494  liftM toBool $
1495  {# call gtk_tree_view_get_rubber_banding #}
1496    (toTreeView self)
1497
1498-- %hash c:4a69 d:93aa
1499-- | Enables or disables rubber banding in @treeView@. If the selection mode
1500-- is 'SelectionMultiple', rubber banding will allow the user to select
1501-- multiple rows by dragging the mouse.
1502--
1503-- * Available since Gtk+ version 2.10
1504--
1505treeViewSetRubberBanding :: TreeViewClass self => self
1506 -> Bool -- ^ @enable@ - @True@ to enable rubber banding
1507 -> IO ()
1508treeViewSetRubberBanding self enable =
1509  {# call gtk_tree_view_set_rubber_banding #}
1510    (toTreeView self)
1511    (fromBool enable)
1512
1513-- %hash c:c8f8 d:c47
1514-- | Returns whether or not tree lines are drawn in @treeView@.
1515--
1516-- * Available since Gtk+ version 2.10
1517--
1518treeViewGetEnableTreeLines :: TreeViewClass self => self
1519 -> IO Bool -- ^ returns @True@ if tree lines are drawn in @treeView@, @False@
1520            -- otherwise.
1521treeViewGetEnableTreeLines self =
1522  liftM toBool $
1523  {# call gtk_tree_view_get_enable_tree_lines #}
1524    (toTreeView self)
1525
1526-- %hash c:205d d:1df9
1527-- | Sets whether to draw lines interconnecting the expanders in @treeView@.
1528-- This does not have any visible effects for lists.
1529--
1530-- * Available since Gtk+ version 2.10
1531--
1532treeViewSetEnableTreeLines :: TreeViewClass self => self
1533 -> Bool -- ^ @enabled@ - @True@ to enable tree line drawing, @False@
1534         -- otherwise.
1535 -> IO ()
1536treeViewSetEnableTreeLines self enabled =
1537  {# call gtk_tree_view_set_enable_tree_lines #}
1538    (toTreeView self)
1539    (fromBool enabled)
1540
1541-- | Grid lines.
1542{#enum TreeViewGridLines {underscoreToCase}#}
1543
1544-- %hash c:cd40 d:fe96
1545-- | Returns which grid lines are enabled in @treeView@.
1546--
1547-- * Available since Gtk+ version 2.10
1548--
1549treeViewGetGridLines :: TreeViewClass self => self
1550 -> IO TreeViewGridLines -- ^ returns a 'TreeViewGridLines' value indicating
1551                         -- which grid lines are enabled.
1552treeViewGetGridLines self =
1553  liftM (toEnum . fromIntegral) $
1554  {# call gtk_tree_view_get_grid_lines #}
1555    (toTreeView self)
1556
1557-- %hash c:74b0 d:79f0
1558-- | Sets which grid lines to draw in @treeView@.
1559--
1560-- * Available since Gtk+ version 2.10
1561--
1562treeViewSetGridLines :: TreeViewClass self => self
1563 -> TreeViewGridLines -- ^ @gridLines@ - a 'TreeViewGridLines' value
1564                      -- indicating which grid lines to enable.
1565 -> IO ()
1566treeViewSetGridLines self gridLines =
1567  {# call gtk_tree_view_set_grid_lines #}
1568    (toTreeView self)
1569    ((fromIntegral . fromEnum) gridLines)
1570#endif
1571#endif
1572
1573#if GTK_CHECK_VERSION(2,12,0)
1574-- | Sets the tip area of @tooltip@ to be the area covered by @path@. See also
1575-- 'treeViewTooltipColumn' for a simpler alternative. See also
1576-- 'tooltipSetTipArea'.
1577treeViewSetTooltipRow :: TreeViewClass self => self
1578  -> Tooltip -- ^ the @tooltip@
1579  -> TreePath -- ^ @path@ - the position of the @tooltip@
1580  -> IO ()
1581treeViewSetTooltipRow self tip path =
1582  withTreePath path $ \path ->
1583  {#call gtk_tree_view_set_tooltip_row #} (toTreeView self) tip path
1584
1585-- | Sets the tip area of tooltip to the area path, column and cell have in
1586-- common. For example if @path@ is @Nothing@ and @column@ is set, the tip area will be
1587-- set to the full area covered by column. See also
1588-- 'tooltipSetTipArea'. Note that if @path@ is not specified and @cell@ is
1589-- set and part of a column containing the expander, the tooltip might not
1590-- show and hide at the correct position. In such cases @path@ must be set to
1591-- the current node under the mouse cursor for this function to operate
1592-- correctly. See also 'treeViewTooltipColumn' for a simpler alternative.
1593--
1594treeViewSetTooltipCell :: (TreeViewClass self, TreeViewColumnClass col,
1595                           CellRendererClass renderer) => self
1596  -> Tooltip -- ^ the @tooltip@
1597  -> Maybe TreePath -- ^ @path@ at which the tip should be shown
1598  -> Maybe col -- ^ @column@ at which the tip should be shown
1599  -> Maybe renderer -- ^ the @renderer@ for which to show the tip
1600  -> IO ()
1601treeViewSetTooltipCell self tip mPath mColumn mRenderer =
1602  (case mPath of Just path -> withTreePath path
1603                 Nothing -> \f -> f (NativeTreePath nullPtr)) $ \path -> do
1604  {#call gtk_tree_view_set_tooltip_cell#} (toTreeView self) tip path
1605    (maybe (TreeViewColumn nullForeignPtr) toTreeViewColumn mColumn)
1606    (maybe (CellRenderer nullForeignPtr) toCellRenderer mRenderer)
1607
1608-- | This function is supposed to be used in a 'widgetQueryTooltip' signal handler
1609-- for this 'TreeView'. The @point@ value which is received in the
1610-- signal handler should be passed to this function without modification. A
1611-- return value of @Just iter@ indicates that there is a tree view row at the given
1612-- coordinates (if @Just (x,y)@ is passed in, denoting a mouse position), resp.
1613-- the cursor row (if @Nothing@ is passed in, denoting a keyboard request).
1614--
1615treeViewGetTooltipContext :: TreeViewClass self => self
1616  -> Maybe Point -- ^ @point@ - the coordinates of the mouse or @Nothing@
1617                 --   if a keyboard tooltip is to be generated
1618  -> IO (Maybe TreeIter) -- ^ @Just iter@ if a tooltip should be shown for that row
1619treeViewGetTooltipContext self (Just (x,y)) =
1620  alloca $ \xPtr -> alloca $ \yPtr -> receiveTreeIter $
1621    {#call gtk_tree_view_get_tooltip_context#} (toTreeView self)
1622    xPtr yPtr 0 nullPtr nullPtr
1623treeViewGetTooltipContext self Nothing =
1624  receiveTreeIter $
1625    {#call gtk_tree_view_get_tooltip_context#} (toTreeView self)
1626    nullPtr nullPtr 1 nullPtr nullPtr
1627#endif
1628
1629--------------------
1630-- Attributes
1631
1632-- | The model for the tree view.
1633--
1634treeViewModel :: TreeViewClass self => Attr self (Maybe TreeModel)
1635treeViewModel = newAttr
1636  treeViewGetModel
1637  treeViewSetModel
1638
1639-- | Horizontal Adjustment for the widget.
1640--
1641treeViewHAdjustment :: TreeViewClass self => Attr self (Maybe Adjustment)
1642treeViewHAdjustment = newAttr
1643  treeViewGetHAdjustment
1644  treeViewSetHAdjustment
1645
1646-- | Vertical Adjustment for the widget.
1647--
1648treeViewVAdjustment :: TreeViewClass self => Attr self (Maybe Adjustment)
1649treeViewVAdjustment = newAttr
1650  treeViewGetVAdjustment
1651  treeViewSetVAdjustment
1652
1653-- | Show the column header buttons.
1654--
1655-- Default value: @True@
1656--
1657treeViewHeadersVisible :: TreeViewClass self => Attr self Bool
1658treeViewHeadersVisible = newAttr
1659  treeViewGetHeadersVisible
1660  treeViewSetHeadersVisible
1661
1662-- | Column headers respond to click events.
1663--
1664-- Default value: @False@
1665--
1666treeViewHeadersClickable :: TreeViewClass self => Attr self Bool
1667treeViewHeadersClickable = newAttrFromBoolProperty "headers-clickable"
1668
1669-- | Set the column for the expander column.
1670--
1671treeViewExpanderColumn :: TreeViewClass self => ReadWriteAttr self TreeViewColumn (Maybe TreeViewColumn)
1672treeViewExpanderColumn = newAttr
1673  treeViewGetExpanderColumn
1674  treeViewSetExpanderColumn
1675
1676-- | View is reorderable.
1677--
1678-- Default value: @False@
1679--
1680treeViewReorderable :: TreeViewClass self => Attr self Bool
1681treeViewReorderable = newAttr
1682  treeViewGetReorderable
1683  treeViewSetReorderable
1684
1685-- | Set a hint to the theme engine to draw rows in alternating colors.
1686--
1687-- Default value: @False@
1688--
1689treeViewRulesHint :: TreeViewClass self => Attr self Bool
1690treeViewRulesHint = newAttr
1691  treeViewGetRulesHint
1692  treeViewSetRulesHint
1693
1694-- | View allows user to search through columns interactively.
1695--
1696-- Default value: @True@
1697--
1698treeViewEnableSearch :: TreeViewClass self => Attr self Bool
1699treeViewEnableSearch = newAttr
1700  treeViewGetEnableSearch
1701  treeViewSetEnableSearch
1702
1703-- %hash c:e732
1704-- | Model column to search through when searching through code.
1705--
1706-- Default value: 'invalidColumnId'
1707--
1708treeViewSearchColumn :: (TreeViewClass self, GlibString string) => Attr self (ColumnId row string)
1709treeViewSearchColumn = newAttr
1710  treeViewGetSearchColumn
1711  treeViewSetSearchColumn
1712
1713#if GTK_CHECK_VERSION(2,4,0)
1714-- %hash c:c7ff d:24d1
1715-- | Setting the 'treeViewFixedHeightMode' property to @True@ speeds up 'TreeView'
1716-- by assuming that all rows have the same height. Only enable this option if
1717-- all rows are the same height. Please see 'treeViewSetFixedHeightMode' for
1718-- more information on this option.
1719--
1720-- Default value: @False@
1721--
1722-- * Available since Gtk+ version 2.4
1723--
1724treeViewFixedHeightMode :: TreeViewClass self => Attr self Bool
1725treeViewFixedHeightMode = newAttrFromBoolProperty "fixed-height-mode"
1726
1727#if GTK_CHECK_VERSION(2,6,0)
1728-- %hash c:2026 d:839a
1729-- | Enables of disables the hover selection mode of @treeView@. Hover
1730-- selection makes the selected row follow the pointer. Currently, this works
1731-- only for the selection modes 'SelectionSingle' and 'SelectionBrowse'.
1732--
1733-- This mode is primarily intended for 'TreeView's in popups, e.g. in
1734-- 'ComboBox' or 'EntryCompletion'.
1735--
1736-- Default value: @False@
1737--
1738-- * Available since Gtk+ version 2.6
1739--
1740treeViewHoverSelection :: TreeViewClass self => Attr self Bool
1741treeViewHoverSelection = newAttrFromBoolProperty "hover-selection"
1742
1743-- %hash c:c694 d:3f15
1744-- | Enables of disables the hover expansion mode of @treeView@. Hover
1745-- expansion makes rows expand or collaps if the pointer moves over them.
1746--
1747-- This mode is primarily intended for 'TreeView's in popups, e.g. in
1748-- 'ComboBox' or 'EntryCompletion'.
1749--
1750-- Default value: @False@
1751--
1752-- * Available since Gtk+ version 2.6
1753--
1754treeViewHoverExpand :: TreeViewClass self => Attr self Bool
1755treeViewHoverExpand = newAttrFromBoolProperty "hover-expand"
1756#endif
1757#endif
1758
1759-- %hash c:b409 d:2ed2
1760-- | View has expanders.
1761--
1762-- Default value: @True@
1763--
1764treeViewShowExpanders :: TreeViewClass self => Attr self Bool
1765treeViewShowExpanders = newAttrFromBoolProperty "show-expanders"
1766
1767-- %hash c:f0e5 d:9017
1768-- | Extra indentation for each level.
1769--
1770-- Allowed values: >= 0
1771--
1772-- Default value: 0
1773--
1774treeViewLevelIndentation :: TreeViewClass self => Attr self Int
1775treeViewLevelIndentation = newAttrFromIntProperty "level-indentation"
1776
1777-- %hash c:a647 d:9e53
1778-- | Whether to enable selection of multiple items by dragging the mouse
1779-- pointer.
1780--
1781-- Default value: @False@
1782--
1783treeViewRubberBanding :: TreeViewClass self => Attr self Bool
1784treeViewRubberBanding = newAttrFromBoolProperty "rubber-banding"
1785
1786#if GTK_CHECK_VERSION(2,10,0)
1787-- %hash c:e926 d:86a8
1788-- | Whether grid lines should be drawn in the tree view.
1789--
1790-- Default value: 'TreeViewGridLinesNone'
1791--
1792treeViewEnableGridLines :: TreeViewClass self => Attr self TreeViewGridLines
1793treeViewEnableGridLines = newAttrFromEnumProperty "enable-grid-lines"
1794                            {# call pure unsafe gtk_tree_view_grid_lines_get_type #}
1795#endif
1796
1797-- %hash c:a7eb d:4c53
1798-- | Whether tree lines should be drawn in the tree view.
1799--
1800-- Default value: @False@
1801--
1802treeViewEnableTreeLines :: TreeViewClass self => Attr self Bool
1803treeViewEnableTreeLines = newAttrFromBoolProperty "enable-tree-lines"
1804
1805#if GTK_CHECK_VERSION(2,10,0)
1806-- %hash c:688c d:cbcd
1807-- | \'gridLines\' property. See 'treeViewGetGridLines' and
1808-- 'treeViewSetGridLines'
1809--
1810treeViewGridLines :: TreeViewClass self => Attr self TreeViewGridLines
1811treeViewGridLines = newAttr
1812  treeViewGetGridLines
1813  treeViewSetGridLines
1814
1815-- %hash c:9cbe d:2962
1816-- | \'searchEntry\' property. See 'treeViewGetSearchEntry' and
1817-- 'treeViewSetSearchEntry'
1818--
1819treeViewSearchEntry :: (TreeViewClass self, EntryClass entry) => ReadWriteAttr self (Maybe Entry) (Maybe entry)
1820treeViewSearchEntry = newAttr
1821  treeViewGetSearchEntry
1822  treeViewSetSearchEntry
1823#endif
1824
1825#if GTK_CHECK_VERSION(2,12,0)
1826-- | The column for which to show tooltips.
1827--
1828-- If you only plan to have simple (text-only) tooltips on full rows, you can
1829-- use this function to have 'TreeView' handle these automatically for you.
1830-- @column@ should be set to a column in model containing the tooltip texts,
1831-- or @-1@ to disable this feature. When enabled, 'widgetHasTooltip' will be
1832-- set to @True@ and this view will connect to the 'widgetQueryTooltip' signal
1833-- handler.
1834--
1835-- Note that the signal handler sets the text as 'Markup',
1836-- so \&, \<, etc have to be escaped in the text.
1837--
1838-- Default value: 'invalidColumnId'
1839--
1840treeViewTooltipColumn :: (TreeViewClass self, GlibString string) => Attr self (ColumnId row string)
1841treeViewTooltipColumn = newAttr
1842  (\self -> liftM (makeColumnIdString . fromIntegral) $
1843  {# call unsafe tree_view_get_tooltip_column #}
1844    (toTreeView self)
1845  )
1846  (\self column ->
1847  {# call tree_view_set_tooltip_column #}
1848    (toTreeView self)
1849    (fromIntegral (columnIdToNumber column))
1850  )
1851#endif
1852
1853--------------------
1854-- Signals
1855
1856-- %hash c:9fc5 d:3e66
1857-- | The given row is about to be expanded (show its children nodes). Use this
1858-- signal if you need to control the expandability of individual rows.
1859--
1860testExpandRow :: TreeViewClass self => Signal self (TreeIter -> TreePath -> IO Bool)
1861testExpandRow = Signal (connect_BOXED_BOXED__BOOL "test-expand-row" peek readNTP)
1862
1863-- %hash c:20de d:96a3
1864-- | The given row is about to be collapsed (hide its children nodes). Use
1865-- this signal if you need to control the collapsibility of individual rows.
1866--
1867testCollapseRow :: TreeViewClass self => Signal self (TreeIter -> TreePath -> IO Bool)
1868testCollapseRow = Signal (connect_BOXED_BOXED__BOOL "test-collapse-row" peek readNTP)
1869
1870-- %hash c:16dc d:b113
1871-- | The given row has been expanded (child nodes are shown).
1872--
1873rowExpanded :: TreeViewClass self => Signal self (TreeIter -> TreePath -> IO ())
1874rowExpanded = Signal (connect_BOXED_BOXED__NONE "row-expanded" peek readNTP)
1875
1876-- | A row was activated.
1877--
1878-- * Activation usually means the user has pressed return on a row.
1879--
1880rowActivated :: TreeViewClass self => Signal self (TreePath -> TreeViewColumn -> IO ())
1881rowActivated = Signal (connect_BOXED_OBJECT__NONE "row-activated" readNTP)
1882
1883-- %hash c:9ee6 d:325e
1884-- | The given row has been collapsed (child nodes are hidden).
1885--
1886rowCollapsed :: TreeViewClass self => Signal self (TreeIter -> TreePath -> IO ())
1887rowCollapsed = Signal (connect_BOXED_BOXED__NONE "row-collapsed" peek readNTP)
1888
1889-- %hash c:4350 d:4f94
1890-- | The number of columns of the treeview has changed.
1891--
1892columnsChanged :: TreeViewClass self => Signal self (IO ())
1893columnsChanged = Signal (connect_NONE__NONE "columns-changed")
1894
1895-- %hash c:6487 d:5b57
1896-- | The position of the cursor (focused cell) has changed.
1897--
1898cursorChanged :: TreeViewClass self => Signal self (IO ())
1899cursorChanged = Signal (connect_NONE__NONE "cursor-changed")
1900
1901--------------------
1902-- Deprecated Signals
1903
1904#ifndef DISABLE_DEPRECATED
1905
1906-- | The user has dragged a column to another position.
1907--
1908onColumnsChanged, afterColumnsChanged :: TreeViewClass self => self
1909 -> IO ()
1910 -> IO (ConnectId self)
1911onColumnsChanged = connect_NONE__NONE "columns_changed" False
1912afterColumnsChanged = connect_NONE__NONE "columns_changed" True
1913
1914-- | The cursor in the tree has moved.
1915--
1916onCursorChanged, afterCursorChanged :: TreeViewClass self => self
1917 -> IO ()
1918 -> IO (ConnectId self)
1919onCursorChanged = connect_NONE__NONE "cursor_changed" False
1920afterCursorChanged = connect_NONE__NONE "cursor_changed" True
1921
1922-- | A row was activated.
1923--
1924-- * Activation usually means the user has pressed return on a row.
1925--
1926onRowActivated, afterRowActivated :: TreeViewClass self => self
1927 -> (TreePath -> TreeViewColumn -> IO ())
1928 -> IO (ConnectId self)
1929onRowActivated = connect_BOXED_OBJECT__NONE "row_activated"
1930                   readNTP False
1931afterRowActivated = connect_BOXED_OBJECT__NONE "row_activated"
1932                      readNTP True
1933
1934-- | Children of this node were hidden.
1935--
1936onRowCollapsed, afterRowCollapsed :: TreeViewClass self => self
1937 -> (TreeIter -> TreePath -> IO ())
1938 -> IO (ConnectId self)
1939onRowCollapsed = connect_BOXED_BOXED__NONE "row_collapsed"
1940  peek readNTP False
1941afterRowCollapsed = connect_BOXED_BOXED__NONE "row_collapsed"
1942  peek readNTP True
1943
1944-- | Children of this node are made visible.
1945--
1946onRowExpanded, afterRowExpanded :: TreeViewClass self => self
1947 -> (TreeIter -> TreePath -> IO ())
1948 -> IO (ConnectId self)
1949onRowExpanded = connect_BOXED_BOXED__NONE "row_expanded"
1950  peek readNTP False
1951afterRowExpanded = connect_BOXED_BOXED__NONE "row_expanded"
1952  peek readNTP True
1953
1954-- | The user wants to search interactively.
1955--
1956-- * Connect to this signal if you want to provide you own search facility.
1957--   Note that you must handle all keyboard input yourself.
1958--
1959onStartInteractiveSearch, afterStartInteractiveSearch ::
1960  TreeViewClass self => self -> IO () -> IO (ConnectId self)
1961
1962#if GTK_CHECK_VERSION(2,2,0)
1963
1964onStartInteractiveSearch self fun =
1965  connect_NONE__BOOL "start_interactive_search" False self (fun >> return True)
1966afterStartInteractiveSearch self fun =
1967  connect_NONE__BOOL "start_interactive_search" True self (fun >> return True)
1968
1969#else
1970
1971onStartInteractiveSearch =
1972  connect_NONE__NONE "start_interactive_search" False
1973afterStartInteractiveSearch =
1974  connect_NONE__NONE "start_interactive_search" True
1975
1976#endif
1977
1978-- | Determine if this row should be collapsed.
1979--
1980-- * If the application connects to this function and returns @False@,
1981--   the specifc row will not be altered.
1982--
1983onTestCollapseRow, afterTestCollapseRow :: TreeViewClass self => self
1984 -> (TreeIter -> TreePath -> IO Bool)
1985 -> IO (ConnectId self)
1986onTestCollapseRow = connect_BOXED_BOXED__BOOL "test_collapse_row"
1987  peek readNTP False
1988afterTestCollapseRow = connect_BOXED_BOXED__BOOL "test_collapse_row"
1989  peek readNTP True
1990
1991-- | Determine if this row should be expanded.
1992--
1993-- * If the application connects to this function and returns @False@,
1994--   the specifc row will not be altered.
1995--
1996onTestExpandRow, afterTestExpandRow :: TreeViewClass self => self
1997 -> (TreeIter -> TreePath -> IO Bool)
1998 -> IO (ConnectId self)
1999onTestExpandRow = connect_BOXED_BOXED__BOOL "test_expand_row"
2000  peek readNTP False
2001afterTestExpandRow = connect_BOXED_BOXED__BOOL "test_expand_row"
2002  peek readNTP True
2003#endif
2004