{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- @GtkColumnViewCell@ is used by t'GI.Gtk.Objects.ColumnViewColumn.ColumnViewColumn' to represent items
-- in a cell in t'GI.Gtk.Objects.ColumnView.ColumnView'.
-- 
-- The @GtkColumnViewCell@s are managed by the columnview widget (with its factory)
-- and cannot be created by applications, but they need to be populated
-- by application code. This is done by calling 'GI.Gtk.Objects.ColumnViewCell.columnViewCellSetChild'.
-- 
-- @GtkColumnViewCell@s exist in 2 stages:
-- 
-- 1. The unbound stage where the listitem is not currently connected to
--    an item in the list. In that case, the [ColumnViewCell:item]("GI.Gtk.Objects.ColumnViewCell#g:attr:item")
--    property is set to 'P.Nothing'.
-- 
-- 2. The bound stage where the listitem references an item from the list.
--    The [ColumnViewCell:item]("GI.Gtk.Objects.ColumnViewCell#g:attr:item") property is not 'P.Nothing'.
-- 
-- /Since: 4.12/

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

module GI.Gtk.Objects.ColumnViewCell
    ( 

-- * Exported types
    ColumnViewCell(..)                      ,
    IsColumnViewCell                        ,
    toColumnViewCell                        ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getAccessibleDescription]("GI.Gtk.Objects.ListItem#g:method:getAccessibleDescription"), [getAccessibleLabel]("GI.Gtk.Objects.ListItem#g:method:getAccessibleLabel"), [getActivatable]("GI.Gtk.Objects.ListItem#g:method:getActivatable"), [getChild]("GI.Gtk.Objects.ColumnViewCell#g:method:getChild"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getFocusable]("GI.Gtk.Objects.ColumnViewCell#g:method:getFocusable"), [getItem]("GI.Gtk.Objects.ColumnViewCell#g:method:getItem"), [getPosition]("GI.Gtk.Objects.ColumnViewCell#g:method:getPosition"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getSelectable]("GI.Gtk.Objects.ListItem#g:method:getSelectable"), [getSelected]("GI.Gtk.Objects.ColumnViewCell#g:method:getSelected").
-- 
-- ==== Setters
-- [setAccessibleDescription]("GI.Gtk.Objects.ListItem#g:method:setAccessibleDescription"), [setAccessibleLabel]("GI.Gtk.Objects.ListItem#g:method:setAccessibleLabel"), [setActivatable]("GI.Gtk.Objects.ListItem#g:method:setActivatable"), [setChild]("GI.Gtk.Objects.ColumnViewCell#g:method:setChild"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setFocusable]("GI.Gtk.Objects.ColumnViewCell#g:method:setFocusable"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setSelectable]("GI.Gtk.Objects.ListItem#g:method:setSelectable").

#if defined(ENABLE_OVERLOADING)
    ResolveColumnViewCellMethod             ,
#endif

-- ** getChild #method:getChild#

#if defined(ENABLE_OVERLOADING)
    ColumnViewCellGetChildMethodInfo        ,
#endif
    columnViewCellGetChild                  ,


-- ** getFocusable #method:getFocusable#

#if defined(ENABLE_OVERLOADING)
    ColumnViewCellGetFocusableMethodInfo    ,
#endif
    columnViewCellGetFocusable              ,


-- ** getItem #method:getItem#

#if defined(ENABLE_OVERLOADING)
    ColumnViewCellGetItemMethodInfo         ,
#endif
    columnViewCellGetItem                   ,


-- ** getPosition #method:getPosition#

#if defined(ENABLE_OVERLOADING)
    ColumnViewCellGetPositionMethodInfo     ,
#endif
    columnViewCellGetPosition               ,


-- ** getSelected #method:getSelected#

#if defined(ENABLE_OVERLOADING)
    ColumnViewCellGetSelectedMethodInfo     ,
#endif
    columnViewCellGetSelected               ,


-- ** setChild #method:setChild#

#if defined(ENABLE_OVERLOADING)
    ColumnViewCellSetChildMethodInfo        ,
#endif
    columnViewCellSetChild                  ,


-- ** setFocusable #method:setFocusable#

#if defined(ENABLE_OVERLOADING)
    ColumnViewCellSetFocusableMethodInfo    ,
#endif
    columnViewCellSetFocusable              ,




 -- * Properties


-- ** child #attr:child#
-- | Widget used for display.
-- 
-- /Since: 4.12/

#if defined(ENABLE_OVERLOADING)
    ColumnViewCellChildPropertyInfo         ,
#endif
    clearColumnViewCellChild                ,
#if defined(ENABLE_OVERLOADING)
    columnViewCellChild                     ,
#endif
    constructColumnViewCellChild            ,
    getColumnViewCellChild                  ,
    setColumnViewCellChild                  ,


-- ** focusable #attr:focusable#
-- | If the item can be focused with the keyboard.
-- 
-- /Since: 4.12/

#if defined(ENABLE_OVERLOADING)
    ColumnViewCellFocusablePropertyInfo     ,
#endif
#if defined(ENABLE_OVERLOADING)
    columnViewCellFocusable                 ,
#endif
    constructColumnViewCellFocusable        ,
    getColumnViewCellFocusable              ,
    setColumnViewCellFocusable              ,


-- ** item #attr:item#
-- | Displayed item.
-- 
-- /Since: 4.12/

#if defined(ENABLE_OVERLOADING)
    ColumnViewCellItemPropertyInfo          ,
#endif
#if defined(ENABLE_OVERLOADING)
    columnViewCellItem                      ,
#endif
    getColumnViewCellItem                   ,


-- ** position #attr:position#
-- | Position of the item.
-- 
-- /Since: 4.12/

#if defined(ENABLE_OVERLOADING)
    ColumnViewCellPositionPropertyInfo      ,
#endif
#if defined(ENABLE_OVERLOADING)
    columnViewCellPosition                  ,
#endif
    getColumnViewCellPosition               ,


-- ** selected #attr:selected#
-- | If the item is currently selected.
-- 
-- /Since: 4.12/

#if defined(ENABLE_OVERLOADING)
    ColumnViewCellSelectedPropertyInfo      ,
#endif
#if defined(ENABLE_OVERLOADING)
    columnViewCellSelected                  ,
#endif
    getColumnViewCellSelected               ,




    ) 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

