{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A widget displaying a single row of a GtkTreeModel
-- 
-- A @GtkCellView@ displays a single row of a @GtkTreeModel@ using a @GtkCellArea@
-- and @GtkCellAreaContext@. A @GtkCellAreaContext@ can be provided to the
-- @GtkCellView@ at construction time in order to keep the cellview in context
-- of a group of cell views, this ensures that the renderers displayed will
-- be properly aligned with each other (like the aligned cells in the menus
-- of @GtkComboBox@).
-- 
-- @GtkCellView@ is @GtkOrientable@ in order to decide in which orientation
-- the underlying @GtkCellAreaContext@ should be allocated. Taking the @GtkComboBox@
-- menu as an example, cellviews should be oriented horizontally if the menus are
-- listed top-to-bottom and thus all share the same width but may have separate
-- individual heights (left-to-right menus should be allocated vertically since
-- they all share the same height but may have variable widths).
-- 
-- = CSS nodes
-- 
-- GtkCellView has a single CSS node with name cellview.

#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif

module GI.Gtk.Objects.CellView
    ( 

-- * Exported types
    CellView(..)                            ,
    IsCellView                              ,
    toCellView                              ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [actionSetEnabled]("GI.Gtk.Objects.Widget#g:method:actionSetEnabled"), [activate]("GI.Gtk.Objects.Widget#g:method:activate"), [activateAction]("GI.Gtk.Objects.Widget#g:method:activateAction"), [activateDefault]("GI.Gtk.Objects.Widget#g:method:activateDefault"), [addAttribute]("GI.Gtk.Interfaces.CellLayout#g:method:addAttribute"), [addController]("GI.Gtk.Objects.Widget#g:method:addController"), [addCssClass]("GI.Gtk.Objects.Widget#g:method:addCssClass"), [addMnemonicLabel]("GI.Gtk.Objects.Widget#g:method:addMnemonicLabel"), [addTickCallback]("GI.Gtk.Objects.Widget#g:method:addTickCallback"), [allocate]("GI.Gtk.Objects.Widget#g:method:allocate"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [childFocus]("GI.Gtk.Objects.Widget#g:method:childFocus"), [clear]("GI.Gtk.Interfaces.CellLayout#g:method:clear"), [clearAttributes]("GI.Gtk.Interfaces.CellLayout#g:method:clearAttributes"), [computeBounds]("GI.Gtk.Objects.Widget#g:method:computeBounds"), [computeExpand]("GI.Gtk.Objects.Widget#g:method:computeExpand"), [computePoint]("GI.Gtk.Objects.Widget#g:method:computePoint"), [computeTransform]("GI.Gtk.Objects.Widget#g:method:computeTransform"), [contains]("GI.Gtk.Objects.Widget#g:method:contains"), [createPangoContext]("GI.Gtk.Objects.Widget#g:method:createPangoContext"), [createPangoLayout]("GI.Gtk.Objects.Widget#g:method:createPangoLayout"), [dragCheckThreshold]("GI.Gtk.Objects.Widget#g:method:dragCheckThreshold"), [errorBell]("GI.Gtk.Objects.Widget#g:method:errorBell"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [grabFocus]("GI.Gtk.Objects.Widget#g:method:grabFocus"), [hasCssClass]("GI.Gtk.Objects.Widget#g:method:hasCssClass"), [hasDefault]("GI.Gtk.Objects.Widget#g:method:hasDefault"), [hasFocus]("GI.Gtk.Objects.Widget#g:method:hasFocus"), [hasVisibleFocus]("GI.Gtk.Objects.Widget#g:method:hasVisibleFocus"), [hide]("GI.Gtk.Objects.Widget#g:method:hide"), [inDestruction]("GI.Gtk.Objects.Widget#g:method:inDestruction"), [initTemplate]("GI.Gtk.Objects.Widget#g:method:initTemplate"), [insertActionGroup]("GI.Gtk.Objects.Widget#g:method:insertActionGroup"), [insertAfter]("GI.Gtk.Objects.Widget#g:method:insertAfter"), [insertBefore]("GI.Gtk.Objects.Widget#g:method:insertBefore"), [isAncestor]("GI.Gtk.Objects.Widget#g:method:isAncestor"), [isDrawable]("GI.Gtk.Objects.Widget#g:method:isDrawable"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [isFocus]("GI.Gtk.Objects.Widget#g:method:isFocus"), [isSensitive]("GI.Gtk.Objects.Widget#g:method:isSensitive"), [isVisible]("GI.Gtk.Objects.Widget#g:method:isVisible"), [keynavFailed]("GI.Gtk.Objects.Widget#g:method:keynavFailed"), [listMnemonicLabels]("GI.Gtk.Objects.Widget#g:method:listMnemonicLabels"), [map]("GI.Gtk.Objects.Widget#g:method:map"), [measure]("GI.Gtk.Objects.Widget#g:method:measure"), [mnemonicActivate]("GI.Gtk.Objects.Widget#g:method:mnemonicActivate"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [observeChildren]("GI.Gtk.Objects.Widget#g:method:observeChildren"), [observeControllers]("GI.Gtk.Objects.Widget#g:method:observeControllers"), [packEnd]("GI.Gtk.Interfaces.CellLayout#g:method:packEnd"), [packStart]("GI.Gtk.Interfaces.CellLayout#g:method:packStart"), [pick]("GI.Gtk.Objects.Widget#g:method:pick"), [queueAllocate]("GI.Gtk.Objects.Widget#g:method:queueAllocate"), [queueDraw]("GI.Gtk.Objects.Widget#g:method:queueDraw"), [queueResize]("GI.Gtk.Objects.Widget#g:method:queueResize"), [realize]("GI.Gtk.Objects.Widget#g:method:realize"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [removeController]("GI.Gtk.Objects.Widget#g:method:removeController"), [removeCssClass]("GI.Gtk.Objects.Widget#g:method:removeCssClass"), [removeMnemonicLabel]("GI.Gtk.Objects.Widget#g:method:removeMnemonicLabel"), [removeTickCallback]("GI.Gtk.Objects.Widget#g:method:removeTickCallback"), [reorder]("GI.Gtk.Interfaces.CellLayout#g:method:reorder"), [resetProperty]("GI.Gtk.Interfaces.Accessible#g:method:resetProperty"), [resetRelation]("GI.Gtk.Interfaces.Accessible#g:method:resetRelation"), [resetState]("GI.Gtk.Interfaces.Accessible#g:method:resetState"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [shouldLayout]("GI.Gtk.Objects.Widget#g:method:shouldLayout"), [show]("GI.Gtk.Objects.Widget#g:method:show"), [sizeAllocate]("GI.Gtk.Objects.Widget#g:method:sizeAllocate"), [snapshotChild]("GI.Gtk.Objects.Widget#g:method:snapshotChild"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [translateCoordinates]("GI.Gtk.Objects.Widget#g:method:translateCoordinates"), [triggerTooltipQuery]("GI.Gtk.Objects.Widget#g:method:triggerTooltipQuery"), [unmap]("GI.Gtk.Objects.Widget#g:method:unmap"), [unparent]("GI.Gtk.Objects.Widget#g:method:unparent"), [unrealize]("GI.Gtk.Objects.Widget#g:method:unrealize"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [unsetStateFlags]("GI.Gtk.Objects.Widget#g:method:unsetStateFlags"), [updateProperty]("GI.Gtk.Interfaces.Accessible#g:method:updateProperty"), [updateRelation]("GI.Gtk.Interfaces.Accessible#g:method:updateRelation"), [updateState]("GI.Gtk.Interfaces.Accessible#g:method:updateState"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getAccessibleRole]("GI.Gtk.Interfaces.Accessible#g:method:getAccessibleRole"), [getAllocatedBaseline]("GI.Gtk.Objects.Widget#g:method:getAllocatedBaseline"), [getAllocatedHeight]("GI.Gtk.Objects.Widget#g:method:getAllocatedHeight"), [getAllocatedWidth]("GI.Gtk.Objects.Widget#g:method:getAllocatedWidth"), [getAllocation]("GI.Gtk.Objects.Widget#g:method:getAllocation"), [getAncestor]("GI.Gtk.Objects.Widget#g:method:getAncestor"), [getArea]("GI.Gtk.Interfaces.CellLayout#g:method:getArea"), [getBuildableId]("GI.Gtk.Interfaces.Buildable#g:method:getBuildableId"), [getCanFocus]("GI.Gtk.Objects.Widget#g:method:getCanFocus"), [getCanTarget]("GI.Gtk.Objects.Widget#g:method:getCanTarget"), [getCells]("GI.Gtk.Interfaces.CellLayout#g:method:getCells"), [getChildVisible]("GI.Gtk.Objects.Widget#g:method:getChildVisible"), [getClipboard]("GI.Gtk.Objects.Widget#g:method:getClipboard"), [getCssClasses]("GI.Gtk.Objects.Widget#g:method:getCssClasses"), [getCssName]("GI.Gtk.Objects.Widget#g:method:getCssName"), [getCursor]("GI.Gtk.Objects.Widget#g:method:getCursor"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDirection]("GI.Gtk.Objects.Widget#g:method:getDirection"), [getDisplay]("GI.Gtk.Objects.Widget#g:method:getDisplay"), [getDisplayedRow]("GI.Gtk.Objects.CellView#g:method:getDisplayedRow"), [getDrawSensitive]("GI.Gtk.Objects.CellView#g:method:getDrawSensitive"), [getFirstChild]("GI.Gtk.Objects.Widget#g:method:getFirstChild"), [getFitModel]("GI.Gtk.Objects.CellView#g:method:getFitModel"), [getFocusChild]("GI.Gtk.Objects.Widget#g:method:getFocusChild"), [getFocusOnClick]("GI.Gtk.Objects.Widget#g:method:getFocusOnClick"), [getFocusable]("GI.Gtk.Objects.Widget#g:method:getFocusable"), [getFontMap]("GI.Gtk.Objects.Widget#g:method:getFontMap"), [getFontOptions]("GI.Gtk.Objects.Widget#g:method:getFontOptions"), [getFrameClock]("GI.Gtk.Objects.Widget#g:method:getFrameClock"), [getHalign]("GI.Gtk.Objects.Widget#g:method:getHalign"), [getHasTooltip]("GI.Gtk.Objects.Widget#g:method:getHasTooltip"), [getHeight]("GI.Gtk.Objects.Widget#g:method:getHeight"), [getHexpand]("GI.Gtk.Objects.Widget#g:method:getHexpand"), [getHexpandSet]("GI.Gtk.Objects.Widget#g:method:getHexpandSet"), [getLastChild]("GI.Gtk.Objects.Widget#g:method:getLastChild"), [getLayoutManager]("GI.Gtk.Objects.Widget#g:method:getLayoutManager"), [getMapped]("GI.Gtk.Objects.Widget#g:method:getMapped"), [getMarginBottom]("GI.Gtk.Objects.Widget#g:method:getMarginBottom"), [getMarginEnd]("GI.Gtk.Objects.Widget#g:method:getMarginEnd"), [getMarginStart]("GI.Gtk.Objects.Widget#g:method:getMarginStart"), [getMarginTop]("GI.Gtk.Objects.Widget#g:method:getMarginTop"), [getModel]("GI.Gtk.Objects.CellView#g:method:getModel"), [getName]("GI.Gtk.Objects.Widget#g:method:getName"), [getNative]("GI.Gtk.Objects.Widget#g:method:getNative"), [getNextSibling]("GI.Gtk.Objects.Widget#g:method:getNextSibling"), [getOpacity]("GI.Gtk.Objects.Widget#g:method:getOpacity"), [getOrientation]("GI.Gtk.Interfaces.Orientable#g:method:getOrientation"), [getOverflow]("GI.Gtk.Objects.Widget#g:method:getOverflow"), [getPangoContext]("GI.Gtk.Objects.Widget#g:method:getPangoContext"), [getParent]("GI.Gtk.Objects.Widget#g:method:getParent"), [getPreferredSize]("GI.Gtk.Objects.Widget#g:method:getPreferredSize"), [getPrevSibling]("GI.Gtk.Objects.Widget#g:method:getPrevSibling"), [getPrimaryClipboard]("GI.Gtk.Objects.Widget#g:method:getPrimaryClipboard"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getRealized]("GI.Gtk.Objects.Widget#g:method:getRealized"), [getReceivesDefault]("GI.Gtk.Objects.Widget#g:method:getReceivesDefault"), [getRequestMode]("GI.Gtk.Objects.Widget#g:method:getRequestMode"), [getRoot]("GI.Gtk.Objects.Widget#g:method:getRoot"), [getScaleFactor]("GI.Gtk.Objects.Widget#g:method:getScaleFactor"), [getSensitive]("GI.Gtk.Objects.Widget#g:method:getSensitive"), [getSettings]("GI.Gtk.Objects.Widget#g:method:getSettings"), [getSize]("GI.Gtk.Objects.Widget#g:method:getSize"), [getSizeRequest]("GI.Gtk.Objects.Widget#g:method:getSizeRequest"), [getStateFlags]("GI.Gtk.Objects.Widget#g:method:getStateFlags"), [getStyleContext]("GI.Gtk.Objects.Widget#g:method:getStyleContext"), [getTemplateChild]("GI.Gtk.Objects.Widget#g:method:getTemplateChild"), [getTooltipMarkup]("GI.Gtk.Objects.Widget#g:method:getTooltipMarkup"), [getTooltipText]("GI.Gtk.Objects.Widget#g:method:getTooltipText"), [getValign]("GI.Gtk.Objects.Widget#g:method:getValign"), [getVexpand]("GI.Gtk.Objects.Widget#g:method:getVexpand"), [getVexpandSet]("GI.Gtk.Objects.Widget#g:method:getVexpandSet"), [getVisible]("GI.Gtk.Objects.Widget#g:method:getVisible"), [getWidth]("GI.Gtk.Objects.Widget#g:method:getWidth").
-- 
-- ==== Setters
-- [setCanFocus]("GI.Gtk.Objects.Widget#g:method:setCanFocus"), [setCanTarget]("GI.Gtk.Objects.Widget#g:method:setCanTarget"), [setCellDataFunc]("GI.Gtk.Interfaces.CellLayout#g:method:setCellDataFunc"), [setChildVisible]("GI.Gtk.Objects.Widget#g:method:setChildVisible"), [setCssClasses]("GI.Gtk.Objects.Widget#g:method:setCssClasses"), [setCursor]("GI.Gtk.Objects.Widget#g:method:setCursor"), [setCursorFromName]("GI.Gtk.Objects.Widget#g:method:setCursorFromName"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setDirection]("GI.Gtk.Objects.Widget#g:method:setDirection"), [setDisplayedRow]("GI.Gtk.Objects.CellView#g:method:setDisplayedRow"), [setDrawSensitive]("GI.Gtk.Objects.CellView#g:method:setDrawSensitive"), [setFitModel]("GI.Gtk.Objects.CellView#g:method:setFitModel"), [setFocusChild]("GI.Gtk.Objects.Widget#g:method:setFocusChild"), [setFocusOnClick]("GI.Gtk.Objects.Widget#g:method:setFocusOnClick"), [setFocusable]("GI.Gtk.Objects.Widget#g:method:setFocusable"), [setFontMap]("GI.Gtk.Objects.Widget#g:method:setFontMap"), [setFontOptions]("GI.Gtk.Objects.Widget#g:method:setFontOptions"), [setHalign]("GI.Gtk.Objects.Widget#g:method:setHalign"), [setHasTooltip]("GI.Gtk.Objects.Widget#g:method:setHasTooltip"), [setHexpand]("GI.Gtk.Objects.Widget#g:method:setHexpand"), [setHexpandSet]("GI.Gtk.Objects.Widget#g:method:setHexpandSet"), [setLayoutManager]("GI.Gtk.Objects.Widget#g:method:setLayoutManager"), [setMarginBottom]("GI.Gtk.Objects.Widget#g:method:setMarginBottom"), [setMarginEnd]("GI.Gtk.Objects.Widget#g:method:setMarginEnd"), [setMarginStart]("GI.Gtk.Objects.Widget#g:method:setMarginStart"), [setMarginTop]("GI.Gtk.Objects.Widget#g:method:setMarginTop"), [setModel]("GI.Gtk.Objects.CellView#g:method:setModel"), [setName]("GI.Gtk.Objects.Widget#g:method:setName"), [setOpacity]("GI.Gtk.Objects.Widget#g:method:setOpacity"), [setOrientation]("GI.Gtk.Interfaces.Orientable#g:method:setOrientation"), [setOverflow]("GI.Gtk.Objects.Widget#g:method:setOverflow"), [setParent]("GI.Gtk.Objects.Widget#g:method:setParent"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setReceivesDefault]("GI.Gtk.Objects.Widget#g:method:setReceivesDefault"), [setSensitive]("GI.Gtk.Objects.Widget#g:method:setSensitive"), [setSizeRequest]("GI.Gtk.Objects.Widget#g:method:setSizeRequest"), [setStateFlags]("GI.Gtk.Objects.Widget#g:method:setStateFlags"), [setTooltipMarkup]("GI.Gtk.Objects.Widget#g:method:setTooltipMarkup"), [setTooltipText]("GI.Gtk.Objects.Widget#g:method:setTooltipText"), [setValign]("GI.Gtk.Objects.Widget#g:method:setValign"), [setVexpand]("GI.Gtk.Objects.Widget#g:method:setVexpand"), [setVexpandSet]("GI.Gtk.Objects.Widget#g:method:setVexpandSet"), [setVisible]("GI.Gtk.Objects.Widget#g:method:setVisible").

#if defined(ENABLE_OVERLOADING)
    ResolveCellViewMethod                   ,
#endif

-- ** getDisplayedRow #method:getDisplayedRow#

#if defined(ENABLE_OVERLOADING)
    CellViewGetDisplayedRowMethodInfo       ,
#endif
    cellViewGetDisplayedRow                 ,


-- ** getDrawSensitive #method:getDrawSensitive#

#if defined(ENABLE_OVERLOADING)
    CellViewGetDrawSensitiveMethodInfo      ,
#endif
    cellViewGetDrawSensitive                ,


-- ** getFitModel #method:getFitModel#

#if defined(ENABLE_OVERLOADING)
    CellViewGetFitModelMethodInfo           ,
#endif
    cellViewGetFitModel                     ,


-- ** getModel #method:getModel#

#if defined(ENABLE_OVERLOADING)
    CellViewGetModelMethodInfo              ,
#endif
    cellViewGetModel                        ,


-- ** new #method:new#

    cellViewNew                             ,


-- ** newWithContext #method:newWithContext#

    cellViewNewWithContext                  ,


-- ** newWithMarkup #method:newWithMarkup#

    cellViewNewWithMarkup                   ,


-- ** newWithText #method:newWithText#

    cellViewNewWithText                     ,


-- ** newWithTexture #method:newWithTexture#

    cellViewNewWithTexture                  ,


-- ** setDisplayedRow #method:setDisplayedRow#

#if defined(ENABLE_OVERLOADING)
    CellViewSetDisplayedRowMethodInfo       ,
#endif
    cellViewSetDisplayedRow                 ,


-- ** setDrawSensitive #method:setDrawSensitive#

#if defined(ENABLE_OVERLOADING)
    CellViewSetDrawSensitiveMethodInfo      ,
#endif
    cellViewSetDrawSensitive                ,


-- ** setFitModel #method:setFitModel#

#if defined(ENABLE_OVERLOADING)
    CellViewSetFitModelMethodInfo           ,
#endif
    cellViewSetFitModel                     ,


-- ** setModel #method:setModel#

#if defined(ENABLE_OVERLOADING)
    CellViewSetModelMethodInfo              ,
#endif
    cellViewSetModel                        ,




 -- * Properties


-- ** cellArea #attr:cellArea#
-- | The @GtkCellArea@ rendering cells
-- 
-- If no area is specified when creating the cell view with 'GI.Gtk.Objects.CellView.cellViewNewWithContext'
-- a horizontally oriented @GtkCellArea@Box will be used.
-- 
-- since 3.0

#if defined(ENABLE_OVERLOADING)
    CellViewCellAreaPropertyInfo            ,
#endif
#if defined(ENABLE_OVERLOADING)
    cellViewCellArea                        ,
#endif
    constructCellViewCellArea               ,
    getCellViewCellArea                     ,


-- ** cellAreaContext #attr:cellAreaContext#
-- | The @GtkCellAreaContext@ used to compute the geometry of the cell view.
-- 
-- A group of cell views can be assigned the same context in order to
-- ensure the sizes and cell alignments match across all the views with
-- the same context.
-- 
-- @GtkComboBox@ menus uses this to assign the same context to all cell views
-- in the menu items for a single menu (each submenu creates its own
-- context since the size of each submenu does not depend on parent
-- or sibling menus).
-- 
-- since 3.0

#if defined(ENABLE_OVERLOADING)
    CellViewCellAreaContextPropertyInfo     ,
#endif
#if defined(ENABLE_OVERLOADING)
    cellViewCellAreaContext                 ,
#endif
    constructCellViewCellAreaContext        ,
    getCellViewCellAreaContext              ,


-- ** drawSensitive #attr:drawSensitive#
-- | Whether all cells should be draw as sensitive for this view regardless
-- of the actual cell properties (used to make menus with submenus appear
-- sensitive when the items in submenus might be insensitive).
-- 
-- since 3.0

#if defined(ENABLE_OVERLOADING)
    CellViewDrawSensitivePropertyInfo       ,
#endif
#if defined(ENABLE_OVERLOADING)
    cellViewDrawSensitive                   ,
#endif
    constructCellViewDrawSensitive          ,
    getCellViewDrawSensitive                ,
    setCellViewDrawSensitive                ,


-- ** fitModel #attr:fitModel#
-- | Whether the view should request enough space to always fit
-- the size of every row in the model (used by the combo box to
-- ensure the combo box size doesn\'t change when different items
-- are selected).
-- 
-- since 3.0

#if defined(ENABLE_OVERLOADING)
    CellViewFitModelPropertyInfo            ,
#endif
#if defined(ENABLE_OVERLOADING)
    cellViewFitModel                        ,
#endif
    constructCellViewFitModel               ,
    getCellViewFitModel                     ,
    setCellViewFitModel                     ,


-- ** model #attr:model#
-- | The model for cell view
-- 
-- since 2.10

#if defined(ENABLE_OVERLOADING)
    CellViewModelPropertyInfo               ,
#endif
#if defined(ENABLE_OVERLOADING)
    cellViewModel                           ,
#endif
    clearCellViewModel                      ,
    constructCellViewModel                  ,
    getCellViewModel                        ,
    setCellViewModel                        ,




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R

import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gdk.Objects.Texture as Gdk.Texture
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Accessible as Gtk.Accessible
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.CellLayout as Gtk.CellLayout
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.ConstraintTarget as Gtk.ConstraintTarget
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Orientable as Gtk.Orientable
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.TreeModel as Gtk.TreeModel
import {-# SOURCE #-} qualified GI.Gtk.Objects.CellArea as Gtk.CellArea
import {-# SOURCE #-} qualified GI.Gtk.Objects.CellAreaContext as Gtk.CellAreaContext
import {-# SOURCE #-} qualified GI.Gtk.Objects.Widget as Gtk.Widget
import {-# SOURCE #-} qualified GI.Gtk.Structs.TreePath as Gtk.TreePath

-- | Memory-managed wrapper type.
newtype CellView = CellView (SP.ManagedPtr CellView)
    deriving (CellView -> CellView -> Bool
(CellView -> CellView -> Bool)
-> (CellView -> CellView -> Bool) -> Eq CellView
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CellView -> CellView -> Bool
$c/= :: CellView -> CellView -> Bool
== :: CellView -> CellView -> Bool
$c== :: CellView -> CellView -> Bool
Eq)

instance SP.ManagedPtrNewtype CellView where
    toManagedPtr :: CellView -> ManagedPtr CellView
toManagedPtr (CellView ManagedPtr CellView
p) = ManagedPtr CellView
p

foreign import ccall "gtk_cell_view_get_type"
    c_gtk_cell_view_get_type :: IO B.Types.GType

instance B.Types.TypedObject CellView where
    glibType :: IO GType
glibType = IO GType
c_gtk_cell_view_get_type

instance B.Types.GObject CellView

-- | Type class for types which can be safely cast to `CellView`, for instance with `toCellView`.
class (SP.GObject o, O.IsDescendantOf CellView o) => IsCellView o
instance (SP.GObject o, O.IsDescendantOf CellView o) => IsCellView o

instance O.HasParentTypes CellView
type instance O.ParentTypes CellView = '[Gtk.Widget.Widget, GObject.Object.Object, Gtk.Accessible.Accessible, Gtk.Buildable.Buildable, Gtk.CellLayout.CellLayout, Gtk.ConstraintTarget.ConstraintTarget, Gtk.Orientable.Orientable]

-- | Cast to `CellView`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toCellView :: (MIO.MonadIO m, IsCellView o) => o -> m CellView
toCellView :: forall (m :: * -> *) o.
(MonadIO m, IsCellView o) =>
o -> m CellView
toCellView = IO CellView -> m CellView
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO CellView -> m CellView)
-> (o -> IO CellView) -> o -> m CellView
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr CellView -> CellView) -> o -> IO CellView
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr CellView -> CellView
CellView

-- | Convert 'CellView' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe CellView) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gtk_cell_view_get_type
    gvalueSet_ :: Ptr GValue -> Maybe CellView -> IO ()
gvalueSet_ Ptr GValue
gv Maybe CellView
P.Nothing = Ptr GValue -> Ptr CellView -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr CellView
forall a. Ptr a
FP.nullPtr :: FP.Ptr CellView)
    gvalueSet_ Ptr GValue
gv (P.Just CellView
obj) = CellView -> (Ptr CellView -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr CellView
obj (Ptr GValue -> Ptr CellView -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe CellView)
gvalueGet_ Ptr GValue
gv = do
        Ptr CellView
ptr <- Ptr GValue -> IO (Ptr CellView)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr CellView)
        if Ptr CellView
ptr Ptr CellView -> Ptr CellView -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr CellView
forall a. Ptr a
FP.nullPtr
        then CellView -> Maybe CellView
forall a. a -> Maybe a
P.Just (CellView -> Maybe CellView) -> IO CellView -> IO (Maybe CellView)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr CellView -> CellView) -> Ptr CellView -> IO CellView
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr CellView -> CellView
CellView Ptr CellView
ptr
        else Maybe CellView -> IO (Maybe CellView)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe CellView
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveCellViewMethod (t :: Symbol) (o :: *) :: * where
    ResolveCellViewMethod "actionSetEnabled" o = Gtk.Widget.WidgetActionSetEnabledMethodInfo
    ResolveCellViewMethod "activate" o = Gtk.Widget.WidgetActivateMethodInfo
    ResolveCellViewMethod "activateAction" o = Gtk.Widget.WidgetActivateActionMethodInfo
    ResolveCellViewMethod "activateDefault" o = Gtk.Widget.WidgetActivateDefaultMethodInfo
    ResolveCellViewMethod "addAttribute" o = Gtk.CellLayout.CellLayoutAddAttributeMethodInfo
    ResolveCellViewMethod "addController" o = Gtk.Widget.WidgetAddControllerMethodInfo
    ResolveCellViewMethod "addCssClass" o = Gtk.Widget.WidgetAddCssClassMethodInfo
    ResolveCellViewMethod "addMnemonicLabel" o = Gtk.Widget.WidgetAddMnemonicLabelMethodInfo
    ResolveCellViewMethod "addTickCallback" o = Gtk.Widget.WidgetAddTickCallbackMethodInfo
    ResolveCellViewMethod "allocate" o = Gtk.Widget.WidgetAllocateMethodInfo
    ResolveCellViewMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveCellViewMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveCellViewMethod "childFocus" o = Gtk.Widget.WidgetChildFocusMethodInfo
    ResolveCellViewMethod "clear" o = Gtk.CellLayout.CellLayoutClearMethodInfo
    ResolveCellViewMethod "clearAttributes" o = Gtk.CellLayout.CellLayoutClearAttributesMethodInfo
    ResolveCellViewMethod "computeBounds" o = Gtk.Widget.WidgetComputeBoundsMethodInfo
    ResolveCellViewMethod "computeExpand" o = Gtk.Widget.WidgetComputeExpandMethodInfo
    ResolveCellViewMethod "computePoint" o = Gtk.Widget.WidgetComputePointMethodInfo
    ResolveCellViewMethod "computeTransform" o = Gtk.Widget.WidgetComputeTransformMethodInfo
    ResolveCellViewMethod "contains" o = Gtk.Widget.WidgetContainsMethodInfo
    ResolveCellViewMethod "createPangoContext" o = Gtk.Widget.WidgetCreatePangoContextMethodInfo
    ResolveCellViewMethod "createPangoLayout" o = Gtk.Widget.WidgetCreatePangoLayoutMethodInfo
    ResolveCellViewMethod "dragCheckThreshold" o = Gtk.Widget.WidgetDragCheckThresholdMethodInfo
    ResolveCellViewMethod "errorBell" o = Gtk.Widget.WidgetErrorBellMethodInfo
    ResolveCellViewMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveCellViewMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveCellViewMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveCellViewMethod "grabFocus" o = Gtk.Widget.WidgetGrabFocusMethodInfo
    ResolveCellViewMethod "hasCssClass" o = Gtk.Widget.WidgetHasCssClassMethodInfo
    ResolveCellViewMethod "hasDefault" o = Gtk.Widget.WidgetHasDefaultMethodInfo
    ResolveCellViewMethod "hasFocus" o = Gtk.Widget.WidgetHasFocusMethodInfo
    ResolveCellViewMethod "hasVisibleFocus" o = Gtk.Widget.WidgetHasVisibleFocusMethodInfo
    ResolveCellViewMethod "hide" o = Gtk.Widget.WidgetHideMethodInfo
    ResolveCellViewMethod "inDestruction" o = Gtk.Widget.WidgetInDestructionMethodInfo
    ResolveCellViewMethod "initTemplate" o = Gtk.Widget.WidgetInitTemplateMethodInfo
    ResolveCellViewMethod "insertActionGroup" o = Gtk.Widget.WidgetInsertActionGroupMethodInfo
    ResolveCellViewMethod "insertAfter" o = Gtk.Widget.WidgetInsertAfterMethodInfo
    ResolveCellViewMethod "insertBefore" o = Gtk.Widget.WidgetInsertBeforeMethodInfo
    ResolveCellViewMethod "isAncestor" o = Gtk.Widget.WidgetIsAncestorMethodInfo
    ResolveCellViewMethod "isDrawable" o = Gtk.Widget.WidgetIsDrawableMethodInfo
    ResolveCellViewMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveCellViewMethod "isFocus" o = Gtk.Widget.WidgetIsFocusMethodInfo
    ResolveCellViewMethod "isSensitive" o = Gtk.Widget.WidgetIsSensitiveMethodInfo
    ResolveCellViewMethod "isVisible" o = Gtk.Widget.WidgetIsVisibleMethodInfo
    ResolveCellViewMethod "keynavFailed" o = Gtk.Widget.WidgetKeynavFailedMethodInfo
    ResolveCellViewMethod "listMnemonicLabels" o = Gtk.Widget.WidgetListMnemonicLabelsMethodInfo
    ResolveCellViewMethod "map" o = Gtk.Widget.WidgetMapMethodInfo
    ResolveCellViewMethod "measure" o = Gtk.Widget.WidgetMeasureMethodInfo
    ResolveCellViewMethod "mnemonicActivate" o = Gtk.Widget.WidgetMnemonicActivateMethodInfo
    ResolveCellViewMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveCellViewMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveCellViewMethod "observeChildren" o = Gtk.Widget.WidgetObserveChildrenMethodInfo
    ResolveCellViewMethod "observeControllers" o = Gtk.Widget.WidgetObserveControllersMethodInfo
    ResolveCellViewMethod "packEnd" o = Gtk.CellLayout.CellLayoutPackEndMethodInfo
    ResolveCellViewMethod "packStart" o = Gtk.CellLayout.CellLayoutPackStartMethodInfo
    ResolveCellViewMethod "pick" o = Gtk.Widget.WidgetPickMethodInfo
    ResolveCellViewMethod "queueAllocate" o = Gtk.Widget.WidgetQueueAllocateMethodInfo
    ResolveCellViewMethod "queueDraw" o = Gtk.Widget.WidgetQueueDrawMethodInfo
    ResolveCellViewMethod "queueResize" o = Gtk.Widget.WidgetQueueResizeMethodInfo
    ResolveCellViewMethod "realize" o = Gtk.Widget.WidgetRealizeMethodInfo
    ResolveCellViewMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveCellViewMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveCellViewMethod "removeController" o = Gtk.Widget.WidgetRemoveControllerMethodInfo
    ResolveCellViewMethod "removeCssClass" o = Gtk.Widget.WidgetRemoveCssClassMethodInfo
    ResolveCellViewMethod "removeMnemonicLabel" o = Gtk.Widget.WidgetRemoveMnemonicLabelMethodInfo
    ResolveCellViewMethod "removeTickCallback" o = Gtk.Widget.WidgetRemoveTickCallbackMethodInfo
    ResolveCellViewMethod "reorder" o = Gtk.CellLayout.CellLayoutReorderMethodInfo
    ResolveCellViewMethod "resetProperty" o = Gtk.Accessible.AccessibleResetPropertyMethodInfo
    ResolveCellViewMethod "resetRelation" o = Gtk.Accessible.AccessibleResetRelationMethodInfo
    ResolveCellViewMethod "resetState" o = Gtk.Accessible.AccessibleResetStateMethodInfo
    ResolveCellViewMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveCellViewMethod "shouldLayout" o = Gtk.Widget.WidgetShouldLayoutMethodInfo
    ResolveCellViewMethod "show" o = Gtk.Widget.WidgetShowMethodInfo
    ResolveCellViewMethod "sizeAllocate" o = Gtk.Widget.WidgetSizeAllocateMethodInfo
    ResolveCellViewMethod "snapshotChild" o = Gtk.Widget.WidgetSnapshotChildMethodInfo
    ResolveCellViewMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveCellViewMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveCellViewMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveCellViewMethod "translateCoordinates" o = Gtk.Widget.WidgetTranslateCoordinatesMethodInfo
    ResolveCellViewMethod "triggerTooltipQuery" o = Gtk.Widget.WidgetTriggerTooltipQueryMethodInfo
    ResolveCellViewMethod "unmap" o = Gtk.Widget.WidgetUnmapMethodInfo
    ResolveCellViewMethod "unparent" o = Gtk.Widget.WidgetUnparentMethodInfo
    ResolveCellViewMethod "unrealize" o = Gtk.Widget.WidgetUnrealizeMethodInfo
    ResolveCellViewMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveCellViewMethod "unsetStateFlags" o = Gtk.Widget.WidgetUnsetStateFlagsMethodInfo
    ResolveCellViewMethod "updateProperty" o = Gtk.Accessible.AccessibleUpdatePropertyMethodInfo
    ResolveCellViewMethod "updateRelation" o = Gtk.Accessible.AccessibleUpdateRelationMethodInfo
    ResolveCellViewMethod "updateState" o = Gtk.Accessible.AccessibleUpdateStateMethodInfo
    ResolveCellViewMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveCellViewMethod "getAccessibleRole" o = Gtk.Accessible.AccessibleGetAccessibleRoleMethodInfo
    ResolveCellViewMethod "getAllocatedBaseline" o = Gtk.Widget.WidgetGetAllocatedBaselineMethodInfo
    ResolveCellViewMethod "getAllocatedHeight" o = Gtk.Widget.WidgetGetAllocatedHeightMethodInfo
    ResolveCellViewMethod "getAllocatedWidth" o = Gtk.Widget.WidgetGetAllocatedWidthMethodInfo
    ResolveCellViewMethod "getAllocation" o = Gtk.Widget.WidgetGetAllocationMethodInfo
    ResolveCellViewMethod "getAncestor" o = Gtk.Widget.WidgetGetAncestorMethodInfo
    ResolveCellViewMethod "getArea" o = Gtk.CellLayout.CellLayoutGetAreaMethodInfo
    ResolveCellViewMethod "getBuildableId" o = Gtk.Buildable.BuildableGetBuildableIdMethodInfo
    ResolveCellViewMethod "getCanFocus" o = Gtk.Widget.WidgetGetCanFocusMethodInfo
    ResolveCellViewMethod "getCanTarget" o = Gtk.Widget.WidgetGetCanTargetMethodInfo
    ResolveCellViewMethod "getCells" o = Gtk.CellLayout.CellLayoutGetCellsMethodInfo
    ResolveCellViewMethod "getChildVisible" o = Gtk.Widget.WidgetGetChildVisibleMethodInfo
    ResolveCellViewMethod "getClipboard" o = Gtk.Widget.WidgetGetClipboardMethodInfo
    ResolveCellViewMethod "getCssClasses" o = Gtk.Widget.WidgetGetCssClassesMethodInfo
    ResolveCellViewMethod "getCssName" o = Gtk.Widget.WidgetGetCssNameMethodInfo
    ResolveCellViewMethod "getCursor" o = Gtk.Widget.WidgetGetCursorMethodInfo
    ResolveCellViewMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveCellViewMethod "getDirection" o = Gtk.Widget.WidgetGetDirectionMethodInfo
    ResolveCellViewMethod "getDisplay" o = Gtk.Widget.WidgetGetDisplayMethodInfo
    ResolveCellViewMethod "getDisplayedRow" o = CellViewGetDisplayedRowMethodInfo
    ResolveCellViewMethod "getDrawSensitive" o = CellViewGetDrawSensitiveMethodInfo
    ResolveCellViewMethod "getFirstChild" o = Gtk.Widget.WidgetGetFirstChildMethodInfo
    ResolveCellViewMethod "getFitModel" o = CellViewGetFitModelMethodInfo
    ResolveCellViewMethod "getFocusChild" o = Gtk.Widget.WidgetGetFocusChildMethodInfo
    ResolveCellViewMethod "getFocusOnClick" o = Gtk.Widget.WidgetGetFocusOnClickMethodInfo
    ResolveCellViewMethod "getFocusable" o = Gtk.Widget.WidgetGetFocusableMethodInfo
    ResolveCellViewMethod "getFontMap" o = Gtk.Widget.WidgetGetFontMapMethodInfo
    ResolveCellViewMethod "getFontOptions" o = Gtk.Widget.WidgetGetFontOptionsMethodInfo
    ResolveCellViewMethod "getFrameClock" o = Gtk.Widget.WidgetGetFrameClockMethodInfo
    ResolveCellViewMethod "getHalign" o = Gtk.Widget.WidgetGetHalignMethodInfo
    ResolveCellViewMethod "getHasTooltip" o = Gtk.Widget.WidgetGetHasTooltipMethodInfo
    ResolveCellViewMethod "getHeight" o = Gtk.Widget.WidgetGetHeightMethodInfo
    ResolveCellViewMethod "getHexpand" o = Gtk.Widget.WidgetGetHexpandMethodInfo
    ResolveCellViewMethod "getHexpandSet" o = Gtk.Widget.WidgetGetHexpandSetMethodInfo
    ResolveCellViewMethod "getLastChild" o = Gtk.Widget.WidgetGetLastChildMethodInfo
    ResolveCellViewMethod "getLayoutManager" o = Gtk.Widget.WidgetGetLayoutManagerMethodInfo
    ResolveCellViewMethod "getMapped" o = Gtk.Widget.WidgetGetMappedMethodInfo
    ResolveCellViewMethod "getMarginBottom" o = Gtk.Widget.WidgetGetMarginBottomMethodInfo
    ResolveCellViewMethod "getMarginEnd" o = Gtk.Widget.WidgetGetMarginEndMethodInfo
    ResolveCellViewMethod "getMarginStart" o = Gtk.Widget.WidgetGetMarginStartMethodInfo
    ResolveCellViewMethod "getMarginTop" o = Gtk.Widget.WidgetGetMarginTopMethodInfo
    ResolveCellViewMethod "getModel" o = CellViewGetModelMethodInfo
    ResolveCellViewMethod "getName" o = Gtk.Widget.WidgetGetNameMethodInfo
    ResolveCellViewMethod "getNative" o = Gtk.Widget.WidgetGetNativeMethodInfo
    ResolveCellViewMethod "getNextSibling" o = Gtk.Widget.WidgetGetNextSiblingMethodInfo
    ResolveCellViewMethod "getOpacity" o = Gtk.Widget.WidgetGetOpacityMethodInfo
    ResolveCellViewMethod "getOrientation" o = Gtk.Orientable.OrientableGetOrientationMethodInfo
    ResolveCellViewMethod "getOverflow" o = Gtk.Widget.WidgetGetOverflowMethodInfo
    ResolveCellViewMethod "getPangoContext" o = Gtk.Widget.WidgetGetPangoContextMethodInfo
    ResolveCellViewMethod "getParent" o = Gtk.Widget.WidgetGetParentMethodInfo
    ResolveCellViewMethod "getPreferredSize" o = Gtk.Widget.WidgetGetPreferredSizeMethodInfo
    ResolveCellViewMethod "getPrevSibling" o = Gtk.Widget.WidgetGetPrevSiblingMethodInfo
    ResolveCellViewMethod "getPrimaryClipboard" o = Gtk.Widget.WidgetGetPrimaryClipboardMethodInfo
    ResolveCellViewMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveCellViewMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveCellViewMethod "getRealized" o = Gtk.Widget.WidgetGetRealizedMethodInfo
    ResolveCellViewMethod "getReceivesDefault" o = Gtk.Widget.WidgetGetReceivesDefaultMethodInfo
    ResolveCellViewMethod "getRequestMode" o = Gtk.Widget.WidgetGetRequestModeMethodInfo
    ResolveCellViewMethod "getRoot" o = Gtk.Widget.WidgetGetRootMethodInfo
    ResolveCellViewMethod "getScaleFactor" o = Gtk.Widget.WidgetGetScaleFactorMethodInfo
    ResolveCellViewMethod "getSensitive" o = Gtk.Widget.WidgetGetSensitiveMethodInfo
    ResolveCellViewMethod "getSettings" o = Gtk.Widget.WidgetGetSettingsMethodInfo
    ResolveCellViewMethod "getSize" o = Gtk.Widget.WidgetGetSizeMethodInfo
    ResolveCellViewMethod "getSizeRequest" o = Gtk.Widget.WidgetGetSizeRequestMethodInfo
    ResolveCellViewMethod "getStateFlags" o = Gtk.Widget.WidgetGetStateFlagsMethodInfo
    ResolveCellViewMethod "getStyleContext" o = Gtk.Widget.WidgetGetStyleContextMethodInfo
    ResolveCellViewMethod "getTemplateChild" o = Gtk.Widget.WidgetGetTemplateChildMethodInfo
    ResolveCellViewMethod "getTooltipMarkup" o = Gtk.Widget.WidgetGetTooltipMarkupMethodInfo
    ResolveCellViewMethod "getTooltipText" o = Gtk.Widget.WidgetGetTooltipTextMethodInfo
    ResolveCellViewMethod "getValign" o = Gtk.Widget.WidgetGetValignMethodInfo
    ResolveCellViewMethod "getVexpand" o = Gtk.Widget.WidgetGetVexpandMethodInfo
    ResolveCellViewMethod "getVexpandSet" o = Gtk.Widget.WidgetGetVexpandSetMethodInfo
    ResolveCellViewMethod "getVisible" o = Gtk.Widget.WidgetGetVisibleMethodInfo
    ResolveCellViewMethod "getWidth" o = Gtk.Widget.WidgetGetWidthMethodInfo
    ResolveCellViewMethod "setCanFocus" o = Gtk.Widget.WidgetSetCanFocusMethodInfo
    ResolveCellViewMethod "setCanTarget" o = Gtk.Widget.WidgetSetCanTargetMethodInfo
    ResolveCellViewMethod "setCellDataFunc" o = Gtk.CellLayout.CellLayoutSetCellDataFuncMethodInfo
    ResolveCellViewMethod "setChildVisible" o = Gtk.Widget.WidgetSetChildVisibleMethodInfo
    ResolveCellViewMethod "setCssClasses" o = Gtk.Widget.WidgetSetCssClassesMethodInfo
    ResolveCellViewMethod "setCursor" o = Gtk.Widget.WidgetSetCursorMethodInfo
    ResolveCellViewMethod "setCursorFromName" o = Gtk.Widget.WidgetSetCursorFromNameMethodInfo
    ResolveCellViewMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveCellViewMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveCellViewMethod "setDirection" o = Gtk.Widget.WidgetSetDirectionMethodInfo
    ResolveCellViewMethod "setDisplayedRow" o = CellViewSetDisplayedRowMethodInfo
    ResolveCellViewMethod "setDrawSensitive" o = CellViewSetDrawSensitiveMethodInfo
    ResolveCellViewMethod "setFitModel" o = CellViewSetFitModelMethodInfo
    ResolveCellViewMethod "setFocusChild" o = Gtk.Widget.WidgetSetFocusChildMethodInfo
    ResolveCellViewMethod "setFocusOnClick" o = Gtk.Widget.WidgetSetFocusOnClickMethodInfo
    ResolveCellViewMethod "setFocusable" o = Gtk.Widget.WidgetSetFocusableMethodInfo
    ResolveCellViewMethod "setFontMap" o = Gtk.Widget.WidgetSetFontMapMethodInfo
    ResolveCellViewMethod "setFontOptions" o = Gtk.Widget.WidgetSetFontOptionsMethodInfo
    ResolveCellViewMethod "setHalign" o = Gtk.Widget.WidgetSetHalignMethodInfo
    ResolveCellViewMethod "setHasTooltip" o = Gtk.Widget.WidgetSetHasTooltipMethodInfo
    ResolveCellViewMethod "setHexpand" o = Gtk.Widget.WidgetSetHexpandMethodInfo
    ResolveCellViewMethod "setHexpandSet" o = Gtk.Widget.WidgetSetHexpandSetMethodInfo
    ResolveCellViewMethod "setLayoutManager" o = Gtk.Widget.WidgetSetLayoutManagerMethodInfo
    ResolveCellViewMethod "setMarginBottom" o = Gtk.Widget.WidgetSetMarginBottomMethodInfo
    ResolveCellViewMethod "setMarginEnd" o = Gtk.Widget.WidgetSetMarginEndMethodInfo
    ResolveCellViewMethod "setMarginStart" o = Gtk.Widget.WidgetSetMarginStartMethodInfo
    ResolveCellViewMethod "setMarginTop" o = Gtk.Widget.WidgetSetMarginTopMethodInfo
    ResolveCellViewMethod "setModel" o = CellViewSetModelMethodInfo
    ResolveCellViewMethod "setName" o = Gtk.Widget.WidgetSetNameMethodInfo
    ResolveCellViewMethod "setOpacity" o = Gtk.Widget.WidgetSetOpacityMethodInfo
    ResolveCellViewMethod "setOrientation" o = Gtk.Orientable.OrientableSetOrientationMethodInfo
    ResolveCellViewMethod "setOverflow" o = Gtk.Widget.WidgetSetOverflowMethodInfo
    ResolveCellViewMethod "setParent" o = Gtk.Widget.WidgetSetParentMethodInfo
    ResolveCellViewMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveCellViewMethod "setReceivesDefault" o = Gtk.Widget.WidgetSetReceivesDefaultMethodInfo
    ResolveCellViewMethod "setSensitive" o = Gtk.Widget.WidgetSetSensitiveMethodInfo
    ResolveCellViewMethod "setSizeRequest" o = Gtk.Widget.WidgetSetSizeRequestMethodInfo
    ResolveCellViewMethod "setStateFlags" o = Gtk.Widget.WidgetSetStateFlagsMethodInfo
    ResolveCellViewMethod "setTooltipMarkup" o = Gtk.Widget.WidgetSetTooltipMarkupMethodInfo
    ResolveCellViewMethod "setTooltipText" o = Gtk.Widget.WidgetSetTooltipTextMethodInfo
    ResolveCellViewMethod "setValign" o = Gtk.Widget.WidgetSetValignMethodInfo
    ResolveCellViewMethod "setVexpand" o = Gtk.Widget.WidgetSetVexpandMethodInfo
    ResolveCellViewMethod "setVexpandSet" o = Gtk.Widget.WidgetSetVexpandSetMethodInfo
    ResolveCellViewMethod "setVisible" o = Gtk.Widget.WidgetSetVisibleMethodInfo
    ResolveCellViewMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveCellViewMethod t CellView, O.OverloadedMethod info CellView p) => OL.IsLabel t (CellView -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveCellViewMethod t CellView, O.OverloadedMethod info CellView p, R.HasField t CellView p) => R.HasField t CellView p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveCellViewMethod t CellView, O.OverloadedMethodInfo info CellView) => OL.IsLabel t (O.MethodProxy info CellView) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif

-- VVV Prop "cell-area"
   -- Type: TInterface (Name {namespace = "Gtk", name = "CellArea"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@cell-area@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' cellView #cellArea
-- @
getCellViewCellArea :: (MonadIO m, IsCellView o) => o -> m (Maybe Gtk.CellArea.CellArea)
getCellViewCellArea :: forall (m :: * -> *) o.
(MonadIO m, IsCellView o) =>
o -> m (Maybe CellArea)
getCellViewCellArea o
obj = IO (Maybe CellArea) -> m (Maybe CellArea)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe CellArea) -> m (Maybe CellArea))
-> IO (Maybe CellArea) -> m (Maybe CellArea)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr CellArea -> CellArea)
-> IO (Maybe CellArea)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"cell-area" ManagedPtr CellArea -> CellArea
Gtk.CellArea.CellArea

-- | Construct a `GValueConstruct` with valid value for the “@cell-area@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructCellViewCellArea :: (IsCellView o, MIO.MonadIO m, Gtk.CellArea.IsCellArea a) => a -> m (GValueConstruct o)
constructCellViewCellArea :: forall o (m :: * -> *) a.
(IsCellView o, MonadIO m, IsCellArea a) =>
a -> m (GValueConstruct o)
constructCellViewCellArea a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"cell-area" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

#if defined(ENABLE_OVERLOADING)
data CellViewCellAreaPropertyInfo
instance AttrInfo CellViewCellAreaPropertyInfo where
    type AttrAllowedOps CellViewCellAreaPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint CellViewCellAreaPropertyInfo = IsCellView
    type AttrSetTypeConstraint CellViewCellAreaPropertyInfo = Gtk.CellArea.IsCellArea
    type AttrTransferTypeConstraint CellViewCellAreaPropertyInfo = Gtk.CellArea.IsCellArea
    type AttrTransferType CellViewCellAreaPropertyInfo = Gtk.CellArea.CellArea
    type AttrGetType CellViewCellAreaPropertyInfo = (Maybe Gtk.CellArea.CellArea)
    type AttrLabel CellViewCellAreaPropertyInfo = "cell-area"
    type AttrOrigin CellViewCellAreaPropertyInfo = CellView
    attrGet = getCellViewCellArea
    attrSet = undefined
    attrTransfer _ v = do
        unsafeCastTo Gtk.CellArea.CellArea v
    attrConstruct = constructCellViewCellArea
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.CellView.cellArea"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Objects-CellView.html#g:attr:cellArea"
        })
#endif

-- VVV Prop "cell-area-context"
   -- Type: TInterface (Name {namespace = "Gtk", name = "CellAreaContext"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@cell-area-context@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' cellView #cellAreaContext
-- @
getCellViewCellAreaContext :: (MonadIO m, IsCellView o) => o -> m (Maybe Gtk.CellAreaContext.CellAreaContext)
getCellViewCellAreaContext :: forall (m :: * -> *) o.
(MonadIO m, IsCellView o) =>
o -> m (Maybe CellAreaContext)
getCellViewCellAreaContext o
obj = IO (Maybe CellAreaContext) -> m (Maybe CellAreaContext)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe CellAreaContext) -> m (Maybe CellAreaContext))
-> IO (Maybe CellAreaContext) -> m (Maybe CellAreaContext)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr CellAreaContext -> CellAreaContext)
-> IO (Maybe CellAreaContext)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"cell-area-context" ManagedPtr CellAreaContext -> CellAreaContext
Gtk.CellAreaContext.CellAreaContext

-- | Construct a `GValueConstruct` with valid value for the “@cell-area-context@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructCellViewCellAreaContext :: (IsCellView o, MIO.MonadIO m, Gtk.CellAreaContext.IsCellAreaContext a) => a -> m (GValueConstruct o)
constructCellViewCellAreaContext :: forall o (m :: * -> *) a.
(IsCellView o, MonadIO m, IsCellAreaContext a) =>
a -> m (GValueConstruct o)
constructCellViewCellAreaContext a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"cell-area-context" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

#if defined(ENABLE_OVERLOADING)
data CellViewCellAreaContextPropertyInfo
instance AttrInfo CellViewCellAreaContextPropertyInfo where
    type AttrAllowedOps CellViewCellAreaContextPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint CellViewCellAreaContextPropertyInfo = IsCellView
    type AttrSetTypeConstraint CellViewCellAreaContextPropertyInfo = Gtk.CellAreaContext.IsCellAreaContext
    type AttrTransferTypeConstraint CellViewCellAreaContextPropertyInfo = Gtk.CellAreaContext.IsCellAreaContext
    type AttrTransferType CellViewCellAreaContextPropertyInfo = Gtk.CellAreaContext.CellAreaContext
    type AttrGetType CellViewCellAreaContextPropertyInfo = (Maybe Gtk.CellAreaContext.CellAreaContext)
    type AttrLabel CellViewCellAreaContextPropertyInfo = "cell-area-context"
    type AttrOrigin CellViewCellAreaContextPropertyInfo = CellView
    attrGet = getCellViewCellAreaContext
    attrSet = undefined
    attrTransfer _ v = do
        unsafeCastTo Gtk.CellAreaContext.CellAreaContext v
    attrConstruct = constructCellViewCellAreaContext
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.CellView.cellAreaContext"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Objects-CellView.html#g:attr:cellAreaContext"
        })
#endif

-- VVV Prop "draw-sensitive"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@draw-sensitive@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' cellView #drawSensitive
-- @
getCellViewDrawSensitive :: (MonadIO m, IsCellView o) => o -> m Bool
getCellViewDrawSensitive :: forall (m :: * -> *) o. (MonadIO m, IsCellView o) => o -> m Bool
getCellViewDrawSensitive o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"draw-sensitive"

-- | Set the value of the “@draw-sensitive@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' cellView [ #drawSensitive 'Data.GI.Base.Attributes.:=' value ]
-- @
setCellViewDrawSensitive :: (MonadIO m, IsCellView o) => o -> Bool -> m ()
setCellViewDrawSensitive :: forall (m :: * -> *) o.
(MonadIO m, IsCellView o) =>
o -> Bool -> m ()
setCellViewDrawSensitive o
obj Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"draw-sensitive" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@draw-sensitive@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructCellViewDrawSensitive :: (IsCellView o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructCellViewDrawSensitive :: forall o (m :: * -> *).
(IsCellView o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructCellViewDrawSensitive Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"draw-sensitive" Bool
val

#if defined(ENABLE_OVERLOADING)
data CellViewDrawSensitivePropertyInfo
instance AttrInfo CellViewDrawSensitivePropertyInfo where
    type AttrAllowedOps CellViewDrawSensitivePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint CellViewDrawSensitivePropertyInfo = IsCellView
    type AttrSetTypeConstraint CellViewDrawSensitivePropertyInfo = (~) Bool
    type AttrTransferTypeConstraint CellViewDrawSensitivePropertyInfo = (~) Bool
    type AttrTransferType CellViewDrawSensitivePropertyInfo = Bool
    type AttrGetType CellViewDrawSensitivePropertyInfo = Bool
    type AttrLabel CellViewDrawSensitivePropertyInfo = "draw-sensitive"
    type AttrOrigin CellViewDrawSensitivePropertyInfo = CellView
    attrGet = getCellViewDrawSensitive
    attrSet = setCellViewDrawSensitive
    attrTransfer _ v = do
        return v
    attrConstruct = constructCellViewDrawSensitive
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.CellView.drawSensitive"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Objects-CellView.html#g:attr:drawSensitive"
        })
#endif

-- VVV Prop "fit-model"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@fit-model@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' cellView #fitModel
-- @
getCellViewFitModel :: (MonadIO m, IsCellView o) => o -> m Bool
getCellViewFitModel :: forall (m :: * -> *) o. (MonadIO m, IsCellView o) => o -> m Bool
getCellViewFitModel o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"fit-model"

-- | Set the value of the “@fit-model@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' cellView [ #fitModel 'Data.GI.Base.Attributes.:=' value ]
-- @
setCellViewFitModel :: (MonadIO m, IsCellView o) => o -> Bool -> m ()
setCellViewFitModel :: forall (m :: * -> *) o.
(MonadIO m, IsCellView o) =>
o -> Bool -> m ()
setCellViewFitModel o
obj Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"fit-model" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@fit-model@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructCellViewFitModel :: (IsCellView o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructCellViewFitModel :: forall o (m :: * -> *).
(IsCellView o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructCellViewFitModel Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"fit-model" Bool
val

#if defined(ENABLE_OVERLOADING)
data CellViewFitModelPropertyInfo
instance AttrInfo CellViewFitModelPropertyInfo where
    type AttrAllowedOps CellViewFitModelPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint CellViewFitModelPropertyInfo = IsCellView
    type AttrSetTypeConstraint CellViewFitModelPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint CellViewFitModelPropertyInfo = (~) Bool
    type AttrTransferType CellViewFitModelPropertyInfo = Bool
    type AttrGetType CellViewFitModelPropertyInfo = Bool
    type AttrLabel CellViewFitModelPropertyInfo = "fit-model"
    type AttrOrigin CellViewFitModelPropertyInfo = CellView
    attrGet = getCellViewFitModel
    attrSet = setCellViewFitModel
    attrTransfer _ v = do
        return v
    attrConstruct = constructCellViewFitModel
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.CellView.fitModel"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Objects-CellView.html#g:attr:fitModel"
        })
#endif

-- VVV Prop "model"
   -- Type: TInterface (Name {namespace = "Gtk", name = "TreeModel"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just True,Just True)

-- | Get the value of the “@model@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' cellView #model
-- @
getCellViewModel :: (MonadIO m, IsCellView o) => o -> m (Maybe Gtk.TreeModel.TreeModel)
getCellViewModel :: forall (m :: * -> *) o.
(MonadIO m, IsCellView o) =>
o -> m (Maybe TreeModel)
getCellViewModel o
obj = IO (Maybe TreeModel) -> m (Maybe TreeModel)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe TreeModel) -> m (Maybe TreeModel))
-> IO (Maybe TreeModel) -> m (Maybe TreeModel)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr TreeModel -> TreeModel)
-> IO (Maybe TreeModel)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"model" ManagedPtr TreeModel -> TreeModel
Gtk.TreeModel.TreeModel

