{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- @GtkColumnViewRow@ is used by t'GI.Gtk.Objects.ColumnView.ColumnView' to allow configuring
-- how rows are displayed.
-- 
-- It is not used to set the widgets displayed in the individual cells. For that
-- see [method/@gtkColumnViewColumn@/.set_factory] and [class/@gtkColumnViewCell@/].
-- 
-- /Since: 4.12/

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

module GI.Gtk.Objects.ColumnViewRow
    ( 

-- * Exported types
    ColumnViewRow(..)                       ,
    IsColumnViewRow                         ,
    toColumnViewRow                         ,


 -- * 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.ColumnViewRow#g:method:getAccessibleDescription"), [getAccessibleLabel]("GI.Gtk.Objects.ColumnViewRow#g:method:getAccessibleLabel"), [getActivatable]("GI.Gtk.Objects.ColumnViewRow#g:method:getActivatable"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getFocusable]("GI.Gtk.Objects.ColumnViewRow#g:method:getFocusable"), [getItem]("GI.Gtk.Objects.ColumnViewRow#g:method:getItem"), [getPosition]("GI.Gtk.Objects.ColumnViewRow#g:method:getPosition"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getSelectable]("GI.Gtk.Objects.ColumnViewRow#g:method:getSelectable"), [getSelected]("GI.Gtk.Objects.ColumnViewRow#g:method:getSelected").
-- 
-- ==== Setters
-- [setAccessibleDescription]("GI.Gtk.Objects.ColumnViewRow#g:method:setAccessibleDescription"), [setAccessibleLabel]("GI.Gtk.Objects.ColumnViewRow#g:method:setAccessibleLabel"), [setActivatable]("GI.Gtk.Objects.ColumnViewRow#g:method:setActivatable"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setFocusable]("GI.Gtk.Objects.ColumnViewRow#g:method:setFocusable"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setSelectable]("GI.Gtk.Objects.ColumnViewRow#g:method:setSelectable").

#if defined(ENABLE_OVERLOADING)
    ResolveColumnViewRowMethod              ,
#endif

-- ** getAccessibleDescription #method:getAccessibleDescription#

#if defined(ENABLE_OVERLOADING)
    ColumnViewRowGetAccessibleDescriptionMethodInfo,
#endif
    columnViewRowGetAccessibleDescription   ,


-- ** getAccessibleLabel #method:getAccessibleLabel#

#if defined(ENABLE_OVERLOADING)
    ColumnViewRowGetAccessibleLabelMethodInfo,
#endif
    columnViewRowGetAccessibleLabel         ,


-- ** getActivatable #method:getActivatable#

#if defined(ENABLE_OVERLOADING)
    ColumnViewRowGetActivatableMethodInfo   ,
#endif
    columnViewRowGetActivatable             ,


-- ** getFocusable #method:getFocusable#

#if defined(ENABLE_OVERLOADING)
    ColumnViewRowGetFocusableMethodInfo     ,
#endif
    columnViewRowGetFocusable               ,


-- ** getItem #method:getItem#

#if defined(ENABLE_OVERLOADING)
    ColumnViewRowGetItemMethodInfo          ,
#endif
    columnViewRowGetItem                    ,


-- ** getPosition #method:getPosition#

#if defined(ENABLE_OVERLOADING)
    ColumnViewRowGetPositionMethodInfo      ,
#endif
    columnViewRowGetPosition                ,


-- ** getSelectable #method:getSelectable#

#if defined(ENABLE_OVERLOADING)
    ColumnViewRowGetSelectableMethodInfo    ,
#endif
    columnViewRowGetSelectable              ,


-- ** getSelected #method:getSelected#

#if defined(ENABLE_OVERLOADING)
    ColumnViewRowGetSelectedMethodInfo      ,
#endif
    columnViewRowGetSelected                ,


-- ** setAccessibleDescription #method:setAccessibleDescription#

#if defined(ENABLE_OVERLOADING)
    ColumnViewRowSetAccessibleDescriptionMethodInfo,
#endif
    columnViewRowSetAccessibleDescription   ,


-- ** setAccessibleLabel #method:setAccessibleLabel#

#if defined(ENABLE_OVERLOADING)
    ColumnViewRowSetAccessibleLabelMethodInfo,
#endif
    columnViewRowSetAccessibleLabel         ,


-- ** setActivatable #method:setActivatable#

#if defined(ENABLE_OVERLOADING)
    ColumnViewRowSetActivatableMethodInfo   ,
#endif
    columnViewRowSetActivatable             ,


-- ** setFocusable #method:setFocusable#

#if defined(ENABLE_OVERLOADING)
    ColumnViewRowSetFocusableMethodInfo     ,
#endif
    columnViewRowSetFocusable               ,


-- ** setSelectable #method:setSelectable#

#if defined(ENABLE_OVERLOADING)
    ColumnViewRowSetSelectableMethodInfo    ,
#endif
    columnViewRowSetSelectable              ,




 -- * Properties


-- ** accessibleDescription #attr:accessibleDescription#
-- | The accessible description to set on the row.
-- 
-- /Since: 4.12/

#if defined(ENABLE_OVERLOADING)
    ColumnViewRowAccessibleDescriptionPropertyInfo,
#endif
#if defined(ENABLE_OVERLOADING)
    columnViewRowAccessibleDescription      ,
#endif
    constructColumnViewRowAccessibleDescription,
    getColumnViewRowAccessibleDescription   ,
    setColumnViewRowAccessibleDescription   ,


-- ** accessibleLabel #attr:accessibleLabel#
-- | The accessible label to set on the row.
-- 
-- /Since: 4.12/

#if defined(ENABLE_OVERLOADING)
    ColumnViewRowAccessibleLabelPropertyInfo,
#endif
#if defined(ENABLE_OVERLOADING)
    columnViewRowAccessibleLabel            ,
#endif
    constructColumnViewRowAccessibleLabel   ,
    getColumnViewRowAccessibleLabel         ,
    setColumnViewRowAccessibleLabel         ,


-- ** activatable #attr:activatable#
-- | If the row can be activated by the user.
-- 
-- /Since: 4.12/

#if defined(ENABLE_OVERLOADING)
    ColumnViewRowActivatablePropertyInfo    ,
#endif
#if defined(ENABLE_OVERLOADING)
    columnViewRowActivatable                ,
#endif
    constructColumnViewRowActivatable       ,
    getColumnViewRowActivatable             ,
    setColumnViewRowActivatable             ,


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

#if defined(ENABLE_OVERLOADING)
    ColumnViewRowFocusablePropertyInfo      ,
#endif
#if defined(ENABLE_OVERLOADING)
    columnViewRowFocusable                  ,
#endif
    constructColumnViewRowFocusable         ,
    getColumnViewRowFocusable               ,
    setColumnViewRowFocusable               ,


-- ** item #attr:item#
-- | The item for this row.
-- 
-- /Since: 4.12/

#if defined(ENABLE_OVERLOADING)
    ColumnViewRowItemPropertyInfo           ,
#endif
#if defined(ENABLE_OVERLOADING)
    columnViewRowItem                       ,
#endif
    getColumnViewRowItem                    ,


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

#if defined(ENABLE_OVERLOADING)
    ColumnViewRowPositionPropertyInfo       ,
#endif
#if defined(ENABLE_OVERLOADING)
    columnViewRowPosition                   ,
#endif
    getColumnViewRowPosition                ,


-- ** selectable #attr:selectable#
-- | If the row can be selected by the user.
-- 
-- /Since: 4.12/

#if defined(ENABLE_OVERLOADING)
    ColumnViewRowSelectablePropertyInfo     ,
#endif
#if defined(ENABLE_OVERLOADING)
    columnViewRowSelectable                 ,
#endif
    constructColumnViewRowSelectable        ,
    getColumnViewRowSelectable              ,
    setColumnViewRowSelectable              ,


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

#if defined(ENABLE_OVERLOADING)
    ColumnViewRowSelectedPropertyInfo       ,
#endif
#if defined(ENABLE_OVERLOADING)
    columnViewRowSelected                   ,
#endif
    getColumnViewRowSelected                ,




    ) 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.GObject.Objects.Object as GObject.Object

#else
import qualified GI.GObject.Objects.Object as GObject.Object

#endif

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

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

foreign import ccall "gtk_column_view_row_get_type"
    c_gtk_column_view_row_get_type :: IO B.Types.GType

instance B.Types.TypedObject ColumnViewRow where
    glibType :: IO GType
glibType = IO GType
c_gtk_column_view_row_get_type

instance B.Types.GObject ColumnViewRow

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

instance O.HasParentTypes ColumnViewRow
type instance O.ParentTypes ColumnViewRow = '[GObject.Object.Object]

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

-- | Convert 'ColumnViewRow' 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 ColumnViewRow) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gtk_column_view_row_get_type
    gvalueSet_ :: Ptr GValue -> Maybe ColumnViewRow -> IO ()
