{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Objects.CellView
    ( 
    CellView(..)                            ,
    IsCellView                              ,
    toCellView                              ,
 
#if defined(ENABLE_OVERLOADING)
    ResolveCellViewMethod                   ,
#endif
#if defined(ENABLE_OVERLOADING)
    CellViewGetDisplayedRowMethodInfo       ,
#endif
    cellViewGetDisplayedRow                 ,
#if defined(ENABLE_OVERLOADING)
    CellViewGetDrawSensitiveMethodInfo      ,
#endif
    cellViewGetDrawSensitive                ,
#if defined(ENABLE_OVERLOADING)
    CellViewGetFitModelMethodInfo           ,
#endif
    cellViewGetFitModel                     ,
#if defined(ENABLE_OVERLOADING)
    CellViewGetModelMethodInfo              ,
#endif
    cellViewGetModel                        ,
#if defined(ENABLE_OVERLOADING)
    CellViewGetSizeOfRowMethodInfo          ,
#endif
    cellViewGetSizeOfRow                    ,
    cellViewNew                             ,
    cellViewNewWithContext                  ,
    cellViewNewWithMarkup                   ,
    cellViewNewWithPixbuf                   ,
    cellViewNewWithText                     ,
#if defined(ENABLE_OVERLOADING)
    CellViewSetBackgroundColorMethodInfo    ,
#endif
    cellViewSetBackgroundColor              ,
#if defined(ENABLE_OVERLOADING)
    CellViewSetBackgroundRgbaMethodInfo     ,
#endif
    cellViewSetBackgroundRgba               ,
#if defined(ENABLE_OVERLOADING)
    CellViewSetDisplayedRowMethodInfo       ,
#endif
    cellViewSetDisplayedRow                 ,
#if defined(ENABLE_OVERLOADING)
    CellViewSetDrawSensitiveMethodInfo      ,
#endif
    cellViewSetDrawSensitive                ,
#if defined(ENABLE_OVERLOADING)
    CellViewSetFitModelMethodInfo           ,
#endif
    cellViewSetFitModel                     ,
#if defined(ENABLE_OVERLOADING)
    CellViewSetModelMethodInfo              ,
#endif
    cellViewSetModel                        ,
 
#if defined(ENABLE_OVERLOADING)
    CellViewBackgroundPropertyInfo          ,
#endif
#if defined(ENABLE_OVERLOADING)
    cellViewBackground                      ,
#endif
    clearCellViewBackground                 ,
    constructCellViewBackground             ,
    setCellViewBackground                   ,
#if defined(ENABLE_OVERLOADING)
    CellViewBackgroundGdkPropertyInfo       ,
#endif
#if defined(ENABLE_OVERLOADING)
    cellViewBackgroundGdk                   ,
#endif
    clearCellViewBackgroundGdk              ,
    constructCellViewBackgroundGdk          ,
    getCellViewBackgroundGdk                ,
    setCellViewBackgroundGdk                ,
#if defined(ENABLE_OVERLOADING)
    CellViewBackgroundRgbaPropertyInfo      ,
#endif
#if defined(ENABLE_OVERLOADING)
    cellViewBackgroundRgba                  ,
#endif
    constructCellViewBackgroundRgba         ,
    getCellViewBackgroundRgba               ,
    setCellViewBackgroundRgba               ,
#if defined(ENABLE_OVERLOADING)
    CellViewBackgroundSetPropertyInfo       ,
#endif
#if defined(ENABLE_OVERLOADING)
    cellViewBackgroundSet                   ,
#endif
    constructCellViewBackgroundSet          ,
    getCellViewBackgroundSet                ,
    setCellViewBackgroundSet                ,
#if defined(ENABLE_OVERLOADING)
    CellViewCellAreaPropertyInfo            ,
#endif
#if defined(ENABLE_OVERLOADING)
    cellViewCellArea                        ,
#endif
    constructCellViewCellArea               ,
    getCellViewCellArea                     ,
#if defined(ENABLE_OVERLOADING)
    CellViewCellAreaContextPropertyInfo     ,
#endif
#if defined(ENABLE_OVERLOADING)
    cellViewCellAreaContext                 ,
#endif
    constructCellViewCellAreaContext        ,
    getCellViewCellAreaContext              ,
#if defined(ENABLE_OVERLOADING)
    CellViewDrawSensitivePropertyInfo       ,
#endif
#if defined(ENABLE_OVERLOADING)
    cellViewDrawSensitive                   ,
#endif
    constructCellViewDrawSensitive          ,
    getCellViewDrawSensitive                ,
    setCellViewDrawSensitive                ,
#if defined(ENABLE_OVERLOADING)
    CellViewFitModelPropertyInfo            ,
#endif
#if defined(ENABLE_OVERLOADING)
    cellViewFitModel                        ,
#endif
    constructCellViewFitModel               ,
    getCellViewFitModel                     ,
    setCellViewFitModel                     ,
#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.GHashTable as B.GHT
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.Kind as DK
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 Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT
#if MIN_VERSION_base(4,18,0)
import qualified GI.Atk.Interfaces.ImplementorIface as Atk.ImplementorIface
import qualified GI.Atk.Objects.Object as Atk.Object
import qualified GI.Cairo.Structs.Context as Cairo.Context
import qualified GI.Cairo.Structs.FontOptions as Cairo.FontOptions
import qualified GI.Cairo.Structs.Region as Cairo.Region
import qualified GI.Cairo.Structs.Surface as Cairo.Surface
import qualified GI.GLib.Callbacks as GLib.Callbacks
import qualified GI.GLib.Structs.MarkupParser as GLib.MarkupParser
import qualified GI.GObject.Callbacks as GObject.Callbacks
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gdk.Enums as Gdk.Enums
import qualified GI.Gdk.Flags as Gdk.Flags
import qualified GI.Gdk.Objects.Device as Gdk.Device
import qualified GI.Gdk.Objects.Display as Gdk.Display
import qualified GI.Gdk.Objects.DragContext as Gdk.DragContext
import qualified GI.Gdk.Objects.FrameClock as Gdk.FrameClock
import qualified GI.Gdk.Objects.Screen as Gdk.Screen
import qualified GI.Gdk.Objects.Visual as Gdk.Visual
import qualified GI.Gdk.Objects.Window as Gdk.Window
import qualified GI.Gdk.Structs.Atom as Gdk.Atom
import qualified GI.Gdk.Structs.Color as Gdk.Color
import qualified GI.Gdk.Structs.EventAny as Gdk.EventAny
import qualified GI.Gdk.Structs.EventButton as Gdk.EventButton
import qualified GI.Gdk.Structs.EventConfigure as Gdk.EventConfigure
import qualified GI.Gdk.Structs.EventCrossing as Gdk.EventCrossing
import qualified GI.Gdk.Structs.EventExpose as Gdk.EventExpose
import qualified GI.Gdk.Structs.EventFocus as Gdk.EventFocus
import qualified GI.Gdk.Structs.EventGrabBroken as Gdk.EventGrabBroken
import qualified GI.Gdk.Structs.EventKey as Gdk.EventKey
import qualified GI.Gdk.Structs.EventMotion as Gdk.EventMotion
import qualified GI.Gdk.Structs.EventOwnerChange as Gdk.EventOwnerChange
import qualified GI.Gdk.Structs.EventProperty as Gdk.EventProperty
import qualified GI.Gdk.Structs.EventProximity as Gdk.EventProximity
import qualified GI.Gdk.Structs.EventScroll as Gdk.EventScroll
import qualified GI.Gdk.Structs.EventSelection as Gdk.EventSelection
import qualified GI.Gdk.Structs.EventVisibility as Gdk.EventVisibility
import qualified GI.Gdk.Structs.EventWindowState as Gdk.EventWindowState
import qualified GI.Gdk.Structs.Geometry as Gdk.Geometry
import qualified GI.Gdk.Structs.RGBA as Gdk.RGBA
import qualified GI.Gdk.Structs.Rectangle as Gdk.Rectangle
import qualified GI.Gdk.Unions.Event as Gdk.Event
import qualified GI.GdkPixbuf.Objects.Pixbuf as GdkPixbuf.Pixbuf
import qualified GI.Gio.Flags as Gio.Flags
import qualified GI.Gio.Interfaces.ActionGroup as Gio.ActionGroup
import qualified GI.Gio.Interfaces.ActionMap as Gio.ActionMap
import qualified GI.Gio.Interfaces.File as Gio.File
import qualified GI.Gio.Interfaces.Icon as Gio.Icon
import qualified GI.Gio.Objects.Application as Gio.Application
import qualified GI.Gio.Objects.Menu as Gio.Menu
import qualified GI.Gio.Objects.MenuModel as Gio.MenuModel
import qualified GI.Gtk.Callbacks as Gtk.Callbacks
import {-# SOURCE #-} qualified GI.Gtk.Enums as Gtk.Enums
import {-# SOURCE #-} qualified GI.Gtk.Flags as Gtk.Flags
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.CellEditable as Gtk.CellEditable
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.CellLayout as Gtk.CellLayout
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Orientable as Gtk.Orientable
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.StyleProvider as Gtk.StyleProvider
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.TreeModel as Gtk.TreeModel
import {-# SOURCE #-} qualified GI.Gtk.Objects.AccelGroup as Gtk.AccelGroup
import {-# SOURCE #-} qualified GI.Gtk.Objects.Adjustment as Gtk.Adjustment
import {-# SOURCE #-} qualified GI.Gtk.Objects.Application as Gtk.Application
import {-# SOURCE #-} qualified GI.Gtk.Objects.Bin as Gtk.Bin
import {-# SOURCE #-} qualified GI.Gtk.Objects.Builder as Gtk.Builder
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.CellRenderer as Gtk.CellRenderer
import {-# SOURCE #-} qualified GI.Gtk.Objects.Clipboard as Gtk.Clipboard
import {-# SOURCE #-} qualified GI.Gtk.Objects.Container as Gtk.Container
import {-# SOURCE #-} qualified GI.Gtk.Objects.IconFactory as Gtk.IconFactory
import {-# SOURCE #-} qualified GI.Gtk.Objects.RcStyle as Gtk.RcStyle
import {-# SOURCE #-} qualified GI.Gtk.Objects.Settings as Gtk.Settings
import {-# SOURCE #-} qualified GI.Gtk.Objects.Style as Gtk.Style
import {-# SOURCE #-} qualified GI.Gtk.Objects.StyleContext as Gtk.StyleContext
import {-# SOURCE #-} qualified GI.Gtk.Objects.StyleProperties as Gtk.StyleProperties
import {-# SOURCE #-} qualified GI.Gtk.Objects.TextBuffer as Gtk.TextBuffer
import {-# SOURCE #-} qualified GI.Gtk.Objects.TextChildAnchor as Gtk.TextChildAnchor
import {-# SOURCE #-} qualified GI.Gtk.Objects.TextMark as Gtk.TextMark
import {-# SOURCE #-} qualified GI.Gtk.Objects.TextTag as Gtk.TextTag
import {-# SOURCE #-} qualified GI.Gtk.Objects.TextTagTable as Gtk.TextTagTable
import {-# SOURCE #-} qualified GI.Gtk.Objects.Tooltip as Gtk.Tooltip
import {-# SOURCE #-} qualified GI.Gtk.Objects.Widget as Gtk.Widget
import {-# SOURCE #-} qualified GI.Gtk.Objects.Window as Gtk.Window
import {-# SOURCE #-} qualified GI.Gtk.Objects.WindowGroup as Gtk.WindowGroup
import {-# SOURCE #-} qualified GI.Gtk.Structs.AccelGroupEntry as Gtk.AccelGroupEntry
import {-# SOURCE #-} qualified GI.Gtk.Structs.AccelKey as Gtk.AccelKey
import {-# SOURCE #-} qualified GI.Gtk.Structs.Border as Gtk.Border
import {-# SOURCE #-} qualified GI.Gtk.Structs.CssSection as Gtk.CssSection
import {-# SOURCE #-} qualified GI.Gtk.Structs.IconSet as Gtk.IconSet
import {-# SOURCE #-} qualified GI.Gtk.Structs.IconSource as Gtk.IconSource
import {-# SOURCE #-} qualified GI.Gtk.Structs.Requisition as Gtk.Requisition
import {-# SOURCE #-} qualified GI.Gtk.Structs.SelectionData as Gtk.SelectionData
import {-# SOURCE #-} qualified GI.Gtk.Structs.SettingsValue as Gtk.SettingsValue
import {-# SOURCE #-} qualified GI.Gtk.Structs.SymbolicColor as Gtk.SymbolicColor
import {-# SOURCE #-} qualified GI.Gtk.Structs.TargetEntry as Gtk.TargetEntry
import {-# SOURCE #-} qualified GI.Gtk.Structs.TargetList as Gtk.TargetList
import {-# SOURCE #-} qualified GI.Gtk.Structs.TextAppearance as Gtk.TextAppearance
import {-# SOURCE #-} qualified GI.Gtk.Structs.TextAttributes as Gtk.TextAttributes
import {-# SOURCE #-} qualified GI.Gtk.Structs.TextIter as Gtk.TextIter
import {-# SOURCE #-} qualified GI.Gtk.Structs.TreeIter as Gtk.TreeIter
import {-# SOURCE #-} qualified GI.Gtk.Structs.TreePath as Gtk.TreePath
import {-# SOURCE #-} qualified GI.Gtk.Structs.WidgetPath as Gtk.WidgetPath
import qualified GI.Pango.Enums as Pango.Enums
import qualified GI.Pango.Objects.Context as Pango.Context
import qualified GI.Pango.Objects.FontMap as Pango.FontMap
import qualified GI.Pango.Objects.Layout as Pango.Layout
import qualified GI.Pango.Structs.FontDescription as Pango.FontDescription
import qualified GI.Pango.Structs.Language as Pango.Language
import qualified GI.Pango.Structs.TabArray as Pango.TabArray
#else
import qualified GI.Atk.Interfaces.ImplementorIface as Atk.ImplementorIface
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gdk.Structs.Color as Gdk.Color
import qualified GI.Gdk.Structs.RGBA as Gdk.RGBA
import qualified GI.GdkPixbuf.Objects.Pixbuf as GdkPixbuf.Pixbuf
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.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.Requisition as Gtk.Requisition
import {-# SOURCE #-} qualified GI.Gtk.Structs.TreePath as Gtk.TreePath
#endif
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
$c== :: CellView -> CellView -> Bool
== :: CellView -> CellView -> Bool
$c/= :: CellView -> CellView -> Bool
/= :: 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
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, Atk.ImplementorIface.ImplementorIface, Gtk.Buildable.Buildable, Gtk.CellLayout.CellLayout, Gtk.Orientable.Orientable]
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 a. IO a -> m a
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
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 a. a -> IO a
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 :: DK.Type) :: DK.Type where
    ResolveCellViewMethod "activate" o = Gtk.Widget.WidgetActivateMethodInfo
    ResolveCellViewMethod "addAccelerator" o = Gtk.Widget.WidgetAddAcceleratorMethodInfo
    ResolveCellViewMethod "addAttribute" o = Gtk.CellLayout.CellLayoutAddAttributeMethodInfo
    ResolveCellViewMethod "addChild" o = Gtk.Buildable.BuildableAddChildMethodInfo
    ResolveCellViewMethod "addDeviceEvents" o = Gtk.Widget.WidgetAddDeviceEventsMethodInfo
    ResolveCellViewMethod "addEvents" o = Gtk.Widget.WidgetAddEventsMethodInfo
    ResolveCellViewMethod "addMnemonicLabel" o = Gtk.Widget.WidgetAddMnemonicLabelMethodInfo
    ResolveCellViewMethod "addTickCallback" o = Gtk.Widget.WidgetAddTickCallbackMethodInfo
    ResolveCellViewMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveCellViewMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveCellViewMethod "canActivateAccel" o = Gtk.Widget.WidgetCanActivateAccelMethodInfo
    ResolveCellViewMethod "childFocus" o = Gtk.Widget.WidgetChildFocusMethodInfo
    ResolveCellViewMethod "childNotify" o = Gtk.Widget.WidgetChildNotifyMethodInfo
    ResolveCellViewMethod "classPath" o = Gtk.Widget.WidgetClassPathMethodInfo
    ResolveCellViewMethod "clear" o = Gtk.CellLayout.CellLayoutClearMethodInfo
    ResolveCellViewMethod "clearAttributes" o = Gtk.CellLayout.CellLayoutClearAttributesMethodInfo
    ResolveCellViewMethod "computeExpand" o = Gtk.Widget.WidgetComputeExpandMethodInfo
    ResolveCellViewMethod "constructChild" o = Gtk.Buildable.BuildableConstructChildMethodInfo
    ResolveCellViewMethod "createPangoContext" o = Gtk.Widget.WidgetCreatePangoContextMethodInfo
    ResolveCellViewMethod "createPangoLayout" o = Gtk.Widget.WidgetCreatePangoLayoutMethodInfo
    ResolveCellViewMethod "customFinished" o = Gtk.Buildable.BuildableCustomFinishedMethodInfo
    ResolveCellViewMethod "customTagEnd" o = Gtk.Buildable.BuildableCustomTagEndMethodInfo
    ResolveCellViewMethod "customTagStart" o = Gtk.Buildable.BuildableCustomTagStartMethodInfo
    ResolveCellViewMethod "destroy" o = Gtk.Widget.WidgetDestroyMethodInfo
    ResolveCellViewMethod "destroyed" o = Gtk.Widget.WidgetDestroyedMethodInfo
    ResolveCellViewMethod "deviceIsShadowed" o = Gtk.Widget.WidgetDeviceIsShadowedMethodInfo
    ResolveCellViewMethod "dragBegin" o = Gtk.Widget.WidgetDragBeginMethodInfo
    ResolveCellViewMethod "dragBeginWithCoordinates" o = Gtk.Widget.WidgetDragBeginWithCoordinatesMethodInfo
    ResolveCellViewMethod "dragCheckThreshold" o = Gtk.Widget.WidgetDragCheckThresholdMethodInfo
    ResolveCellViewMethod "dragDestAddImageTargets" o = Gtk.Widget.WidgetDragDestAddImageTargetsMethodInfo
    ResolveCellViewMethod "dragDestAddTextTargets" o = Gtk.Widget.WidgetDragDestAddTextTargetsMethodInfo
    ResolveCellViewMethod "dragDestAddUriTargets" o = Gtk.Widget.WidgetDragDestAddUriTargetsMethodInfo
    ResolveCellViewMethod "dragDestFindTarget" o = Gtk.Widget.WidgetDragDestFindTargetMethodInfo
    ResolveCellViewMethod "dragDestGetTargetList" o = Gtk.Widget.WidgetDragDestGetTargetListMethodInfo
    ResolveCellViewMethod "dragDestGetTrackMotion" o = Gtk.Widget.WidgetDragDestGetTrackMotionMethodInfo
    ResolveCellViewMethod "dragDestSet" o = Gtk.Widget.WidgetDragDestSetMethodInfo
    ResolveCellViewMethod "dragDestSetProxy" o = Gtk.Widget.WidgetDragDestSetProxyMethodInfo
    ResolveCellViewMethod "dragDestSetTargetList" o = Gtk.Widget.WidgetDragDestSetTargetListMethodInfo
    ResolveCellViewMethod "dragDestSetTrackMotion" o = Gtk.Widget.WidgetDragDestSetTrackMotionMethodInfo
    ResolveCellViewMethod "dragDestUnset" o = Gtk.Widget.WidgetDragDestUnsetMethodInfo
    ResolveCellViewMethod "dragGetData" o = Gtk.Widget.WidgetDragGetDataMethodInfo
    ResolveCellViewMethod "dragHighlight" o = Gtk.Widget.WidgetDragHighlightMethodInfo
    ResolveCellViewMethod "dragSourceAddImageTargets" o = Gtk.Widget.WidgetDragSourceAddImageTargetsMethodInfo
    ResolveCellViewMethod "dragSourceAddTextTargets" o = Gtk.Widget.WidgetDragSourceAddTextTargetsMethodInfo
    ResolveCellViewMethod "dragSourceAddUriTargets" o = Gtk.Widget.WidgetDragSourceAddUriTargetsMethodInfo
    ResolveCellViewMethod "dragSourceGetTargetList" o = Gtk.Widget.WidgetDragSourceGetTargetListMethodInfo
    ResolveCellViewMethod "dragSourceSet" o = Gtk.Widget.WidgetDragSourceSetMethodInfo
    ResolveCellViewMethod "dragSourceSetIconGicon" o = Gtk.Widget.WidgetDragSourceSetIconGiconMethodInfo
    ResolveCellViewMethod "dragSourceSetIconName" o = Gtk.Widget.WidgetDragSourceSetIconNameMethodInfo
    ResolveCellViewMethod "dragSourceSetIconPixbuf" o = Gtk.Widget.WidgetDragSourceSetIconPixbufMethodInfo
    ResolveCellViewMethod "dragSourceSetIconStock" o = Gtk.Widget.WidgetDragSourceSetIconStockMethodInfo
    ResolveCellViewMethod "dragSourceSetTargetList" o = Gtk.Widget.WidgetDragSourceSetTargetListMethodInfo
    ResolveCellViewMethod "dragSourceUnset" o = Gtk.Widget.WidgetDragSourceUnsetMethodInfo
    ResolveCellViewMethod "dragUnhighlight" o = Gtk.Widget.WidgetDragUnhighlightMethodInfo
    ResolveCellViewMethod "draw" o = Gtk.Widget.WidgetDrawMethodInfo
    ResolveCellViewMethod "ensureStyle" o = Gtk.Widget.WidgetEnsureStyleMethodInfo
    ResolveCellViewMethod "errorBell" o = Gtk.Widget.WidgetErrorBellMethodInfo
    ResolveCellViewMethod "event" o = Gtk.Widget.WidgetEventMethodInfo
    ResolveCellViewMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveCellViewMethod "freezeChildNotify" o = Gtk.Widget.WidgetFreezeChildNotifyMethodInfo
    ResolveCellViewMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveCellViewMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveCellViewMethod "grabAdd" o = Gtk.Widget.WidgetGrabAddMethodInfo
    ResolveCellViewMethod "grabDefault" o = Gtk.Widget.WidgetGrabDefaultMethodInfo
    ResolveCellViewMethod "grabFocus" o = Gtk.Widget.WidgetGrabFocusMethodInfo
    ResolveCellViewMethod "grabRemove" o = Gtk.Widget.WidgetGrabRemoveMethodInfo
    ResolveCellViewMethod "hasDefault" o = Gtk.Widget.WidgetHasDefaultMethodInfo
    ResolveCellViewMethod "hasFocus" o = Gtk.Widget.WidgetHasFocusMethodInfo
    ResolveCellViewMethod "hasGrab" o = Gtk.Widget.WidgetHasGrabMethodInfo
    ResolveCellViewMethod "hasRcStyle" o = Gtk.Widget.WidgetHasRcStyleMethodInfo
    ResolveCellViewMethod "hasScreen" o = Gtk.Widget.WidgetHasScreenMethodInfo
    ResolveCellViewMethod "hasVisibleFocus" o = Gtk.Widget.WidgetHasVisibleFocusMethodInfo
    ResolveCellViewMethod "hide" o = Gtk.Widget.WidgetHideMethodInfo
    ResolveCellViewMethod "hideOnDelete" o = Gtk.Widget.WidgetHideOnDeleteMethodInfo
    ResolveCellViewMethod "inDestruction" o = Gtk.Widget.WidgetInDestructionMethodInfo
    ResolveCellViewMethod "initTemplate" o = Gtk.Widget.WidgetInitTemplateMethodInfo
    ResolveCellViewMethod "inputShapeCombineRegion" o = Gtk.Widget.WidgetInputShapeCombineRegionMethodInfo
    ResolveCellViewMethod "insertActionGroup" o = Gtk.Widget.WidgetInsertActionGroupMethodInfo
    ResolveCellViewMethod "intersect" o = Gtk.Widget.WidgetIntersectMethodInfo
    ResolveCellViewMethod "isAncestor" o = Gtk.Widget.WidgetIsAncestorMethodInfo
    ResolveCellViewMethod "isComposited" o = Gtk.Widget.WidgetIsCompositedMethodInfo
    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 "isToplevel" o = Gtk.Widget.WidgetIsToplevelMethodInfo
    ResolveCellViewMethod "isVisible" o = Gtk.Widget.WidgetIsVisibleMethodInfo
    ResolveCellViewMethod "keynavFailed" o = Gtk.Widget.WidgetKeynavFailedMethodInfo
    ResolveCellViewMethod "listAccelClosures" o = Gtk.Widget.WidgetListAccelClosuresMethodInfo
    ResolveCellViewMethod "listActionPrefixes" o = Gtk.Widget.WidgetListActionPrefixesMethodInfo
    ResolveCellViewMethod "listMnemonicLabels" o = Gtk.Widget.WidgetListMnemonicLabelsMethodInfo
    ResolveCellViewMethod "map" o = Gtk.Widget.WidgetMapMethodInfo
    ResolveCellViewMethod "mnemonicActivate" o = Gtk.Widget.WidgetMnemonicActivateMethodInfo
    ResolveCellViewMethod "modifyBase" o = Gtk.Widget.WidgetModifyBaseMethodInfo
    ResolveCellViewMethod "modifyBg" o = Gtk.Widget.WidgetModifyBgMethodInfo
    ResolveCellViewMethod "modifyCursor" o = Gtk.Widget.WidgetModifyCursorMethodInfo
    ResolveCellViewMethod "modifyFg" o = Gtk.Widget.WidgetModifyFgMethodInfo
    ResolveCellViewMethod "modifyFont" o = Gtk.Widget.WidgetModifyFontMethodInfo
    ResolveCellViewMethod "modifyStyle" o = Gtk.Widget.WidgetModifyStyleMethodInfo
    ResolveCellViewMethod "modifyText" o = Gtk.Widget.WidgetModifyTextMethodInfo
    ResolveCellViewMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveCellViewMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveCellViewMethod "overrideBackgroundColor" o = Gtk.Widget.WidgetOverrideBackgroundColorMethodInfo
    ResolveCellViewMethod "overrideColor" o = Gtk.Widget.WidgetOverrideColorMethodInfo
    ResolveCellViewMethod "overrideCursor" o = Gtk.Widget.WidgetOverrideCursorMethodInfo
    ResolveCellViewMethod "overrideFont" o = Gtk.Widget.WidgetOverrideFontMethodInfo
    ResolveCellViewMethod "overrideSymbolicColor" o = Gtk.Widget.WidgetOverrideSymbolicColorMethodInfo
    ResolveCellViewMethod "packEnd" o = Gtk.CellLayout.CellLayoutPackEndMethodInfo
    ResolveCellViewMethod "packStart" o = Gtk.CellLayout.CellLayoutPackStartMethodInfo
    ResolveCellViewMethod "parserFinished" o = Gtk.Buildable.BuildableParserFinishedMethodInfo
    ResolveCellViewMethod "path" o = Gtk.Widget.WidgetPathMethodInfo
    ResolveCellViewMethod "queueAllocate" o = Gtk.Widget.WidgetQueueAllocateMethodInfo
    ResolveCellViewMethod "queueComputeExpand" o = Gtk.Widget.WidgetQueueComputeExpandMethodInfo
    ResolveCellViewMethod "queueDraw" o = Gtk.Widget.WidgetQueueDrawMethodInfo
    ResolveCellViewMethod "queueDrawArea" o = Gtk.Widget.WidgetQueueDrawAreaMethodInfo
    ResolveCellViewMethod "queueDrawRegion" o = Gtk.Widget.WidgetQueueDrawRegionMethodInfo
    ResolveCellViewMethod "queueResize" o = Gtk.Widget.WidgetQueueResizeMethodInfo
    ResolveCellViewMethod "queueResizeNoRedraw" o = Gtk.Widget.WidgetQueueResizeNoRedrawMethodInfo
    ResolveCellViewMethod "realize" o = Gtk.Widget.WidgetRealizeMethodInfo
    ResolveCellViewMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveCellViewMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveCellViewMethod "regionIntersect" o = Gtk.Widget.WidgetRegionIntersectMethodInfo
    ResolveCellViewMethod "registerWindow" o = Gtk.Widget.WidgetRegisterWindowMethodInfo
    ResolveCellViewMethod "removeAccelerator" o = Gtk.Widget.WidgetRemoveAcceleratorMethodInfo
    ResolveCellViewMethod "removeMnemonicLabel" o = Gtk.Widget.WidgetRemoveMnemonicLabelMethodInfo
    ResolveCellViewMethod "removeTickCallback" o = Gtk.Widget.WidgetRemoveTickCallbackMethodInfo
    ResolveCellViewMethod "renderIcon" o = Gtk.Widget.WidgetRenderIconMethodInfo
    ResolveCellViewMethod "renderIconPixbuf" o = Gtk.Widget.WidgetRenderIconPixbufMethodInfo
    ResolveCellViewMethod "reorder" o = Gtk.CellLayout.CellLayoutReorderMethodInfo
    ResolveCellViewMethod "reparent" o = Gtk.Widget.WidgetReparentMethodInfo
    ResolveCellViewMethod "resetRcStyles" o = Gtk.Widget.WidgetResetRcStylesMethodInfo
    ResolveCellViewMethod "resetStyle" o = Gtk.Widget.WidgetResetStyleMethodInfo
    ResolveCellViewMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveCellViewMethod "sendExpose" o = Gtk.Widget.WidgetSendExposeMethodInfo
    ResolveCellViewMethod "sendFocusChange" o = Gtk.Widget.WidgetSendFocusChangeMethodInfo
    ResolveCellViewMethod "shapeCombineRegion" o = Gtk.Widget.WidgetShapeCombineRegionMethodInfo
    ResolveCellViewMethod "show" o = Gtk.Widget.WidgetShowMethodInfo
    ResolveCellViewMethod "showAll" o = Gtk.Widget.WidgetShowAllMethodInfo
    ResolveCellViewMethod "showNow" o = Gtk.Widget.WidgetShowNowMethodInfo
    ResolveCellViewMethod "sizeAllocate" o = Gtk.Widget.WidgetSizeAllocateMethodInfo
    ResolveCellViewMethod "sizeAllocateWithBaseline" o = Gtk.Widget.WidgetSizeAllocateWithBaselineMethodInfo
    ResolveCellViewMethod "sizeRequest" o = Gtk.Widget.WidgetSizeRequestMethodInfo
    ResolveCellViewMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveCellViewMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveCellViewMethod "styleAttach" o = Gtk.Widget.WidgetStyleAttachMethodInfo
    ResolveCellViewMethod "styleGetProperty" o = Gtk.Widget.WidgetStyleGetPropertyMethodInfo
    ResolveCellViewMethod "thawChildNotify" o = Gtk.Widget.WidgetThawChildNotifyMethodInfo
    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 "unregisterWindow" o = Gtk.Widget.WidgetUnregisterWindowMethodInfo
    ResolveCellViewMethod "unsetStateFlags" o = Gtk.Widget.WidgetUnsetStateFlagsMethodInfo
    ResolveCellViewMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveCellViewMethod "getAccessible" o = Gtk.Widget.WidgetGetAccessibleMethodInfo
    ResolveCellViewMethod "getActionGroup" o = Gtk.Widget.WidgetGetActionGroupMethodInfo
    ResolveCellViewMethod "getAllocatedBaseline" o = Gtk.Widget.WidgetGetAllocatedBaselineMethodInfo
    ResolveCellViewMethod "getAllocatedHeight" o = Gtk.Widget.WidgetGetAllocatedHeightMethodInfo
    ResolveCellViewMethod "getAllocatedSize" o = Gtk.Widget.WidgetGetAllocatedSizeMethodInfo
    ResolveCellViewMethod "getAllocatedWidth" o = Gtk.Widget.WidgetGetAllocatedWidthMethodInfo
    ResolveCellViewMethod "getAllocation" o = Gtk.Widget.WidgetGetAllocationMethodInfo
    ResolveCellViewMethod "getAncestor" o = Gtk.Widget.WidgetGetAncestorMethodInfo
    ResolveCellViewMethod "getAppPaintable" o = Gtk.Widget.WidgetGetAppPaintableMethodInfo
    ResolveCellViewMethod "getArea" o = Gtk.CellLayout.CellLayoutGetAreaMethodInfo
    ResolveCellViewMethod "getCanDefault" o = Gtk.Widget.WidgetGetCanDefaultMethodInfo
    ResolveCellViewMethod "getCanFocus" o = Gtk.Widget.WidgetGetCanFocusMethodInfo
    ResolveCellViewMethod "getCells" o = Gtk.CellLayout.CellLayoutGetCellsMethodInfo
    ResolveCellViewMethod "getChildRequisition" o = Gtk.Widget.WidgetGetChildRequisitionMethodInfo
    ResolveCellViewMethod "getChildVisible" o = Gtk.Widget.WidgetGetChildVisibleMethodInfo
    ResolveCellViewMethod "getClip" o = Gtk.Widget.WidgetGetClipMethodInfo
    ResolveCellViewMethod "getClipboard" o = Gtk.Widget.WidgetGetClipboardMethodInfo
    ResolveCellViewMethod "getCompositeName" o = Gtk.Widget.WidgetGetCompositeNameMethodInfo
    ResolveCellViewMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveCellViewMethod "getDeviceEnabled" o = Gtk.Widget.WidgetGetDeviceEnabledMethodInfo
    ResolveCellViewMethod "getDeviceEvents" o = Gtk.Widget.WidgetGetDeviceEventsMethodInfo
    ResolveCellViewMethod "getDirection" o = Gtk.Widget.WidgetGetDirectionMethodInfo
    ResolveCellViewMethod "getDisplay" o = Gtk.Widget.WidgetGetDisplayMethodInfo
    ResolveCellViewMethod "getDisplayedRow" o = CellViewGetDisplayedRowMethodInfo
    ResolveCellViewMethod "getDoubleBuffered" o = Gtk.Widget.WidgetGetDoubleBufferedMethodInfo
    ResolveCellViewMethod "getDrawSensitive" o = CellViewGetDrawSensitiveMethodInfo
    ResolveCellViewMethod "getEvents" o = Gtk.Widget.WidgetGetEventsMethodInfo
    ResolveCellViewMethod "getFitModel" o = CellViewGetFitModelMethodInfo
    ResolveCellViewMethod "getFocusOnClick" o = Gtk.Widget.WidgetGetFocusOnClickMethodInfo
    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 "getHasWindow" o = Gtk.Widget.WidgetGetHasWindowMethodInfo
    ResolveCellViewMethod "getHexpand" o = Gtk.Widget.WidgetGetHexpandMethodInfo
    ResolveCellViewMethod "getHexpandSet" o = Gtk.Widget.WidgetGetHexpandSetMethodInfo
    ResolveCellViewMethod "getInternalChild" o = Gtk.Buildable.BuildableGetInternalChildMethodInfo
    ResolveCellViewMethod "getMapped" o = Gtk.Widget.WidgetGetMappedMethodInfo
    ResolveCellViewMethod "getMarginBottom" o = Gtk.Widget.WidgetGetMarginBottomMethodInfo
    ResolveCellViewMethod "getMarginEnd" o = Gtk.Widget.WidgetGetMarginEndMethodInfo
    ResolveCellViewMethod "getMarginLeft" o = Gtk.Widget.WidgetGetMarginLeftMethodInfo
    ResolveCellViewMethod "getMarginRight" o = Gtk.Widget.WidgetGetMarginRightMethodInfo
    ResolveCellViewMethod "getMarginStart" o = Gtk.Widget.WidgetGetMarginStartMethodInfo
    ResolveCellViewMethod "getMarginTop" o = Gtk.Widget.WidgetGetMarginTopMethodInfo
    ResolveCellViewMethod "getModel" o = CellViewGetModelMethodInfo
    ResolveCellViewMethod "getModifierMask" o = Gtk.Widget.WidgetGetModifierMaskMethodInfo
    ResolveCellViewMethod "getModifierStyle" o = Gtk.Widget.WidgetGetModifierStyleMethodInfo
    ResolveCellViewMethod "getName" o = Gtk.Widget.WidgetGetNameMethodInfo
    ResolveCellViewMethod "getNoShowAll" o = Gtk.Widget.WidgetGetNoShowAllMethodInfo
    ResolveCellViewMethod "getOpacity" o = Gtk.Widget.WidgetGetOpacityMethodInfo
    ResolveCellViewMethod "getOrientation" o = Gtk.Orientable.OrientableGetOrientationMethodInfo
    ResolveCellViewMethod "getPangoContext" o = Gtk.Widget.WidgetGetPangoContextMethodInfo
    ResolveCellViewMethod "getParent" o = Gtk.Widget.WidgetGetParentMethodInfo
    ResolveCellViewMethod "getParentWindow" o = Gtk.Widget.WidgetGetParentWindowMethodInfo
    ResolveCellViewMethod "getPath" o = Gtk.Widget.WidgetGetPathMethodInfo
    ResolveCellViewMethod "getPointer" o = Gtk.Widget.WidgetGetPointerMethodInfo
    ResolveCellViewMethod "getPreferredHeight" o = Gtk.Widget.WidgetGetPreferredHeightMethodInfo
    ResolveCellViewMethod "getPreferredHeightAndBaselineForWidth" o = Gtk.Widget.WidgetGetPreferredHeightAndBaselineForWidthMethodInfo
    ResolveCellViewMethod "getPreferredHeightForWidth" o = Gtk.Widget.WidgetGetPreferredHeightForWidthMethodInfo
    ResolveCellViewMethod "getPreferredSize" o = Gtk.Widget.WidgetGetPreferredSizeMethodInfo
    ResolveCellViewMethod "getPreferredWidth" o = Gtk.Widget.WidgetGetPreferredWidthMethodInfo
    ResolveCellViewMethod "getPreferredWidthForHeight" o = Gtk.Widget.WidgetGetPreferredWidthForHeightMethodInfo
    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 "getRequisition" o = Gtk.Widget.WidgetGetRequisitionMethodInfo
    ResolveCellViewMethod "getRootWindow" o = Gtk.Widget.WidgetGetRootWindowMethodInfo
    ResolveCellViewMethod "getScaleFactor" o = Gtk.Widget.WidgetGetScaleFactorMethodInfo
    ResolveCellViewMethod "getScreen" o = Gtk.Widget.WidgetGetScreenMethodInfo
    ResolveCellViewMethod "getSensitive" o = Gtk.Widget.WidgetGetSensitiveMethodInfo
    ResolveCellViewMethod "getSettings" o = Gtk.Widget.WidgetGetSettingsMethodInfo
    ResolveCellViewMethod "getSizeOfRow" o = CellViewGetSizeOfRowMethodInfo
    ResolveCellViewMethod "getSizeRequest" o = Gtk.Widget.WidgetGetSizeRequestMethodInfo
    ResolveCellViewMethod "getState" o = Gtk.Widget.WidgetGetStateMethodInfo
    ResolveCellViewMethod "getStateFlags" o = Gtk.Widget.WidgetGetStateFlagsMethodInfo
    ResolveCellViewMethod "getStyle" o = Gtk.Widget.WidgetGetStyleMethodInfo
    ResolveCellViewMethod "getStyleContext" o = Gtk.Widget.WidgetGetStyleContextMethodInfo
    ResolveCellViewMethod "getSupportMultidevice" o = Gtk.Widget.WidgetGetSupportMultideviceMethodInfo
    ResolveCellViewMethod "getTemplateChild" o = Gtk.Widget.WidgetGetTemplateChildMethodInfo
    ResolveCellViewMethod "getTooltipMarkup" o = Gtk.Widget.WidgetGetTooltipMarkupMethodInfo
    ResolveCellViewMethod "getTooltipText" o = Gtk.Widget.WidgetGetTooltipTextMethodInfo
    ResolveCellViewMethod "getTooltipWindow" o = Gtk.Widget.WidgetGetTooltipWindowMethodInfo
    ResolveCellViewMethod "getToplevel" o = Gtk.Widget.WidgetGetToplevelMethodInfo
    ResolveCellViewMethod "getValign" o = Gtk.Widget.WidgetGetValignMethodInfo
    ResolveCellViewMethod "getValignWithBaseline" o = Gtk.Widget.WidgetGetValignWithBaselineMethodInfo
    ResolveCellViewMethod "getVexpand" o = Gtk.Widget.WidgetGetVexpandMethodInfo
    ResolveCellViewMethod "getVexpandSet" o = Gtk.Widget.WidgetGetVexpandSetMethodInfo
    ResolveCellViewMethod "getVisible" o = Gtk.Widget.WidgetGetVisibleMethodInfo
    ResolveCellViewMethod "getVisual" o = Gtk.Widget.WidgetGetVisualMethodInfo
    ResolveCellViewMethod "getWindow" o = Gtk.Widget.WidgetGetWindowMethodInfo
    ResolveCellViewMethod "setAccelPath" o = Gtk.Widget.WidgetSetAccelPathMethodInfo
    ResolveCellViewMethod "setAllocation" o = Gtk.Widget.WidgetSetAllocationMethodInfo
    ResolveCellViewMethod "setAppPaintable" o = Gtk.Widget.WidgetSetAppPaintableMethodInfo
    ResolveCellViewMethod "setBackgroundColor" o = CellViewSetBackgroundColorMethodInfo
    ResolveCellViewMethod "setBackgroundRgba" o = CellViewSetBackgroundRgbaMethodInfo
    ResolveCellViewMethod "setBuildableProperty" o = Gtk.Buildable.BuildableSetBuildablePropertyMethodInfo
    ResolveCellViewMethod "setCanDefault" o = Gtk.Widget.WidgetSetCanDefaultMethodInfo
    ResolveCellViewMethod "setCanFocus" o = Gtk.Widget.WidgetSetCanFocusMethodInfo
    ResolveCellViewMethod "setCellDataFunc" o = Gtk.CellLayout.CellLayoutSetCellDataFuncMethodInfo
    ResolveCellViewMethod "setChildVisible" o = Gtk.Widget.WidgetSetChildVisibleMethodInfo
    ResolveCellViewMethod "setClip" o = Gtk.Widget.WidgetSetClipMethodInfo
    ResolveCellViewMethod "setCompositeName" o = Gtk.Widget.WidgetSetCompositeNameMethodInfo
    ResolveCellViewMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveCellViewMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveCellViewMethod "setDeviceEnabled" o = Gtk.Widget.WidgetSetDeviceEnabledMethodInfo
    ResolveCellViewMethod "setDeviceEvents" o = Gtk.Widget.WidgetSetDeviceEventsMethodInfo
    ResolveCellViewMethod "setDirection" o = Gtk.Widget.WidgetSetDirectionMethodInfo
    ResolveCellViewMethod "setDisplayedRow" o = CellViewSetDisplayedRowMethodInfo
    ResolveCellViewMethod "setDoubleBuffered" o = Gtk.Widget.WidgetSetDoubleBufferedMethodInfo
    ResolveCellViewMethod "setDrawSensitive" o = CellViewSetDrawSensitiveMethodInfo
    ResolveCellViewMethod "setEvents" o = Gtk.Widget.WidgetSetEventsMethodInfo
    ResolveCellViewMethod "setFitModel" o = CellViewSetFitModelMethodInfo
    ResolveCellViewMethod "setFocusOnClick" o = Gtk.Widget.WidgetSetFocusOnClickMethodInfo
    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 "setHasWindow" o = Gtk.Widget.WidgetSetHasWindowMethodInfo
    ResolveCellViewMethod "setHexpand" o = Gtk.Widget.WidgetSetHexpandMethodInfo
    ResolveCellViewMethod "setHexpandSet" o = Gtk.Widget.WidgetSetHexpandSetMethodInfo
    ResolveCellViewMethod "setMapped" o = Gtk.Widget.WidgetSetMappedMethodInfo
    ResolveCellViewMethod "setMarginBottom" o = Gtk.Widget.WidgetSetMarginBottomMethodInfo
    ResolveCellViewMethod "setMarginEnd" o = Gtk.Widget.WidgetSetMarginEndMethodInfo
    ResolveCellViewMethod "setMarginLeft" o = Gtk.Widget.WidgetSetMarginLeftMethodInfo
    ResolveCellViewMethod "setMarginRight" o = Gtk.Widget.WidgetSetMarginRightMethodInfo
    ResolveCellViewMethod "setMarginStart" o = Gtk.Widget.WidgetSetMarginStartMethodInfo
    ResolveCellViewMethod "setMarginTop" o = Gtk.Widget.WidgetSetMarginTopMethodInfo
    ResolveCellViewMethod "setModel" o = CellViewSetModelMethodInfo
    ResolveCellViewMethod "setName" o = Gtk.Widget.WidgetSetNameMethodInfo
    ResolveCellViewMethod "setNoShowAll" o = Gtk.Widget.WidgetSetNoShowAllMethodInfo
    ResolveCellViewMethod "setOpacity" o = Gtk.Widget.WidgetSetOpacityMethodInfo
    ResolveCellViewMethod "setOrientation" o = Gtk.Orientable.OrientableSetOrientationMethodInfo
    ResolveCellViewMethod "setParent" o = Gtk.Widget.WidgetSetParentMethodInfo
    ResolveCellViewMethod "setParentWindow" o = Gtk.Widget.WidgetSetParentWindowMethodInfo
    ResolveCellViewMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveCellViewMethod "setRealized" o = Gtk.Widget.WidgetSetRealizedMethodInfo
    ResolveCellViewMethod "setReceivesDefault" o = Gtk.Widget.WidgetSetReceivesDefaultMethodInfo
    ResolveCellViewMethod "setRedrawOnAllocate" o = Gtk.Widget.WidgetSetRedrawOnAllocateMethodInfo
    ResolveCellViewMethod "setSensitive" o = Gtk.Widget.WidgetSetSensitiveMethodInfo
    ResolveCellViewMethod "setSizeRequest" o = Gtk.Widget.WidgetSetSizeRequestMethodInfo
    ResolveCellViewMethod "setState" o = Gtk.Widget.WidgetSetStateMethodInfo
    ResolveCellViewMethod "setStateFlags" o = Gtk.Widget.WidgetSetStateFlagsMethodInfo
    ResolveCellViewMethod "setStyle" o = Gtk.Widget.WidgetSetStyleMethodInfo
    ResolveCellViewMethod "setSupportMultidevice" o = Gtk.Widget.WidgetSetSupportMultideviceMethodInfo
    ResolveCellViewMethod "setTooltipMarkup" o = Gtk.Widget.WidgetSetTooltipMarkupMethodInfo
    ResolveCellViewMethod "setTooltipText" o = Gtk.Widget.WidgetSetTooltipTextMethodInfo
    ResolveCellViewMethod "setTooltipWindow" o = Gtk.Widget.WidgetSetTooltipWindowMethodInfo
    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 "setVisual" o = Gtk.Widget.WidgetSetVisualMethodInfo
    ResolveCellViewMethod "setWindow" o = Gtk.Widget.WidgetSetWindowMethodInfo
    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
   
   
   
setCellViewBackground :: (MonadIO m, IsCellView o) => o -> T.Text -> m ()
setCellViewBackground :: forall (m :: * -> *) o.
(MonadIO m, IsCellView o) =>
o -> Text -> m ()
setCellViewBackground o
obj Text
val = IO () -> m ()
forall a. IO a -> m a
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 Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"background" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
constructCellViewBackground :: (IsCellView o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructCellViewBackground :: forall o (m :: * -> *).
(IsCellView o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructCellViewBackground Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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 a. IO a -> IO a
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 Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"background" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
clearCellViewBackground :: (MonadIO m, IsCellView o) => o -> m ()
clearCellViewBackground :: forall (m :: * -> *) o. (MonadIO m, IsCellView o) => o -> m ()
clearCellViewBackground o
obj = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"background" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)
#if defined(ENABLE_OVERLOADING)
data CellViewBackgroundPropertyInfo
instance AttrInfo CellViewBackgroundPropertyInfo where
    type AttrAllowedOps CellViewBackgroundPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrClear]
    type AttrBaseTypeConstraint CellViewBackgroundPropertyInfo = IsCellView
    type AttrSetTypeConstraint CellViewBackgroundPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint CellViewBackgroundPropertyInfo = (~) T.Text
    type AttrTransferType CellViewBackgroundPropertyInfo = T.Text
    type AttrGetType CellViewBackgroundPropertyInfo = ()
    type AttrLabel CellViewBackgroundPropertyInfo = "background"
    type AttrOrigin CellViewBackgroundPropertyInfo = CellView
    attrGet = undefined
    attrSet = setCellViewBackground
    attrTransfer _ v = do
        return v
    attrConstruct = constructCellViewBackground
    attrClear = clearCellViewBackground
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.CellView.background"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.43/docs/GI-Gtk-Objects-CellView.html#g:attr:background"
        })
#endif
   
   
   
getCellViewBackgroundGdk :: (MonadIO m, IsCellView o) => o -> m (Maybe Gdk.Color.Color)
getCellViewBackgroundGdk :: forall (m :: * -> *) o.
(MonadIO m, IsCellView o) =>
o -> m (Maybe Color)
getCellViewBackgroundGdk o
obj = IO (Maybe Color) -> m (Maybe Color)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Color) -> m (Maybe Color))
-> IO (Maybe Color) -> m (Maybe Color)
forall a b. (a -> b) -> a -> b
$ o -> String -> (ManagedPtr Color -> Color) -> IO (Maybe Color)
forall a b.
(GObject a, GBoxed b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyBoxed o
obj String
"background-gdk" ManagedPtr Color -> Color
Gdk.Color.Color
setCellViewBackgroundGdk :: (MonadIO m, IsCellView o) => o -> Gdk.Color.Color -> m ()
setCellViewBackgroundGdk :: forall (m :: * -> *) o.
(MonadIO m, IsCellView o) =>
o -> Color -> m ()
setCellViewBackgroundGdk o
obj Color
val = IO () -> m ()
forall a. IO a -> m a
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 Color -> IO ()
forall a b.
(GObject a, GBoxed b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyBoxed o
obj String
"background-gdk" (Color -> Maybe Color
forall a. a -> Maybe a
Just Color
val)
constructCellViewBackgroundGdk :: (IsCellView o, MIO.MonadIO m) => Gdk.Color.Color -> m (GValueConstruct o)
constructCellViewBackgroundGdk :: forall o (m :: * -> *).
(IsCellView o, MonadIO m) =>
Color -> m (GValueConstruct o)
constructCellViewBackgroundGdk Color
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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 a. IO a -> IO a
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 Color -> IO (GValueConstruct o)
forall a o. GBoxed a => String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBoxed String
"background-gdk" (Color -> Maybe Color
forall a. a -> Maybe a
P.Just Color
val)
clearCellViewBackgroundGdk :: (MonadIO m, IsCellView o) => o -> m ()
clearCellViewBackgroundGdk :: forall (m :: * -> *) o. (MonadIO m, IsCellView o) => o -> m ()
clearCellViewBackgroundGdk o
obj = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Color -> IO ()
forall a b.
(GObject a, GBoxed b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyBoxed o
obj String
"background-gdk" (Maybe Color
forall a. Maybe a
Nothing :: Maybe Gdk.Color.Color)
#if defined(ENABLE_OVERLOADING)
data CellViewBackgroundGdkPropertyInfo
instance AttrInfo CellViewBackgroundGdkPropertyInfo where
    type AttrAllowedOps CellViewBackgroundGdkPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint CellViewBackgroundGdkPropertyInfo = IsCellView
    type AttrSetTypeConstraint CellViewBackgroundGdkPropertyInfo = (~) Gdk.Color.Color
    type AttrTransferTypeConstraint CellViewBackgroundGdkPropertyInfo = (~) Gdk.Color.Color
    type AttrTransferType CellViewBackgroundGdkPropertyInfo = Gdk.Color.Color
    type AttrGetType CellViewBackgroundGdkPropertyInfo = (Maybe Gdk.Color.Color)
    type AttrLabel CellViewBackgroundGdkPropertyInfo = "background-gdk"
    type AttrOrigin CellViewBackgroundGdkPropertyInfo = CellView
    attrGet = getCellViewBackgroundGdk
    attrSet = setCellViewBackgroundGdk
    attrTransfer _ v = do
        return v
    attrConstruct = constructCellViewBackgroundGdk
    attrClear = clearCellViewBackgroundGdk
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.CellView.backgroundGdk"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.43/docs/GI-Gtk-Objects-CellView.html#g:attr:backgroundGdk"
        })
#endif
   
   
   
getCellViewBackgroundRgba :: (MonadIO m, IsCellView o) => o -> m (Maybe Gdk.RGBA.RGBA)
getCellViewBackgroundRgba :: forall (m :: * -> *) o.
(MonadIO m, IsCellView o) =>
o -> m (Maybe RGBA)
getCellViewBackgroundRgba o
obj = IO (Maybe RGBA) -> m (Maybe RGBA)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe RGBA) -> m (Maybe RGBA))
-> IO (Maybe RGBA) -> m (Maybe RGBA)
forall a b. (a -> b) -> a -> b
$ o -> String -> (ManagedPtr RGBA -> RGBA) -> IO (Maybe RGBA)
forall a b.
(GObject a, GBoxed b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyBoxed o
obj String
"background-rgba" ManagedPtr RGBA -> RGBA
Gdk.RGBA.RGBA
setCellViewBackgroundRgba :: (MonadIO m, IsCellView o) => o -> Gdk.RGBA.RGBA -> m ()
setCellViewBackgroundRgba :: forall (m :: * -> *) o.
(MonadIO m, IsCellView o) =>
o -> RGBA -> m ()
setCellViewBackgroundRgba o
obj RGBA
val = IO () -> m ()
forall a. IO a -> m a
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 RGBA -> IO ()
forall a b.
(GObject a, GBoxed b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyBoxed o
obj String
"background-rgba" (RGBA -> Maybe RGBA
forall a. a -> Maybe a
Just RGBA
val)
constructCellViewBackgroundRgba :: (IsCellView o, MIO.MonadIO m) => Gdk.RGBA.RGBA -> m (GValueConstruct o)
constructCellViewBackgroundRgba :: forall o (m :: * -> *).
(IsCellView o, MonadIO m) =>
RGBA -> m (GValueConstruct o)
constructCellViewBackgroundRgba RGBA
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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 a. IO a -> IO a
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 RGBA -> IO (GValueConstruct o)
forall a o. GBoxed a => String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBoxed String
"background-rgba" (RGBA -> Maybe RGBA
forall a. a -> Maybe a
P.Just RGBA
val)
#if defined(ENABLE_OVERLOADING)
data CellViewBackgroundRgbaPropertyInfo
instance AttrInfo CellViewBackgroundRgbaPropertyInfo where
    type AttrAllowedOps CellViewBackgroundRgbaPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint CellViewBackgroundRgbaPropertyInfo = IsCellView
    type AttrSetTypeConstraint CellViewBackgroundRgbaPropertyInfo = (~) Gdk.RGBA.RGBA
    type AttrTransferTypeConstraint CellViewBackgroundRgbaPropertyInfo = (~) Gdk.RGBA.RGBA
    type AttrTransferType CellViewBackgroundRgbaPropertyInfo = Gdk.RGBA.RGBA
    type AttrGetType CellViewBackgroundRgbaPropertyInfo = (Maybe Gdk.RGBA.RGBA)
    type AttrLabel CellViewBackgroundRgbaPropertyInfo = "background-rgba"
    type AttrOrigin CellViewBackgroundRgbaPropertyInfo = CellView
    attrGet = getCellViewBackgroundRgba
    attrSet = setCellViewBackgroundRgba
    attrTransfer _ v = do
        return v
    attrConstruct = constructCellViewBackgroundRgba
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.CellView.backgroundRgba"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.43/docs/GI-Gtk-Objects-CellView.html#g:attr:backgroundRgba"
        })
#endif
   
   
   
getCellViewBackgroundSet :: (MonadIO m, IsCellView o) => o -> m Bool
getCellViewBackgroundSet :: forall (m :: * -> *) o. (MonadIO m, IsCellView o) => o -> m Bool
getCellViewBackgroundSet o
obj = IO Bool -> m Bool
forall a. IO a -> m a
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
"background-set"
setCellViewBackgroundSet :: (MonadIO m, IsCellView o) => o -> Bool -> m ()
setCellViewBackgroundSet :: forall (m :: * -> *) o.
(MonadIO m, IsCellView o) =>
o -> Bool -> m ()
setCellViewBackgroundSet o
obj Bool
val = IO () -> m ()
forall a. IO a -> m a
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
"background-set" Bool
val
constructCellViewBackgroundSet :: (IsCellView o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructCellViewBackgroundSet :: forall o (m :: * -> *).
(IsCellView o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructCellViewBackgroundSet Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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 a. IO a -> IO a
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
"background-set" Bool
val
#if defined(ENABLE_OVERLOADING)
data CellViewBackgroundSetPropertyInfo
instance AttrInfo CellViewBackgroundSetPropertyInfo where
    type AttrAllowedOps CellViewBackgroundSetPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint CellViewBackgroundSetPropertyInfo = IsCellView
    type AttrSetTypeConstraint CellViewBackgroundSetPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint CellViewBackgroundSetPropertyInfo = (~) Bool
    type AttrTransferType CellViewBackgroundSetPropertyInfo = Bool
    type AttrGetType CellViewBackgroundSetPropertyInfo = Bool
    type AttrLabel CellViewBackgroundSetPropertyInfo = "background-set"
    type AttrOrigin CellViewBackgroundSetPropertyInfo = CellView
    attrGet = getCellViewBackgroundSet
    attrSet = setCellViewBackgroundSet
    attrTransfer _ v = do
        return v
    attrConstruct = constructCellViewBackgroundSet
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.CellView.backgroundSet"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.43/docs/GI-Gtk-Objects-CellView.html#g:attr:backgroundSet"
        })
#endif
   
   
   
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 a. IO a -> m a
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
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 a. IO a -> m a
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 a. IO a -> IO a
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-3.0.43/docs/GI-Gtk-Objects-CellView.html#g:attr:cellArea"
        })
#endif
   
   
   
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 a. IO a -> m a
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
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 a. IO a -> m a
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 a. IO a -> IO a
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-3.0.43/docs/GI-Gtk-Objects-CellView.html#g:attr:cellAreaContext"
        })
#endif
   
   
   
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 a. IO a -> m a
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"
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 a. IO a -> m a
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
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 a. IO a -> m a
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 a. IO a -> IO a
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-3.0.43/docs/GI-Gtk-Objects-CellView.html#g:attr:drawSensitive"
        })
#endif
   
   
   
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 a. IO a -> m a
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"
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 a. IO a -> m a
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
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 a. IO a -> m a
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 a. IO a -> IO a
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-3.0.43/docs/GI-Gtk-Objects-CellView.html#g:attr:fitModel"
        })
#endif
   
   
   
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 a. IO a -> m a
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
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 a. IO a -> m a
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)
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 a. IO a -> m a
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 a. IO a -> IO a
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)
clearCellViewModel :: (MonadIO m, IsCellView o) => o -> m ()
clearCellViewModel :: forall (m :: * -> *) o. (MonadIO m, IsCellView o) => o -> m ()
clearCellViewModel o
obj = IO () -> m ()
forall a. IO a -> m a
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-3.0.43/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 = ('[ '("appPaintable", Gtk.Widget.WidgetAppPaintablePropertyInfo), '("background", CellViewBackgroundPropertyInfo), '("backgroundGdk", CellViewBackgroundGdkPropertyInfo), '("backgroundRgba", CellViewBackgroundRgbaPropertyInfo), '("backgroundSet", CellViewBackgroundSetPropertyInfo), '("canDefault", Gtk.Widget.WidgetCanDefaultPropertyInfo), '("canFocus", Gtk.Widget.WidgetCanFocusPropertyInfo), '("cellArea", CellViewCellAreaPropertyInfo), '("cellAreaContext", CellViewCellAreaContextPropertyInfo), '("compositeChild", Gtk.Widget.WidgetCompositeChildPropertyInfo), '("doubleBuffered", Gtk.Widget.WidgetDoubleBufferedPropertyInfo), '("drawSensitive", CellViewDrawSensitivePropertyInfo), '("events", Gtk.Widget.WidgetEventsPropertyInfo), '("expand", Gtk.Widget.WidgetExpandPropertyInfo), '("fitModel", CellViewFitModelPropertyInfo), '("focusOnClick", Gtk.Widget.WidgetFocusOnClickPropertyInfo), '("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), '("isFocus", Gtk.Widget.WidgetIsFocusPropertyInfo), '("margin", Gtk.Widget.WidgetMarginPropertyInfo), '("marginBottom", Gtk.Widget.WidgetMarginBottomPropertyInfo), '("marginEnd", Gtk.Widget.WidgetMarginEndPropertyInfo), '("marginLeft", Gtk.Widget.WidgetMarginLeftPropertyInfo), '("marginRight", Gtk.Widget.WidgetMarginRightPropertyInfo), '("marginStart", Gtk.Widget.WidgetMarginStartPropertyInfo), '("marginTop", Gtk.Widget.WidgetMarginTopPropertyInfo), '("model", CellViewModelPropertyInfo), '("name", Gtk.Widget.WidgetNamePropertyInfo), '("noShowAll", Gtk.Widget.WidgetNoShowAllPropertyInfo), '("opacity", Gtk.Widget.WidgetOpacityPropertyInfo), '("orientation", Gtk.Orientable.OrientableOrientationPropertyInfo), '("parent", Gtk.Widget.WidgetParentPropertyInfo), '("receivesDefault", Gtk.Widget.WidgetReceivesDefaultPropertyInfo), '("scaleFactor", Gtk.Widget.WidgetScaleFactorPropertyInfo), '("sensitive", Gtk.Widget.WidgetSensitivePropertyInfo), '("style", Gtk.Widget.WidgetStylePropertyInfo), '("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), '("window", Gtk.Widget.WidgetWindowPropertyInfo)] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
cellViewBackground :: AttrLabelProxy "background"
cellViewBackground = AttrLabelProxy
cellViewBackgroundGdk :: AttrLabelProxy "backgroundGdk"
cellViewBackgroundGdk = AttrLabelProxy
cellViewBackgroundRgba :: AttrLabelProxy "backgroundRgba"
cellViewBackgroundRgba = AttrLabelProxy
cellViewBackgroundSet :: AttrLabelProxy "backgroundSet"
cellViewBackgroundSet = AttrLabelProxy
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 = ('[ '("accelClosuresChanged", Gtk.Widget.WidgetAccelClosuresChangedSignalInfo), '("buttonPressEvent", Gtk.Widget.WidgetButtonPressEventSignalInfo), '("buttonReleaseEvent", Gtk.Widget.WidgetButtonReleaseEventSignalInfo), '("canActivateAccel", Gtk.Widget.WidgetCanActivateAccelSignalInfo), '("childNotify", Gtk.Widget.WidgetChildNotifySignalInfo), '("compositedChanged", Gtk.Widget.WidgetCompositedChangedSignalInfo), '("configureEvent", Gtk.Widget.WidgetConfigureEventSignalInfo), '("damageEvent", Gtk.Widget.WidgetDamageEventSignalInfo), '("deleteEvent", Gtk.Widget.WidgetDeleteEventSignalInfo), '("destroy", Gtk.Widget.WidgetDestroySignalInfo), '("destroyEvent", Gtk.Widget.WidgetDestroyEventSignalInfo), '("directionChanged", Gtk.Widget.WidgetDirectionChangedSignalInfo), '("dragBegin", Gtk.Widget.WidgetDragBeginSignalInfo), '("dragDataDelete", Gtk.Widget.WidgetDragDataDeleteSignalInfo), '("dragDataGet", Gtk.Widget.WidgetDragDataGetSignalInfo), '("dragDataReceived", Gtk.Widget.WidgetDragDataReceivedSignalInfo), '("dragDrop", Gtk.Widget.WidgetDragDropSignalInfo), '("dragEnd", Gtk.Widget.WidgetDragEndSignalInfo), '("dragFailed", Gtk.Widget.WidgetDragFailedSignalInfo), '("dragLeave", Gtk.Widget.WidgetDragLeaveSignalInfo), '("dragMotion", Gtk.Widget.WidgetDragMotionSignalInfo), '("draw", Gtk.Widget.WidgetDrawSignalInfo), '("enterNotifyEvent", Gtk.Widget.WidgetEnterNotifyEventSignalInfo), '("event", Gtk.Widget.WidgetEventSignalInfo), '("eventAfter", Gtk.Widget.WidgetEventAfterSignalInfo), '("focus", Gtk.Widget.WidgetFocusSignalInfo), '("focusInEvent", Gtk.Widget.WidgetFocusInEventSignalInfo), '("focusOutEvent", Gtk.Widget.WidgetFocusOutEventSignalInfo), '("grabBrokenEvent", Gtk.Widget.WidgetGrabBrokenEventSignalInfo), '("grabFocus", Gtk.Widget.WidgetGrabFocusSignalInfo), '("grabNotify", Gtk.Widget.WidgetGrabNotifySignalInfo), '("hide", Gtk.Widget.WidgetHideSignalInfo), '("hierarchyChanged", Gtk.Widget.WidgetHierarchyChangedSignalInfo), '("keyPressEvent", Gtk.Widget.WidgetKeyPressEventSignalInfo), '("keyReleaseEvent", Gtk.Widget.WidgetKeyReleaseEventSignalInfo), '("keynavFailed", Gtk.Widget.WidgetKeynavFailedSignalInfo), '("leaveNotifyEvent", Gtk.Widget.WidgetLeaveNotifyEventSignalInfo), '("map", Gtk.Widget.WidgetMapSignalInfo), '("mapEvent", Gtk.Widget.WidgetMapEventSignalInfo), '("mnemonicActivate", Gtk.Widget.WidgetMnemonicActivateSignalInfo), '("motionNotifyEvent", Gtk.Widget.WidgetMotionNotifyEventSignalInfo), '("moveFocus", Gtk.Widget.WidgetMoveFocusSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("parentSet", Gtk.Widget.WidgetParentSetSignalInfo), '("popupMenu", Gtk.Widget.WidgetPopupMenuSignalInfo), '("propertyNotifyEvent", Gtk.Widget.WidgetPropertyNotifyEventSignalInfo), '("proximityInEvent", Gtk.Widget.WidgetProximityInEventSignalInfo), '("proximityOutEvent", Gtk.Widget.WidgetProximityOutEventSignalInfo), '("queryTooltip", Gtk.Widget.WidgetQueryTooltipSignalInfo), '("realize", Gtk.Widget.WidgetRealizeSignalInfo), '("screenChanged", Gtk.Widget.WidgetScreenChangedSignalInfo), '("scrollEvent", Gtk.Widget.WidgetScrollEventSignalInfo), '("selectionClearEvent", Gtk.Widget.WidgetSelectionClearEventSignalInfo), '("selectionGet", Gtk.Widget.WidgetSelectionGetSignalInfo), '("selectionNotifyEvent", Gtk.Widget.WidgetSelectionNotifyEventSignalInfo), '("selectionReceived", Gtk.Widget.WidgetSelectionReceivedSignalInfo), '("selectionRequestEvent", Gtk.Widget.WidgetSelectionRequestEventSignalInfo), '("show", Gtk.Widget.WidgetShowSignalInfo), '("showHelp", Gtk.Widget.WidgetShowHelpSignalInfo), '("sizeAllocate", Gtk.Widget.WidgetSizeAllocateSignalInfo), '("stateChanged", Gtk.Widget.WidgetStateChangedSignalInfo), '("stateFlagsChanged", Gtk.Widget.WidgetStateFlagsChangedSignalInfo), '("styleSet", Gtk.Widget.WidgetStyleSetSignalInfo), '("styleUpdated", Gtk.Widget.WidgetStyleUpdatedSignalInfo), '("touchEvent", Gtk.Widget.WidgetTouchEventSignalInfo), '("unmap", Gtk.Widget.WidgetUnmapSignalInfo), '("unmapEvent", Gtk.Widget.WidgetUnmapEventSignalInfo), '("unrealize", Gtk.Widget.WidgetUnrealizeSignalInfo), '("visibilityNotifyEvent", Gtk.Widget.WidgetVisibilityNotifyEventSignalInfo), '("windowStateEvent", Gtk.Widget.WidgetWindowStateEventSignalInfo)] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "gtk_cell_view_new" gtk_cell_view_new :: 
    IO (Ptr CellView)
cellViewNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m CellView
    
cellViewNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m CellView
cellViewNew  = IO CellView -> m CellView
forall a. IO a -> m a
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CellView
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_cell_view_new_with_context" gtk_cell_view_new_with_context :: 
    Ptr Gtk.CellArea.CellArea ->            
    Ptr Gtk.CellAreaContext.CellAreaContext -> 
    IO (Ptr CellView)
cellViewNewWithContext ::
    (B.CallStack.HasCallStack, MonadIO m, Gtk.CellArea.IsCellArea a, Gtk.CellAreaContext.IsCellAreaContext b) =>
    a
    
    -> b
    
    -> m CellView
    
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 a. IO a -> m a
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CellView
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_cell_view_new_with_markup" gtk_cell_view_new_with_markup :: 
    CString ->                              
    IO (Ptr CellView)
cellViewNewWithMarkup ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    
    -> m CellView
    
cellViewNewWithMarkup :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> m CellView
cellViewNewWithMarkup Text
markup = IO CellView -> m CellView
forall a. IO a -> m a
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CellView
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_cell_view_new_with_pixbuf" gtk_cell_view_new_with_pixbuf :: 
    Ptr GdkPixbuf.Pixbuf.Pixbuf ->          
    IO (Ptr CellView)
cellViewNewWithPixbuf ::
    (B.CallStack.HasCallStack, MonadIO m, GdkPixbuf.Pixbuf.IsPixbuf a) =>
    a
    
    -> m CellView
    
cellViewNewWithPixbuf :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPixbuf a) =>
a -> m CellView
cellViewNewWithPixbuf a
pixbuf = IO CellView -> m CellView
forall a. IO a -> m a
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 Pixbuf
pixbuf' <- a -> IO (Ptr Pixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
pixbuf
    Ptr CellView
result <- Ptr Pixbuf -> IO (Ptr CellView)
gtk_cell_view_new_with_pixbuf Ptr Pixbuf
pixbuf'
    Text -> Ptr CellView -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"cellViewNewWithPixbuf" 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
pixbuf
    CellView -> IO CellView
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CellView
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_cell_view_new_with_text" gtk_cell_view_new_with_text :: 
    CString ->                              
    IO (Ptr CellView)
cellViewNewWithText ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    
    -> m CellView
    
cellViewNewWithText :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> m CellView
cellViewNewWithText Text
text = IO CellView -> m CellView
forall a. IO a -> m a
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CellView
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_cell_view_get_displayed_row" gtk_cell_view_get_displayed_row :: 
    Ptr CellView ->                         
    IO (Ptr Gtk.TreePath.TreePath)
cellViewGetDisplayedRow ::
    (B.CallStack.HasCallStack, MonadIO m, IsCellView a) =>
    a
    
    -> m (Maybe Gtk.TreePath.TreePath)
    
cellViewGetDisplayedRow :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCellView a) =>
a -> m (Maybe TreePath)
cellViewGetDisplayedRow a
cellView = IO (Maybe TreePath) -> m (Maybe TreePath)
forall a. IO a -> m a
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 a. a -> IO a
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 a. a -> IO a
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-3.0.43/docs/GI-Gtk-Objects-CellView.html#v:cellViewGetDisplayedRow"
        })
#endif
foreign import ccall "gtk_cell_view_get_draw_sensitive" gtk_cell_view_get_draw_sensitive :: 
    Ptr CellView ->                         
    IO CInt
cellViewGetDrawSensitive ::
    (B.CallStack.HasCallStack, MonadIO m, IsCellView a) =>
    a
    
    -> m Bool
    
    
cellViewGetDrawSensitive :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCellView a) =>
a -> m Bool
cellViewGetDrawSensitive a
cellView = IO Bool -> m Bool
forall a. IO a -> m a
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 a. a -> IO a
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-3.0.43/docs/GI-Gtk-Objects-CellView.html#v:cellViewGetDrawSensitive"
        })
#endif
foreign import ccall "gtk_cell_view_get_fit_model" gtk_cell_view_get_fit_model :: 
    Ptr CellView ->                         
    IO CInt
cellViewGetFitModel ::
    (B.CallStack.HasCallStack, MonadIO m, IsCellView a) =>
    a
    
    -> m Bool
    
    
cellViewGetFitModel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCellView a) =>
a -> m Bool
cellViewGetFitModel a
cellView = IO Bool -> m Bool
forall a. IO a -> m a
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 a. a -> IO a
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-3.0.43/docs/GI-Gtk-Objects-CellView.html#v:cellViewGetFitModel"
        })
#endif
foreign import ccall "gtk_cell_view_get_model" gtk_cell_view_get_model :: 
    Ptr CellView ->                         
    IO (Ptr Gtk.TreeModel.TreeModel)
cellViewGetModel ::
    (B.CallStack.HasCallStack, MonadIO m, IsCellView a) =>
    a
    
    -> m (Maybe Gtk.TreeModel.TreeModel)
    
cellViewGetModel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCellView a) =>
a -> m (Maybe TreeModel)
cellViewGetModel a
cellView = IO (Maybe TreeModel) -> m (Maybe TreeModel)
forall a. IO a -> m a
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 a. a -> IO a
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 a. a -> IO a
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-3.0.43/docs/GI-Gtk-Objects-CellView.html#v:cellViewGetModel"
        })
#endif
foreign import ccall "gtk_cell_view_get_size_of_row" gtk_cell_view_get_size_of_row :: 
    Ptr CellView ->                         
    Ptr Gtk.TreePath.TreePath ->            
    Ptr Gtk.Requisition.Requisition ->      
    IO CInt
{-# DEPRECATED cellViewGetSizeOfRow ["(Since version 3.0)","Combo box formerly used this to calculate the","sizes for cellviews, now you can achieve this by either using","the [CellView:fitModel](\"GI.Gtk.Objects.CellView#g:attr:fitModel\") property or by setting the currently","displayed row of the t'GI.Gtk.Objects.CellView.CellView' and using 'GI.Gtk.Objects.Widget.widgetGetPreferredSize'."] #-}
cellViewGetSizeOfRow ::
    (B.CallStack.HasCallStack, MonadIO m, IsCellView a) =>
    a
    
    -> Gtk.TreePath.TreePath
    
    -> m ((Bool, Gtk.Requisition.Requisition))
    
cellViewGetSizeOfRow :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCellView a) =>
a -> TreePath -> m (Bool, Requisition)
cellViewGetSizeOfRow a
cellView TreePath
path = IO (Bool, Requisition) -> m (Bool, Requisition)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Requisition) -> m (Bool, Requisition))
-> IO (Bool, Requisition) -> m (Bool, Requisition)
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
path' <- TreePath -> IO (Ptr TreePath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TreePath
path
    Ptr Requisition
requisition <- Int -> IO (Ptr Requisition)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
8 :: IO (Ptr Gtk.Requisition.Requisition)
    CInt
result <- Ptr CellView -> Ptr TreePath -> Ptr Requisition -> IO CInt
gtk_cell_view_get_size_of_row Ptr CellView
cellView' Ptr TreePath
path' Ptr Requisition
requisition
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Requisition
requisition' <- ((ManagedPtr Requisition -> Requisition)
-> Ptr Requisition -> IO Requisition
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Requisition -> Requisition
Gtk.Requisition.Requisition) Ptr Requisition
requisition
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
cellView
    TreePath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TreePath
path
    (Bool, Requisition) -> IO (Bool, Requisition)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', Requisition
requisition')
#if defined(ENABLE_OVERLOADING)
data CellViewGetSizeOfRowMethodInfo
instance (signature ~ (Gtk.TreePath.TreePath -> m ((Bool, Gtk.Requisition.Requisition))), MonadIO m, IsCellView a) => O.OverloadedMethod CellViewGetSizeOfRowMethodInfo a signature where
    overloadedMethod = cellViewGetSizeOfRow
instance O.OverloadedMethodInfo CellViewGetSizeOfRowMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.CellView.cellViewGetSizeOfRow",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.43/docs/GI-Gtk-Objects-CellView.html#v:cellViewGetSizeOfRow"
        })
#endif
foreign import ccall "gtk_cell_view_set_background_color" gtk_cell_view_set_background_color :: 
    Ptr CellView ->                         
    Ptr Gdk.Color.Color ->                  
    IO ()
{-# DEPRECATED cellViewSetBackgroundColor ["(Since version 3.4)","Use 'GI.Gtk.Objects.CellView.cellViewSetBackgroundRgba' instead."] #-}
cellViewSetBackgroundColor ::
    (B.CallStack.HasCallStack, MonadIO m, IsCellView a) =>
    a
    
    -> Gdk.Color.Color
    
    -> m ()
cellViewSetBackgroundColor :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCellView a) =>
a -> Color -> m ()
cellViewSetBackgroundColor a
cellView Color
color = IO () -> m ()
forall a. IO a -> m a
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 Color
color' <- Color -> IO (Ptr Color)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Color
color
    Ptr CellView -> Ptr Color -> IO ()
gtk_cell_view_set_background_color Ptr CellView
cellView' Ptr Color
color'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
cellView
    Color -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Color
color
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data CellViewSetBackgroundColorMethodInfo
instance (signature ~ (Gdk.Color.Color -> m ()), MonadIO m, IsCellView a) => O.OverloadedMethod CellViewSetBackgroundColorMethodInfo a signature where
    overloadedMethod = cellViewSetBackgroundColor
instance O.OverloadedMethodInfo CellViewSetBackgroundColorMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.CellView.cellViewSetBackgroundColor",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.43/docs/GI-Gtk-Objects-CellView.html#v:cellViewSetBackgroundColor"
        })
#endif
foreign import ccall "gtk_cell_view_set_background_rgba" gtk_cell_view_set_background_rgba :: 
    Ptr CellView ->                         
    Ptr Gdk.RGBA.RGBA ->                    
    IO ()
cellViewSetBackgroundRgba ::
    (B.CallStack.HasCallStack, MonadIO m, IsCellView a) =>
    a
    
    -> Gdk.RGBA.RGBA
    
    -> m ()
cellViewSetBackgroundRgba :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCellView a) =>
a -> RGBA -> m ()
cellViewSetBackgroundRgba a
cellView RGBA
rgba = IO () -> m ()
forall a. IO a -> m a
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 RGBA
rgba' <- RGBA -> IO (Ptr RGBA)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RGBA
rgba
    Ptr CellView -> Ptr RGBA -> IO ()
gtk_cell_view_set_background_rgba Ptr CellView
cellView' Ptr RGBA
rgba'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
cellView
    RGBA -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr RGBA
rgba
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data CellViewSetBackgroundRgbaMethodInfo
instance (signature ~ (Gdk.RGBA.RGBA -> m ()), MonadIO m, IsCellView a) => O.OverloadedMethod CellViewSetBackgroundRgbaMethodInfo a signature where
    overloadedMethod = cellViewSetBackgroundRgba
instance O.OverloadedMethodInfo CellViewSetBackgroundRgbaMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.CellView.cellViewSetBackgroundRgba",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.43/docs/GI-Gtk-Objects-CellView.html#v:cellViewSetBackgroundRgba"
        })
#endif
foreign import ccall "gtk_cell_view_set_displayed_row" gtk_cell_view_set_displayed_row :: 
    Ptr CellView ->                         
    Ptr Gtk.TreePath.TreePath ->            
    IO ()
cellViewSetDisplayedRow ::
    (B.CallStack.HasCallStack, MonadIO m, IsCellView a) =>
    a
    
    -> Maybe (Gtk.TreePath.TreePath)
    
    -> m ()
cellViewSetDisplayedRow :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCellView a) =>
a -> Maybe TreePath -> m ()
cellViewSetDisplayedRow a
cellView Maybe TreePath
path = IO () -> m ()
forall a. IO a -> m a
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TreePath
forall a. Ptr a
FP.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 a. a -> IO a
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 a. a -> IO a
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-3.0.43/docs/GI-Gtk-Objects-CellView.html#v:cellViewSetDisplayedRow"
        })
#endif
foreign import ccall "gtk_cell_view_set_draw_sensitive" gtk_cell_view_set_draw_sensitive :: 
    Ptr CellView ->                         
    CInt ->                                 
    IO ()
cellViewSetDrawSensitive ::
    (B.CallStack.HasCallStack, MonadIO m, IsCellView a) =>
    a
    
    -> Bool
    
    -> m ()
cellViewSetDrawSensitive :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCellView a) =>
a -> Bool -> m ()
cellViewSetDrawSensitive a
cellView Bool
drawSensitive = IO () -> m ()
forall a. IO a -> m a
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
P.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
P.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 a. a -> IO a
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-3.0.43/docs/GI-Gtk-Objects-CellView.html#v:cellViewSetDrawSensitive"
        })
#endif
foreign import ccall "gtk_cell_view_set_fit_model" gtk_cell_view_set_fit_model :: 
    Ptr CellView ->                         
    CInt ->                                 
    IO ()
cellViewSetFitModel ::
    (B.CallStack.HasCallStack, MonadIO m, IsCellView a) =>
    a
    
    -> Bool
    
    -> m ()
cellViewSetFitModel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCellView a) =>
a -> Bool -> m ()
cellViewSetFitModel a
cellView Bool
fitModel = IO () -> m ()
forall a. IO a -> m a
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
P.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
P.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 a. a -> IO a
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-3.0.43/docs/GI-Gtk-Objects-CellView.html#v:cellViewSetFitModel"
        })
#endif
foreign import ccall "gtk_cell_view_set_model" gtk_cell_view_set_model :: 
    Ptr CellView ->                         
    Ptr Gtk.TreeModel.TreeModel ->          
    IO ()
cellViewSetModel ::
    (B.CallStack.HasCallStack, MonadIO m, IsCellView a, Gtk.TreeModel.IsTreeModel b) =>
    a
    
    -> Maybe (b)
    
    -> 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 a. IO a -> m a
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TreeModel
forall a. Ptr a
FP.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 a. a -> IO a
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 a. a -> IO a
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-3.0.43/docs/GI-Gtk-Objects-CellView.html#v:cellViewSetModel"
        })
#endif