-- | Set the value of the “@model@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' cellView [ #model 'Data.GI.Base.Attributes.:=' value ]
-- @
setCellViewModel :: (MonadIO m, IsCellView o, Gtk.TreeModel.IsTreeModel a) => o -> a -> m ()
setCellViewModel :: forall (m :: * -> *) o a.
(MonadIO m, IsCellView o, IsTreeModel a) =>
o -> a -> m ()
setCellViewModel o
obj a
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"model" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)

-- | Construct a `GValueConstruct` with valid value for the “@model@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructCellViewModel :: (IsCellView o, MIO.MonadIO m, Gtk.TreeModel.IsTreeModel a) => a -> m (GValueConstruct o)
constructCellViewModel :: forall o (m :: * -> *) a.
(IsCellView o, MonadIO m, IsTreeModel a) =>
a -> m (GValueConstruct o)
constructCellViewModel a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"model" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

-- | Set the value of the “@model@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #model
-- @
clearCellViewModel :: (MonadIO m, IsCellView o) => o -> m ()
clearCellViewModel :: forall (m :: * -> *) o. (MonadIO m, IsCellView o) => o -> m ()
clearCellViewModel o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe TreeModel -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"model" (Maybe TreeModel
forall a. Maybe a
Nothing :: Maybe Gtk.TreeModel.TreeModel)