gvalueSet_ Ptr GValue
gv Maybe ColumnViewRow
P.Nothing = Ptr GValue -> Ptr ColumnViewRow -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr ColumnViewRow
forall a. Ptr a
FP.nullPtr :: FP.Ptr ColumnViewRow)
    gvalueSet_ Ptr GValue
gv (P.Just ColumnViewRow
obj) = ColumnViewRow -> (Ptr ColumnViewRow -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr ColumnViewRow
obj (Ptr GValue -> Ptr ColumnViewRow -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe ColumnViewRow)
gvalueGet_ Ptr GValue
gv = do
        Ptr ColumnViewRow
ptr <- Ptr GValue -> IO (Ptr ColumnViewRow)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr ColumnViewRow)
        if Ptr ColumnViewRow
ptr Ptr ColumnViewRow -> Ptr ColumnViewRow -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr ColumnViewRow
forall a. Ptr a
FP.nullPtr
        then ColumnViewRow -> Maybe ColumnViewRow
forall a. a -> Maybe a
P.Just (ColumnViewRow -> Maybe ColumnViewRow)
-> IO ColumnViewRow -> IO (Maybe ColumnViewRow)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr ColumnViewRow -> ColumnViewRow)
-> Ptr ColumnViewRow -> IO ColumnViewRow
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr ColumnViewRow -> ColumnViewRow
ColumnViewRow Ptr ColumnViewRow
ptr
        else Maybe ColumnViewRow -> IO (Maybe ColumnViewRow)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ColumnViewRow
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveColumnViewRowMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveColumnViewRowMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveColumnViewRowMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveColumnViewRowMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveColumnViewRowMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveColumnViewRowMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveColumnViewRowMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveColumnViewRowMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveColumnViewRowMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveColumnViewRowMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveColumnViewRowMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveColumnViewRowMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveColumnViewRowMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveColumnViewRowMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveColumnViewRowMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveColumnViewRowMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveColumnViewRowMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveColumnViewRowMethod "getAccessibleDescription" o = ColumnViewRowGetAccessibleDescriptionMethodInfo
    ResolveColumnViewRowMethod "getAccessibleLabel" o = ColumnViewRowGetAccessibleLabelMethodInfo
    ResolveColumnViewRowMethod "getActivatable" o = ColumnViewRowGetActivatableMethodInfo
    ResolveColumnViewRowMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveColumnViewRowMethod "getFocusable" o = ColumnViewRowGetFocusableMethodInfo
    ResolveColumnViewRowMethod "getItem" o = ColumnViewRowGetItemMethodInfo
    ResolveColumnViewRowMethod "getPosition" o = ColumnViewRowGetPositionMethodInfo
    ResolveColumnViewRowMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveColumnViewRowMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveColumnViewRowMethod "getSelectable" o = ColumnViewRowGetSelectableMethodInfo
    ResolveColumnViewRowMethod "getSelected" o = ColumnViewRowGetSelectedMethodInfo
    ResolveColumnViewRowMethod "setAccessibleDescription" o = ColumnViewRowSetAccessibleDescriptionMethodInfo
    ResolveColumnViewRowMethod "setAccessibleLabel" o = ColumnViewRowSetAccessibleLabelMethodInfo
    ResolveColumnViewRowMethod "setActivatable" o = ColumnViewRowSetActivatableMethodInfo
    ResolveColumnViewRowMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveColumnViewRowMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveColumnViewRowMethod "setFocusable" o = ColumnViewRowSetFocusableMethodInfo
    ResolveColumnViewRowMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveColumnViewRowMethod "setSelectable" o = ColumnViewRowSetSelectableMethodInfo
    ResolveColumnViewRowMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

