| Copyright | Will Thompson and Iñaki García Etxebarria | 
|---|---|
| License | LGPL-2.1 | 
| Maintainer | Iñaki García Etxebarria | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
GI.Gtk.Objects.CellArea
Contents
- Exported types
 - Methods
- activate
 - activateCell
 - add
 - addFocusSibling
 - applyAttributes
 - attributeConnect
 - attributeDisconnect
 - attributeGetColumn
 - cellGetProperty
 - cellSetProperty
 - copyContext
 - createContext
 - event
 - focus
 - foreach
 - foreachAlloc
 - getCellAllocation
 - getCellAtPosition
 - getCurrentPathString
 - getEditWidget
 - getEditedCell
 - getFocusCell
 - getFocusFromSibling
 - getFocusSiblings
 - getPreferredHeight
 - getPreferredHeightForWidth
 - getPreferredWidth
 - getPreferredWidthForHeight
 - getRequestMode
 - hasRenderer
 - innerCellArea
 - isActivatable
 - isFocusSibling
 - remove
 - removeFocusSibling
 - requestRenderer
 - setFocusCell
 - snapshot
 - stopEditing
 
 - Properties
 - Signals
 
Description
An abstract class for laying out GtkCellRenderers
The GtkCellArea is an abstract class for CellLayout
 widgets (also referred to as "layouting widgets") to interface with
 an arbitrary number of CellRenderers and interact with the user
 for a given TreeModel row.
The cell area handles events, focus navigation, drawing and size requests and allocations for a given row of data.
Usually users dont have to interact with the GtkCellArea directly
 unless they are implementing a cell-layouting widget themselves.
Requesting area sizes
As outlined in
 GtkWidget’s geometry management section,
 GTK uses a height-for-width
 geometry management system to compute the sizes of widgets and user
 interfaces. GtkCellArea uses the same semantics to calculate the
 size of an area for an arbitrary number of GtkTreeModel rows.
When requesting the size of a cell area one needs to calculate
 the size for a handful of rows, and this will be done differently by
 different layouting widgets. For instance a TreeViewColumn
 always lines up the areas from top to bottom while a IconView
 on the other hand might enforce that all areas received the same
 width and wrap the areas around, requesting height for more cell
 areas when allocated less width.
It’s also important for areas to maintain some cell
 alignments with areas rendered for adjacent rows (cells can
 appear “columnized” inside an area even when the size of
 cells are different in each row). For this reason the GtkCellArea
 uses a CellAreaContext object to store the alignments
 and sizes along the way (as well as the overall largest minimum
 and natural size for all the rows which have been calculated
 with the said context).
The CellAreaContext is an opaque object specific to the
 GtkCellArea which created it (see cellAreaCreateContext).
The owning cell-layouting widget can create as many contexts as
 it wishes to calculate sizes of rows which should receive the
 same size in at least one orientation (horizontally or vertically),
 However, it’s important that the same CellAreaContext which
 was used to request the sizes for a given GtkTreeModel row be
 used when rendering or processing events for that row.
In order to request the width of all the rows at the root level
 of a GtkTreeModel one would do the following:
c code
GtkTreeIter iter;
int minimum_width;
int natural_width;
valid = gtk_tree_model_get_iter_first (model, &iter);
while (valid)
  {
    gtk_cell_area_apply_attributes (area, model, &iter, FALSE, FALSE);
    gtk_cell_area_get_preferred_width (area, context, widget, NULL, NULL);
    valid = gtk_tree_model_iter_next (model, &iter);
  }
gtk_cell_area_context_get_preferred_width (context, &minimum_width, &natural_width);Note that in this example it’s not important to observe the
 returned minimum and natural width of the area for each row
 unless the cell-layouting object is actually interested in the
 widths of individual rows. The overall width is however stored
 in the accompanying GtkCellAreaContext object and can be consulted
 at any time.
This can be useful since GtkCellLayout widgets usually have to
 support requesting and rendering rows in treemodels with an
 exceedingly large amount of rows. The GtkCellLayout widget in
 that case would calculate the required width of the rows in an
 idle or timeout source (see timeoutAdd) and when the widget
 is requested its actual width in Widget.measure()
 it can simply consult the width accumulated so far in the
 GtkCellAreaContext object.
A simple example where rows are rendered from top to bottom and take up the full width of the layouting widget would look like:
c code
static void
foo_get_preferred_width (GtkWidget *widget,
                         int       *minimum_size,
                         int       *natural_size)
{
  Foo *self = FOO (widget);
  FooPrivate *priv = foo_get_instance_private (self);
  foo_ensure_at_least_one_handfull_of_rows_have_been_requested (self);
  gtk_cell_area_context_get_preferred_width (priv->context, minimum_size, natural_size);
}In the above example the Foo widget has to make sure that some
 row sizes have been calculated (the amount of rows that Foo judged
 was appropriate to request space for in a single timeout iteration)
 before simply returning the amount of space required by the area via
 the GtkCellAreaContext.
Requesting the height for width (or width for height) of an area is
 a similar task except in this case the GtkCellAreaContext does not
 store the data (actually, it does not know how much space the layouting
 widget plans to allocate it for every row. It’s up to the layouting
 widget to render each row of data with the appropriate height and
 width which was requested by the GtkCellArea).
In order to request the height for width of all the rows at the
 root level of a GtkTreeModel one would do the following:
c code
GtkTreeIter iter;
int minimum_height;
int natural_height;
int full_minimum_height = 0;
int full_natural_height = 0;
valid = gtk_tree_model_get_iter_first (model, &iter);
while (valid)
  {
    gtk_cell_area_apply_attributes (area, model, &iter, FALSE, FALSE);
    gtk_cell_area_get_preferred_height_for_width (area, context, widget,
                                                  width, &minimum_height, &natural_height);
    if (width_is_for_allocation)
       cache_row_height (&iter, minimum_height, natural_height);
    full_minimum_height += minimum_height;
    full_natural_height += natural_height;
    valid = gtk_tree_model_iter_next (model, &iter);
  }Note that in the above example we would need to cache the heights returned for each row so that we would know what sizes to render the areas for each row. However we would only want to really cache the heights if the request is intended for the layouting widgets real allocation.
