gi-gtk-hs-0.3.13: A wrapper for gi-gtk, adding a few more idiomatic API parts on top
Stabilityprovisional
Portabilityportable (depends on GHC)
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.GI.Gtk.ModelView.Types

Description

Common types and classes for the ModelView modules.

Synopsis

Documentation

newtype TypedTreeModel row Source #

Instances

Instances details
IsTypedTreeModel TypedTreeModel Source # 
Instance details

Defined in Data.GI.Gtk.ModelView.Types

Methods

dummy :: TypedTreeModel a -> a

class IsTypedTreeModel model Source #

Instances

Instances details
IsTypedTreeModel ForestStore Source # 
Instance details

Defined in Data.GI.Gtk.ModelView.ForestStore

Methods

dummy :: ForestStore a -> a

IsTypedTreeModel SeqStore Source # 
Instance details

Defined in Data.GI.Gtk.ModelView.SeqStore

Methods

dummy :: SeqStore a -> a

IsTypedTreeModel TypedTreeModel Source # 
Instance details

Defined in Data.GI.Gtk.ModelView.Types

Methods

dummy :: TypedTreeModel a -> a

IsTypedTreeModel TypedTreeModelFilter Source # 
Instance details

Defined in Data.GI.Gtk.ModelView.Types

Methods

dummy :: TypedTreeModelFilter a -> a

IsTypedTreeModel TypedTreeModelSort Source # 
Instance details

Defined in Data.GI.Gtk.ModelView.Types

Methods

dummy :: TypedTreeModelSort a -> a

newtype TypedTreeModelSort row Source #

Instances

Instances details
IsTypedTreeModel TypedTreeModelSort Source # 
Instance details

Defined in Data.GI.Gtk.ModelView.Types

Methods

dummy :: TypedTreeModelSort a -> a

GObject (TypedTreeModelSort row) Source # 
Instance details

Defined in Data.GI.Gtk.ModelView.Types

TypedObject (TypedTreeModelSort row) Source # 
Instance details

Defined in Data.GI.Gtk.ModelView.Types

Methods

glibType :: IO GType #

HasParentTypes (TypedTreeModelSort row) Source # 
Instance details

Defined in Data.GI.Gtk.ModelView.Types

type ParentTypes (TypedTreeModelSort row) Source # 
Instance details

Defined in Data.GI.Gtk.ModelView.Types

newtype TypedTreeModelFilter row Source #

Instances

Instances details
IsTypedTreeModel TypedTreeModelFilter Source # 
Instance details

Defined in Data.GI.Gtk.ModelView.Types

Methods

dummy :: TypedTreeModelFilter a -> a

treePathNewFromIndices' :: MonadIO m => [Int32] -> m TreePath Source #

TreePath is a list of indices to specify a subtree or node in a TreeModel. The node that correspond to a given TreePath might change if nodes are removed or added and a TreePath may refer to a different or even non-existent node after a modification of the model. In contrast, a TreeIter is a more compact representation of a TreePath which becomes invalid after each modification of the underlying model. An intelligent index that is adjusted with each update of the model to point to the same node (whenever possible) is TreeRowReference.

withTreePath :: MonadIO m => [Int32] -> (TreePath -> m a) -> m a Source #

stringToTreePath :: Text -> [Int32] Source #

Convert a comma or colon separated string into a TreePath. Any non-digit characters are assumed to separate indices, thus, the function always is always successful.

data ColumnAccess row where Source #

Accessing a row for a specific value. Used for ColumnMap.

Constructors

CAInvalid :: ColumnAccess row 
CAInt :: (row -> Int32) -> ColumnAccess row 
CABool :: (row -> Bool) -> ColumnAccess row 
CAString :: (row -> Text) -> ColumnAccess row 
CAPixbuf :: (row -> Pixbuf) -> ColumnAccess row 

data ColumnId row ty Source #

The type of a tree column.

Constructors

ColumnId (GValue -> IO ty) ((row -> ty) -> ColumnAccess row) Int32 

Instances

Instances details
Show (ColumnId row ty) Source # 
Instance details

Defined in Data.GI.Gtk.ModelView.TreeModel

Methods

showsPrec :: Int -> ColumnId row ty -> ShowS #

show :: ColumnId row ty -> String #

showList :: [ColumnId row ty] -> ShowS #

Eq (ColumnId row ty) Source # 
Instance details

Defined in Data.GI.Gtk.ModelView.TreeModel

Methods

(==) :: ColumnId row ty -> ColumnId row ty -> Bool #

(/=) :: ColumnId row ty -> ColumnId row ty -> Bool #