-- VVV Prop "accessible-description"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@accessible-description@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' columnViewRow #accessibleDescription
-- @
getColumnViewRowAccessibleDescription :: (MonadIO m, IsColumnViewRow o) => o -> m T.Text
getColumnViewRowAccessibleDescription :: forall (m :: * -> *) o.
(MonadIO m, IsColumnViewRow o) =>
o -> m Text
getColumnViewRowAccessibleDescription o
obj = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getColumnViewRowAccessibleDescription" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"accessible-description"

-- | Set the value of the “@accessible-description@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' columnViewRow [ #accessibleDescription 'Data.GI.Base.Attributes.:=' value ]
-- @
setColumnViewRowAccessibleDescription :: (MonadIO m, IsColumnViewRow o) => o -> T.Text -> m ()
setColumnViewRowAccessibleDescription :: forall (m :: * -> *) o.
(MonadIO m, IsColumnViewRow o) =>
o -> Text -> m ()
setColumnViewRowAccessibleDescription 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
"accessible-description" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

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

#if defined(ENABLE_OVERLOADING)
data ColumnViewRowAccessibleDescriptionPropertyInfo
instance AttrInfo ColumnViewRowAccessibleDescriptionPropertyInfo where
    type AttrAllowedOps ColumnViewRowAccessibleDescriptionPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint ColumnViewRowAccessibleDescriptionPropertyInfo = IsColumnViewRow
    type AttrSetTypeConstraint ColumnViewRowAccessibleDescriptionPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint ColumnViewRowAccessibleDescriptionPropertyInfo = (~) T.Text
    type AttrTransferType ColumnViewRowAccessibleDescriptionPropertyInfo = T.Text
    type AttrGetType ColumnViewRowAccessibleDescriptionPropertyInfo = T.Text
    type AttrLabel ColumnViewRowAccessibleDescriptionPropertyInfo = "accessible-description"
    type AttrOrigin ColumnViewRowAccessibleDescriptionPropertyInfo = ColumnViewRow
    attrGet = getColumnViewRowAccessibleDescription
    attrSet = setColumnViewRowAccessibleDescription
    attrTransfer _ v = do
        return v
    attrConstruct = constructColumnViewRowAccessibleDescription
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.ColumnViewRow.accessibleDescription"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.9/docs/GI-Gtk-Objects-ColumnViewRow.html#g:attr:accessibleDescription"
        })
#endif

-- VVV Prop "accessible-label"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@accessible-label@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' columnViewRow #accessibleLabel
-- @
getColumnViewRowAccessibleLabel :: (MonadIO m, IsColumnViewRow o) => o -> m T.Text
getColumnViewRowAccessibleLabel :: forall (m :: * -> *) o.
(MonadIO m, IsColumnViewRow o) =>
o -> m Text
getColumnViewRowAccessibleLabel o
obj = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getColumnViewRowAccessibleLabel" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"accessible-label"

-- | Set the value of the “@accessible-label@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' columnViewRow [ #accessibleLabel 'Data.GI.Base.Attributes.:=' value ]
-- @
setColumnViewRowAccessibleLabel :: (MonadIO m, IsColumnViewRow o) => o -> T.Text -> m ()
setColumnViewRowAccessibleLabel :: forall (m :: * -> *) o.
(MonadIO m, IsColumnViewRow o) =>
o -> Text -> m ()
setColumnViewRowAccessibleLabel 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
"accessible-label" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

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

#if defined(ENABLE_OVERLOADING)
data ColumnViewRowAccessibleLabelPropertyInfo
instance AttrInfo ColumnViewRowAccessibleLabelPropertyInfo where
    type AttrAllowedOps ColumnViewRowAccessibleLabelPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint ColumnViewRowAccessibleLabelPropertyInfo = IsColumnViewRow
    type AttrSetTypeConstraint ColumnViewRowAccessibleLabelPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint ColumnViewRowAccessibleLabelPropertyInfo = (~) T.Text
    type AttrTransferType ColumnViewRowAccessibleLabelPropertyInfo = T.Text
    type AttrGetType ColumnViewRowAccessibleLabelPropertyInfo = T.Text
    type AttrLabel ColumnViewRowAccessibleLabelPropertyInfo = "accessible-label"
    type AttrOrigin ColumnViewRowAccessibleLabelPropertyInfo = ColumnViewRow
    attrGet = getColumnViewRowAccessibleLabel
    attrSet = setColumnViewRowAccessibleLabel
    attrTransfer _ v = do
        return v
    attrConstruct = constructColumnViewRowAccessibleLabel
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.ColumnViewRow.accessibleLabel"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.9/docs/GI-Gtk-Objects-ColumnViewRow.html#g:attr:accessibleLabel"
        })
#endif

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

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

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

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