In some cases the layouting widget is requested the height for an
 arbitrary for_width, this is a special case for layouting widgets
 who need to request size for tens of thousands  of rows. For this
 case it’s only important that the layouting widget calculate
 one reasonably sized chunk of rows and return that height
 synchronously. The reasoning here is that any layouting widget is
 at least capable of synchronously calculating enough height to fill
 the screen height (or scrolled window height) in response to a single
 call to Widget.measure(). Returning
 a perfect height for width that is larger than the screen area is
 inconsequential since after the layouting receives an allocation
 from a scrolled window it simply continues to drive the scrollbar
 values while more and more height is required for the row heights
 that are calculated in the background.
Rendering Areas
Once area sizes have been acquired at least for the rows in the
 visible area of the layouting widget they can be rendered at
 Widget.snapshot() time.
A crude example of how to render all the rows at the root level runs as follows:
c code
GtkAllocation allocation;
GdkRectangle cell_area = { 0, };
GtkTreeIter iter;
int minimum_width;
int natural_width;
gtk_widget_get_allocation (widget, &allocation);
cell_area.width = allocation.width;
valid = gtk_tree_model_get_iter_first (model, &iter);
while (valid)
  {
    cell_area.height = get_cached_height_for_row (&iter);
    gtk_cell_area_apply_attributes (area, model, &iter, FALSE, FALSE);
    gtk_cell_area_render (area, context, widget, cr,
                          &cell_area, &cell_area, state_flags, FALSE);
    cell_area.y += cell_area.height;
    valid = gtk_tree_model_iter_next (model, &iter);
  }Note that the cached height in this example really depends on how
 the layouting widget works. The layouting widget might decide to
 give every row its minimum or natural height or, if the model content
 is expected to fit inside the layouting widget without scrolling, it
 would make sense to calculate the allocation for each row at
 the time the widget is allocated using distributeNaturalAllocation.
Handling Events and Driving Keyboard Focus
Passing events to the area is as simple as handling events on any
 normal widget and then passing them to the cellAreaEvent
 API as they come in. Usually GtkCellArea is only interested in
 button events, however some customized derived areas can be implemented
 who are interested in handling other events. Handling an event can
 trigger the CellArea::focusChanged signal to fire; as well
 as CellArea::addEditable in the case that an editable cell
 was clicked and needs to start editing. You can call
 cellAreaStopEditing at any time to cancel any cell editing
 that is currently in progress.
The GtkCellArea drives keyboard focus from cell to cell in a way
 similar to GtkWidget. For layouting widgets that support giving
 focus to cells it’s important to remember to pass GTK_CELL_RENDERER_FOCUSED
 to the area functions for the row that has focus and to tell the
 area to paint the focus at render time.
Layouting widgets that accept focus on cells should implement the
 Widget.focus() virtual method. The layouting widget is always
 responsible for knowing where GtkTreeModel rows are rendered inside
 the widget, so at Widget.focus() time the layouting widget
 should use the GtkCellArea methods to navigate focus inside the area
 and then observe the DirectionType to pass the focus to adjacent
 rows and areas.
A basic example of how the Widget.focus() virtual method
 should be implemented:
static gboolean
foo_focus (GtkWidget       *widget,
           GtkDirectionType direction)
{
  Foo *self = FOO (widget);
  FooPrivate *priv = foo_get_instance_private (self);
  int focus_row = priv->focus_row;
  gboolean have_focus = FALSE;
  if (!gtk_widget_has_focus (widget))
    gtk_widget_grab_focus (widget);
  valid = gtk_tree_model_iter_nth_child (priv->model, &iter, NULL, priv->focus_row);
  while (valid)
    {
      gtk_cell_area_apply_attributes (priv->area, priv->model, &iter, FALSE, FALSE);
      if (gtk_cell_area_focus (priv->area, direction))
        {
           priv->focus_row = focus_row;
           have_focus = TRUE;
           break;
        }
      else
        {
          if (direction == GTK_DIR_RIGHT ||
              direction == GTK_DIR_LEFT)
            break;
          else if (direction == GTK_DIR_UP ||
                   direction == GTK_DIR_TAB_BACKWARD)
           {
              if (focus_row == 0)
                break;
              else
               {
                  focus_row--;
                  valid = gtk_tree_model_iter_nth_child (priv->model, &iter, NULL, focus_row);
               }
            }
          else
            {
              if (focus_row == last_row)
                break;
              else
                {
                  focus_row++;
                  valid = gtk_tree_model_iter_next (priv->model, &iter);
                }
            }
        }
    }
    return have_focus;
}Note that the layouting widget is responsible for matching the
 GtkDirectionType values to the way it lays out its cells.
Cell Properties
The GtkCellArea introduces cell properties for GtkCellRenderers.
 This provides some general interfaces for defining the relationship
 cell areas have with their cells. For instance in a CellAreaBox
 a cell might “expand” and receive extra space when the area is allocated
 more than its full natural request, or a cell might be configured to “align”
 with adjacent rows which were requested and rendered with the same
 GtkCellAreaContext.
Use cellAreaClassInstallCellProperty to install cell
 properties for a cell area class and cellAreaClassFindCellProperty
 or cellAreaClassListCellProperties to get information about
 existing cell properties.
To set the value of a cell property, use cellAreaCellSetProperty,
 CellArea.cell_set() or CellArea.cell_set_valist(). To obtain
 the value of a cell property, use cellAreaCellGetProperty
 CellArea.cell_get() or CellArea.cell_get_valist().