#if defined(ENABLE_OVERLOADING)
data CellViewModelPropertyInfo
instance AttrInfo CellViewModelPropertyInfo where
    type AttrAllowedOps CellViewModelPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint CellViewModelPropertyInfo = IsCellView
    type AttrSetTypeConstraint CellViewModelPropertyInfo = Gtk.TreeModel.IsTreeModel
    type AttrTransferTypeConstraint CellViewModelPropertyInfo = Gtk.TreeModel.IsTreeModel
    type AttrTransferType CellViewModelPropertyInfo = Gtk.TreeModel.TreeModel
    type AttrGetType CellViewModelPropertyInfo = (Maybe Gtk.TreeModel.TreeModel)
    type AttrLabel CellViewModelPropertyInfo = "model"
    type AttrOrigin CellViewModelPropertyInfo = CellView
    attrGet = getCellViewModel
    attrSet = setCellViewModel
    attrTransfer _ v = do
        unsafeCastTo Gtk.TreeModel.TreeModel v
    attrConstruct = constructCellViewModel
    attrClear = clearCellViewModel
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.CellView.model"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Objects-CellView.html#g:attr:model"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList CellView
type instance O.AttributeList CellView = CellViewAttributeList
type CellViewAttributeList = ('[ '("accessibleRole", Gtk.Accessible.AccessibleAccessibleRolePropertyInfo), '("canFocus", Gtk.Widget.WidgetCanFocusPropertyInfo), '("canTarget", Gtk.Widget.WidgetCanTargetPropertyInfo), '("cellArea", CellViewCellAreaPropertyInfo), '("cellAreaContext", CellViewCellAreaContextPropertyInfo), '("cssClasses", Gtk.Widget.WidgetCssClassesPropertyInfo), '("cssName", Gtk.Widget.WidgetCssNamePropertyInfo), '("cursor", Gtk.Widget.WidgetCursorPropertyInfo), '("drawSensitive", CellViewDrawSensitivePropertyInfo), '("fitModel", CellViewFitModelPropertyInfo), '("focusOnClick", Gtk.Widget.WidgetFocusOnClickPropertyInfo), '("focusable", Gtk.Widget.WidgetFocusablePropertyInfo), '("halign", Gtk.Widget.WidgetHalignPropertyInfo), '("hasDefault", Gtk.Widget.WidgetHasDefaultPropertyInfo), '("hasFocus", Gtk.Widget.WidgetHasFocusPropertyInfo), '("hasTooltip", Gtk.Widget.WidgetHasTooltipPropertyInfo), '("heightRequest", Gtk.Widget.WidgetHeightRequestPropertyInfo), '("hexpand", Gtk.Widget.WidgetHexpandPropertyInfo), '("hexpandSet", Gtk.Widget.WidgetHexpandSetPropertyInfo), '("layoutManager", Gtk.Widget.WidgetLayoutManagerPropertyInfo), '("marginBottom", Gtk.Widget.WidgetMarginBottomPropertyInfo), '("marginEnd", Gtk.Widget.WidgetMarginEndPropertyInfo), '("marginStart", Gtk.Widget.WidgetMarginStartPropertyInfo), '("marginTop", Gtk.Widget.WidgetMarginTopPropertyInfo), '("model", CellViewModelPropertyInfo), '("name", Gtk.Widget.WidgetNamePropertyInfo), '("opacity", Gtk.Widget.WidgetOpacityPropertyInfo), '("orientation", Gtk.Orientable.OrientableOrientationPropertyInfo), '("overflow", Gtk.Widget.WidgetOverflowPropertyInfo), '("parent", Gtk.Widget.WidgetParentPropertyInfo), '("receivesDefault", Gtk.Widget.WidgetReceivesDefaultPropertyInfo), '("root", Gtk.Widget.WidgetRootPropertyInfo), '("scaleFactor", Gtk.Widget.WidgetScaleFactorPropertyInfo), '("sensitive", Gtk.Widget.WidgetSensitivePropertyInfo), '("tooltipMarkup", Gtk.Widget.WidgetTooltipMarkupPropertyInfo), '("tooltipText", Gtk.Widget.WidgetTooltipTextPropertyInfo), '("valign", Gtk.Widget.WidgetValignPropertyInfo), '("vexpand", Gtk.Widget.WidgetVexpandPropertyInfo), '("vexpandSet", Gtk.Widget.WidgetVexpandSetPropertyInfo), '("visible", Gtk.Widget.WidgetVisiblePropertyInfo), '("widthRequest", Gtk.Widget.WidgetWidthRequestPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
cellViewCellArea :: AttrLabelProxy "cellArea"
cellViewCellArea = AttrLabelProxy

cellViewCellAreaContext :: AttrLabelProxy "cellAreaContext"
cellViewCellAreaContext = AttrLabelProxy

cellViewDrawSensitive :: AttrLabelProxy "drawSensitive"
cellViewDrawSensitive = AttrLabelProxy

cellViewFitModel :: AttrLabelProxy "fitModel"
cellViewFitModel = AttrLabelProxy

cellViewModel :: AttrLabelProxy "model"
cellViewModel = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList CellView = CellViewSignalList
type CellViewSignalList = ('[ '("destroy", Gtk.Widget.WidgetDestroySignalInfo), '("directionChanged", Gtk.Widget.WidgetDirectionChangedSignalInfo), '("hide", Gtk.Widget.WidgetHideSignalInfo), '("keynavFailed", Gtk.Widget.WidgetKeynavFailedSignalInfo), '("map", Gtk.Widget.WidgetMapSignalInfo), '("mnemonicActivate", Gtk.Widget.WidgetMnemonicActivateSignalInfo), '("moveFocus", Gtk.Widget.WidgetMoveFocusSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("queryTooltip", Gtk.Widget.WidgetQueryTooltipSignalInfo), '("realize", Gtk.Widget.WidgetRealizeSignalInfo), '("show", Gtk.Widget.WidgetShowSignalInfo), '("stateFlagsChanged", Gtk.Widget.WidgetStateFlagsChangedSignalInfo), '("unmap", Gtk.Widget.WidgetUnmapSignalInfo), '("unrealize", Gtk.Widget.WidgetUnrealizeSignalInfo)] :: [(Symbol, *)])

#endif

-- method CellView::new
-- method type : Constructor
-- Args: []
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "CellView" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_cell_view_new" gtk_cell_view_new :: 
    IO (Ptr CellView)

-- | Creates a new @GtkCellView@ widget.
cellViewNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m CellView
    -- ^ __Returns:__ A newly created @GtkCellView@ widget.
cellViewNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m CellView
cellViewNew  = IO CellView -> m CellView
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CellView -> m CellView) -> IO CellView -> m CellView
forall a b. (a -> b) -> a -> b
$ do
    Ptr CellView
result <- IO (Ptr CellView)
gtk_cell_view_new
    Text -> Ptr CellView -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"cellViewNew" Ptr CellView
result
    CellView
result' <- ((ManagedPtr CellView -> CellView) -> Ptr CellView -> IO CellView
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr CellView -> CellView
CellView) Ptr CellView
result
    CellView -> IO CellView
forall (m :: * -> *) a. Monad m => a -> m a
return CellView
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method CellView::new_with_context
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "area"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "CellArea" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the `GtkCellArea` to layout cells"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "CellAreaContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the `GtkCellAreaContext` in which to calculate cell geometry"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "CellView" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_cell_view_new_with_context" gtk_cell_view_new_with_context :: 
    Ptr Gtk.CellArea.CellArea ->            -- area : TInterface (Name {namespace = "Gtk", name = "CellArea"})
    Ptr Gtk.CellAreaContext.CellAreaContext -> -- context : TInterface (Name {namespace = "Gtk", name = "CellAreaContext"})
    IO (Ptr CellView)

-- | Creates a new @GtkCellView@ widget with a specific @GtkCellArea@
-- to layout cells and a specific @GtkCellAreaContext@.
-- 
-- Specifying the same context for a handful of cells lets
-- the underlying area synchronize the geometry for those cells,
-- in this way alignments with cellviews for other rows are
-- possible.
cellViewNewWithContext ::
    (B.CallStack.HasCallStack, MonadIO m, Gtk.CellArea.IsCellArea a, Gtk.CellAreaContext.IsCellAreaContext b) =>
    a
    -- ^ /@area@/: the @GtkCellArea@ to layout cells
    -> b
    -- ^ /@context@/: the @GtkCellAreaContext@ in which to calculate cell geometry
    -> m CellView
    -- ^ __Returns:__ A newly created @GtkCellView@ widget.
cellViewNewWithContext :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsCellArea a, IsCellAreaContext b) =>
a -> b -> m CellView
cellViewNewWithContext a
area b
context = IO CellView -> m CellView
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CellView -> m CellView) -> IO CellView -> m CellView
forall a b. (a -> b) -> a -> b
$ do
    Ptr CellArea