#if defined(ENABLE_OVERLOADING)
data ColumnViewRowActivatablePropertyInfo
instance AttrInfo ColumnViewRowActivatablePropertyInfo where
    type AttrAllowedOps ColumnViewRowActivatablePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint ColumnViewRowActivatablePropertyInfo = IsColumnViewRow
    type AttrSetTypeConstraint ColumnViewRowActivatablePropertyInfo = (~) Bool
    type AttrTransferTypeConstraint ColumnViewRowActivatablePropertyInfo = (~) Bool
    type AttrTransferType ColumnViewRowActivatablePropertyInfo = Bool
    type AttrGetType ColumnViewRowActivatablePropertyInfo = Bool
    type AttrLabel ColumnViewRowActivatablePropertyInfo = "activatable"
    type AttrOrigin ColumnViewRowActivatablePropertyInfo = ColumnViewRow
    attrGet = getColumnViewRowActivatable
    attrSet = setColumnViewRowActivatable
    attrTransfer _ v = do
        return v
    attrConstruct = constructColumnViewRowActivatable
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.ColumnViewRow.activatable"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.9/docs/GI-Gtk-Objects-ColumnViewRow.html#g:attr:activatable"
        })
#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' columnViewRow #focusable
-- @
getColumnViewRowFocusable :: (MonadIO m, IsColumnViewRow o) => o -> m Bool
getColumnViewRowFocusable :: forall (m :: * -> *) o.
(MonadIO m, IsColumnViewRow o) =>
o -> m Bool
getColumnViewRowFocusable 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' columnViewRow [ #focusable 'Data.GI.Base.Attributes.:=' value ]
-- @
setColumnViewRowFocusable :: (MonadIO m, IsColumnViewRow o) => o -> Bool -> m ()
setColumnViewRowFocusable :: forall (m :: * -> *) o.
(MonadIO m, IsColumnViewRow o) =>
o -> Bool -> m ()
setColumnViewRowFocusable 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`.
constructColumnViewRowFocusable :: (IsColumnViewRow o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructColumnViewRowFocusable :: forall o (m :: * -> *).
(IsColumnViewRow o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructColumnViewRowFocusable 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 ColumnViewRowFocusablePropertyInfo
instance AttrInfo ColumnViewRowFocusablePropertyInfo where
    type AttrAllowedOps ColumnViewRowFocusablePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint ColumnViewRowFocusablePropertyInfo = IsColumnViewRow
    type AttrSetTypeConstraint ColumnViewRowFocusablePropertyInfo = (~) Bool
    type AttrTransferTypeConstraint ColumnViewRowFocusablePropertyInfo = (~) Bool
    type AttrTransferType ColumnViewRowFocusablePropertyInfo = Bool
    type AttrGetType ColumnViewRowFocusablePropertyInfo = Bool
    type AttrLabel ColumnViewRowFocusablePropertyInfo = "focusable"
    type AttrOrigin ColumnViewRowFocusablePropertyInfo = ColumnViewRow
    attrGet = getColumnViewRowFocusable
    attrSet = setColumnViewRowFocusable
    attrTransfer _ v = do
        return v
    attrConstruct = constructColumnViewRowFocusable
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.ColumnViewRow.focusable"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.9/docs/GI-Gtk-Objects-ColumnViewRow.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' columnViewRow #item
-- @
getColumnViewRowItem :: (MonadIO m, IsColumnViewRow o) => o -> m (Maybe GObject.Object.Object)
getColumnViewRowItem :: forall (m :: * -> *) o.
(MonadIO m, IsColumnViewRow o) =>
o -> m (Maybe Object)
getColumnViewRowItem 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 ColumnViewRowItemPropertyInfo
instance AttrInfo ColumnViewRowItemPropertyInfo where
    type AttrAllowedOps ColumnViewRowItemPropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ColumnViewRowItemPropertyInfo = IsColumnViewRow
    type AttrSetTypeConstraint ColumnViewRowItemPropertyInfo = (~) ()
    type AttrTransferTypeConstraint ColumnViewRowItemPropertyInfo = (~) ()
    type AttrTransferType ColumnViewRowItemPropertyInfo = ()
    type AttrGetType ColumnViewRowItemPropertyInfo = (Maybe GObject.Object.Object)
    type AttrLabel ColumnViewRowItemPropertyInfo = "item"
    type AttrOrigin ColumnViewRowItemPropertyInfo = ColumnViewRow
    attrGet = getColumnViewRowItem
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.ColumnViewRow.item"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.9/docs/GI-Gtk-Objects-ColumnViewRow.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' columnViewRow #position
-- @
getColumnViewRowPosition :: (MonadIO m, IsColumnViewRow o) => o -> m Word32
getColumnViewRowPosition :: forall (m :: * -> *) o.
(MonadIO m, IsColumnViewRow o) =>
o -> m Word32
getColumnViewRowPosition 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 ColumnViewRowPositionPropertyInfo
instance AttrInfo ColumnViewRowPositionPropertyInfo where
    type AttrAllowedOps ColumnViewRowPositionPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint ColumnViewRowPositionPropertyInfo = IsColumnViewRow
    type AttrSetTypeConstraint ColumnViewRowPositionPropertyInfo = (~) ()
    type AttrTransferTypeConstraint ColumnViewRowPositionPropertyInfo = (~) ()
    type AttrTransferType ColumnViewRowPositionPropertyInfo = ()
    type AttrGetType ColumnViewRowPositionPropertyInfo = Word32
    type AttrLabel ColumnViewRowPositionPropertyInfo = "position"
    type AttrOrigin ColumnViewRowPositionPropertyInfo = ColumnViewRow
    attrGet = getColumnViewRowPosition
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.ColumnViewRow.position"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.9/docs/GI-Gtk-Objects-ColumnViewRow.html#g:attr:position"
        })
#endif

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

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

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

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

#if defined(ENABLE_OVERLOADING)
data ColumnViewRowSelectablePropertyInfo
instance AttrInfo ColumnViewRowSelectablePropertyInfo where
    type AttrAllowedOps ColumnViewRowSelectablePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint ColumnViewRowSelectablePropertyInfo = IsColumnViewRow
    type AttrSetTypeConstraint ColumnViewRowSelectablePropertyInfo = (~) Bool
    type AttrTransferTypeConstraint ColumnViewRowSelectablePropertyInfo = (~) Bool
    type AttrTransferType ColumnViewRowSelectablePropertyInfo = Bool
    type AttrGetType ColumnViewRowSelectablePropertyInfo = Bool
    type AttrLabel ColumnViewRowSelectablePropertyInfo = "selectable"
    type AttrOrigin ColumnViewRowSelectablePropertyInfo = ColumnViewRow
    attrGet = getColumnViewRowSelectable
    attrSet = setColumnViewRowSelectable
    attrTransfer _ v = do
        return v
    attrConstruct = constructColumnViewRowSelectable
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.ColumnViewRow.selectable"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.9/docs/GI-Gtk-Objects-ColumnViewRow.html#g:attr:selectable"
        })
#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' columnViewRow #selected
-- @
getColumnViewRowSelected :: (MonadIO m, IsColumnViewRow o) => o -> m Bool
getColumnViewRowSelected :: forall (m :: * -> *) o.
(MonadIO m, IsColumnViewRow o) =>
o -> m Bool
getColumnViewRowSelected 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 ColumnViewRowSelectedPropertyInfo
instance AttrInfo ColumnViewRowSelectedPropertyInfo where
    type AttrAllowedOps ColumnViewRowSelectedPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint ColumnViewRowSelectedPropertyInfo = IsColumnViewRow
    type AttrSetTypeConstraint ColumnViewRowSelectedPropertyInfo = (~) ()
    type AttrTransferTypeConstraint ColumnViewRowSelectedPropertyInfo = (~) ()
    type AttrTransferType ColumnViewRowSelectedPropertyInfo = ()
    type AttrGetType ColumnViewRowSelectedPropertyInfo = Bool
    type AttrLabel ColumnViewRowSelectedPropertyInfo = "selected"
    type AttrOrigin ColumnViewRowSelectedPropertyInfo = ColumnViewRow
    attrGet = getColumnViewRowSelected
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.ColumnViewRow.selected"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.9/docs/GI-Gtk-Objects-ColumnViewRow.html#g:attr:selected"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList ColumnViewRow
type instance O.AttributeList ColumnViewRow = ColumnViewRowAttributeList
type ColumnViewRowAttributeList = ('[ '("accessibleDescription", ColumnViewRowAccessibleDescriptionPropertyInfo), '("accessibleLabel", ColumnViewRowAccessibleLabelPropertyInfo), '("activatable", ColumnViewRowActivatablePropertyInfo), '("focusable", ColumnViewRowFocusablePropertyInfo), '("item", ColumnViewRowItemPropertyInfo), '("position", ColumnViewRowPositionPropertyInfo), '("selectable", ColumnViewRowSelectablePropertyInfo), '("selected", ColumnViewRowSelectedPropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
columnViewRowAccessibleDescription :: AttrLabelProxy "accessibleDescription"
columnViewRowAccessibleDescription = AttrLabelProxy

columnViewRowAccessibleLabel :: AttrLabelProxy "accessibleLabel"
columnViewRowAccessibleLabel = AttrLabelProxy

columnViewRowActivatable :: AttrLabelProxy "activatable"
columnViewRowActivatable = AttrLabelProxy

columnViewRowFocusable :: AttrLabelProxy "focusable"
columnViewRowFocusable = AttrLabelProxy

columnViewRowItem :: AttrLabelProxy "item"
columnViewRowItem = AttrLabelProxy

columnViewRowPosition :: AttrLabelProxy "position"
columnViewRowPosition = AttrLabelProxy

columnViewRowSelectable :: AttrLabelProxy "selectable"
columnViewRowSelectable = AttrLabelProxy

columnViewRowSelected :: AttrLabelProxy "selected"
columnViewRowSelected = AttrLabelProxy

#endif

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

#endif

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

foreign import ccall "gtk_column_view_row_get_accessible_description" gtk_column_view_row_get_accessible_description :: 
    Ptr ColumnViewRow ->                    -- self : TInterface (Name {namespace = "Gtk", name = "ColumnViewRow"})
    IO CString

-- | Gets the accessible description of /@self@/.
-- 
-- /Since: 4.12/
columnViewRowGetAccessibleDescription ::
    (B.CallStack.HasCallStack, MonadIO m, IsColumnViewRow a) =>
    a
    -- ^ /@self@/: a @GtkColumnViewRow@
    -> m T.Text
    -- ^ __Returns:__ the accessible description
columnViewRowGetAccessibleDescription :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsColumnViewRow a) =>
a -> m Text
columnViewRowGetAccessibleDescription a
self = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr ColumnViewRow
self' <- a -> IO (Ptr ColumnViewRow)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr ColumnViewRow -> IO CString
gtk_column_view_row_get_accessible_description Ptr ColumnViewRow
self'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"columnViewRowGetAccessibleDescription" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data ColumnViewRowGetAccessibleDescriptionMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsColumnViewRow a) => O.OverloadedMethod ColumnViewRowGetAccessibleDescriptionMethodInfo a signature where
    overloadedMethod = columnViewRowGetAccessibleDescription

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


#endif

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

foreign import ccall "gtk_column_view_row_get_accessible_label" gtk_column_view_row_get_accessible_label :: 
    Ptr ColumnViewRow ->                    -- self : TInterface (Name {namespace = "Gtk", name = "ColumnViewRow"})
    IO CString

-- | Gets the accessible label of /@self@/.
-- 
-- /Since: 4.12/
columnViewRowGetAccessibleLabel ::
    (B.CallStack.HasCallStack, MonadIO m, IsColumnViewRow a) =>
    a
    -- ^ /@self@/: a @GtkColumnViewRow@
    -> m T.Text
    -- ^ __Returns:__ the accessible label
columnViewRowGetAccessibleLabel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsColumnViewRow a) =>
a -> m Text
columnViewRowGetAccessibleLabel a
self = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr ColumnViewRow
self' <- a -> IO (Ptr ColumnViewRow)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr ColumnViewRow -> IO CString
gtk_column_view_row_get_accessible_label Ptr ColumnViewRow
self'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"columnViewRowGetAccessibleLabel" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data ColumnViewRowGetAccessibleLabelMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsColumnViewRow a) => O.OverloadedMethod ColumnViewRowGetAccessibleLabelMethodInfo a signature where
    overloadedMethod = columnViewRowGetAccessibleLabel

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


#endif

-- method ColumnViewRow::get_activatable
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ColumnViewRow" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkColumnViewRow`"
--                 , 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_row_get_activatable" gtk_column_view_row_get_activatable :: 
    Ptr ColumnViewRow ->                    -- self : TInterface (Name {namespace = "Gtk", name = "ColumnViewRow"})
    IO CInt

