gi-gtk-3.0.34: Gtk bindings
CopyrightWill Thompson Iñaki García Etxebarria and Jonas Platte
LicenseLGPL-2.1
MaintainerIñaki García Etxebarria
Safe HaskellNone
LanguageHaskell2010

GI.Gtk.Objects.CellArea

Description

The CellArea is an abstract class for CellLayout widgets (also referred to as "layouting widgets") to interface with an arbitrary number of GtkCellRenderers 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 CellArea directly unless they are implementing a cell-layouting widget themselves.

Requesting area sizes

As outlined in [GtkWidget’s geometry management section][geometry-management], GTK+ uses a height-for-width geometry management system to compute the sizes of widgets and user interfaces. CellArea uses the same semantics to calculate the size of an area for an arbitrary number of TreeModel 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 CellArea 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 CellArea 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 TreeModel 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 TreeModel one would do the following:

C code

GtkTreeIter iter;
gint        minimum_width;
gint        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 CellAreaContext object and can be consulted at any time.

This can be useful since CellLayout widgets usually have to support requesting and rendering rows in treemodels with an exceedingly large amount of rows. The CellLayout widget in that case would calculate the required width of the rows in an idle or timeout source (see g_timeout_add()) and when the widget is requested its actual width in WidgetClass.get_preferred_width() it can simply consult the width accumulated so far in the CellAreaContext 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,
                         gint            *minimum_size,
                         gint            *natural_size)
{
  Foo        *foo  = FOO (widget);
  FooPrivate *priv = foo->priv;

  foo_ensure_at_least_one_handfull_of_rows_have_been_requested (foo);

  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 CellAreaContext.

Requesting the height for width (or width for height) of an area is a similar task except in this case the CellAreaContext 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 CellArea).

In order to request the height for width of all the rows at the root level of a TreeModel one would do the following:

C code

GtkTreeIter iter;
gint        minimum_height;
gint        natural_height;
gint        full_minimum_height = 0;
gint        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 WidgetClass.get_preferred_height_for_width(). 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 aquired at least for the rows in the visible area of the layouting widget they can be rendered at WidgetClass.draw() 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;
gint          minimum_width;
gint          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 sizeAllocate time 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 CellArea 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 focusChanged signal to fire; as well as 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 CellArea drives keyboard focus from cell to cell in a way similar to Widget. For layouting widgets that support giving focus to cells it’s important to remember to pass CellRendererStateFocused 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 WidgetClass.focus() virtual method. The layouting widget is always responsible for knowing where TreeModel rows are rendered inside the widget, so at WidgetClass.focus() time the layouting widget should use the CellArea methods to navigate focus inside the area and then observe the GtkDirectionType to pass the focus to adjacent rows and areas.

A basic example of how the WidgetClass.focus() virtual method should be implemented:

C code