area' <- a -> IO (Ptr CellArea)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
area
    Ptr CellAreaContext
context' <- b -> IO (Ptr CellAreaContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
context
    Ptr CellView
result <- Ptr CellArea -> Ptr CellAreaContext -> IO (Ptr CellView)
gtk_cell_view_new_with_context Ptr CellArea
area' Ptr CellAreaContext
context'
    Text -> Ptr CellView -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"cellViewNewWithContext" Ptr CellView
result
    CellView
result' <- ((ManagedPtr CellView -> CellView) -> Ptr CellView -> IO CellView
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr CellView -> CellView
CellView) Ptr CellView
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
area
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
context
    CellView -> IO CellView
forall (m :: * -> *) a. Monad m => a -> m a
return CellView
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method CellView::new_with_markup
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "markup"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the text to display in the cell view"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "CellView" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_cell_view_new_with_markup" gtk_cell_view_new_with_markup :: 
    CString ->                              -- markup : TBasicType TUTF8
    IO (Ptr CellView)

-- | Creates a new @GtkCellView@ widget, adds a @GtkCellRendererText@
-- to it, and makes it show /@markup@/. The text can be marked up with
-- the <https://docs.gtk.org/Pango/pango_markup.html Pango text markup language>.
cellViewNewWithMarkup ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@markup@/: the text to display in the cell view
    -> m CellView
    -- ^ __Returns:__ A newly created @GtkCellView@ widget.