Synopsis
- newtype CellArea = CellArea (ManagedPtr CellArea)
 - class (GObject o, IsDescendantOf CellArea o) => IsCellArea o
 - toCellArea :: (MonadIO m, IsCellArea o) => o -> m CellArea
 - cellAreaActivate :: (HasCallStack, MonadIO m, IsCellArea a, IsCellAreaContext b, IsWidget c) => a -> b -> c -> Rectangle -> [CellRendererState] -> Bool -> m Bool
 - cellAreaActivateCell :: (HasCallStack, MonadIO m, IsCellArea a, IsWidget b, IsCellRenderer c, IsEvent d) => a -> b -> c -> d -> Rectangle -> [CellRendererState] -> m Bool
 - cellAreaAdd :: (HasCallStack, MonadIO m, IsCellArea a, IsCellRenderer b) => a -> b -> m ()
 - cellAreaAddFocusSibling :: (HasCallStack, MonadIO m, IsCellArea a, IsCellRenderer b, IsCellRenderer c) => a -> b -> c -> m ()
 - cellAreaApplyAttributes :: (HasCallStack, MonadIO m, IsCellArea a, IsTreeModel b) => a -> b -> TreeIter -> Bool -> Bool -> m ()
 - cellAreaAttributeConnect :: (HasCallStack, MonadIO m, IsCellArea a, IsCellRenderer b) => a -> b -> Text -> Int32 -> m ()
 - cellAreaAttributeDisconnect :: (HasCallStack, MonadIO m, IsCellArea a, IsCellRenderer b) => a -> b -> Text -> m ()
 - cellAreaAttributeGetColumn :: (HasCallStack, MonadIO m, IsCellArea a, IsCellRenderer b) => a -> b -> Text -> m Int32
 - cellAreaCellGetProperty :: (HasCallStack, MonadIO m, IsCellArea a, IsCellRenderer b) => a -> b -> Text -> GValue -> m ()
 - cellAreaCellSetProperty :: (HasCallStack, MonadIO m, IsCellArea a, IsCellRenderer b) => a -> b -> Text -> GValue -> m ()
 - cellAreaCopyContext :: (HasCallStack, MonadIO m, IsCellArea a, IsCellAreaContext b) => a -> b -> m CellAreaContext
 - cellAreaCreateContext :: (HasCallStack, MonadIO m, IsCellArea a) => a -> m CellAreaContext
 - cellAreaEvent :: (HasCallStack, MonadIO m, IsCellArea a, IsCellAreaContext b, IsWidget c, IsEvent d) => a -> b -> c -> d -> Rectangle -> [CellRendererState] -> m Int32
 - cellAreaFocus :: (HasCallStack, MonadIO m, IsCellArea a) => a -> DirectionType -> m Bool
 - cellAreaForeach :: (HasCallStack, MonadIO m, IsCellArea a) => a -> CellCallback -> m ()
 - cellAreaForeachAlloc :: (HasCallStack, MonadIO m, IsCellArea a, IsCellAreaContext b, IsWidget c) => a -> b -> c -> Rectangle -> Rectangle -> CellAllocCallback -> m ()
 - cellAreaGetCellAllocation :: (HasCallStack, MonadIO m, IsCellArea a, IsCellAreaContext b, IsWidget c, IsCellRenderer d) => a -> b -> c -> d -> Rectangle -> m Rectangle
 - cellAreaGetCellAtPosition :: (HasCallStack, MonadIO m, IsCellArea a, IsCellAreaContext b, IsWidget c) => a -> b -> c -> Rectangle -> Int32 -> Int32 -> m (CellRenderer, Rectangle)
 - cellAreaGetCurrentPathString :: (HasCallStack, MonadIO m, IsCellArea a) => a -> m Text
 - cellAreaGetEditWidget :: (HasCallStack, MonadIO m, IsCellArea a) => a -> m (Maybe CellEditable)
 - cellAreaGetEditedCell :: (HasCallStack, MonadIO m, IsCellArea a) => a -> m (Maybe CellRenderer)
 - cellAreaGetFocusCell :: (HasCallStack, MonadIO m, IsCellArea a) => a -> m (Maybe CellRenderer)
 - cellAreaGetFocusFromSibling :: (HasCallStack, MonadIO m, IsCellArea a, IsCellRenderer b) => a -> b -> m (Maybe CellRenderer)
 - cellAreaGetFocusSiblings :: (HasCallStack, MonadIO m, IsCellArea a, IsCellRenderer b) => a -> b -> m [CellRenderer]
 - cellAreaGetPreferredHeight :: (HasCallStack, MonadIO m, IsCellArea a, IsCellAreaContext b, IsWidget c) => a -> b -> c -> m (Int32, Int32)
 - cellAreaGetPreferredHeightForWidth :: (HasCallStack, MonadIO m, IsCellArea a, IsCellAreaContext b, IsWidget c) => a -> b -> c -> Int32 -> m (Int32, Int32)
 - cellAreaGetPreferredWidth :: (HasCallStack, MonadIO m, IsCellArea a, IsCellAreaContext b, IsWidget c) => a -> b -> c -> m (Int32, Int32)
 - cellAreaGetPreferredWidthForHeight :: (HasCallStack, MonadIO m, IsCellArea a, IsCellAreaContext b, IsWidget c) => a -> b -> c -> Int32 -> m (Int32, Int32)
 - cellAreaGetRequestMode :: (HasCallStack, MonadIO m, IsCellArea a) => a -> m SizeRequestMode
 - cellAreaHasRenderer :: (HasCallStack, MonadIO m, IsCellArea a, IsCellRenderer b) => a -> b -> m Bool
 - cellAreaInnerCellArea :: (HasCallStack, MonadIO m, IsCellArea a, IsWidget b) => a -> b -> Rectangle -> m Rectangle
 - cellAreaIsActivatable :: (HasCallStack, MonadIO m, IsCellArea a) => a -> m Bool
 - cellAreaIsFocusSibling :: (HasCallStack, MonadIO m, IsCellArea a, IsCellRenderer b, IsCellRenderer c) => a -> b -> c -> m Bool
 - cellAreaRemove :: (HasCallStack, MonadIO m, IsCellArea a, IsCellRenderer b) => a -> b -> m ()
 - cellAreaRemoveFocusSibling :: (HasCallStack, MonadIO m, IsCellArea a, IsCellRenderer b, IsCellRenderer c) => a -> b -> c -> m ()
 - cellAreaRequestRenderer :: (HasCallStack, MonadIO m, IsCellArea a, IsCellRenderer b, IsWidget c) => a -> b -> Orientation -> c -> Int32 -> m (Int32, Int32)
 - cellAreaSetFocusCell :: (HasCallStack, MonadIO m, IsCellArea a, IsCellRenderer b) => a -> Maybe b -> m ()
 - cellAreaSnapshot :: (HasCallStack, MonadIO m, IsCellArea a, IsCellAreaContext b, IsWidget c, IsSnapshot d) => a -> b -> c -> d -> Rectangle -> Rectangle -> [CellRendererState] -> Bool -> m ()
 - cellAreaStopEditing :: (HasCallStack, MonadIO m, IsCellArea a) => a -> Bool -> m ()
 - getCellAreaEditWidget :: (MonadIO m, IsCellArea o) => o -> m (Maybe CellEditable)
 - getCellAreaEditedCell :: (MonadIO m, IsCellArea o) => o -> m (Maybe CellRenderer)
 - clearCellAreaFocusCell :: (MonadIO m, IsCellArea o) => o -> m ()
 - constructCellAreaFocusCell :: (IsCellArea o, MonadIO m, IsCellRenderer a) => a -> m (GValueConstruct o)
 - getCellAreaFocusCell :: (MonadIO m, IsCellArea o) => o -> m (Maybe CellRenderer)
 - setCellAreaFocusCell :: (MonadIO m, IsCellArea o, IsCellRenderer a) => o -> a -> m ()
 - type CellAreaAddEditableCallback = CellRenderer -> CellEditable -> Rectangle -> Text -> IO ()
 - afterCellAreaAddEditable :: (IsCellArea a, MonadIO m) => a -> ((?self :: a) => CellAreaAddEditableCallback) -> m SignalHandlerId
 - onCellAreaAddEditable :: (IsCellArea a, MonadIO m) => a -> ((?self :: a) => CellAreaAddEditableCallback) -> m SignalHandlerId
 - type CellAreaApplyAttributesCallback = TreeModel -> TreeIter -> Bool -> Bool -> IO ()
 - afterCellAreaApplyAttributes :: (IsCellArea a, MonadIO m) => a -> ((?self :: a) => CellAreaApplyAttributesCallback) -> m SignalHandlerId
 - onCellAreaApplyAttributes :: (IsCellArea a, MonadIO m) => a -> ((?self :: a) => CellAreaApplyAttributesCallback) -> m SignalHandlerId
 - type CellAreaFocusChangedCallback = CellRenderer -> Text -> IO ()
 - afterCellAreaFocusChanged :: (IsCellArea a, MonadIO m) => a -> ((?self :: a) => CellAreaFocusChangedCallback) -> m SignalHandlerId
 - onCellAreaFocusChanged :: (IsCellArea a, MonadIO m) => a -> ((?self :: a) => CellAreaFocusChangedCallback) -> m SignalHandlerId
 - type CellAreaRemoveEditableCallback = CellRenderer -> CellEditable -> IO ()
 - afterCellAreaRemoveEditable :: (IsCellArea a, MonadIO m) => a -> ((?self :: a) => CellAreaRemoveEditableCallback) -> m SignalHandlerId
 - onCellAreaRemoveEditable :: (IsCellArea a, MonadIO m) => a -> ((?self :: a) => CellAreaRemoveEditableCallback) -> m SignalHandlerId
 