static gboolean
foo_focus (GtkWidget       *widget,
           GtkDirectionType direction)
{
  Foo        *foo  = FOO (widget);
  FooPrivate *priv = foo->priv;
  gint        focus_row;
  gboolean    have_focus = FALSE;

  focus_row = priv->focus_row;

  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 CellArea introduces cell properties for GtkCellRenderers in very much the same way that Container introduces [child properties][child-properties] for GtkWidgets. 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 CellAreaContext.

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, gtk_cell_area_cell_set() or gtk_cell_area_cell_set_valist(). To obtain the value of a cell property, use cellAreaCellGetProperty, gtk_cell_area_cell_get() or gtk_cell_area_cell_get_valist().

Synopsis

Exported types

newtype CellArea Source #

Memory-managed wrapper type.

Constructors

CellArea (ManagedPtr CellArea) 

Instances

Instances details
Eq CellArea Source # 
Instance details

Defined in GI.Gtk.Objects.CellArea

Methods

(==) :: CellArea -> CellArea -> Bool

(/=) :: CellArea -> CellArea -> Bool

GObject CellArea Source # 
Instance details

Defined in GI.Gtk.Objects.CellArea

ManagedPtrNewtype CellArea Source # 
Instance details

Defined in GI.Gtk.Objects.CellArea

Methods

toManagedPtr :: CellArea -> ManagedPtr CellArea

TypedObject CellArea Source # 
Instance details

Defined in GI.Gtk.Objects.CellArea

Methods

glibType :: IO GType

IsGValue CellArea Source #

Convert CellArea to and from GValue with toGValue and fromGValue.

Instance details

Defined in GI.Gtk.Objects.CellArea

Methods

toGValue :: CellArea -> IO GValue

fromGValue :: GValue -> IO CellArea

HasParentTypes CellArea Source # 
Instance details

Defined in GI.Gtk.Objects.CellArea

type ParentTypes CellArea Source # 
Instance details

Defined in GI.Gtk.Objects.CellArea

type ParentTypes CellArea = '[Object, Buildable, CellLayout]

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

Instances details
(GObject o, IsDescendantOf CellArea o) => IsCellArea o Source # 
Instance details

Defined in GI.Gtk.Objects.CellArea

toCellArea :: (MonadIO m, IsCellArea o) => o -> m CellArea Source #

Cast to CellArea, for types for which this is known to be safe. For general casts, use castTo.

Methods

Overloaded methods

activate

cellAreaActivate Source #

Arguments

:: (HasCallStack, MonadIO m, IsCellArea a, IsCellAreaContext b, IsWidget c) 
=> a

area: a CellArea

-> b

context: the CellAreaContext in context with the current row data

-> c

widget: the Widget that area is rendering on

-> Rectangle

cellArea: the size and location of area relative to widget’s allocation

-> [CellRendererState]

flags: the CellRendererState flags for area for this row of data.

-> Bool

editOnly: if True then only cell renderers that are CellRendererModeEditable will be activated.

-> m Bool

Returns: Whether area was successfully activated.

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.

Since: 3.0

activateCell

cellAreaActivateCell Source #

Arguments

:: (HasCallStack, MonadIO m, IsCellArea a, IsWidget b, IsCellRenderer c) 
=> a

area: a CellArea

-> b

widget: the Widget that area is rendering onto

-> c

renderer: the CellRenderer in area to activate

-> Event

event: the Event for which cell activation should occur

-> Rectangle

cellArea: the Rectangle in widget relative coordinates of renderer for the current row.

-> [CellRendererState]

flags: the CellRendererState for renderer

-> m Bool

Returns: whether cell activation was successful

This is used by CellArea subclasses when handling events to activate cells, the base CellArea class activates cells for keyboard events for free in its own GtkCellArea->activate() implementation.

Since: 3.0

add

cellAreaAdd Source #

Arguments

:: (HasCallStack, MonadIO m, IsCellArea a, IsCellRenderer b) 
=> a

area: a CellArea

-> b

renderer: the CellRenderer to add to area

-> m () 

Adds renderer to area with the default child cell properties.

Since: 3.0

addFocusSibling

cellAreaAddFocusSibling Source #

Arguments

:: (HasCallStack, MonadIO m, IsCellArea a, IsCellRenderer b, IsCellRenderer c) 
=> a

area: a CellArea

-> b

renderer: the CellRenderer expected to have focus

-> c

sibling: the CellRenderer to add to renderer’s focus area

-> m () 

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.

Since: 3.0

applyAttributes

cellAreaApplyAttributes Source #

Arguments

:: (HasCallStack, MonadIO m, IsCellArea a, IsTreeModel b) 
=> a

area: a CellArea

-> b

treeModel: the TreeModel to pull values from

-> TreeIter

iter: the TreeIter in treeModel to apply values for

-> Bool

isExpander: whether iter has children

-> Bool

isExpanded: whether iter is expanded in the view and children are visible

-> m () 

Applies any connected attributes to the renderers in area by pulling the values from treeModel.

Since: 3.0

attributeConnect

cellAreaAttributeConnect Source #

Arguments

:: (HasCallStack, MonadIO m, IsCellArea a, IsCellRenderer b) 
=> a

area: a CellArea

-> b

renderer: the CellRenderer to connect an attribute for

-> Text

attribute: the attribute name

-> Int32

column: the TreeModel column to fetch attribute values from

-> m () 

Connects an attribute to apply values from column for the TreeModel in use.

Since: 3.0

attributeDisconnect

cellAreaAttributeDisconnect Source #

Arguments

:: (HasCallStack, MonadIO m, IsCellArea a, IsCellRenderer b) 
=> a

area: a CellArea

-> b

renderer: the CellRenderer to disconnect an attribute for

-> Text

attribute: the attribute name

-> m () 

Disconnects attribute for the renderer in area so that attribute will no longer be updated with values from the model.

Since: 3.0

attributeGetColumn

cellAreaAttributeGetColumn Source #

Arguments

:: (HasCallStack, MonadIO m, IsCellArea a, IsCellRenderer b) 
=> a

area: a CellArea

-> b

renderer: a CellRenderer

-> Text

attribute: an attribute on the renderer

-> m Int32

Returns: the model column, or -1

Returns the model column that an attribute has been mapped to, or -1 if the attribute is not mapped.

Since: 3.14

cellGetProperty

cellAreaCellGetProperty Source #

Arguments

:: (HasCallStack, MonadIO m, IsCellArea a, IsCellRenderer b) 
=> a

area: a CellArea

-> b

renderer: a CellRenderer inside area

-> Text

propertyName: the name of the property to get

-> GValue

value: a location to return the value

-> m () 

Gets the value of a cell property for renderer in area.

Since: 3.0

cellSetProperty

cellAreaCellSetProperty Source #

Arguments

:: (HasCallStack, MonadIO m, IsCellArea a, IsCellRenderer b) 
=> a

area: a CellArea

-> b

renderer: a CellRenderer inside area

-> Text

propertyName: the name of the cell property to set

-> GValue

value: the value to set the cell property to

-> m () 

Sets a cell property for renderer in area.

Since: 3.0

copyContext

cellAreaCopyContext Source #

Arguments

:: (HasCallStack, MonadIO m, IsCellArea a, IsCellAreaContext b) 
=> a

area: a CellArea

-> b

context: the CellAreaContext to copy

-> m CellAreaContext

Returns: a newly created CellAreaContext copy of context.

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, IconView 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. IconView 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.

Since: 3.0

createContext

cellAreaCreateContext Source #

Arguments

:: (HasCallStack, MonadIO m, IsCellArea a) 
=> a

area: a CellArea

-> m CellAreaContext

Returns: a newly created CellAreaContext which can be used with area.

Creates a CellAreaContext to be used with area for all purposes. CellAreaContext 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 CellAreaContext which was used to request the size of those rows of data).