cellViewNewWithMarkup :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> m CellView
cellViewNewWithMarkup Text
markup = IO CellView -> m CellView
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CellView -> m CellView) -> IO CellView -> m CellView
forall a b. (a -> b) -> a -> b
$ do
    CString
markup' <- Text -> IO CString
textToCString Text
markup
    Ptr CellView
result <- CString -> IO (Ptr CellView)
gtk_cell_view_new_with_markup CString
markup'
    Text -> Ptr CellView -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"cellViewNewWithMarkup" Ptr CellView
result
    CellView
result' <- ((ManagedPtr CellView -> CellView) -> Ptr CellView -> IO CellView
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr CellView -> CellView
CellView) Ptr CellView
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
markup'
    CellView -> IO CellView
forall (m :: * -> *) a. Monad m => a -> m a
return CellView
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method CellView::new_with_text
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "text"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the text to display in the cell view"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "CellView" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_cell_view_new_with_text" gtk_cell_view_new_with_text :: 
    CString ->                              -- text : TBasicType TUTF8
    IO (Ptr CellView)

-- | Creates a new @GtkCellView@ widget, adds a @GtkCellRendererText@
-- to it, and makes it show /@text@/.
cellViewNewWithText ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@text@/: the text to display in the cell view
    -> m CellView
    -- ^ __Returns:__ A newly created @GtkCellView@ widget.