Exported types
Memory-managed wrapper type.
Constructors
| CellArea (ManagedPtr CellArea) | 
Instances
| Eq CellArea Source # | |
| GObject CellArea Source # | |
Defined in GI.Gtk.Objects.CellArea  | |
| ManagedPtrNewtype CellArea Source # | |
Defined in GI.Gtk.Objects.CellArea Methods toManagedPtr :: CellArea -> ManagedPtr CellArea #  | |
| TypedObject CellArea Source # | |
Defined in GI.Gtk.Objects.CellArea  | |
| HasParentTypes CellArea Source # | |
Defined in GI.Gtk.Objects.CellArea  | |
| IsGValue (Maybe CellArea) Source # | Convert   | 
Defined in GI.Gtk.Objects.CellArea  | |
| type ParentTypes CellArea Source # | |
Defined in GI.Gtk.Objects.CellArea  | |
class (GObject o, IsDescendantOf CellArea o) => IsCellArea o Source #
Type class for types which can be safely cast to CellArea, for instance with toCellArea.
Instances
| (GObject o, IsDescendantOf CellArea o) => IsCellArea o Source # | |
Defined in GI.Gtk.Objects.CellArea  | |
toCellArea :: (MonadIO m, IsCellArea o) => o -> m CellArea Source #
Methods
Click to display all available methods, including inherited ones
Methods
activate, activateCell, add, addAttribute, addFocusSibling, applyAttributes, attributeConnect, attributeDisconnect, attributeGetColumn, bindProperty, bindPropertyFull, cellGetProperty, cellSetProperty, clear, clearAttributes, copyContext, createContext, event, focus, forceFloating, foreach, foreachAlloc, freezeNotify, getv, hasRenderer, innerCellArea, isActivatable, isFloating, isFocusSibling, notify, notifyByPspec, packEnd, packStart, ref, refSink, remove, removeFocusSibling, reorder, requestRenderer, runDispose, snapshot, stealData, stealQdata, stopEditing, thawNotify, unref, watchClosure.
Getters
getArea, getBuildableId, getCellAllocation, getCellAtPosition, getCells, getCurrentPathString, getData, getEditWidget, getEditedCell, getFocusCell, getFocusFromSibling, getFocusSiblings, getPreferredHeight, getPreferredHeightForWidth, getPreferredWidth, getPreferredWidthForHeight, getProperty, getQdata, getRequestMode.
Setters
setCellDataFunc, setData, setDataFull, setFocusCell, setProperty.
activate
Arguments
| :: (HasCallStack, MonadIO m, IsCellArea a, IsCellAreaContext b, IsWidget c) | |
| => a | 
  | 
| -> b | 
  | 
| -> c | 
  | 
| -> Rectangle | 
  | 
| -> [CellRendererState] | 
  | 
| -> Bool | 
  | 
| -> m Bool | Returns: Whether   | 
Deprecated: (Since version 4.10)
Activates area, usually by activating the currently focused
 cell, however some subclasses which embed widgets in the area
 can also activate a widget if it currently has the focus.