Since: 3.0

event

cellAreaEvent Source #

Arguments

:: (HasCallStack, MonadIO m, IsCellArea a, IsCellAreaContext b, IsWidget c) 
=> a

area: a CellArea

-> b

context: the CellAreaContext for this row of data.

-> c

widget: the Widget that area is rendering to

-> Event

event: the Event to handle

-> Rectangle

cellArea: the widget relative coordinates for area

-> [CellRendererState]

flags: the CellRendererState for area in this row.

-> m Int32

Returns: True if the event was handled by area.

Delegates event handling to a CellArea.

Since: 3.0

focus

cellAreaFocus Source #

Arguments

:: (HasCallStack, MonadIO m, IsCellArea a) 
=> a

area: a CellArea

-> DirectionType

direction: the DirectionType

-> m Bool

Returns: True if focus remains inside area as a result of this call.

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 CellArea classes should implement this method to receive and navigate focus in its own way particular to how it lays out cells.

Since: 3.0

foreach

cellAreaForeach Source #

Arguments

:: (HasCallStack, MonadIO m, IsCellArea a) 
=> a

area: a CellArea

-> CellCallback

callback: the CellCallback to call

-> m () 

Calls callback for every CellRenderer in area.

Since: 3.0

foreachAlloc

cellAreaForeachAlloc Source #

Arguments

:: (HasCallStack, MonadIO m, IsCellArea a, IsCellAreaContext b, IsWidget c) 
=> a

area: a CellArea

-> b

context: the CellAreaContext for this row of data.

-> c

widget: the Widget that area is rendering to

-> Rectangle

cellArea: the widget relative coordinates and size for area

-> Rectangle

backgroundArea: the widget relative coordinates of the background area

-> CellAllocCallback

callback: the CellAllocCallback to call

-> m () 

Calls callback for every CellRenderer in area with the allocated rectangle inside cellArea.

Since: 3.0

getCellAllocation

cellAreaGetCellAllocation Source #

Arguments

:: (HasCallStack, MonadIO m, IsCellArea a, IsCellAreaContext b, IsWidget c, IsCellRenderer d) 
=> a

area: a CellArea

-> b

context: the CellAreaContext used to hold sizes for area.

-> c

widget: the Widget that area is rendering on

-> d

renderer: the CellRenderer to get the allocation for

-> Rectangle

cellArea: the whole allocated area for area in widget for this row

-> m Rectangle 

