Gtk2HsContentsIndex
Graphics.UI.Gtk.ModelView.TreeModel
Portabilityportable (depends on GHC)
Stabilityprovisional
Maintainergtk2hs-users@lists.sourceforge.net
Contents
Detail
Class Hierarchy
Types
Methods
Description
The tree interface used by TreeView
Synopsis
data TreeModel
class GObjectClass o => TreeModelClass o
castToTreeModel :: GObjectClass obj => obj -> TreeModel
toTreeModel :: TreeModelClass o => o -> TreeModel
data TreeModelFlags
= TreeModelItersPersist
| TreeModelListOnly
type TreePath = [Int]
data TreeRowReference
data TreeIter
treeModelGetFlags :: TreeModelClass self => self -> IO [TreeModelFlags]
treeModelGetNColumns :: TreeModelClass self => self -> IO Int
treeModelGetColumnType :: TreeModelClass self => self -> Int -> IO TMType
treeModelGetValue :: TreeModelClass self => self -> TreeIter -> Int -> IO GenericValue
treeRowReferenceNew :: TreeModelClass self => self -> NativeTreePath -> IO TreeRowReference
treeRowReferenceGetPath :: TreeRowReference -> IO TreePath
treeRowReferenceValid :: TreeRowReference -> IO Bool
treeModelGetIter :: TreeModelClass self => self -> TreePath -> IO (Maybe TreeIter)
treeModelGetIterFromString :: TreeModelClass self => self -> String -> IO (Maybe TreeIter)
gtk_tree_model_get_iter_from_string :: Ptr TreeModel -> Ptr TreeIter -> Ptr CChar -> IO CInt
treeModelGetIterFirst :: TreeModelClass self => self -> IO (Maybe TreeIter)
treeModelGetPath :: TreeModelClass self => self -> TreeIter -> IO TreePath
treeModelIterNext :: TreeModelClass self => self -> TreeIter -> IO (Maybe TreeIter)
treeModelIterChildren :: TreeModelClass self => self -> TreeIter -> IO (Maybe TreeIter)
treeModelIterHasChild :: TreeModelClass self => self -> TreeIter -> IO Bool
treeModelIterNChildren :: TreeModelClass self => self -> Maybe TreeIter -> IO Int
treeModelIterNthChild :: TreeModelClass self => self -> Maybe TreeIter -> Int -> IO (Maybe TreeIter)
treeModelIterParent :: TreeModelClass self => self -> TreeIter -> IO (Maybe TreeIter)
Detail

The TreeModel interface defines a generic storage object for use by the TreeView widget. It is purely abstract, concrete implementations that store data for a list or tree are ListStore and TreeStore.

The model is represented as a hierarchical tree of strongly-typed, columned data. In other words, the model can be seen as a tree where every node has different values depending on which column is being queried. The type of data found in a column can be arbitrary, ranging from basic types like Strings or Int to user specific types. The types are homogeneous per column across all nodes. It is important to note that this interface only provides a way of examining a model and observing changes. The implementation of each individual model decides how and if changes are made.

Two generic models are provided that implement the TreeModel interface: the TreeStore and the ListStore. To use these, the developer simply pushes data into these models as necessary. These models provide the data structure as well as the TreeModel interface. In fact, they implement other interfaces making drag and drop, sorting, and storing data trivial.

Models are accessed on a node/column level of granularity. One can query for the value of a model at a certain node and a certain column on that node. There are two structures used to reference a particular node in a model. They are the TreePath and the TreeIter Most of the interface consists of operations on a TreeIter.

A path is essentially a potential node. It is a location on a model that may or may not actually correspond to a node on a specific model. A TreePath is in fact just a list of Ints and hence are easy to manipulate. Each number refers to the offset at that level. Thus, the path [0] refers to the root node and the path [2,4] refers to the fifth child of the third node.

By contrast, a TreeIter is a reference to a specific node on a specific model. It is an abstract data type filled in by the model. One can convert a path to an iterator by calling treeModelGetIter. These iterators are the primary way of accessing a model and are similar to the iterators used by TextBuffer. The model interface defines a set of operations using them for navigating the model.