activateCell
Arguments
| :: (HasCallStack, MonadIO m, IsCellArea a, IsWidget b, IsCellRenderer c, IsEvent d) | |
| => a | 
  | 
| -> b | 
  | 
| -> c | 
  | 
| -> d | 
  | 
| -> Rectangle | 
  | 
| -> [CellRendererState] | 
  | 
| -> m Bool | Returns: whether cell activation was successful  | 
Deprecated: (Since version 4.10)
This is used by GtkCellArea subclasses when handling events
 to activate cells, the base GtkCellArea class activates cells
 for keyboard events for free in its own GtkCellArea->activate()
 implementation.
add
Arguments
| :: (HasCallStack, MonadIO m, IsCellArea a, IsCellRenderer b) | |
| => a | 
  | 
| -> b | 
  | 
| -> m () | 
Deprecated: (Since version 4.10)
Adds renderer to area with the default child cell properties.
addFocusSibling
cellAreaAddFocusSibling Source #
Arguments
| :: (HasCallStack, MonadIO m, IsCellArea a, IsCellRenderer b, IsCellRenderer c) | |
| => a | 
  | 
| -> b | 
  | 
| -> c | 
  | 
| -> m () | 
Deprecated: (Since version 4.10)
Adds sibling to renderer’s focusable area, focus will be drawn
 around renderer and all of its siblings if renderer can
 focus for a given row.
Events handled by focus siblings can also activate the given
 focusable renderer.
applyAttributes
cellAreaApplyAttributes Source #
Arguments
| :: (HasCallStack, MonadIO m, IsCellArea a, IsTreeModel b) | |
| => a | 
  | 
| -> b | 
  | 
| -> TreeIter | 
  | 
| -> Bool | 
  | 
| -> Bool | 
  | 
| -> m () | 
Deprecated: (Since version 4.10)
Applies any connected attributes to the renderers in
 area by pulling the values from treeModel.
attributeConnect
cellAreaAttributeConnect Source #
Arguments
| :: (HasCallStack, MonadIO m, IsCellArea a, IsCellRenderer b) | |
| => a | 
  | 
| -> b | 
  | 
| -> Text | 
  | 
| -> Int32 | 
  | 
| -> m () | 
Deprecated: (Since version 4.10)
Connects an attribute to apply values from column for the
 GtkTreeModel in use.
attributeDisconnect
cellAreaAttributeDisconnect Source #
Arguments
| :: (HasCallStack, MonadIO m, IsCellArea a, IsCellRenderer b) | |
| => a | 
  | 
| -> b | 
  | 
| -> Text | 
  | 
| -> m () | 
Deprecated: (Since version 4.10)
Disconnects attribute for the renderer in area so that
 attribute will no longer be updated with values from the
 model.
attributeGetColumn
cellAreaAttributeGetColumn Source #
Arguments
| :: (HasCallStack, MonadIO m, IsCellArea a, IsCellRenderer b) | |
| => a | 
  | 
| -> b | 
  | 
| -> Text | 
  | 
| -> m Int32 | Returns: the model column, or -1  | 
Deprecated: (Since version 4.10)
Returns the model column that an attribute has been mapped to, or -1 if the attribute is not mapped.
cellGetProperty
cellAreaCellGetProperty Source #
Arguments
| :: (HasCallStack, MonadIO m, IsCellArea a, IsCellRenderer b) | |
| => a | 
  | 
| -> b | 
  | 
| -> Text | 
  | 
| -> GValue | 
  | 
| -> m () | 
Deprecated: (Since version 4.10)
Gets the value of a cell property for renderer in area.
cellSetProperty
cellAreaCellSetProperty Source #
Arguments
| :: (HasCallStack, MonadIO m, IsCellArea a, IsCellRenderer b) | |
| => a | 
  | 
| -> b | 
  | 
| -> Text | 
  | 
| -> GValue | 
  | 
| -> m () | 
Deprecated: (Since version 4.10)
Sets a cell property for renderer in area.
copyContext
Arguments
| :: (HasCallStack, MonadIO m, IsCellArea a, IsCellAreaContext b) | |
| => a | 
  | 
| -> b | 
  | 
| -> m CellAreaContext | Returns: a newly created   | 
Deprecated: (Since version 4.10)
This is sometimes needed for cases where rows need to share alignments in one orientation but may be separately grouped in the opposing orientation.
For instance, GtkIconView creates all icons (rows) to have
 the same width and the cells theirin to have the same
 horizontal alignments. However each row of icons may have
 a separate collective height. GtkIconView uses this to
 request the heights of each row based on a context which
 was already used to request all the row widths that are
 to be displayed.
createContext
cellAreaCreateContext Source #
Arguments
| :: (HasCallStack, MonadIO m, IsCellArea a) | |
| => a | 
  | 
| -> m CellAreaContext | Returns: a newly created   | 
Deprecated: (Since version 4.10)
Creates a GtkCellAreaContext to be used with area for
 all purposes. GtkCellAreaContext stores geometry information
 for rows for which it was operated on, it is important to use
 the same context for the same row of data at all times (i.e.
 one should render and handle events with the same GtkCellAreaContext
 which was used to request the size of those rows of data).
event
Arguments
| :: (HasCallStack, MonadIO m, IsCellArea a, IsCellAreaContext b, IsWidget c, IsEvent d) | |
| => a | 
  | 
| -> b | 
  | 
| -> c | 
  | 
| -> d | 
  | 
| -> Rectangle | 
  | 
| -> [CellRendererState] | 
  | 
| -> m Int32 | Returns:   | 
Deprecated: (Since version 4.10)
Delegates event handling to a GtkCellArea.
focus
Arguments
| :: (HasCallStack, MonadIO m, IsCellArea a) | |
| => a | 
  | 
| -> DirectionType | 
  | 
| -> m Bool | Returns:   | 
Deprecated: (Since version 4.10)
This should be called by the area’s owning layout widget
 when focus is to be passed to area, or moved within area
 for a given direction and row data.
Implementing GtkCellArea classes should implement this
 method to receive and navigate focus in its own way particular
 to how it lays out cells.