cellViewNewWithText :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> m CellView
cellViewNewWithText Text
text = IO CellView -> m CellView
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CellView -> m CellView) -> IO CellView -> m CellView
forall a b. (a -> b) -> a -> b
$ do
    CString
text' <- Text -> IO CString
textToCString Text
text
    Ptr CellView
result <- CString -> IO (Ptr CellView)
gtk_cell_view_new_with_text CString
text'
    Text -> Ptr CellView -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"cellViewNewWithText" Ptr CellView
result
    CellView
result' <- ((ManagedPtr CellView -> CellView) -> Ptr CellView -> IO CellView
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr CellView -> CellView
CellView) Ptr CellView
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
text'
    CellView -> IO CellView
forall (m :: * -> *) a. Monad m => a -> m a
return CellView
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method CellView::new_with_texture
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "texture"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Texture" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the image to display in the cell view"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "CellView" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_cell_view_new_with_texture" gtk_cell_view_new_with_texture :: 
    Ptr Gdk.Texture.Texture ->              -- texture : TInterface (Name {namespace = "Gdk", name = "Texture"})
    IO (Ptr CellView)

-- | Creates a new @GtkCellView@ widget, adds a @GtkCellRendererPixbuf@
-- to it, and makes it show /@texture@/.
cellViewNewWithTexture ::
    (B.CallStack.HasCallStack, MonadIO m, Gdk.Texture.IsTexture a) =>
    a
    -- ^ /@texture@/: the image to display in the cell view
    -> m CellView
    -- ^ __Returns:__ A newly created @GtkCellView@ widget.