Derives the allocation of renderer inside area if area were to be renderered in cellArea.

Since: 3.0

getCellAtPosition

cellAreaGetCellAtPosition Source #

Arguments

:: (HasCallStack, MonadIO m, IsCellArea a, IsCellAreaContext b, IsWidget c) 
=> a

area: a CellArea

-> b

context: the CellAreaContext used to hold sizes for area.

-> c

widget: the Widget that area is rendering on

-> Rectangle

cellArea: the whole allocated area for area in widget for this row

-> Int32

x: the x position

-> Int32

y: the y position

-> m (CellRenderer, Rectangle)

Returns: the CellRenderer at x and y.

Gets the CellRenderer at x and y coordinates inside area and optionally returns the full cell allocation for it inside cellArea.

Since: 3.0

getCurrentPathString

cellAreaGetCurrentPathString Source #

Arguments

:: (HasCallStack, MonadIO m, IsCellArea a) 
=> a

area: a CellArea

-> m Text

Returns: The current TreePath string for the current attributes applied to area. This string belongs to the area and should not be freed.

Gets the current TreePath string for the currently applied TreeIter, this is implicitly updated when cellAreaApplyAttributes is called and can be used to interact with renderers from CellArea subclasses.

Since: 3.0

getEditWidget

cellAreaGetEditWidget Source #

Arguments

:: (HasCallStack, MonadIO m, IsCellArea a) 
=> a

area: a CellArea

-> m CellEditable

Returns: The currently active CellEditable widget

Gets the CellEditable widget currently used to edit the currently edited cell.

Since: 3.0

getEditedCell

cellAreaGetEditedCell Source #

Arguments

:: (HasCallStack, MonadIO m, IsCellArea a) 
=> a

area: a CellArea

-> m CellRenderer

Returns: The currently edited CellRenderer

Gets the CellRenderer in area that is currently being edited.

Since: 3.0

getFocusCell

cellAreaGetFocusCell Source #

Arguments

:: (HasCallStack, MonadIO m, IsCellArea a) 
=> a

area: a CellArea

-> m CellRenderer

Returns: the currently focused cell in area.

Retrieves the currently focused cell for area

Since: 3.0

getFocusFromSibling

cellAreaGetFocusFromSibling Source #

Arguments

:: (HasCallStack, MonadIO m, IsCellArea a, IsCellRenderer b) 
=> a

area: a CellArea

-> b

renderer: the CellRenderer

-> m (Maybe CellRenderer)

Returns: the CellRenderer for which renderer is a sibling, or Nothing.

Gets the CellRenderer which is expected to be focusable for which renderer is, or may be a sibling.

This is handy for CellArea 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.

Since: 3.0

getFocusSiblings

cellAreaGetFocusSiblings Source #

Arguments

:: (HasCallStack, MonadIO m, IsCellArea a, IsCellRenderer b) 
=> a

area: a CellArea

-> b

renderer: the CellRenderer expected to have focus

-> m [CellRenderer]

Returns: A List of GtkCellRenderers. The returned list is internal and should not be freed.

Gets the focus sibling cell renderers for renderer.

Since: 3.0

getPreferredHeight

cellAreaGetPreferredHeight Source #

Arguments

:: (HasCallStack, MonadIO m, IsCellArea a, IsCellAreaContext b, IsWidget c) 
=> a

area: a CellArea

-> b

context: the CellAreaContext to perform this request with

-> c

widget: the Widget where area will be rendering

-> m (Int32, Int32) 

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.

Since: 3.0

getPreferredHeightForWidth

cellAreaGetPreferredHeightForWidth Source #

Arguments

:: (HasCallStack, MonadIO m, IsCellArea a, IsCellAreaContext b, IsWidget c) 
=> a

area: a CellArea

-> b

context: the CellAreaContext which has already been requested for widths.

-> c

widget: the Widget where area will be rendering

-> Int32

width: the width for which to check the height of this area

-> m (Int32, Int32) 

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.

Since: 3.0

getPreferredWidth

cellAreaGetPreferredWidth Source #

Arguments

:: (HasCallStack, MonadIO m, IsCellArea a, IsCellAreaContext b, IsWidget c) 
=> a

area: a CellArea

-> b

context: the CellAreaContext to perform this request with

-> c

widget: the Widget where area will be rendering

-> m (Int32, Int32) 

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.

Since: 3.0

getPreferredWidthForHeight

