{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Data.GI.Gtk.ModelView.CellLayout (
module GI.Gtk.Interfaces.CellLayout
, cellLayoutSetAttributes
, cellLayoutSetDataFunction
, cellLayoutSetDataFunc'
, convertIterFromParentToChildModel
) where
import Control.Monad.IO.Class (MonadIO(..))
import Foreign.Ptr (castPtr)
import Foreign.Storable (peek)
import Data.GI.Base.Attributes (AttrOp, AttrOpTag(..), set)
import Data.GI.Base.ManagedPtr (castTo, withManagedPtr)
import GI.Gtk.Interfaces.CellLayout
import GI.Gtk.Objects.TreeModelFilter (TreeModelFilter(..), getTreeModelFilterChildModel, treeModelFilterConvertIterToChildIter)
import GI.Gtk.Objects.TreeModelSort (TreeModelSort(..), getTreeModelSortModel, treeModelSortConvertIterToChildIter)
import GI.Gtk.Structs.TreeIter
(getTreeIterStamp, getTreeIterUserData3, getTreeIterUserData2,
getTreeIterUserData, TreeIter(..))
import GI.Gtk.Objects.CellRenderer (IsCellRenderer, CellRenderer(..), toCellRenderer)
import Data.GI.Gtk.ModelView.Types
import Data.GI.Gtk.ModelView.TreeModel
import Data.GI.Gtk.ModelView.CustomStore (customStoreGetRow)
import Data.GI.Base (get)
import Data.GI.Base.BasicTypes (ManagedPtr(..))
cellLayoutSetAttributes :: (MonadIO m,
IsCellLayout self,
IsCellRenderer cell,
IsTreeModel (model row),
IsTypedTreeModel model)
=> self
-> cell
-> model row
-> (row -> [AttrOp cell 'AttrSet]) -- ^ Function to set attributes on the cell renderer.
-> m ()
cellLayoutSetAttributes self cell model attributes =
cellLayoutSetDataFunc' self cell model $ \iter -> do
row <- customStoreGetRow model iter
set cell (attributes row)
-- | Like 'cellLayoutSetAttributes', but allows any IO action to be used
cellLayoutSetDataFunction :: (MonadIO m,
IsCellLayout self,
IsCellRenderer cell,
IsTreeModel (model row),
IsTypedTreeModel model)
=> self
-> cell -- ^ @cell@ - A 'CellRenderer'.
-> model row -- ^ @model@ - A model containing rows of type @row@.
-> (row -> IO ()) -- ^ Function to set data on the cell renderer.
-> m ()
cellLayoutSetDataFunction self cell model callback =
cellLayoutSetDataFunc' self cell model $ \iter -> do
row <- customStoreGetRow model iter
callback row
-- | Install a function that looks up a row in the model and sets the
-- attributes of the 'CellRenderer' @cell@ using the row's content.
--
cellLayoutSetDataFunc' :: (MonadIO m,
IsCellLayout self,
IsCellRenderer cell,
IsTreeModel model)
=> self
-> cell -- ^ @cell@ - A 'CellRenderer'.
-> model -- ^ @model@ - A model from which to draw data.
-> (TreeIter -> IO ()) -- ^ Function to set attributes on the cell renderer.
-> m ()
cellLayoutSetDataFunc' self cell model func = liftIO $
cellLayoutSetCellDataFunc self cell . Just $ \_ (CellRenderer cellPtr') model' iter -> do
iter <- convertIterFromParentToChildModel iter model' =<< toTreeModel model
CellRenderer cellPtr <- toCellRenderer cell
if managedForeignPtr cellPtr /= managedForeignPtr cellPtr' then
error ("cellLayoutSetAttributeFunc: attempt to set attributes of "++
"a different CellRenderer.")
else func iter
-- Given a 'TreeModelFilter' or a 'TreeModelSort' and a 'TreeIter', get the
-- child model of these models and convert the iter to an iter of the child
-- model. This is an ugly internal function that is needed for some widgets
-- which pass iterators to the callback function of set_cell_data_func that
-- refer to some internal TreeModelFilter models that they create around the
-- user model. This is a bug but since C programs mostly use the columns
-- rather than the cell_layout way to extract attributes, this bug does not
-- show up in many programs. Reported in the case of EntryCompletion as bug
-- \#551202.
--
convertIterFromParentToChildModel ::
TreeIter -- ^ the iterator
-> TreeModel -- ^ the model that we got from the all back
-> TreeModel -- ^ the model that we actually want
-> IO TreeIter
convertIterFromParentToChildModel iter parentModel@(TreeModel parentModelPtr) childModel =
let (TreeModel modelPtr) = childModel in
if managedForeignPtr modelPtr == managedForeignPtr parentModelPtr
then return iter
else
castTo TreeModelFilter parentModel >>= \case
Just tmFilter -> do
childIter <- treeModelFilterConvertIterToChildIter tmFilter iter
Just child@(TreeModel childPtr) <- getTreeModelFilterChildModel tmFilter
if managedForeignPtr childPtr == managedForeignPtr modelPtr
then return childIter
else convertIterFromParentToChildModel childIter child childModel
Nothing -> do
castTo TreeModelSort parentModel >>= \case
Just tmSort -> do
childIter <- treeModelSortConvertIterToChildIter tmSort iter
child@(TreeModel childPtr) <- getTreeModelSortModel tmSort
if managedForeignPtr childPtr == managedForeignPtr modelPtr
then return childIter
else convertIterFromParentToChildModel childIter child childModel
Nothing -> do
stamp <- getTreeIterStamp iter
ud1 <- getTreeIterUserData iter
ud2 <- getTreeIterUserData2 iter
ud3 <- getTreeIterUserData3 iter
error ("CellLayout: don't know how to convert iter "++show (stamp, ud1, ud2, ud3)++
" from model "++show (managedForeignPtr parentModelPtr)++" to model "++
show (managedForeignPtr modelPtr)++". Is it possible that you are setting the "++
"attributes of a CellRenderer using a different model than "++
"that which was set in the view?")