-- Workaround for https://gitlab.haskell.org/ghc/ghc/-/issues/23392
#if MIN_VERSION_base(4,18,0)
import qualified GI.Cairo.Structs.Context as Cairo.Context
import qualified GI.Cairo.Structs.FontOptions as Cairo.FontOptions
import qualified GI.GLib.Callbacks as GLib.Callbacks
import qualified GI.GLib.Structs.Bytes as GLib.Bytes
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gdk.Flags as Gdk.Flags
import qualified GI.Gdk.Interfaces.Paintable as Gdk.Paintable
import qualified GI.Gdk.Objects.Clipboard as Gdk.Clipboard
import qualified GI.Gdk.Objects.Cursor as Gdk.Cursor
import qualified GI.Gdk.Objects.Device as Gdk.Device
import qualified GI.Gdk.Objects.Display as Gdk.Display
import qualified GI.Gdk.Objects.Event as Gdk.Event
import qualified GI.Gdk.Objects.FrameClock as Gdk.FrameClock
import qualified GI.Gdk.Objects.Snapshot as Gdk.Snapshot
import qualified GI.Gdk.Objects.Surface as Gdk.Surface
import qualified GI.Gdk.Objects.Texture as Gdk.Texture
import qualified GI.Gdk.Structs.RGBA as Gdk.RGBA
import qualified GI.Gdk.Structs.Rectangle as Gdk.Rectangle
import qualified GI.Gio.Interfaces.ActionGroup as Gio.ActionGroup
import qualified GI.Gio.Interfaces.Icon as Gio.Icon
import qualified GI.Gio.Interfaces.ListModel as Gio.ListModel
import qualified GI.Graphene.Structs.Matrix as Graphene.Matrix
import qualified GI.Graphene.Structs.Point as Graphene.Point
import qualified GI.Graphene.Structs.Point3D as Graphene.Point3D
import qualified GI.Graphene.Structs.Rect as Graphene.Rect
import qualified GI.Graphene.Structs.Size as Graphene.Size
import qualified GI.Graphene.Structs.Vec3 as Graphene.Vec3
import qualified GI.Graphene.Structs.Vec4 as Graphene.Vec4
import qualified GI.Gsk.Enums as Gsk.Enums
import qualified GI.Gsk.Objects.GLShader as Gsk.GLShader
import qualified GI.Gsk.Objects.RenderNode as Gsk.RenderNode
import qualified GI.Gsk.Objects.Renderer as Gsk.Renderer
import qualified GI.Gsk.Structs.ColorStop as Gsk.ColorStop
import qualified GI.Gsk.Structs.Path as Gsk.Path
import qualified GI.Gsk.Structs.RoundedRect as Gsk.RoundedRect
import qualified GI.Gsk.Structs.Shadow as Gsk.Shadow
import qualified GI.Gsk.Structs.Stroke as Gsk.Stroke
import qualified GI.Gsk.Structs.Transform as Gsk.Transform
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.Accessible as Gtk.Accessible
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.ConstraintTarget as Gtk.ConstraintTarget
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Native as Gtk.Native
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Root as Gtk.Root
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.StyleProvider as Gtk.StyleProvider
import {-# SOURCE #-} qualified GI.Gtk.Objects.ATContext as Gtk.ATContext
import {-# SOURCE #-} qualified GI.Gtk.Objects.EventController as Gtk.EventController
import {-# SOURCE #-} qualified GI.Gtk.Objects.LayoutChild as Gtk.LayoutChild
import {-# SOURCE #-} qualified GI.Gtk.Objects.LayoutManager as Gtk.LayoutManager
import {-# SOURCE #-} qualified GI.Gtk.Objects.ListItem as Gtk.ListItem
import {-# SOURCE #-} qualified GI.Gtk.Objects.Settings as Gtk.Settings
import {-# SOURCE #-} qualified GI.Gtk.Objects.Snapshot as Gtk.Snapshot
import {-# SOURCE #-} qualified GI.Gtk.Objects.StyleContext as Gtk.StyleContext
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.Structs.Border as Gtk.Border
import {-# SOURCE #-} qualified GI.Gtk.Structs.Requisition as Gtk.Requisition
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

#else
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gtk.Objects.ListItem as Gtk.ListItem
import {-# SOURCE #-} qualified GI.Gtk.Objects.Widget as Gtk.Widget

#endif

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

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

foreign import ccall "gtk_column_view_cell_get_type"
    c_gtk_column_view_cell_get_type :: IO B.Types.GType

instance B.Types.TypedObject ColumnViewCell where
    glibType :: IO GType
glibType = IO GType
c_gtk_column_view_cell_get_type

instance B.Types.GObject ColumnViewCell

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

instance O.HasParentTypes ColumnViewCell
type instance O.ParentTypes ColumnViewCell = '[Gtk.ListItem.ListItem, GObject.Object.Object]

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveColumnViewCellMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveColumnViewCellMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveColumnViewCellMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveColumnViewCellMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveColumnViewCellMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveColumnViewCellMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveColumnViewCellMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveColumnViewCellMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveColumnViewCellMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveColumnViewCellMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveColumnViewCellMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveColumnViewCellMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveColumnViewCellMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveColumnViewCellMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveColumnViewCellMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveColumnViewCellMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveColumnViewCellMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveColumnViewCellMethod "getAccessibleDescription" o = Gtk.ListItem.ListItemGetAccessibleDescriptionMethodInfo
    ResolveColumnViewCellMethod "getAccessibleLabel" o = Gtk.ListItem.ListItemGetAccessibleLabelMethodInfo
    ResolveColumnViewCellMethod "getActivatable" o = Gtk.ListItem.ListItemGetActivatableMethodInfo
    ResolveColumnViewCellMethod "getChild" o = ColumnViewCellGetChildMethodInfo
    ResolveColumnViewCellMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveColumnViewCellMethod "getFocusable" o = ColumnViewCellGetFocusableMethodInfo
    ResolveColumnViewCellMethod "getItem" o = ColumnViewCellGetItemMethodInfo
    ResolveColumnViewCellMethod "getPosition" o = ColumnViewCellGetPositionMethodInfo
    ResolveColumnViewCellMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveColumnViewCellMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveColumnViewCellMethod "getSelectable" o = Gtk.ListItem.ListItemGetSelectableMethodInfo
    ResolveColumnViewCellMethod "getSelected" o = ColumnViewCellGetSelectedMethodInfo
    ResolveColumnViewCellMethod "setAccessibleDescription" o = Gtk.ListItem.ListItemSetAccessibleDescriptionMethodInfo
    ResolveColumnViewCellMethod "setAccessibleLabel" o = Gtk.ListItem.ListItemSetAccessibleLabelMethodInfo
    ResolveColumnViewCellMethod "setActivatable" o = Gtk.ListItem.ListItemSetActivatableMethodInfo
    ResolveColumnViewCellMethod "setChild" o = ColumnViewCellSetChildMethodInfo
    ResolveColumnViewCellMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveColumnViewCellMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveColumnViewCellMethod "setFocusable" o = ColumnViewCellSetFocusableMethodInfo
    ResolveColumnViewCellMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveColumnViewCellMethod "setSelectable" o = Gtk.ListItem.ListItemSetSelectableMethodInfo
    ResolveColumnViewCellMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveColumnViewCellMethod t ColumnViewCell, O.OverloadedMethod info ColumnViewCell p) => OL.IsLabel t (ColumnViewCell -> 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 ~ ResolveColumnViewCellMethod t ColumnViewCell, O.OverloadedMethod info ColumnViewCell p, R.HasField t ColumnViewCell p) => R.HasField t ColumnViewCell p where
    getField = O.overloadedMethod @info

#endif

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

#endif

--- XXX Duplicated object with different types:
  --- Name {namespace = "Gtk", name = "ColumnViewCell"} -> Property {propName = "child", propType = TInterface (Name {namespace = "Gtk", name = "Widget"}), propFlags = [PropertyReadable,PropertyWritable], propReadNullable = Just True, propWriteNullable = Just True, propTransfer = TransferNothing, propDoc = Documentation {rawDocText = Just "Widget used for display.", sinceVersion = Just "4.12"}, propDeprecated = Nothing}
  --- Name {namespace = "Gtk", name = "ListItem"} -> Property {propName = "child", propType = TInterface (Name {namespace = "Gtk", name = "Widget"}), propFlags = [PropertyReadable,PropertyWritable], propReadNullable = Just True, propWriteNullable = Just True, propTransfer = TransferNothing, propDoc = Documentation {rawDocText = Just "Widget used for display.", sinceVersion = Nothing}, propDeprecated = Nothing}
--- XXX Duplicated object with different types:
  --- Name {namespace = "Gtk", name = "ColumnViewCell"} -> Property {propName = "item", propType = TInterface (Name {namespace = "GObject", name = "Object"}), propFlags = [PropertyReadable], propReadNullable = Just True, propWriteNullable = Nothing, propTransfer = TransferNothing, propDoc = Documentation {rawDocText = Just "Displayed item.", sinceVersion = Just "4.12"}, propDeprecated = Nothing}
  --- Name {namespace = "Gtk", name = "ListItem"} -> Property {propName = "item", propType = TInterface (Name {namespace = "GObject", name = "Object"}), propFlags = [PropertyReadable], propReadNullable = Just True, propWriteNullable = Nothing, propTransfer = TransferNothing, propDoc = Documentation {rawDocText = Just "Displayed item.", sinceVersion = Nothing}, propDeprecated = Nothing}
--- XXX Duplicated object with different types:
  --- Name {namespace = "Gtk", name = "ColumnViewCell"} -> Property {propName = "position", propType = TBasicType TUInt, propFlags = [PropertyReadable], propReadNullable = Just False, propWriteNullable = Nothing, propTransfer = TransferNothing, propDoc = Documentation {rawDocText = Just "Position of the item.", sinceVersion = Just "4.12"}, propDeprecated = Nothing}
  --- Name {namespace = "Gtk", name = "ListItem"} -> Property {propName = "position", propType = TBasicType TUInt, propFlags = [PropertyReadable], propReadNullable = Just False, propWriteNullable = Nothing, propTransfer = TransferNothing, propDoc = Documentation {rawDocText = Just "Position of the item.", sinceVersion = Nothing}, propDeprecated = Nothing}
--- XXX Duplicated object with different types:
  --- Name {namespace = "Gtk", name = "ColumnViewCell"} -> Property {propName = "selected", propType = TBasicType TBoolean, propFlags = [PropertyReadable], propReadNullable = Just False, propWriteNullable = Nothing, propTransfer = TransferNothing, propDoc = Documentation {rawDocText = Just "If the item is currently selected.", sinceVersion = Just "4.12"}, propDeprecated = Nothing}
  --- Name {namespace = "Gtk", name = "ListItem"} -> Property {propName = "selected", propType = TBasicType TBoolean, propFlags = [PropertyReadable], propReadNullable = Just False, propWriteNullable = Nothing, propTransfer = TransferNothing, propDoc = Documentation {rawDocText = Just "If the item is currently selected.", sinceVersion = Nothing}, propDeprecated = Nothing}
-- VVV Prop "child"
   -- Type: TInterface (Name {namespace = "Gtk", name = "Widget"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just True,Just True)

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

-- | Set the value of the “@child@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' columnViewCell [ #child 'Data.GI.Base.Attributes.:=' value ]
-- @
setColumnViewCellChild :: (MonadIO m, IsColumnViewCell o, Gtk.Widget.IsWidget a) => o -> a -> m ()
setColumnViewCellChild :: forall (m :: * -> *) o a.
(MonadIO m, IsColumnViewCell o, IsWidget a) =>
o -> a -> m ()
setColumnViewCellChild 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
"child" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)

-- | Construct a `GValueConstruct` with valid value for the “@child@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructColumnViewCellChild :: (IsColumnViewCell o, MIO.MonadIO m, Gtk.Widget.IsWidget a) => a -> m (GValueConstruct o)
constructColumnViewCellChild :: forall o (m :: * -> *) a.
(IsColumnViewCell o, MonadIO m, IsWidget a) =>
a -> m (GValueConstruct o)
constructColumnViewCellChild 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
"child" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

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

#if defined(ENABLE_OVERLOADING)
data ColumnViewCellChildPropertyInfo
instance AttrInfo ColumnViewCellChildPropertyInfo where
    type AttrAllowedOps ColumnViewCellChildPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ColumnViewCellChildPropertyInfo = IsColumnViewCell
    type AttrSetTypeConstraint ColumnViewCellChildPropertyInfo = Gtk.Widget.IsWidget
    type AttrTransferTypeConstraint ColumnViewCellChildPropertyInfo = Gtk.Widget.IsWidget
    type AttrTransferType ColumnViewCellChildPropertyInfo = Gtk.Widget.Widget
    type AttrGetType ColumnViewCellChildPropertyInfo = (Maybe Gtk.Widget.Widget)
    type AttrLabel ColumnViewCellChildPropertyInfo = "child"
    type AttrOrigin ColumnViewCellChildPropertyInfo = ColumnViewCell
    attrGet = getColumnViewCellChild
    attrSet = setColumnViewCellChild
    attrTransfer _ v = do
        unsafeCastTo Gtk.Widget.Widget v
    attrConstruct = constructColumnViewCellChild
    attrClear = clearColumnViewCellChild
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.ColumnViewCell.child"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.9/docs/GI-Gtk-Objects-ColumnViewCell.html#g:attr:child"
        })
#endif

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

-- | Get the value of the “@focusable@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' columnViewCell #focusable
-- @
getColumnViewCellFocusable :: (MonadIO m, IsColumnViewCell o) => o -> m Bool
getColumnViewCellFocusable :: forall (m :: * -> *) o.
(MonadIO m, IsColumnViewCell o) =>
o -> m Bool
getColumnViewCellFocusable 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
"focusable"

-- | Set the value of the “@focusable@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' columnViewCell [ #focusable 'Data.GI.Base.Attributes.:=' value ]
-- @
setColumnViewCellFocusable :: (MonadIO m, IsColumnViewCell o) => o -> Bool -> m ()
setColumnViewCellFocusable :: forall (m :: * -> *) o.
(MonadIO m, IsColumnViewCell o) =>
o -> Bool -> m ()
setColumnViewCellFocusable 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
"focusable" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@focusable@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructColumnViewCellFocusable :: (IsColumnViewCell o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructColumnViewCellFocusable :: forall o (m :: * -> *).
(IsColumnViewCell o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructColumnViewCellFocusable 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
"focusable" Bool
val

#if defined(ENABLE_OVERLOADING)
data ColumnViewCellFocusablePropertyInfo
instance AttrInfo ColumnViewCellFocusablePropertyInfo where
    type AttrAllowedOps ColumnViewCellFocusablePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint ColumnViewCellFocusablePropertyInfo = IsColumnViewCell
    type AttrSetTypeConstraint ColumnViewCellFocusablePropertyInfo = (~) Bool
    type AttrTransferTypeConstraint ColumnViewCellFocusablePropertyInfo = (~) Bool
    type AttrTransferType ColumnViewCellFocusablePropertyInfo = Bool
    type AttrGetType ColumnViewCellFocusablePropertyInfo = Bool
    type AttrLabel ColumnViewCellFocusablePropertyInfo = "focusable"
    type AttrOrigin ColumnViewCellFocusablePropertyInfo = ColumnViewCell
    attrGet = getColumnViewCellFocusable
    attrSet = setColumnViewCellFocusable
    attrTransfer _ v = do
        return v
    attrConstruct = constructColumnViewCellFocusable
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.ColumnViewCell.focusable"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.9/docs/GI-Gtk-Objects-ColumnViewCell.html#g:attr:focusable"
        })
#endif

-- VVV Prop "item"
   -- Type: TInterface (Name {namespace = "GObject", name = "Object"})
   -- Flags: [PropertyReadable]
   -- Nullable: (Just True,Nothing)

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

#if defined(ENABLE_OVERLOADING)
data ColumnViewCellItemPropertyInfo
instance AttrInfo ColumnViewCellItemPropertyInfo where
    type AttrAllowedOps ColumnViewCellItemPropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ColumnViewCellItemPropertyInfo = IsColumnViewCell
    type AttrSetTypeConstraint ColumnViewCellItemPropertyInfo = (~) ()
    type AttrTransferTypeConstraint ColumnViewCellItemPropertyInfo = (~) ()
    type AttrTransferType ColumnViewCellItemPropertyInfo = ()
    type AttrGetType ColumnViewCellItemPropertyInfo = (Maybe GObject.Object.Object)
    type AttrLabel ColumnViewCellItemPropertyInfo = "item"
    type AttrOrigin ColumnViewCellItemPropertyInfo = ColumnViewCell
    attrGet = getColumnViewCellItem
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.ColumnViewCell.item"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.9/docs/GI-Gtk-Objects-ColumnViewCell.html#g:attr:item"
        })
#endif

-- VVV Prop "position"
   -- Type: TBasicType TUInt
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

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

#if defined(ENABLE_OVERLOADING)
data ColumnViewCellPositionPropertyInfo
instance AttrInfo ColumnViewCellPositionPropertyInfo where
    type AttrAllowedOps ColumnViewCellPositionPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint ColumnViewCellPositionPropertyInfo = IsColumnViewCell
    type AttrSetTypeConstraint ColumnViewCellPositionPropertyInfo = (~) ()
    type AttrTransferTypeConstraint ColumnViewCellPositionPropertyInfo = (~) ()
    type AttrTransferType ColumnViewCellPositionPropertyInfo = ()
    type AttrGetType ColumnViewCellPositionPropertyInfo = Word32
    type AttrLabel ColumnViewCellPositionPropertyInfo = "position"
    type AttrOrigin ColumnViewCellPositionPropertyInfo = ColumnViewCell
    attrGet = getColumnViewCellPosition
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.ColumnViewCell.position"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.9/docs/GI-Gtk-Objects-ColumnViewCell.html#g:attr:position"
        })
#endif

-- VVV Prop "selected"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@selected@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' columnViewCell #selected
-- @
getColumnViewCellSelected :: (MonadIO m, IsColumnViewCell o) => o -> m Bool
getColumnViewCellSelected :: forall (m :: * -> *) o.
(MonadIO m, IsColumnViewCell o) =>
o -> m Bool
getColumnViewCellSelected 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
"selected"

#if defined(ENABLE_OVERLOADING)
data ColumnViewCellSelectedPropertyInfo
instance AttrInfo ColumnViewCellSelectedPropertyInfo where
    type AttrAllowedOps ColumnViewCellSelectedPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint ColumnViewCellSelectedPropertyInfo = IsColumnViewCell
    type AttrSetTypeConstraint ColumnViewCellSelectedPropertyInfo = (~) ()
    type AttrTransferTypeConstraint ColumnViewCellSelectedPropertyInfo = (~) ()
    type AttrTransferType ColumnViewCellSelectedPropertyInfo = ()
    type AttrGetType ColumnViewCellSelectedPropertyInfo = Bool
    type AttrLabel ColumnViewCellSelectedPropertyInfo = "selected"
    type AttrOrigin ColumnViewCellSelectedPropertyInfo = ColumnViewCell
    attrGet = getColumnViewCellSelected
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.ColumnViewCell.selected"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.9/docs/GI-Gtk-Objects-ColumnViewCell.html#g:attr:selected"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList ColumnViewCell
type instance O.AttributeList ColumnViewCell = ColumnViewCellAttributeList
type ColumnViewCellAttributeList = ('[ '("accessibleDescription", Gtk.ListItem.ListItemAccessibleDescriptionPropertyInfo), '("accessibleLabel", Gtk.ListItem.ListItemAccessibleLabelPropertyInfo), '("activatable", Gtk.ListItem.ListItemActivatablePropertyInfo), '("child", ColumnViewCellChildPropertyInfo), '("focusable", ColumnViewCellFocusablePropertyInfo), '("item", ColumnViewCellItemPropertyInfo), '("position", ColumnViewCellPositionPropertyInfo), '("selectable", Gtk.ListItem.ListItemSelectablePropertyInfo), '("selected", ColumnViewCellSelectedPropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
columnViewCellChild :: AttrLabelProxy "child"
columnViewCellChild = AttrLabelProxy

columnViewCellFocusable :: AttrLabelProxy "focusable"
columnViewCellFocusable = AttrLabelProxy

columnViewCellItem :: AttrLabelProxy "item"
columnViewCellItem = AttrLabelProxy

columnViewCellPosition :: AttrLabelProxy "position"
columnViewCellPosition = AttrLabelProxy

columnViewCellSelected :: AttrLabelProxy "selected"
columnViewCellSelected = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList ColumnViewCell = ColumnViewCellSignalList
type ColumnViewCellSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])

#endif

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

foreign import ccall "gtk_column_view_cell_get_child" gtk_column_view_cell_get_child :: 
    Ptr ColumnViewCell ->                   -- self : TInterface (Name {namespace = "Gtk", name = "ColumnViewCell"})
    IO (Ptr Gtk.Widget.Widget)

-- | Gets the child previously set via 'GI.Gtk.Objects.ColumnViewCell.columnViewCellSetChild' or
-- 'P.Nothing' if none was set.
-- 
-- /Since: 4.12/
columnViewCellGetChild ::
    (B.CallStack.HasCallStack, MonadIO m, IsColumnViewCell a) =>
    a
    -- ^ /@self@/: a @GtkColumnViewCell@
    -> m (Maybe Gtk.Widget.Widget)
    -- ^ __Returns:__ The child
columnViewCellGetChild :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsColumnViewCell a) =>
a -> m (Maybe Widget)
columnViewCellGetChild a
self = IO (Maybe Widget) -> m (Maybe Widget)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Widget) -> m (Maybe Widget))
-> IO (Maybe Widget) -> m (Maybe Widget)
forall a b. (a -> b) -> a -> b
$ do
    Ptr ColumnViewCell