cellAreaGetPreferredWidthForHeight Source #

Arguments

:: (HasCallStack, MonadIO m, IsCellArea a, IsCellAreaContext b, IsWidget c) 
=> a

area: a CellArea

-> b

context: the CellAreaContext which has already been requested for widths.

-> c

widget: the Widget where area will be rendering

-> Int32

height: the height for which to check the width of this area

-> m (Int32, Int32) 

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.

Since: 3.0

getRequestMode

cellAreaGetRequestMode Source #

Arguments

:: (HasCallStack, MonadIO m, IsCellArea a) 
=> a

area: a CellArea

-> m SizeRequestMode

Returns: The SizeRequestMode preferred by area.

Gets whether the area prefers a height-for-width layout or a width-for-height layout.

Since: 3.0

hasRenderer

cellAreaHasRenderer Source #

Arguments

:: (HasCallStack, MonadIO m, IsCellArea a, IsCellRenderer b) 
=> a

area: a CellArea

-> b

renderer: the CellRenderer to check

-> m Bool

Returns: True if renderer is in the area.

Checks if area contains renderer.

Since: 3.0

innerCellArea

cellAreaInnerCellArea Source #

Arguments

:: (HasCallStack, MonadIO m, IsCellArea a, IsWidget b) 
=> a

area: a CellArea

-> b

widget: the Widget that area is rendering onto

-> Rectangle

cellArea: the widget relative coordinates where one of area’s cells is to be placed

-> m Rectangle 

This is a convenience function for CellArea implementations to get the inner area where a given CellRenderer will be rendered. It removes any padding previously added by cellAreaRequestRenderer.

Since: 3.0

isActivatable

cellAreaIsActivatable Source #

Arguments

:: (HasCallStack, MonadIO m, IsCellArea a) 
=> a

area: a CellArea

-> m Bool

Returns: whether area can do anything when activated.

Returns whether the area can do anything when activated, after applying new attributes to area.

Since: 3.0

isFocusSibling

cellAreaIsFocusSibling Source #

Arguments

:: (HasCallStack, MonadIO m, IsCellArea a, IsCellRenderer b, IsCellRenderer c) 
=> a

area: a CellArea

-> b

renderer: the CellRenderer expected to have focus

-> c

sibling: the CellRenderer to check against renderer’s sibling list

-> m Bool

Returns: True if sibling is a focus sibling of renderer

Returns whether sibling is one of renderer’s focus siblings (see cellAreaAddFocusSibling).

Since: 3.0

remove

cellAreaRemove Source #

Arguments

:: (HasCallStack, MonadIO m, IsCellArea a, IsCellRenderer b) 
=> a

area: a CellArea

-> b

renderer: the CellRenderer to remove from area

-> m () 

Removes renderer from area.

Since: 3.0

removeFocusSibling

cellAreaRemoveFocusSibling Source #

Arguments

:: (HasCallStack, MonadIO m, IsCellArea a, IsCellRenderer b, IsCellRenderer c) 
=> a

area: a CellArea

-> b

renderer: the CellRenderer expected to have focus

-> c

sibling: the CellRenderer to remove from renderer’s focus area

-> m () 

Removes sibling from renderer’s focus sibling list (see cellAreaAddFocusSibling).

Since: 3.0

render

cellAreaRender Source #

Arguments

:: (HasCallStack, MonadIO m, IsCellArea a, IsCellAreaContext b, IsWidget c) 
=> a

area: a CellArea

-> b

context: the CellAreaContext for this row of data.

-> c

widget: the Widget that area is rendering to

-> Context

cr: the Context to render with

-> Rectangle

backgroundArea: the widget relative coordinates for area’s background

-> Rectangle

cellArea: the widget relative coordinates for area

-> [CellRendererState]

flags: the CellRendererState for area in this row.

-> Bool

paintFocus: whether area should paint focus on focused cells for focused rows or not.

-> m () 

Renders area’s cells according to area’s layout onto widget at the given coordinates.

Since: 3.0

requestRenderer

cellAreaRequestRenderer Source #

Arguments

:: (HasCallStack, MonadIO m, IsCellArea a, IsCellRenderer b, IsWidget c) 
=> a

area: a CellArea

-> b

renderer: the CellRenderer to request size for

-> Orientation

orientation: the Orientation in which to request size

-> c

widget: the Widget that area is rendering onto

-> Int32