cellViewNewWithTexture :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTexture a) =>
a -> m CellView
cellViewNewWithTexture a
texture = IO CellView -> m CellView
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CellView -> m CellView) -> IO CellView -> m CellView
forall a b. (a -> b) -> a -> b
$ do
    Ptr Texture
texture' <- a -> IO (Ptr Texture)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
texture
    Ptr CellView
result <- Ptr Texture -> IO (Ptr CellView)
gtk_cell_view_new_with_texture Ptr Texture
texture'
    Text -> Ptr CellView -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"cellViewNewWithTexture" Ptr CellView
result
    CellView
result' <- ((ManagedPtr CellView -> CellView) -> Ptr CellView -> IO CellView
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr CellView -> CellView
CellView) Ptr CellView
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
texture
    CellView -> IO CellView
forall (m :: * -> *) a. Monad m => a -> m a
return CellView
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method CellView::get_displayed_row
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "cell_view"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "CellView" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkCellView`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "TreePath" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_cell_view_get_displayed_row" gtk_cell_view_get_displayed_row :: 
    Ptr CellView ->                         -- cell_view : TInterface (Name {namespace = "Gtk", name = "CellView"})
    IO (Ptr Gtk.TreePath.TreePath)

-- | Returns a @GtkTreePath@ referring to the currently
-- displayed row. If no row is currently displayed,
-- 'P.Nothing' is returned.
cellViewGetDisplayedRow ::
    (B.CallStack.HasCallStack, MonadIO m, IsCellView a) =>
    a
    -- ^ /@cellView@/: a @GtkCellView@
    -> m (Maybe Gtk.TreePath.TreePath)
    -- ^ __Returns:__ the currently displayed row
cellViewGetDisplayedRow :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCellView a) =>
a -> m (Maybe TreePath)
cellViewGetDisplayedRow a
cellView = IO (Maybe TreePath) -> m (Maybe TreePath)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe TreePath) -> m (Maybe TreePath))
-> IO (Maybe TreePath) -> m (Maybe TreePath)
forall a b. (a -> b) -> a -> b
$ do
    Ptr CellView
cellView' <- a -> IO (Ptr CellView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
cellView
    Ptr TreePath
result <- Ptr CellView -> IO (Ptr TreePath)
gtk_cell_view_get_displayed_row Ptr CellView
cellView'
    Maybe TreePath
maybeResult <- Ptr TreePath
-> (Ptr TreePath -> IO TreePath) -> IO (Maybe TreePath)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr TreePath
result ((Ptr TreePath -> IO TreePath) -> IO (Maybe TreePath))
-> (Ptr TreePath -> IO TreePath) -> IO (Maybe TreePath)
forall a b. (a -> b) -> a -> b
$ \Ptr TreePath
result' -> do
        TreePath
result'' <- ((ManagedPtr TreePath -> TreePath) -> Ptr TreePath -> IO TreePath
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr TreePath -> TreePath
Gtk.TreePath.TreePath) Ptr TreePath
result'
        TreePath -> IO TreePath
forall (m :: * -> *) a. Monad m => a -> m a
return TreePath
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
cellView
    Maybe TreePath -> IO (Maybe TreePath)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TreePath
maybeResult

#if defined(ENABLE_OVERLOADING)
data CellViewGetDisplayedRowMethodInfo
instance (signature ~ (m (Maybe Gtk.TreePath.TreePath)), MonadIO m, IsCellView a) => O.OverloadedMethod CellViewGetDisplayedRowMethodInfo a signature where
    overloadedMethod = cellViewGetDisplayedRow

instance O.OverloadedMethodInfo CellViewGetDisplayedRowMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.CellView.cellViewGetDisplayedRow",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Objects-CellView.html#v:cellViewGetDisplayedRow"
        })


#endif

-- method CellView::get_draw_sensitive
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "cell_view"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "CellView" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkCellView`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_cell_view_get_draw_sensitive" gtk_cell_view_get_draw_sensitive :: 
    Ptr CellView ->                         -- cell_view : TInterface (Name {namespace = "Gtk", name = "CellView"})
    IO CInt

-- | Gets whether /@cellView@/ is configured to draw all of its
-- cells in a sensitive state.
cellViewGetDrawSensitive ::
    (B.CallStack.HasCallStack, MonadIO m, IsCellView a) =>
    a
    -- ^ /@cellView@/: a @GtkCellView@
    -> m Bool
    -- ^ __Returns:__ whether /@cellView@/ draws all of its
    -- cells in a sensitive state
cellViewGetDrawSensitive :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCellView a) =>
a -> m Bool
cellViewGetDrawSensitive a
cellView = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr CellView
cellView' <- a -> IO (Ptr CellView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
cellView
    CInt
result <- Ptr CellView -> IO CInt
gtk_cell_view_get_draw_sensitive Ptr CellView
cellView'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
cellView
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data CellViewGetDrawSensitiveMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsCellView a) => O.OverloadedMethod CellViewGetDrawSensitiveMethodInfo a signature where
    overloadedMethod = cellViewGetDrawSensitive

instance O.OverloadedMethodInfo CellViewGetDrawSensitiveMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.CellView.cellViewGetDrawSensitive",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Objects-CellView.html#v:cellViewGetDrawSensitive"
        })


#endif

-- method CellView::get_fit_model
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "cell_view"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "CellView" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkCellView`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_cell_view_get_fit_model" gtk_cell_view_get_fit_model :: 
    Ptr CellView ->                         -- cell_view : TInterface (Name {namespace = "Gtk", name = "CellView"})
    IO CInt

-- | Gets whether /@cellView@/ is configured to request space
-- to fit the entire @GtkTreeModel@.
cellViewGetFitModel ::
    (B.CallStack.HasCallStack, MonadIO m, IsCellView a) =>
    a
    -- ^ /@cellView@/: a @GtkCellView@
    -> m Bool
    -- ^ __Returns:__ whether /@cellView@/ requests space to fit
    -- the entire @GtkTreeModel@.
cellViewGetFitModel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCellView a) =>
a -> m Bool
cellViewGetFitModel a
cellView = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr CellView
cellView' <- a -> IO (Ptr CellView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
cellView
    CInt
result <- Ptr CellView -> IO CInt
gtk_cell_view_get_fit_model Ptr CellView
cellView'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
cellView
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data CellViewGetFitModelMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsCellView a) => O.OverloadedMethod CellViewGetFitModelMethodInfo a signature where
    overloadedMethod = cellViewGetFitModel

instance O.OverloadedMethodInfo CellViewGetFitModelMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.CellView.cellViewGetFitModel",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Objects-CellView.html#v:cellViewGetFitModel"
        })


#endif

-- method CellView::get_model
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "cell_view"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "CellView" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkCellView`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "TreeModel" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_cell_view_get_model" gtk_cell_view_get_model :: 
    Ptr CellView ->                         -- cell_view : TInterface (Name {namespace = "Gtk", name = "CellView"})
    IO (Ptr Gtk.TreeModel.TreeModel)