foreach
Arguments
| :: (HasCallStack, MonadIO m, IsCellArea a) | |
| => a | 
  | 
| -> CellCallback | 
  | 
| -> m () | 
Deprecated: (Since version 4.10)
Calls callback for every GtkCellRenderer in area.
foreachAlloc
Arguments
| :: (HasCallStack, MonadIO m, IsCellArea a, IsCellAreaContext b, IsWidget c) | |
| => a | 
  | 
| -> b | 
  | 
| -> c | 
  | 
| -> Rectangle | 
  | 
| -> Rectangle | 
  | 
| -> CellAllocCallback | 
  | 
| -> m () | 
Calls callback for every GtkCellRenderer in area with the
 allocated rectangle inside cellArea.
getCellAllocation
cellAreaGetCellAllocation Source #
Arguments
| :: (HasCallStack, MonadIO m, IsCellArea a, IsCellAreaContext b, IsWidget c, IsCellRenderer d) | |
| => a | 
  | 
| -> b | 
  | 
| -> c | 
  | 
| -> d | 
  | 
| -> Rectangle | 
  | 
| -> m Rectangle | 
Deprecated: (Since version 4.10)
Derives the allocation of renderer inside area if area
 were to be rendered in cellArea.
getCellAtPosition
cellAreaGetCellAtPosition Source #
Arguments
| :: (HasCallStack, MonadIO m, IsCellArea a, IsCellAreaContext b, IsWidget c) | |
| => a | 
  | 
| -> b | 
  | 
| -> c | 
  | 
| -> Rectangle | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> m (CellRenderer, Rectangle) | Returns: the   | 
Deprecated: (Since version 4.10)
Gets the GtkCellRenderer at x and y coordinates inside area and optionally
 returns the full cell allocation for it inside cellArea.
getCurrentPathString
cellAreaGetCurrentPathString Source #
Arguments
| :: (HasCallStack, MonadIO m, IsCellArea a) | |
| => a | 
  | 
| -> m Text | Returns: The current   | 
Gets the current GtkTreePath string for the currently
 applied GtkTreeIter, this is implicitly updated when
 cellAreaApplyAttributes is called and can be
 used to interact with renderers from GtkCellArea
 subclasses.
getEditWidget
cellAreaGetEditWidget Source #
Arguments
| :: (HasCallStack, MonadIO m, IsCellArea a) | |
| => a | 
  | 
| -> m (Maybe CellEditable) | Returns: The currently active   | 
Deprecated: (Since version 4.10)
Gets the GtkCellEditable widget currently used
 to edit the currently edited cell.
getEditedCell
cellAreaGetEditedCell Source #
Arguments
| :: (HasCallStack, MonadIO m, IsCellArea a) | |
| => a | 
  | 
| -> m (Maybe CellRenderer) | Returns: The currently edited   | 
Deprecated: (Since version 4.10)
Gets the GtkCellRenderer in area that is currently
 being edited.
getFocusCell
Arguments
| :: (HasCallStack, MonadIO m, IsCellArea a) | |
| => a | 
  | 
| -> m (Maybe CellRenderer) | Returns: the currently focused cell in   | 
Deprecated: (Since version 4.10)
Retrieves the currently focused cell for area
getFocusFromSibling
cellAreaGetFocusFromSibling Source #
Arguments
| :: (HasCallStack, MonadIO m, IsCellArea a, IsCellRenderer b) | |
| => a | 
  | 
| -> b | 
  | 
| -> m (Maybe CellRenderer) | Returns: the   | 
Deprecated: (Since version 4.10)
Gets the GtkCellRenderer which is expected to be focusable
 for which renderer is, or may be a sibling.
This is handy for GtkCellArea subclasses when handling events,
 after determining the renderer at the event location it can
 then chose to activate the focus cell for which the event
 cell may have been a sibling.
getFocusSiblings
cellAreaGetFocusSiblings Source #
Arguments
| :: (HasCallStack, MonadIO m, IsCellArea a, IsCellRenderer b) | |
| => a | 
  | 
| -> b | 
  | 
| -> m [CellRenderer] | Returns: A   | 
Deprecated: (Since version 4.10)
Gets the focus sibling cell renderers for renderer.
getPreferredHeight
cellAreaGetPreferredHeight Source #
Arguments
| :: (HasCallStack, MonadIO m, IsCellArea a, IsCellAreaContext b, IsWidget c) | |
| => a | 
  | 
| -> b | 
  | 
| -> c | 
  | 
| -> m (Int32, Int32) | 
Deprecated: (Since version 4.10)
Retrieves a cell area’s initial minimum and natural height.
area will store some geometrical information in context along the way;
 when requesting sizes over an arbitrary number of rows, it’s not important
 to check the minimumHeight and naturalHeight of this call but rather to
 consult cellAreaContextGetPreferredHeight after a series of
 requests.
getPreferredHeightForWidth
cellAreaGetPreferredHeightForWidth Source #
Arguments
| :: (HasCallStack, MonadIO m, IsCellArea a, IsCellAreaContext b, IsWidget c) | |
| => a | 
  | 
| -> b | 
  | 
| -> c | 
  | 
| -> Int32 | 
  | 
| -> m (Int32, Int32) | 
Deprecated: (Since version 4.10)
Retrieves a cell area’s minimum and natural height if it would be given
 the specified width.
area stores some geometrical information in context along the way
 while calling cellAreaGetPreferredWidth. It’s important to
 perform a series of cellAreaGetPreferredWidth requests with
 context first and then call cellAreaGetPreferredHeightForWidth
 on each cell area individually to get the height for width of each
 fully requested row.
If at some point, the width of a single row changes, it should be
 requested with cellAreaGetPreferredWidth again and then
 the full width of the requested rows checked again with
 cellAreaContextGetPreferredWidth.
getPreferredWidth
cellAreaGetPreferredWidth Source #
Arguments
| :: (HasCallStack, MonadIO m, IsCellArea a, IsCellAreaContext b, IsWidget c) | |
| => a | 
  | 
| -> b | 
  | 
| -> c | 
  | 