self' <- a -> IO (Ptr ColumnViewCell)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Widget
result <- Ptr ColumnViewCell -> IO (Ptr Widget)
gtk_column_view_cell_get_child Ptr ColumnViewCell
self'
    Maybe Widget
maybeResult <- Ptr Widget -> (Ptr Widget -> IO Widget) -> IO (Maybe Widget)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Widget
result ((Ptr Widget -> IO Widget) -> IO (Maybe Widget))
-> (Ptr Widget -> IO Widget) -> IO (Maybe Widget)
forall a b. (a -> b) -> a -> b
$ \Ptr Widget
result' -> do
        Widget
result'' <- ((ManagedPtr Widget -> Widget) -> Ptr Widget -> IO Widget
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Widget -> Widget
Gtk.Widget.Widget) Ptr Widget
result'
        Widget -> IO Widget
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Widget
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe Widget -> IO (Maybe Widget)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Widget
maybeResult

#if defined(ENABLE_OVERLOADING)
data ColumnViewCellGetChildMethodInfo
instance (signature ~ (m (Maybe Gtk.Widget.Widget)), MonadIO m, IsColumnViewCell a) => O.OverloadedMethod ColumnViewCellGetChildMethodInfo a signature where
    overloadedMethod = columnViewCellGetChild

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