-- | Checks if the row has been set to be activatable via
-- 'GI.Gtk.Objects.ColumnViewRow.columnViewRowSetActivatable'.
-- 
-- /Since: 4.12/
columnViewRowGetActivatable ::
    (B.CallStack.HasCallStack, MonadIO m, IsColumnViewRow a) =>
    a
    -- ^ /@self@/: a @GtkColumnViewRow@
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the row is activatable
columnViewRowGetActivatable :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsColumnViewRow a) =>
a -> m Bool
columnViewRowGetActivatable 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 ColumnViewRow
self' <- a -> IO (Ptr ColumnViewRow)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CInt
result <- Ptr ColumnViewRow -> IO CInt
gtk_column_view_row_get_activatable Ptr ColumnViewRow
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 ColumnViewRowGetActivatableMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsColumnViewRow a) => O.OverloadedMethod ColumnViewRowGetActivatableMethodInfo a signature where
    overloadedMethod = columnViewRowGetActivatable

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


#endif

-- method ColumnViewRow::get_focusable
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ColumnViewRow" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkColumnViewRow`"
--                 , 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_row_get_focusable" gtk_column_view_row_get_focusable :: 
    Ptr ColumnViewRow ->                    -- self : TInterface (Name {namespace = "Gtk", name = "ColumnViewRow"})
    IO CInt