| -> m (Int32, Int32) | 
Deprecated: (Since version 4.10)
Retrieves a cell area’s initial minimum and natural width.
area will store some geometrical information in context along the way;
 when requesting sizes over an arbitrary number of rows, it’s not important
 to check the minimumWidth and naturalWidth of this call but rather to
 consult cellAreaContextGetPreferredWidth after a series of
 requests.
getPreferredWidthForHeight
cellAreaGetPreferredWidthForHeight Source #
Arguments
| :: (HasCallStack, MonadIO m, IsCellArea a, IsCellAreaContext b, IsWidget c) | |
| => a | 
  | 
| -> b | 
  | 
| -> c | 
  | 
| -> Int32 | 
  | 
| -> m (Int32, Int32) | 
Deprecated: (Since version 4.10)
Retrieves a cell area’s minimum and natural width if it would be given
 the specified height.
area stores some geometrical information in context along the way
 while calling cellAreaGetPreferredHeight. It’s important to
 perform a series of cellAreaGetPreferredHeight requests with
 context first and then call cellAreaGetPreferredWidthForHeight
 on each cell area individually to get the height for width of each
 fully requested row.
If at some point, the height of a single row changes, it should be
 requested with cellAreaGetPreferredHeight again and then
 the full height of the requested rows checked again with
 cellAreaContextGetPreferredHeight.
getRequestMode
cellAreaGetRequestMode Source #
Arguments
| :: (HasCallStack, MonadIO m, IsCellArea a) | |
| => a | 
  | 
| -> m SizeRequestMode | Returns: The   | 
Gets whether the area prefers a height-for-width layout or a width-for-height layout.
hasRenderer
Arguments
| :: (HasCallStack, MonadIO m, IsCellArea a, IsCellRenderer b) | |
| => a | 
  | 
| -> b | 
  | 
| -> m Bool | Returns:   | 
Deprecated: (Since version 4.10)
Checks if area contains renderer.
innerCellArea
cellAreaInnerCellArea Source #
Arguments
| :: (HasCallStack, MonadIO m, IsCellArea a, IsWidget b) | |
| => a | 
  | 
| -> b | 
  | 
| -> Rectangle | 
  | 
| -> m Rectangle | 
Deprecated: (Since version 4.10)
This is a convenience function for GtkCellArea implementations
 to get the inner area where a given GtkCellRenderer will be
 rendered. It removes any padding previously added by cellAreaRequestRenderer.
isActivatable
cellAreaIsActivatable Source #
Arguments
| :: (HasCallStack, MonadIO m, IsCellArea a) | |
| => a | 
  | 
| -> m Bool | Returns: whether   | 
Deprecated: (Since version 4.10)
Returns whether the area can do anything when activated,
 after applying new attributes to area.
isFocusSibling
cellAreaIsFocusSibling Source #
Arguments
| :: (HasCallStack, MonadIO m, IsCellArea a, IsCellRenderer b, IsCellRenderer c) | |
| => a | 
  | 
| -> b | 
  | 
| -> c | 
  | 
| -> m Bool | Returns:   | 
Deprecated: (Since version 4.10)
Returns whether sibling is one of renderer’s focus siblings
 (see cellAreaAddFocusSibling).
remove
Arguments
| :: (HasCallStack, MonadIO m, IsCellArea a, IsCellRenderer b) | |
| => a | 
  | 
| -> b | 
  | 
| -> m () | 
Deprecated: (Since version 4.10)
Removes renderer from area.
removeFocusSibling
cellAreaRemoveFocusSibling Source #
Arguments
| :: (HasCallStack, MonadIO m, IsCellArea a, IsCellRenderer b, IsCellRenderer c) | |
| => a | 
  | 
| -> b | 
  | 
| -> c | 
  | 
| -> m () | 
Deprecated: (Since version 4.10)
Removes sibling from renderer’s focus sibling list
 (see cellAreaAddFocusSibling).
requestRenderer
cellAreaRequestRenderer Source #
Arguments
| :: (HasCallStack, MonadIO m, IsCellArea a, IsCellRenderer b, IsWidget c) | |
| => a | 
  | 
| -> b | 
  | 
| -> Orientation | 
  | 
| -> c | 
  | 
| -> Int32 | 
  | 
| -> m (Int32, Int32) | 
Deprecated: (Since version 4.10)
This is a convenience function for GtkCellArea implementations
 to request size for cell renderers. It’s important to use this
 function to request size and then use cellAreaInnerCellArea
 at render and event time since this function will add padding
 around the cell for focus painting.
setFocusCell
Arguments
| :: (HasCallStack, MonadIO m, IsCellArea a, IsCellRenderer b) | |
| => a | 
  | 
| -> Maybe b | 
  | 
| -> m () | 
Deprecated: (Since version 4.10)
Explicitly sets the currently focused cell to renderer.
This is generally called by implementations of
 GtkCellAreaClass.focus() or GtkCellAreaClass.event(),
 however it can also be used to implement functions such
 as treeViewSetCursorOnCell.
snapshot
Arguments
| :: (HasCallStack, MonadIO m, IsCellArea a, IsCellAreaContext b, IsWidget c, IsSnapshot d) | |
| => a | 
  | 
| -> b | 
  | 
| -> c | 
  | 
| -> d | 
  | 
| -> Rectangle | 
  | 
| -> Rectangle | 
  | 
| -> [CellRendererState] | 
  | 
| -> Bool | 
  | 
| -> m () | 
Deprecated: (Since version 4.10)
Snapshots area’s cells according to area’s layout onto at
 the given coordinates.
stopEditing
Arguments
| :: (HasCallStack, MonadIO m, IsCellArea a) | |
| => a | 
  | 
| -> Bool | 
  | 
| -> m () | 
Deprecated: (Since version 4.10)
Explicitly stops the editing of the currently edited cell.
If canceled is True, the currently edited cell renderer
 will emit the editingCanceled signal, otherwise the
 the editingDone signal will be emitted on the current
 edit widget.
Properties
editWidget
The widget currently editing the edited cell
This property is read-only and only changes as
 a result of a call cellAreaActivateCell.