#endif

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

foreign import ccall "gtk_column_view_cell_get_focusable" gtk_column_view_cell_get_focusable :: 
    Ptr ColumnViewCell ->                   -- self : TInterface (Name {namespace = "Gtk", name = "ColumnViewCell"})
    IO CInt

-- | Checks if a list item has been set to be focusable via
-- 'GI.Gtk.Objects.ColumnViewCell.columnViewCellSetFocusable'.
-- 
-- /Since: 4.12/
columnViewCellGetFocusable ::
    (B.CallStack.HasCallStack, MonadIO m, IsColumnViewCell a) =>
    a
    -- ^ /@self@/: a @GtkColumnViewCell@
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the item is focusable
columnViewCellGetFocusable :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsColumnViewCell a) =>
a -> m Bool
columnViewCellGetFocusable a
self = 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 ColumnViewCell
self' <- a -> IO (Ptr ColumnViewCell)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CInt
result <- Ptr ColumnViewCell -> IO CInt
gtk_column_view_cell_get_focusable Ptr ColumnViewCell
self'
    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
self
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data ColumnViewCellGetFocusableMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsColumnViewCell a) => O.OverloadedMethod ColumnViewCellGetFocusableMethodInfo a signature where
    overloadedMethod = columnViewCellGetFocusable

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