-- | Checks if a row item has been set to be focusable via
-- 'GI.Gtk.Objects.ColumnViewRow.columnViewRowSetFocusable'.
-- 
-- /Since: 4.12/
columnViewRowGetFocusable ::
    (B.CallStack.HasCallStack, MonadIO m, IsColumnViewRow a) =>
    a
    -- ^ /@self@/: a @GtkColumnViewRow@
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the row is focusable
columnViewRowGetFocusable :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsColumnViewRow a) =>
a -> m Bool
columnViewRowGetFocusable 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 ColumnViewRow
self' <- a -> IO (Ptr ColumnViewRow)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CInt
result <- Ptr ColumnViewRow -> IO CInt
gtk_column_view_row_get_focusable Ptr ColumnViewRow
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 ColumnViewRowGetFocusableMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsColumnViewRow a) => O.OverloadedMethod ColumnViewRowGetFocusableMethodInfo a signature where
    overloadedMethod = columnViewRowGetFocusable

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


#endif

-- method ColumnViewRow::get_item
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ColumnViewRow" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkColumnViewRow`"
--                 , 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_row_get_item" gtk_column_view_row_get_item :: 
    Ptr ColumnViewRow ->                    -- self : TInterface (Name {namespace = "Gtk", name = "ColumnViewRow"})
    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/
columnViewRowGetItem ::
    (B.CallStack.HasCallStack, MonadIO m, IsColumnViewRow a) =>
    a
    -- ^ /@self@/: a @GtkColumnViewRow@
    -> m (Maybe GObject.Object.Object)
    -- ^ __Returns:__ The item displayed
columnViewRowGetItem :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsColumnViewRow a) =>
a -> m (Maybe Object)
columnViewRowGetItem 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 ColumnViewRow
self' <- a -> IO (Ptr ColumnViewRow)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Object
result <- Ptr ColumnViewRow -> IO (Ptr Object)
gtk_column_view_row_get_item Ptr ColumnViewRow
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 ColumnViewRowGetItemMethodInfo
instance (signature ~ (m (Maybe GObject.Object.Object)), MonadIO m, IsColumnViewRow a) => O.OverloadedMethod ColumnViewRowGetItemMethodInfo a signature where
    overloadedMethod = columnViewRowGetItem

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


#endif

-- method ColumnViewRow::get_position
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ColumnViewRow" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkColumnViewRow`"
--                 , 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_row_get_position" gtk_column_view_row_get_position :: 
    Ptr ColumnViewRow ->                    -- self : TInterface (Name {namespace = "Gtk", name = "ColumnViewRow"})
    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/
columnViewRowGetPosition ::
    (B.CallStack.HasCallStack, MonadIO m, IsColumnViewRow a) =>
    a
    -- ^ /@self@/: a @GtkColumnViewRow@
    -> m Word32
    -- ^ __Returns:__ The position of this row