getCellAreaEditWidget :: (MonadIO m, IsCellArea o) => o -> m (Maybe CellEditable) Source #
Get the value of the “edit-widget” property.
 When overloading is enabled, this is equivalent to
get cellArea #editWidget
editedCell
The cell in the area that is currently edited
This property is read-only and only changes as
 a result of a call cellAreaActivateCell.
getCellAreaEditedCell :: (MonadIO m, IsCellArea o) => o -> m (Maybe CellRenderer) Source #
Get the value of the “edited-cell” property.
 When overloading is enabled, this is equivalent to
get cellArea #editedCell
focusCell
The cell in the area that currently has focus
clearCellAreaFocusCell :: (MonadIO m, IsCellArea o) => o -> m () Source #
Set the value of the “focus-cell” property to Nothing.
 When overloading is enabled, this is equivalent to
clear #focusCell
constructCellAreaFocusCell :: (IsCellArea o, MonadIO m, IsCellRenderer a) => a -> m (GValueConstruct o) Source #
Construct a GValueConstruct with valid value for the “focus-cell” property. This is rarely needed directly, but it is used by new.
getCellAreaFocusCell :: (MonadIO m, IsCellArea o) => o -> m (Maybe CellRenderer) Source #
Get the value of the “focus-cell” property.
 When overloading is enabled, this is equivalent to
get cellArea #focusCell
setCellAreaFocusCell :: (MonadIO m, IsCellArea o, IsCellRenderer a) => o -> a -> m () Source #
Set the value of the “focus-cell” property.
 When overloading is enabled, this is equivalent to
setcellArea [ #focusCell:=value ]
Signals
addEditable
type CellAreaAddEditableCallback Source #
Arguments
| = CellRenderer | 
  | 
| -> CellEditable | 
  | 
| -> Rectangle | 
  | 
| -> Text | 
  | 
| -> IO () | 
Indicates that editing has started on renderer and that editable
 should be added to the owning cell-layouting widget at cellArea.
afterCellAreaAddEditable :: (IsCellArea a, MonadIO m) => a -> ((?self :: a) => CellAreaAddEditableCallback) -> m SignalHandlerId Source #
Connect a signal handler for the addEditable signal, to be run after the default handler. When overloading is enabled, this is equivalent to
after cellArea #addEditable callback
By default the object invoking the signal is not passed to the callback.
 If you need to access it, you can use the implit ?self parameter.
 Note that this requires activating the ImplicitParams GHC extension.
onCellAreaAddEditable :: (IsCellArea a, MonadIO m) => a -> ((?self :: a) => CellAreaAddEditableCallback) -> m SignalHandlerId Source #
Connect a signal handler for the addEditable signal, to be run before the default handler. When overloading is enabled, this is equivalent to
on cellArea #addEditable callback
applyAttributes
type CellAreaApplyAttributesCallback Source #
Arguments
| = TreeModel | 
  | 
| -> TreeIter | 
  | 
| -> Bool | 
  | 
| -> Bool | 
  | 
| -> IO () | 
This signal is emitted whenever applying attributes to area from model
afterCellAreaApplyAttributes :: (IsCellArea a, MonadIO m) => a -> ((?self :: a) => CellAreaApplyAttributesCallback) -> m SignalHandlerId Source #
Connect a signal handler for the applyAttributes signal, to be run after the default handler. When overloading is enabled, this is equivalent to
after cellArea #applyAttributes callback
By default the object invoking the signal is not passed to the callback.
 If you need to access it, you can use the implit ?self parameter.
 Note that this requires activating the ImplicitParams GHC extension.
onCellAreaApplyAttributes :: (IsCellArea a, MonadIO m) => a -> ((?self :: a) => CellAreaApplyAttributesCallback) -> m SignalHandlerId Source #
Connect a signal handler for the applyAttributes signal, to be run before the default handler. When overloading is enabled, this is equivalent to
on cellArea #applyAttributes callback
focusChanged
type CellAreaFocusChangedCallback Source #
Arguments
| = CellRenderer | 
  | 
| -> Text | 
  | 
| -> IO () | 
Indicates that focus changed on this area. This signal
 is emitted either as a result of focus handling or event
 handling.
It's possible that the signal is emitted even if the currently focused renderer did not change, this is because focus may change to the same renderer in the same cell area for a different row of data.
afterCellAreaFocusChanged :: (IsCellArea a, MonadIO m) => a -> ((?self :: a) => CellAreaFocusChangedCallback) -> m SignalHandlerId Source #
Connect a signal handler for the focusChanged signal, to be run after the default handler. When overloading is enabled, this is equivalent to
after cellArea #focusChanged callback
By default the object invoking the signal is not passed to the callback.
 If you need to access it, you can use the implit ?self parameter.
 Note that this requires activating the ImplicitParams GHC extension.
onCellAreaFocusChanged :: (IsCellArea a, MonadIO m) => a -> ((?self :: a) => CellAreaFocusChangedCallback) -> m SignalHandlerId Source #
Connect a signal handler for the focusChanged signal, to be run before the default handler. When overloading is enabled, this is equivalent to
on cellArea #focusChanged callback
removeEditable
type CellAreaRemoveEditableCallback Source #
Arguments
| = CellRenderer | 
  | 
| -> CellEditable | 
  | 
| -> IO () | 
Indicates that editing finished on renderer and that editable
 should be removed from the owning cell-layouting widget.
afterCellAreaRemoveEditable :: (IsCellArea a, MonadIO m) => a -> ((?self :: a) => CellAreaRemoveEditableCallback) -> m SignalHandlerId Source #
Connect a signal handler for the removeEditable signal, to be run after the default handler. When overloading is enabled, this is equivalent to
after cellArea #removeEditable callback
By default the object invoking the signal is not passed to the callback.
 If you need to access it, you can use the implit ?self parameter.
 Note that this requires activating the ImplicitParams GHC extension.
onCellAreaRemoveEditable :: (IsCellArea a, MonadIO m) => a -> ((?self :: a) => CellAreaRemoveEditableCallback) -> m SignalHandlerId Source #
Connect a signal handler for the removeEditable signal, to be run before the default handler. When overloading is enabled, this is equivalent to
on cellArea #removeEditable callback