-- | Returns the model for /@cellView@/. If no model is used 'P.Nothing' is
-- returned.
cellViewGetModel ::
    (B.CallStack.HasCallStack, MonadIO m, IsCellView a) =>
    a
    -- ^ /@cellView@/: a @GtkCellView@
    -> m (Maybe Gtk.TreeModel.TreeModel)
    -- ^ __Returns:__ a @GtkTreeModel@ used
cellViewGetModel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCellView a) =>
a -> m (Maybe TreeModel)
cellViewGetModel a
cellView = IO (Maybe TreeModel) -> m (Maybe TreeModel)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe TreeModel) -> m (Maybe TreeModel))
-> IO (Maybe TreeModel) -> m (Maybe TreeModel)
forall a b. (a -> b) -> a -> b
$ do
    Ptr CellView
cellView' <- a -> IO (Ptr CellView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
cellView
    Ptr TreeModel
result <- Ptr CellView -> IO (Ptr TreeModel)
gtk_cell_view_get_model Ptr CellView
cellView'
    Maybe TreeModel
maybeResult <- Ptr TreeModel
-> (Ptr TreeModel -> IO TreeModel) -> IO (Maybe TreeModel)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr TreeModel
result ((Ptr TreeModel -> IO TreeModel) -> IO (Maybe TreeModel))
-> (Ptr TreeModel -> IO TreeModel) -> IO (Maybe TreeModel)
forall a b. (a -> b) -> a -> b
$ \Ptr TreeModel
result' -> do
        TreeModel
result'' <- ((ManagedPtr TreeModel -> TreeModel)
-> Ptr TreeModel -> IO TreeModel
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr TreeModel -> TreeModel
Gtk.TreeModel.TreeModel) Ptr TreeModel
result'
        TreeModel -> IO TreeModel
forall (m :: * -> *) a. Monad m => a -> m a
return TreeModel
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
cellView
    Maybe TreeModel -> IO (Maybe TreeModel)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TreeModel
maybeResult

#if defined(ENABLE_OVERLOADING)
data CellViewGetModelMethodInfo
instance (signature ~ (m (Maybe Gtk.TreeModel.TreeModel)), MonadIO m, IsCellView a) => O.OverloadedMethod CellViewGetModelMethodInfo a signature where
    overloadedMethod = cellViewGetModel

instance O.OverloadedMethodInfo CellViewGetModelMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.CellView.cellViewGetModel",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Objects-CellView.html#v:cellViewGetModel"
        })


#endif

-- method CellView::set_displayed_row
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "cell_view"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "CellView" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkCellView`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TreePath" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkTreePath` or %NULL to unset."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_cell_view_set_displayed_row" gtk_cell_view_set_displayed_row :: 
    Ptr CellView ->                         -- cell_view : TInterface (Name {namespace = "Gtk", name = "CellView"})
    Ptr Gtk.TreePath.TreePath ->            -- path : TInterface (Name {namespace = "Gtk", name = "TreePath"})
    IO ()

-- | Sets the row of the model that is currently displayed
-- by the @GtkCellView@. If the path is unset, then the
-- contents of the cellview “stick” at their last value;
-- this is not normally a desired result, but may be
-- a needed intermediate state if say, the model for
-- the @GtkCellView@ becomes temporarily empty.
cellViewSetDisplayedRow ::
    (B.CallStack.HasCallStack, MonadIO m, IsCellView a) =>
    a
    -- ^ /@cellView@/: a @GtkCellView@
    -> Maybe (Gtk.TreePath.TreePath)
    -- ^ /@path@/: a @GtkTreePath@ or 'P.Nothing' to unset.
    -> m ()
cellViewSetDisplayedRow :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCellView a) =>
a -> Maybe TreePath -> m ()
cellViewSetDisplayedRow a
cellView Maybe TreePath
path = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr CellView
cellView' <- a -> IO (Ptr CellView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
cellView
    Ptr TreePath
maybePath <- case Maybe TreePath
path of
        Maybe TreePath
Nothing -> Ptr TreePath -> IO (Ptr TreePath)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TreePath
forall a. Ptr a
nullPtr
        Just TreePath
jPath -> do
            Ptr TreePath
jPath' <- TreePath -> IO (Ptr TreePath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TreePath
jPath
            Ptr TreePath -> IO (Ptr TreePath)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TreePath
jPath'
    Ptr CellView -> Ptr TreePath -> IO ()
gtk_cell_view_set_displayed_row Ptr CellView
cellView' Ptr TreePath
maybePath
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
cellView
    Maybe TreePath -> (TreePath -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe TreePath
path TreePath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data CellViewSetDisplayedRowMethodInfo
instance (signature ~ (Maybe (Gtk.TreePath.TreePath) -> m ()), MonadIO m, IsCellView a) => O.OverloadedMethod CellViewSetDisplayedRowMethodInfo a signature where
    overloadedMethod = cellViewSetDisplayedRow

instance O.OverloadedMethodInfo CellViewSetDisplayedRowMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.CellView.cellViewSetDisplayedRow",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Objects-CellView.html#v:cellViewSetDisplayedRow"
        })


#endif

-- method CellView::set_draw_sensitive
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "cell_view"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "CellView" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkCellView`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "draw_sensitive"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "whether to draw all cells in a sensitive state."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_cell_view_set_draw_sensitive" gtk_cell_view_set_draw_sensitive :: 
    Ptr CellView ->                         -- cell_view : TInterface (Name {namespace = "Gtk", name = "CellView"})
    CInt ->                                 -- draw_sensitive : TBasicType TBoolean
    IO ()

-- | Sets whether /@cellView@/ should draw all of its
-- cells in a sensitive state, this is used by @GtkComboBox@ menus
-- to ensure that rows with insensitive cells that contain
-- children appear sensitive in the parent menu item.
cellViewSetDrawSensitive ::
    (B.CallStack.HasCallStack, MonadIO m, IsCellView a) =>
    a
    -- ^ /@cellView@/: a @GtkCellView@
    -> Bool
    -- ^ /@drawSensitive@/: whether to draw all cells in a sensitive state.
    -> m ()
cellViewSetDrawSensitive :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCellView a) =>
a -> Bool -> m ()
cellViewSetDrawSensitive a
cellView Bool
drawSensitive = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr CellView
cellView' <- a -> IO (Ptr CellView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
cellView
    let drawSensitive' :: CInt
drawSensitive' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
drawSensitive
    Ptr CellView -> CInt -> IO ()
gtk_cell_view_set_draw_sensitive Ptr CellView
cellView' CInt
drawSensitive'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
cellView
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data CellViewSetDrawSensitiveMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsCellView a) => O.OverloadedMethod CellViewSetDrawSensitiveMethodInfo a signature where
    overloadedMethod = cellViewSetDrawSensitive

instance O.OverloadedMethodInfo CellViewSetDrawSensitiveMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.CellView.cellViewSetDrawSensitive",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Objects-CellView.html#v:cellViewSetDrawSensitive"
        })


#endif

-- method CellView::set_fit_model
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "cell_view"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "CellView" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkCellView`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "fit_model"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "whether @cell_view should request space for the whole model."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_cell_view_set_fit_model" gtk_cell_view_set_fit_model :: 
    Ptr CellView ->                         -- cell_view : TInterface (Name {namespace = "Gtk", name = "CellView"})
    CInt ->                                 -- fit_model : TBasicType TBoolean
    IO ()

-- | Sets whether /@cellView@/ should request space to fit the entire @GtkTreeModel@.
-- 
-- This is used by @GtkComboBox@ to ensure that the cell view displayed on
-- the combo box’s button always gets enough space and does not resize
-- when selection changes.
cellViewSetFitModel ::
    (B.CallStack.HasCallStack, MonadIO m, IsCellView a) =>
    a
    -- ^ /@cellView@/: a @GtkCellView@
    -> Bool
    -- ^ /@fitModel@/: whether /@cellView@/ should request space for the whole model.
    -> m ()
cellViewSetFitModel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCellView a) =>
a -> Bool -> m ()
cellViewSetFitModel a
cellView Bool
fitModel = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr CellView
cellView' <- a -> IO (Ptr CellView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
cellView
    let fitModel' :: CInt
fitModel' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
fitModel
    Ptr CellView -> CInt -> IO ()
gtk_cell_view_set_fit_model Ptr CellView
cellView' CInt
fitModel'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
cellView
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data CellViewSetFitModelMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsCellView a) => O.OverloadedMethod CellViewSetFitModelMethodInfo a signature where
    overloadedMethod = cellViewSetFitModel

instance O.OverloadedMethodInfo CellViewSetFitModelMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.CellView.cellViewSetFitModel",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Objects-CellView.html#v:cellViewSetFitModel"
        })


#endif

-- method CellView::set_model
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "cell_view"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "CellView" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkCellView`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "model"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TreeModel" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkTreeModel`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_cell_view_set_model" gtk_cell_view_set_model :: 
    Ptr CellView ->                         -- cell_view : TInterface (Name {namespace = "Gtk", name = "CellView"})
    Ptr Gtk.TreeModel.TreeModel ->          -- model : TInterface (Name {namespace = "Gtk", name = "TreeModel"})
    IO ()

-- | Sets the model for /@cellView@/.  If /@cellView@/ already has a model
-- set, it will remove it before setting the new model.  If /@model@/ is
-- 'P.Nothing', then it will unset the old model.
cellViewSetModel ::
    (B.CallStack.HasCallStack, MonadIO m, IsCellView a, Gtk.TreeModel.IsTreeModel b) =>
    a
    -- ^ /@cellView@/: a @GtkCellView@
    -> Maybe (b)
    -- ^ /@model@/: a @GtkTreeModel@
    -> m ()
cellViewSetModel :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsCellView a, IsTreeModel b) =>
a -> Maybe b -> m ()
cellViewSetModel a
cellView Maybe b
model = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr CellView
cellView' <- a -> IO (Ptr CellView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
cellView
    Ptr TreeModel
maybeModel <- case Maybe b
model of
        Maybe b
Nothing -> Ptr TreeModel -> IO (Ptr TreeModel)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TreeModel
forall a. Ptr a
nullPtr
        Just b
jModel -> do
            Ptr TreeModel
jModel' <- b -> IO (Ptr TreeModel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jModel
            Ptr TreeModel -> IO (Ptr TreeModel)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TreeModel
jModel'
    Ptr CellView -> Ptr TreeModel -> IO ()
gtk_cell_view_set_model Ptr CellView
cellView' Ptr TreeModel
maybeModel
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
cellView
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
model b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data CellViewSetModelMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsCellView a, Gtk.TreeModel.IsTreeModel b) => O.OverloadedMethod CellViewSetModelMethodInfo a signature where
    overloadedMethod = cellViewSetModel

instance O.OverloadedMethodInfo CellViewSetModelMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.CellView.cellViewSetModel",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Objects-CellView.html#v:cellViewSetModel"
        })


#endif