columnViewRowGetPosition :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsColumnViewRow a) =>
a -> m Word32
columnViewRowGetPosition 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 ColumnViewRow
self' <- a -> IO (Ptr ColumnViewRow)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Word32
result <- Ptr ColumnViewRow -> IO Word32
gtk_column_view_row_get_position Ptr ColumnViewRow
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 ColumnViewRowGetPositionMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsColumnViewRow a) => O.OverloadedMethod ColumnViewRowGetPositionMethodInfo a signature where
    overloadedMethod = columnViewRowGetPosition

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


#endif

-- method ColumnViewRow::get_selectable
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ColumnViewRow" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkColumnViewRow`"
--                 , 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_row_get_selectable" gtk_column_view_row_get_selectable :: 
    Ptr ColumnViewRow ->                    -- self : TInterface (Name {namespace = "Gtk", name = "ColumnViewRow"})
    IO CInt

-- | Checks if the row has been set to be selectable via
-- 'GI.Gtk.Objects.ColumnViewRow.columnViewRowSetSelectable'.
-- 
-- Do not confuse this function with 'GI.Gtk.Objects.ColumnViewRow.columnViewRowGetSelected'.
-- 
-- /Since: 4.12/
columnViewRowGetSelectable ::
    (B.CallStack.HasCallStack, MonadIO m, IsColumnViewRow a) =>
    a
    -- ^ /@self@/: a @GtkColumnViewRow@
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the row is selectable
columnViewRowGetSelectable :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsColumnViewRow a) =>
a -> m Bool
columnViewRowGetSelectable 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 ColumnViewRow
self' <- a -> IO (Ptr ColumnViewRow)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CInt
result <- Ptr ColumnViewRow -> IO CInt
gtk_column_view_row_get_selectable Ptr ColumnViewRow
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 ColumnViewRowGetSelectableMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsColumnViewRow a) => O.OverloadedMethod ColumnViewRowGetSelectableMethodInfo a signature where
    overloadedMethod = columnViewRowGetSelectable

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


#endif

-- method ColumnViewRow::get_selected
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ColumnViewRow" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkColumnViewRow`"
--                 , 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_row_get_selected" gtk_column_view_row_get_selected :: 
    Ptr ColumnViewRow ->                    -- self : TInterface (Name {namespace = "Gtk", name = "ColumnViewRow"})
    IO CInt

-- | Checks if the item is selected that this row corresponds to.
-- 
-- The selected state is maintained by the list widget and its model
-- and cannot be set otherwise.
-- 
-- /Since: 4.12/
columnViewRowGetSelected ::
    (B.CallStack.HasCallStack, MonadIO m, IsColumnViewRow a) =>
    a
    -- ^ /@self@/: a @GtkColumnViewRow@
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the item is selected.
columnViewRowGetSelected :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsColumnViewRow a) =>
a -> m Bool
columnViewRowGetSelected 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 ColumnViewRow
self' <- a -> IO (Ptr ColumnViewRow)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CInt
result <- Ptr ColumnViewRow -> IO CInt
gtk_column_view_row_get_selected Ptr ColumnViewRow
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 ColumnViewRowGetSelectedMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsColumnViewRow a) => O.OverloadedMethod ColumnViewRowGetSelectedMethodInfo a signature where
    overloadedMethod = columnViewRowGetSelected

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


#endif

-- method ColumnViewRow::set_accessible_description
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ColumnViewRow" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkColumnViewRow`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "description"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the description" , 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_row_set_accessible_description" gtk_column_view_row_set_accessible_description :: 
    Ptr ColumnViewRow ->                    -- self : TInterface (Name {namespace = "Gtk", name = "ColumnViewRow"})
    CString ->                              -- description : TBasicType TUTF8
    IO ()

-- | Sets the accessible description for the row,
-- which may be used by e.g. screen readers.
-- 
-- /Since: 4.12/
columnViewRowSetAccessibleDescription ::
    (B.CallStack.HasCallStack, MonadIO m, IsColumnViewRow a) =>
    a
    -- ^ /@self@/: a @GtkColumnViewRow@
    -> T.Text
    -- ^ /@description@/: the description
    -> m ()
columnViewRowSetAccessibleDescription :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsColumnViewRow a) =>
a -> Text -> m ()
columnViewRowSetAccessibleDescription a
self Text
description = 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 ColumnViewRow
self' <- a -> IO (Ptr ColumnViewRow)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
description' <- Text -> IO CString
textToCString Text
description
    Ptr ColumnViewRow -> CString -> IO ()
gtk_column_view_row_set_accessible_description Ptr ColumnViewRow
self' CString
description'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
description'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ColumnViewRowSetAccessibleDescriptionMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsColumnViewRow a) => O.OverloadedMethod ColumnViewRowSetAccessibleDescriptionMethodInfo a signature where
    overloadedMethod = columnViewRowSetAccessibleDescription

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


#endif

-- method ColumnViewRow::set_accessible_label
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ColumnViewRow" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkColumnViewRow`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "label"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the label" , 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_row_set_accessible_label" gtk_column_view_row_set_accessible_label :: 
    Ptr ColumnViewRow ->                    -- self : TInterface (Name {namespace = "Gtk", name = "ColumnViewRow"})
    CString ->                              -- label : TBasicType TUTF8
    IO ()

-- | Sets the accessible label for the row,
-- which may be used by e.g. screen readers.
-- 
-- /Since: 4.12/
columnViewRowSetAccessibleLabel ::
    (B.CallStack.HasCallStack, MonadIO m, IsColumnViewRow a) =>
    a
    -- ^ /@self@/: a @GtkColumnViewRow@
    -> T.Text
    -- ^ /@label@/: the label
    -> m ()
columnViewRowSetAccessibleLabel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsColumnViewRow a) =>
a -> Text -> m ()
columnViewRowSetAccessibleLabel a
self Text
label = 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 ColumnViewRow
self' <- a -> IO (Ptr ColumnViewRow)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
label' <- Text -> IO CString
textToCString Text
label
    Ptr ColumnViewRow -> CString -> IO ()