#endif

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

foreign import ccall "gtk_column_view_cell_get_item" gtk_column_view_cell_get_item :: 
    Ptr ColumnViewCell ->                   -- self : TInterface (Name {namespace = "Gtk", name = "ColumnViewCell"})
    IO (Ptr GObject.Object.Object)

-- | Gets the model item that associated with /@self@/.
-- 
-- If /@self@/ is unbound, this function returns 'P.Nothing'.
-- 
-- /Since: 4.12/
columnViewCellGetItem ::
    (B.CallStack.HasCallStack, MonadIO m, IsColumnViewCell a) =>
    a
    -- ^ /@self@/: a @GtkColumnViewCell@
    -> m (Maybe GObject.Object.Object)
    -- ^ __Returns:__ The item displayed
columnViewCellGetItem :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsColumnViewCell a) =>
a -> m (Maybe Object)
columnViewCellGetItem a
self = IO (Maybe Object) -> m (Maybe Object)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Object) -> m (Maybe Object))
-> IO (Maybe Object) -> m (Maybe Object)
forall a b. (a -> b) -> a -> b
$ do
    Ptr ColumnViewCell
self' <- a -> IO (Ptr ColumnViewCell)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Object
result <- Ptr ColumnViewCell -> IO (Ptr Object)
gtk_column_view_cell_get_item Ptr ColumnViewCell
self'
    Maybe Object