forSize: the allocation contextual size to request for, or -1 if the base request for the orientation is to be returned.

-> m (Int32, Int32) 

This is a convenience function for CellArea 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.

Since: 3.0

setFocusCell

cellAreaSetFocusCell Source #

Arguments

:: (HasCallStack, MonadIO m, IsCellArea a, IsCellRenderer b) 
=> a

area: a CellArea

-> b

renderer: the CellRenderer to give focus to

-> m () 

Explicitly sets the currently focused cell to renderer.

This is generally called by implementations of CellAreaClass.focus() or CellAreaClass.event(), however it can also be used to implement functions such as treeViewSetCursorOnCell.

Since: 3.0

stopEditing

cellAreaStopEditing Source #

Arguments

:: (HasCallStack, MonadIO m, IsCellArea a) 
=> a

area: a CellArea

-> Bool

canceled: whether editing was canceled.

-> m () 

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.

See cellAreaGetEditedCell and cellAreaGetEditWidget.

Since: 3.0

Properties

editWidget

The widget currently editing the edited cell

This property is read-only and only changes as a result of a call cellAreaActivateCell.

Since: 3.0

getCellAreaEditWidget :: (MonadIO m, IsCellArea o) => o -> m 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.

Since: 3.0

getCellAreaEditedCell :: (MonadIO m, IsCellArea o) => o -> m 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

Since: 3.0

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 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

set cellArea [ #focusCell := value ]

Signals

addEditable

type C_CellAreaAddEditableCallback = Ptr () -> Ptr CellRenderer -> Ptr CellEditable -> Ptr Rectangle -> CString -> Ptr () -> IO () Source #

Type for the callback on the (unwrapped) C side.

type CellAreaAddEditableCallback Source #

Arguments

 = CellRenderer

renderer: the CellRenderer that started the edited

-> CellEditable

editable: the CellEditable widget to add

-> Rectangle

cellArea: the Widget relative Rectangle coordinates where editable should be added

-> Text

path: the TreePath string this edit was initiated for

-> IO () 

Indicates that editing has started on renderer and that editable should be added to the owning cell-layouting widget at cellArea.

Since: 3.0

afterCellAreaAddEditable :: (IsCellArea a, MonadIO m) => 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

onCellAreaAddEditable :: (IsCellArea a, MonadIO m) => 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 C_CellAreaApplyAttributesCallback = Ptr () -> Ptr TreeModel -> Ptr TreeIter -> CInt -> CInt -> Ptr () -> IO () Source #

Type for the callback on the (unwrapped) C side.

type CellAreaApplyAttributesCallback Source #

Arguments

 = TreeModel

model: the TreeModel to apply the attributes from

-> TreeIter

iter: the TreeIter indicating which row to apply the attributes of

-> Bool

isExpander: whether the view shows children for this row

-> Bool

isExpanded: whether the view is currently showing the children of this row

-> IO () 

This signal is emitted whenever applying attributes to area from model

Since: 3.0

afterCellAreaApplyAttributes :: (IsCellArea a, MonadIO m) => 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

onCellAreaApplyAttributes :: (IsCellArea a, MonadIO m) => 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 C_CellAreaFocusChangedCallback = Ptr () -> Ptr CellRenderer -> CString -> Ptr () -> IO () Source #

Type for the callback on the (unwrapped) C side.

type CellAreaFocusChangedCallback Source #

Arguments

 = CellRenderer

renderer: the CellRenderer that has focus

-> Text

path: the current TreePath string set for area

-> 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.

Since: 3.0

afterCellAreaFocusChanged :: (IsCellArea a, MonadIO m) => 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

onCellAreaFocusChanged :: (IsCellArea a, MonadIO m) => 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 C_CellAreaRemoveEditableCallback = Ptr () -> Ptr CellRenderer -> Ptr CellEditable -> Ptr () -> IO () Source #

Type for the callback on the (unwrapped) C side.

type CellAreaRemoveEditableCallback Source #

Arguments

 = CellRenderer

renderer: the CellRenderer that finished editeding

-> CellEditable

editable: the CellEditable widget to remove

-> IO () 

Indicates that editing finished on renderer and that editable should be removed from the owning cell-layouting widget.

Since: 3.0

afterCellAreaRemoveEditable :: (IsCellArea a, MonadIO m) => 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

onCellAreaRemoveEditable :: (IsCellArea a, MonadIO m) => 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