gtk_column_view_row_set_accessible_label Ptr ColumnViewRow
self' CString
label'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
label'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ColumnViewRowSetAccessibleLabelMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsColumnViewRow a) => O.OverloadedMethod ColumnViewRowSetAccessibleLabelMethodInfo a signature where
    overloadedMethod = columnViewRowSetAccessibleLabel

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


#endif

-- method ColumnViewRow::set_activatable
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ColumnViewRow" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkColumnViewRow`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "activatable"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "if the row should be activatable"
--                 , 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_row_set_activatable" gtk_column_view_row_set_activatable :: 
    Ptr ColumnViewRow ->                    -- self : TInterface (Name {namespace = "Gtk", name = "ColumnViewRow"})
    CInt ->                                 -- activatable : TBasicType TBoolean
    IO ()

-- | Sets /@self@/ to be activatable.
-- 
-- If a row is activatable, double-clicking on the row, using
-- the Return key or calling 'GI.Gtk.Objects.Widget.widgetActivate' will activate
-- the row. Activating instructs the containing columnview to
-- emit the [ColumnView::activate]("GI.Gtk.Objects.ColumnView#g:signal:activate") signal.
-- 
-- By default, row are activatable.
-- 
-- /Since: 4.12/
columnViewRowSetActivatable ::
    (B.CallStack.HasCallStack, MonadIO m, IsColumnViewRow a) =>
    a
    -- ^ /@self@/: a @GtkColumnViewRow@
    -> Bool
    -- ^ /@activatable@/: if the row should be activatable
    -> m ()
columnViewRowSetActivatable :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsColumnViewRow a) =>
a -> Bool -> m ()
columnViewRowSetActivatable a
self Bool
activatable = 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 ColumnViewRow
self' <- a -> IO (Ptr ColumnViewRow)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    let activatable' :: CInt
activatable' = (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
activatable
    Ptr ColumnViewRow -> CInt -> IO ()
gtk_column_view_row_set_activatable Ptr ColumnViewRow
self' CInt
activatable'
    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 ColumnViewRowSetActivatableMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsColumnViewRow a) => O.OverloadedMethod ColumnViewRowSetActivatableMethodInfo a signature where
    overloadedMethod = columnViewRowSetActivatable

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


#endif

-- method ColumnViewRow::set_focusable
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ColumnViewRow" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkColumnViewRow`"
--                 , 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 row 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_row_set_focusable" gtk_column_view_row_set_focusable :: 
    Ptr ColumnViewRow ->                    -- self : TInterface (Name {namespace = "Gtk", name = "ColumnViewRow"})
    CInt ->                                 -- focusable : TBasicType TBoolean
    IO ()

-- | Sets /@self@/ to be focusable.
-- 
-- If a row is focusable, it can be focused using the keyboard.
-- This works similar to 'GI.Gtk.Objects.Widget.widgetSetFocusable'.
-- 
-- Note that if row are not focusable, the contents of cells can still be focused if
-- they are focusable.
-- 
-- By default, rows are focusable.
-- 
-- /Since: 4.12/
columnViewRowSetFocusable ::
    (B.CallStack.HasCallStack, MonadIO m, IsColumnViewRow a) =>
    a
    -- ^ /@self@/: a @GtkColumnViewRow@
    -> Bool
    -- ^ /@focusable@/: if the row should be focusable
    -> m ()
columnViewRowSetFocusable :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsColumnViewRow a) =>
a -> Bool -> m ()
columnViewRowSetFocusable 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 ColumnViewRow
self' <- a -> IO (Ptr ColumnViewRow)
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 ColumnViewRow -> CInt -> IO ()
gtk_column_view_row_set_focusable Ptr ColumnViewRow
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 ColumnViewRowSetFocusableMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsColumnViewRow a) => O.OverloadedMethod ColumnViewRowSetFocusableMethodInfo a signature where
    overloadedMethod = columnViewRowSetFocusable

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


#endif

-- method ColumnViewRow::set_selectable
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ColumnViewRow" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkColumnViewRow`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "selectable"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "if the row should be selectable"
--                 , 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_row_set_selectable" gtk_column_view_row_set_selectable :: 
    Ptr ColumnViewRow ->                    -- self : TInterface (Name {namespace = "Gtk", name = "ColumnViewRow"})
    CInt ->                                 -- selectable : TBasicType TBoolean
    IO ()

-- | Sets /@self@/ to be selectable.
-- 
-- If a row is selectable, clicking on the row or using the keyboard
-- will try to select or unselect the row. Whether this succeeds is up to
-- the model to determine, as it is managing the selected state.
-- 
-- Note that this means that making a row non-selectable has no
-- influence on the selected state at all. A non-selectable row
-- may still be selected.
-- 
-- By default, rows are selectable.
-- 
-- /Since: 4.12/
columnViewRowSetSelectable ::
    (B.CallStack.HasCallStack, MonadIO m, IsColumnViewRow a) =>
    a
    -- ^ /@self@/: a @GtkColumnViewRow@
    -> Bool
    -- ^ /@selectable@/: if the row should be selectable
    -> m ()
columnViewRowSetSelectable :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsColumnViewRow a) =>
a -> Bool -> m ()
columnViewRowSetSelectable a
self Bool
selectable = 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 ColumnViewRow
self' <- a -> IO (Ptr ColumnViewRow)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    let selectable' :: CInt
selectable' = (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
selectable
    Ptr ColumnViewRow -> CInt -> IO ()
gtk_column_view_row_set_selectable Ptr ColumnViewRow
self' CInt
selectable'
    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 ColumnViewRowSetSelectableMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsColumnViewRow a) => O.OverloadedMethod ColumnViewRowSetSelectableMethodInfo a signature where
    overloadedMethod = columnViewRowSetSelectable

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


#endif