maybeResult <- Ptr Object -> (Ptr Object -> IO Object) -> IO (Maybe Object)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Object
result ((Ptr Object -> IO Object) -> IO (Maybe Object))
-> (Ptr Object -> IO Object) -> IO (Maybe Object)
forall a b. (a -> b) -> a -> b
$ \Ptr Object
result' -> do
        Object
result'' <- ((ManagedPtr Object -> Object) -> Ptr Object -> IO Object
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Object -> Object
GObject.Object.Object) Ptr Object
result'
        Object -> IO Object
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Object
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe Object -> IO (Maybe Object)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Object
maybeResult

#if defined(ENABLE_OVERLOADING)
data ColumnViewCellGetItemMethodInfo
instance (signature ~ (m (Maybe GObject.Object.Object)), MonadIO m, IsColumnViewCell a) => O.OverloadedMethod ColumnViewCellGetItemMethodInfo a signature where
    overloadedMethod = columnViewCellGetItem

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


#endif

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

foreign import ccall "gtk_column_view_cell_get_position" gtk_column_view_cell_get_position :: 
    Ptr ColumnViewCell ->                   -- self : TInterface (Name {namespace = "Gtk", name = "ColumnViewCell"})
    IO Word32

-- | Gets the position in the model that /@self@/ currently displays.
-- 
-- If /@self@/ is unbound, 'GI.Gtk.Constants.INVALID_LIST_POSITION' is returned.
-- 
-- /Since: 4.12/
columnViewCellGetPosition ::
    (B.CallStack.HasCallStack, MonadIO m, IsColumnViewCell a) =>
    a
    -- ^ /@self@/: a @GtkColumnViewCell@
    -> m Word32
    -- ^ __Returns:__ The position of this item