The lifecycle of an iterator can be a little confusing at first. Iterators are expected to always be valid for as long as the model is unchanged (and doesn't emit a signal). Additionally, the TreeStore and ListStore models guarantee that an iterator is valid for as long as the node it refers to is valid. Although generally uninteresting, as one always has to allow for the case where iterators do not persist beyond a signal, some very important performance enhancements were made in the sort model. As a result, the TreeModelItersPersist flag was added to indicate this behavior.

Class Hierarchy
 |  GInterface
 |   +----TreeModel
 
Types
data TreeModel
show/hide Instances
class GObjectClass o => TreeModelClass o
show/hide Instances
castToTreeModel :: GObjectClass obj => obj -> TreeModel
toTreeModel :: TreeModelClass o => o -> TreeModel
data TreeModelFlags

These flags indicate various properties of a TreeModel.

Constructors
TreeModelItersPersist
TreeModelListOnly
show/hide Instances
type TreePath = [Int]
TreePath : a list of indices to specify a subtree or node in the hierarchical TreeStore database.
data TreeRowReference
Tree Row Reference : like a TreePath it points to a subtree or node, but it is persistent. It identifies the same node (so long as it exists) even when items are added, removed, or reordered.
data TreeIter
Tree Iterator: a pointer to an entry in a TreeModel.
show/hide Instances
Methods
treeModelGetFlags :: TreeModelClass self => self -> IO [TreeModelFlags]

Returns a set of flags supported by this interface.

The flags supported should not change during the lifecycle of the tree_model.

treeModelGetNColumns
:: TreeModelClass self
=> self
-> IO Intreturns The number of columns.
Returns the number of columns supported by the tree model.
treeModelGetColumnType
:: TreeModelClass self
=> self
-> Intindex - The column index.
-> IO TMType
Returns the type of the column.
treeModelGetValue
:: TreeModelClass self
=> self
-> TreeIter
-> Intcolumn - The column to lookup the value at.
-> IO GenericValue
Read the value of at a specific column and TreeIter.
treeRowReferenceNew :: TreeModelClass self => self -> NativeTreePath -> IO TreeRowReference
Creates a row reference based on a path. This reference will keep pointing to the node pointed to by the given path, so long as it exists.
treeRowReferenceGetPath :: TreeRowReference -> IO TreePath

Returns a path that the row reference currently points to.

  • The returned path may be the empty list if the reference was invalid.
treeRowReferenceValid :: TreeRowReference -> IO Bool
Returns True if the reference refers to a current valid path.
treeModelGetIter
:: TreeModelClass self
=> self
-> TreePathpath - The TreePath.
-> IO (Maybe TreeIter)

Turn a TreePath into a TreeIter.

Returns Nothing if the given TreePath was invalid. The empty list is always invalid. The root node of a tree can be accessed by passing [0] as path.

treeModelGetIterFromString
:: TreeModelClass self
=> self
-> StringpathString - A string representation of a TreePath.
-> IO (Maybe TreeIter)

Turn a String into a TreeIter.

  • Returns Nothing if the string is not a colon separated list of numbers that references a valid node.
gtk_tree_model_get_iter_from_string :: Ptr TreeModel -> Ptr TreeIter -> Ptr CChar -> IO CInt
treeModelGetIterFirst :: TreeModelClass self => self -> IO (Maybe TreeIter)

Retrieves an TreeIter to the first entry.

Returns Nothing if the table is empty.

treeModelGetPath :: TreeModelClass self => self -> TreeIter -> IO TreePath

Turn an abstract TreeIter into a TreePath.

In case the given TreeIter was invalid, an empty list is returned.

treeModelIterNext :: TreeModelClass self => self -> TreeIter -> IO (Maybe TreeIter)
Retrieve an iterator to the next child.
treeModelIterChildren :: TreeModelClass self => self -> TreeIter -> IO (Maybe TreeIter)
Retrieve an iterator to the first child.
treeModelIterHasChild
:: TreeModelClass self
=> self
-> TreeIteriter - The TreeIter to test for children.
-> IO Boolreturns True if iter has children.
Returns True if iter has children, False otherwise.
treeModelIterNChildren
:: TreeModelClass self
=> self
-> Maybe TreeIteriter - The TreeIter, or Nothing.
-> IO Intreturns The number of children of iter.
Returns the number of children that iter has. As a special case, if iter is Nothing, then the number of toplevel nodes is returned.
treeModelIterNthChild
:: TreeModelClass self
=> self
-> Maybe TreeIterparent - The TreeIter to get the child from, or Nothing.
-> Intn - Then index of the desired child.
-> IO (Maybe TreeIter)

Retrieve the nth child.

If Nothing is specified for the self argument, the function will work on toplevel elements.

treeModelIterParent :: TreeModelClass self => self -> TreeIter -> IO (Maybe TreeIter)
Retrieve the parent of this iterator.
Produced by Haddock version 0.8