columnViewCellGetPosition :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsColumnViewCell a) =>
a -> m Word32
columnViewCellGetPosition a
self = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr ColumnViewCell
self' <- a -> IO (Ptr ColumnViewCell)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Word32
result <- Ptr ColumnViewCell -> IO Word32
gtk_column_view_cell_get_position Ptr ColumnViewCell
self'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data ColumnViewCellGetPositionMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsColumnViewCell a) => O.OverloadedMethod ColumnViewCellGetPositionMethodInfo a signature where
    overloadedMethod = columnViewCellGetPosition

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


#endif

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

foreign import ccall "gtk_column_view_cell_get_selected" gtk_column_view_cell_get_selected :: 
    Ptr ColumnViewCell ->                   -- self : TInterface (Name {namespace = "Gtk", name = "ColumnViewCell"})
    IO CInt

-- | Checks if the item is displayed as selected.
-- 
-- The selected state is maintained by the liste widget and its model
-- and cannot be set otherwise.
-- 
-- /Since: 4.12/
columnViewCellGetSelected ::
    (B.CallStack.HasCallStack, MonadIO m, IsColumnViewCell a) =>
    a
    -- ^ /@self@/: a @GtkColumnViewCell@
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the item is selected.
columnViewCellGetSelected :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsColumnViewCell a) =>
a -> m Bool
columnViewCellGetSelected a
self = 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 ColumnViewCell
self' <- a -> IO (Ptr ColumnViewCell)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CInt
result <- Ptr ColumnViewCell -> IO CInt
gtk_column_view_cell_get_selected Ptr ColumnViewCell
self'
    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
self
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data ColumnViewCellGetSelectedMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsColumnViewCell a) => O.OverloadedMethod ColumnViewCellGetSelectedMethodInfo a signature where
    overloadedMethod = columnViewCellGetSelected

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


#endif

-- method ColumnViewCell::set_child
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ColumnViewCell" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkColumnViewCell`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "child"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Widget" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The list item's child or %NULL to unset"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_column_view_cell_set_child" gtk_column_view_cell_set_child :: 
    Ptr ColumnViewCell ->                   -- self : TInterface (Name {namespace = "Gtk", name = "ColumnViewCell"})
    Ptr Gtk.Widget.Widget ->                -- child : TInterface (Name {namespace = "Gtk", name = "Widget"})
    IO ()

-- | Sets the child to be used for this listitem.
-- 
-- This function is typically called by applications when
-- setting up a listitem so that the widget can be reused when
-- binding it multiple times.
-- 
-- /Since: 4.12/
columnViewCellSetChild ::
    (B.CallStack.HasCallStack, MonadIO m, IsColumnViewCell a, Gtk.Widget.IsWidget b) =>
    a
    -- ^ /@self@/: a @GtkColumnViewCell@
    -> Maybe (b)
    -- ^ /@child@/: The list item\'s child or 'P.Nothing' to unset
    -> m ()
columnViewCellSetChild :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsColumnViewCell a, IsWidget b) =>
a -> Maybe b -> m ()
columnViewCellSetChild a
self Maybe b
child = 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 ColumnViewCell
self' <- a -> IO (Ptr ColumnViewCell)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Widget
maybeChild <- case Maybe b
child of
        Maybe b
Nothing -> Ptr Widget -> IO (Ptr Widget)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Widget
forall a. Ptr a
nullPtr
        Just b
jChild -> do
            Ptr Widget
jChild' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jChild
            Ptr Widget -> IO (Ptr Widget)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Widget
jChild'
    Ptr ColumnViewCell -> Ptr Widget -> IO ()
gtk_column_view_cell_set_child Ptr ColumnViewCell
self' Ptr Widget
maybeChild
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
child 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 ColumnViewCellSetChildMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsColumnViewCell a, Gtk.Widget.IsWidget b) => O.OverloadedMethod ColumnViewCellSetChildMethodInfo a signature where
    overloadedMethod = columnViewCellSetChild

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


#endif

-- method ColumnViewCell::set_focusable
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ColumnViewCell" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkColumnViewCell`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "focusable"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "if the item should be focusable"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_column_view_cell_set_focusable" gtk_column_view_cell_set_focusable :: 
    Ptr ColumnViewCell ->                   -- self : TInterface (Name {namespace = "Gtk", name = "ColumnViewCell"})
    CInt ->                                 -- focusable : TBasicType TBoolean
    IO ()

-- | Sets /@self@/ to be focusable.
-- 
-- If an item is focusable, it can be focused using the keyboard.
-- This works similar to 'GI.Gtk.Objects.Widget.widgetSetFocusable'.
-- 
-- Note that if items are not focusable, the keyboard cannot be used to activate
-- them and selecting only works if one of the listitem\'s children is focusable.
-- 
-- By default, list items are focusable.
-- 
-- /Since: 4.12/
columnViewCellSetFocusable ::
    (B.CallStack.HasCallStack, MonadIO m, IsColumnViewCell a) =>
    a
    -- ^ /@self@/: a @GtkColumnViewCell@
    -> Bool
    -- ^ /@focusable@/: if the item should be focusable
    -> m ()
columnViewCellSetFocusable :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsColumnViewCell a) =>
a -> Bool -> m ()
columnViewCellSetFocusable a
self Bool
focusable = 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 ColumnViewCell
self' <- a -> IO (Ptr ColumnViewCell)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    let focusable' :: CInt
focusable' = (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
focusable
    Ptr ColumnViewCell -> CInt -> IO ()
gtk_column_view_cell_set_focusable Ptr ColumnViewCell
self' CInt
focusable'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ColumnViewCellSetFocusableMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsColumnViewCell a) => O.OverloadedMethod ColumnViewCellSetFocusableMethodInfo a signature where
    overloadedMethod = columnViewCellSetFocusable

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


#endif