{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Objects.TreeListModel
    ( 
    TreeListModel(..)                       ,
    IsTreeListModel                         ,
    toTreeListModel                         ,
 
#if defined(ENABLE_OVERLOADING)
    ResolveTreeListModelMethod              ,
#endif
#if defined(ENABLE_OVERLOADING)
    TreeListModelGetAutoexpandMethodInfo    ,
#endif
    treeListModelGetAutoexpand              ,
#if defined(ENABLE_OVERLOADING)
    TreeListModelGetChildRowMethodInfo      ,
#endif
    treeListModelGetChildRow                ,
#if defined(ENABLE_OVERLOADING)
    TreeListModelGetModelMethodInfo         ,
#endif
    treeListModelGetModel                   ,
#if defined(ENABLE_OVERLOADING)
    TreeListModelGetPassthroughMethodInfo   ,
#endif
    treeListModelGetPassthrough             ,
#if defined(ENABLE_OVERLOADING)
    TreeListModelGetRowMethodInfo           ,
#endif
    treeListModelGetRow                     ,
    treeListModelNew                        ,
#if defined(ENABLE_OVERLOADING)
    TreeListModelSetAutoexpandMethodInfo    ,
#endif
    treeListModelSetAutoexpand              ,
 
#if defined(ENABLE_OVERLOADING)
    TreeListModelAutoexpandPropertyInfo     ,
#endif
    constructTreeListModelAutoexpand        ,
    getTreeListModelAutoexpand              ,
    setTreeListModelAutoexpand              ,
#if defined(ENABLE_OVERLOADING)
    treeListModelAutoexpand                 ,
#endif
#if defined(ENABLE_OVERLOADING)
    TreeListModelItemTypePropertyInfo       ,
#endif
    getTreeListModelItemType                ,
#if defined(ENABLE_OVERLOADING)
    treeListModelItemType                   ,
#endif
#if defined(ENABLE_OVERLOADING)
    TreeListModelModelPropertyInfo          ,
#endif
    getTreeListModelModel                   ,
#if defined(ENABLE_OVERLOADING)
    treeListModelModel                      ,
#endif
#if defined(ENABLE_OVERLOADING)
    TreeListModelNItemsPropertyInfo         ,
#endif
    getTreeListModelNItems                  ,
#if defined(ENABLE_OVERLOADING)
    treeListModelNItems                     ,
#endif
#if defined(ENABLE_OVERLOADING)
    TreeListModelPassthroughPropertyInfo    ,
#endif
    constructTreeListModelPassthrough       ,
    getTreeListModelPassthrough             ,
#if defined(ENABLE_OVERLOADING)
    treeListModelPassthrough                ,
#endif
    ) 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.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R
import qualified GI.GLib.Callbacks as GLib.Callbacks
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Interfaces.ListModel as Gio.ListModel
import qualified GI.Gtk.Callbacks as Gtk.Callbacks
import {-# SOURCE #-} qualified GI.Gtk.Objects.TreeListRow as Gtk.TreeListRow
newtype TreeListModel = TreeListModel (SP.ManagedPtr TreeListModel)
    deriving (TreeListModel -> TreeListModel -> Bool
(TreeListModel -> TreeListModel -> Bool)
-> (TreeListModel -> TreeListModel -> Bool) -> Eq TreeListModel
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TreeListModel -> TreeListModel -> Bool
== :: TreeListModel -> TreeListModel -> Bool
$c/= :: TreeListModel -> TreeListModel -> Bool
/= :: TreeListModel -> TreeListModel -> Bool
Eq)
instance SP.ManagedPtrNewtype TreeListModel where
    toManagedPtr :: TreeListModel -> ManagedPtr TreeListModel
toManagedPtr (TreeListModel ManagedPtr TreeListModel
p) = ManagedPtr TreeListModel
p
foreign import ccall "gtk_tree_list_model_get_type"
    c_gtk_tree_list_model_get_type :: IO B.Types.GType
instance B.Types.TypedObject TreeListModel where
    glibType :: IO GType
glibType = IO GType
c_gtk_tree_list_model_get_type
instance B.Types.GObject TreeListModel
class (SP.GObject o, O.IsDescendantOf TreeListModel o) => IsTreeListModel o
instance (SP.GObject o, O.IsDescendantOf TreeListModel o) => IsTreeListModel o
instance O.HasParentTypes TreeListModel
type instance O.ParentTypes TreeListModel = '[GObject.Object.Object, Gio.ListModel.ListModel]
toTreeListModel :: (MIO.MonadIO m, IsTreeListModel o) => o -> m TreeListModel
toTreeListModel :: forall (m :: * -> *) o.
(MonadIO m, IsTreeListModel o) =>
o -> m TreeListModel
toTreeListModel = IO TreeListModel -> m TreeListModel
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO TreeListModel -> m TreeListModel)
-> (o -> IO TreeListModel) -> o -> m TreeListModel
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr TreeListModel -> TreeListModel)
-> o -> IO TreeListModel
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr TreeListModel -> TreeListModel
TreeListModel
instance B.GValue.IsGValue (Maybe TreeListModel) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gtk_tree_list_model_get_type
    gvalueSet_ :: Ptr GValue -> Maybe TreeListModel -> IO ()
gvalueSet_ Ptr GValue
gv Maybe TreeListModel
P.Nothing = Ptr GValue -> Ptr TreeListModel -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr TreeListModel
forall a. Ptr a
FP.nullPtr :: FP.Ptr TreeListModel)
    gvalueSet_ Ptr GValue
gv (P.Just TreeListModel
obj) = TreeListModel -> (Ptr TreeListModel -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr TreeListModel
obj (Ptr GValue -> Ptr TreeListModel -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe TreeListModel)
gvalueGet_ Ptr GValue
gv = do
        Ptr TreeListModel
ptr <- Ptr GValue -> IO (Ptr TreeListModel)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr TreeListModel)
        if Ptr TreeListModel
ptr Ptr TreeListModel -> Ptr TreeListModel -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr TreeListModel
forall a. Ptr a
FP.nullPtr
        then TreeListModel -> Maybe TreeListModel
forall a. a -> Maybe a
P.Just (TreeListModel -> Maybe TreeListModel)
-> IO TreeListModel -> IO (Maybe TreeListModel)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr TreeListModel -> TreeListModel)
-> Ptr TreeListModel -> IO TreeListModel
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr TreeListModel -> TreeListModel
TreeListModel Ptr TreeListModel
ptr
        else Maybe TreeListModel -> IO (Maybe TreeListModel)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TreeListModel
forall a. Maybe a
P.Nothing
        
    
#if defined(ENABLE_OVERLOADING)
type family ResolveTreeListModelMethod (t :: Symbol) (o :: *) :: * where
    ResolveTreeListModelMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveTreeListModelMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveTreeListModelMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveTreeListModelMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveTreeListModelMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveTreeListModelMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveTreeListModelMethod "itemsChanged" o = Gio.ListModel.ListModelItemsChangedMethodInfo
    ResolveTreeListModelMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveTreeListModelMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveTreeListModelMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveTreeListModelMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveTreeListModelMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveTreeListModelMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveTreeListModelMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveTreeListModelMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveTreeListModelMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveTreeListModelMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveTreeListModelMethod "getAutoexpand" o = TreeListModelGetAutoexpandMethodInfo
    ResolveTreeListModelMethod "getChildRow" o = TreeListModelGetChildRowMethodInfo
    ResolveTreeListModelMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveTreeListModelMethod "getItem" o = Gio.ListModel.ListModelGetItemMethodInfo
    ResolveTreeListModelMethod "getItemType" o = Gio.ListModel.ListModelGetItemTypeMethodInfo
    ResolveTreeListModelMethod "getModel" o = TreeListModelGetModelMethodInfo
    ResolveTreeListModelMethod "getNItems" o = Gio.ListModel.ListModelGetNItemsMethodInfo
    ResolveTreeListModelMethod "getPassthrough" o = TreeListModelGetPassthroughMethodInfo
    ResolveTreeListModelMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveTreeListModelMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveTreeListModelMethod "getRow" o = TreeListModelGetRowMethodInfo
    ResolveTreeListModelMethod "setAutoexpand" o = TreeListModelSetAutoexpandMethodInfo
    ResolveTreeListModelMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveTreeListModelMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveTreeListModelMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveTreeListModelMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveTreeListModelMethod t TreeListModel, O.OverloadedMethod info TreeListModel p) => OL.IsLabel t (TreeListModel -> 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 ~ ResolveTreeListModelMethod t TreeListModel, O.OverloadedMethod info TreeListModel p, R.HasField t TreeListModel p) => R.HasField t TreeListModel p where
    getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveTreeListModelMethod t TreeListModel, O.OverloadedMethodInfo info TreeListModel) => OL.IsLabel t (O.MethodProxy info TreeListModel) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif
#endif
   
   
   
getTreeListModelAutoexpand :: (MonadIO m, IsTreeListModel o) => o -> m Bool
getTreeListModelAutoexpand :: forall (m :: * -> *) o.
(MonadIO m, IsTreeListModel o) =>
o -> m Bool
getTreeListModelAutoexpand 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
"autoexpand"
setTreeListModelAutoexpand :: (MonadIO m, IsTreeListModel o) => o -> Bool -> m ()
setTreeListModelAutoexpand :: forall (m :: * -> *) o.
(MonadIO m, IsTreeListModel o) =>
o -> Bool -> m ()
setTreeListModelAutoexpand 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
"autoexpand" Bool
val
constructTreeListModelAutoexpand :: (IsTreeListModel o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructTreeListModelAutoexpand :: forall o (m :: * -> *).
(IsTreeListModel o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructTreeListModelAutoexpand 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
"autoexpand" Bool
val
#if defined(ENABLE_OVERLOADING)
data TreeListModelAutoexpandPropertyInfo
instance AttrInfo TreeListModelAutoexpandPropertyInfo where
    type AttrAllowedOps TreeListModelAutoexpandPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint TreeListModelAutoexpandPropertyInfo = IsTreeListModel
    type AttrSetTypeConstraint TreeListModelAutoexpandPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint TreeListModelAutoexpandPropertyInfo = (~) Bool
    type AttrTransferType TreeListModelAutoexpandPropertyInfo = Bool
    type AttrGetType TreeListModelAutoexpandPropertyInfo = Bool
    type AttrLabel TreeListModelAutoexpandPropertyInfo = "autoexpand"
    type AttrOrigin TreeListModelAutoexpandPropertyInfo = TreeListModel
    attrGet = getTreeListModelAutoexpand
    attrSet = setTreeListModelAutoexpand
    attrTransfer _ v = do
        return v
    attrConstruct = constructTreeListModelAutoexpand
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.TreeListModel.autoexpand"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-TreeListModel.html#g:attr:autoexpand"
        })
#endif
   
   
   
getTreeListModelItemType :: (MonadIO m, IsTreeListModel o) => o -> m GType
getTreeListModelItemType :: forall (m :: * -> *) o.
(MonadIO m, IsTreeListModel o) =>
o -> m GType
getTreeListModelItemType o
obj = IO GType -> m GType
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO GType -> m GType) -> IO GType -> m GType
forall a b. (a -> b) -> a -> b
$ o -> String -> IO GType
forall a. GObject a => a -> String -> IO GType
B.Properties.getObjectPropertyGType o
obj String
"item-type"
#if defined(ENABLE_OVERLOADING)
data TreeListModelItemTypePropertyInfo
instance AttrInfo TreeListModelItemTypePropertyInfo where
    type AttrAllowedOps TreeListModelItemTypePropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint TreeListModelItemTypePropertyInfo = IsTreeListModel
    type AttrSetTypeConstraint TreeListModelItemTypePropertyInfo = (~) ()
    type AttrTransferTypeConstraint TreeListModelItemTypePropertyInfo = (~) ()
    type AttrTransferType TreeListModelItemTypePropertyInfo = ()
    type AttrGetType TreeListModelItemTypePropertyInfo = GType
    type AttrLabel TreeListModelItemTypePropertyInfo = "item-type"
    type AttrOrigin TreeListModelItemTypePropertyInfo = TreeListModel
    attrGet = getTreeListModelItemType
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.TreeListModel.itemType"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-TreeListModel.html#g:attr:itemType"
        })
#endif
   
   
   
getTreeListModelModel :: (MonadIO m, IsTreeListModel o) => o -> m Gio.ListModel.ListModel
getTreeListModelModel :: forall (m :: * -> *) o.
(MonadIO m, IsTreeListModel o) =>
o -> m ListModel
getTreeListModelModel o
obj = IO ListModel -> m ListModel
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO ListModel -> m ListModel) -> IO ListModel -> m ListModel
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe ListModel) -> IO ListModel
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getTreeListModelModel" (IO (Maybe ListModel) -> IO ListModel)
-> IO (Maybe ListModel) -> IO ListModel
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr ListModel -> ListModel)
-> IO (Maybe ListModel)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"model" ManagedPtr ListModel -> ListModel
Gio.ListModel.ListModel
#if defined(ENABLE_OVERLOADING)
data TreeListModelModelPropertyInfo
instance AttrInfo TreeListModelModelPropertyInfo where
    type AttrAllowedOps TreeListModelModelPropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint TreeListModelModelPropertyInfo = IsTreeListModel
    type AttrSetTypeConstraint TreeListModelModelPropertyInfo = (~) ()
    type AttrTransferTypeConstraint TreeListModelModelPropertyInfo = (~) ()
    type AttrTransferType TreeListModelModelPropertyInfo = ()
    type AttrGetType TreeListModelModelPropertyInfo = Gio.ListModel.ListModel
    type AttrLabel TreeListModelModelPropertyInfo = "model"
    type AttrOrigin TreeListModelModelPropertyInfo = TreeListModel
    attrGet = getTreeListModelModel
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.TreeListModel.model"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-TreeListModel.html#g:attr:model"
        })
#endif
   
   
   
getTreeListModelNItems :: (MonadIO m, IsTreeListModel o) => o -> m Word32
getTreeListModelNItems :: forall (m :: * -> *) o.
(MonadIO m, IsTreeListModel o) =>
o -> m Word32
getTreeListModelNItems 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
"n-items"
#if defined(ENABLE_OVERLOADING)
data TreeListModelNItemsPropertyInfo
instance AttrInfo TreeListModelNItemsPropertyInfo where
    type AttrAllowedOps TreeListModelNItemsPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint TreeListModelNItemsPropertyInfo = IsTreeListModel
    type AttrSetTypeConstraint TreeListModelNItemsPropertyInfo = (~) ()
    type AttrTransferTypeConstraint TreeListModelNItemsPropertyInfo = (~) ()
    type AttrTransferType TreeListModelNItemsPropertyInfo = ()
    type AttrGetType TreeListModelNItemsPropertyInfo = Word32
    type AttrLabel TreeListModelNItemsPropertyInfo = "n-items"
    type AttrOrigin TreeListModelNItemsPropertyInfo = TreeListModel
    attrGet = getTreeListModelNItems
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.TreeListModel.nItems"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-TreeListModel.html#g:attr:nItems"
        })
#endif
   
   
   
getTreeListModelPassthrough :: (MonadIO m, IsTreeListModel o) => o -> m Bool
getTreeListModelPassthrough :: forall (m :: * -> *) o.
(MonadIO m, IsTreeListModel o) =>
o -> m Bool
getTreeListModelPassthrough 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
"passthrough"
constructTreeListModelPassthrough :: (IsTreeListModel o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructTreeListModelPassthrough :: forall o (m :: * -> *).
(IsTreeListModel o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructTreeListModelPassthrough 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
"passthrough" Bool
val
#if defined(ENABLE_OVERLOADING)
data TreeListModelPassthroughPropertyInfo
instance AttrInfo TreeListModelPassthroughPropertyInfo where
    type AttrAllowedOps TreeListModelPassthroughPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint TreeListModelPassthroughPropertyInfo = IsTreeListModel
    type AttrSetTypeConstraint TreeListModelPassthroughPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint TreeListModelPassthroughPropertyInfo = (~) Bool
    type AttrTransferType TreeListModelPassthroughPropertyInfo = Bool
    type AttrGetType TreeListModelPassthroughPropertyInfo = Bool
    type AttrLabel TreeListModelPassthroughPropertyInfo = "passthrough"
    type AttrOrigin TreeListModelPassthroughPropertyInfo = TreeListModel
    attrGet = getTreeListModelPassthrough
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructTreeListModelPassthrough
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.TreeListModel.passthrough"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-TreeListModel.html#g:attr:passthrough"
        })
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList TreeListModel
type instance O.AttributeList TreeListModel = TreeListModelAttributeList
type TreeListModelAttributeList = ('[ '("autoexpand", TreeListModelAutoexpandPropertyInfo), '("itemType", TreeListModelItemTypePropertyInfo), '("model", TreeListModelModelPropertyInfo), '("nItems", TreeListModelNItemsPropertyInfo), '("passthrough", TreeListModelPassthroughPropertyInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
treeListModelAutoexpand :: AttrLabelProxy "autoexpand"
treeListModelAutoexpand = AttrLabelProxy
treeListModelItemType :: AttrLabelProxy "itemType"
treeListModelItemType = AttrLabelProxy
treeListModelModel :: AttrLabelProxy "model"
treeListModelModel = AttrLabelProxy
treeListModelNItems :: AttrLabelProxy "nItems"
treeListModelNItems = AttrLabelProxy
treeListModelPassthrough :: AttrLabelProxy "passthrough"
treeListModelPassthrough = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList TreeListModel = TreeListModelSignalList
type TreeListModelSignalList = ('[ '("itemsChanged", Gio.ListModel.ListModelItemsChangedSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "gtk_tree_list_model_new" gtk_tree_list_model_new :: 
    Ptr Gio.ListModel.ListModel ->          
    CInt ->                                 
    CInt ->                                 
    FunPtr Gtk.Callbacks.C_TreeListModelCreateModelFunc -> 
    Ptr () ->                               
    FunPtr GLib.Callbacks.C_DestroyNotify -> 
    IO (Ptr TreeListModel)
treeListModelNew ::
    (B.CallStack.HasCallStack, MonadIO m, Gio.ListModel.IsListModel a) =>
    a
    
    -> Bool
    
    -> Bool
    
    -> Gtk.Callbacks.TreeListModelCreateModelFunc
    
    
    -> m TreeListModel
    
treeListModelNew :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsListModel a) =>
a
-> Bool -> Bool -> TreeListModelCreateModelFunc -> m TreeListModel
treeListModelNew a
root Bool
passthrough Bool
autoexpand TreeListModelCreateModelFunc
createFunc = IO TreeListModel -> m TreeListModel
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TreeListModel -> m TreeListModel)
-> IO TreeListModel -> m TreeListModel
forall a b. (a -> b) -> a -> b
$ do
    Ptr ListModel
root' <- a -> IO (Ptr ListModel)
forall a b. (HasCallStack, GObject a) => a -> IO (Ptr b)
B.ManagedPtr.disownObject a
root
    let passthrough' :: CInt
passthrough' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
passthrough
    let autoexpand' :: CInt
autoexpand' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
autoexpand
    FunPtr C_TreeListModelCreateModelFunc
createFunc' <- C_TreeListModelCreateModelFunc
-> IO (FunPtr C_TreeListModelCreateModelFunc)
Gtk.Callbacks.mk_TreeListModelCreateModelFunc (Maybe (Ptr (FunPtr C_TreeListModelCreateModelFunc))
-> TreeListModelCreateModelFunc_WithClosures
-> C_TreeListModelCreateModelFunc
Gtk.Callbacks.wrap_TreeListModelCreateModelFunc Maybe (Ptr (FunPtr C_TreeListModelCreateModelFunc))
forall a. Maybe a
Nothing (TreeListModelCreateModelFunc
-> TreeListModelCreateModelFunc_WithClosures
Gtk.Callbacks.drop_closures_TreeListModelCreateModelFunc TreeListModelCreateModelFunc
createFunc))
    let userData :: Ptr ()
userData = FunPtr C_TreeListModelCreateModelFunc -> Ptr ()
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr C_TreeListModelCreateModelFunc
createFunc'
    let userDestroy :: FunPtr (Ptr a -> IO ())
userDestroy = FunPtr (Ptr a -> IO ())
forall a. FunPtr (Ptr a -> IO ())
SP.safeFreeFunPtrPtr
    Ptr TreeListModel
result <- Ptr ListModel
-> CInt
-> CInt
-> FunPtr C_TreeListModelCreateModelFunc
-> Ptr ()
-> FunPtr C_DestroyNotify
-> IO (Ptr TreeListModel)
gtk_tree_list_model_new Ptr ListModel
root' CInt
passthrough' CInt
autoexpand' FunPtr C_TreeListModelCreateModelFunc
createFunc' Ptr ()
userData FunPtr C_DestroyNotify
forall a. FunPtr (Ptr a -> IO ())
userDestroy
    Text -> Ptr TreeListModel -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"treeListModelNew" Ptr TreeListModel
result
    TreeListModel
result' <- ((ManagedPtr TreeListModel -> TreeListModel)
-> Ptr TreeListModel -> IO TreeListModel
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr TreeListModel -> TreeListModel
TreeListModel) Ptr TreeListModel
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
root
    TreeListModel -> IO TreeListModel
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return TreeListModel
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_tree_list_model_get_autoexpand" gtk_tree_list_model_get_autoexpand :: 
    Ptr TreeListModel ->                    
    IO CInt
treeListModelGetAutoexpand ::
    (B.CallStack.HasCallStack, MonadIO m, IsTreeListModel a) =>
    a
    
    -> m Bool
    
treeListModelGetAutoexpand :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTreeListModel a) =>
a -> m Bool
treeListModelGetAutoexpand 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 TreeListModel
self' <- a -> IO (Ptr TreeListModel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CInt
result <- Ptr TreeListModel -> IO CInt
gtk_tree_list_model_get_autoexpand Ptr TreeListModel
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 TreeListModelGetAutoexpandMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsTreeListModel a) => O.OverloadedMethod TreeListModelGetAutoexpandMethodInfo a signature where
    overloadedMethod = treeListModelGetAutoexpand
instance O.OverloadedMethodInfo TreeListModelGetAutoexpandMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.TreeListModel.treeListModelGetAutoexpand",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-TreeListModel.html#v:treeListModelGetAutoexpand"
        })
#endif
foreign import ccall "gtk_tree_list_model_get_child_row" gtk_tree_list_model_get_child_row :: 
    Ptr TreeListModel ->                    
    Word32 ->                               
    IO (Ptr Gtk.TreeListRow.TreeListRow)
treeListModelGetChildRow ::
    (B.CallStack.HasCallStack, MonadIO m, IsTreeListModel a) =>
    a
    
    -> Word32
    
    -> m (Maybe Gtk.TreeListRow.TreeListRow)
    
treeListModelGetChildRow :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTreeListModel a) =>
a -> Word32 -> m (Maybe TreeListRow)
treeListModelGetChildRow a
self Word32
position = IO (Maybe TreeListRow) -> m (Maybe TreeListRow)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe TreeListRow) -> m (Maybe TreeListRow))
-> IO (Maybe TreeListRow) -> m (Maybe TreeListRow)
forall a b. (a -> b) -> a -> b
$ do
    Ptr TreeListModel
self' <- a -> IO (Ptr TreeListModel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr TreeListRow
result <- Ptr TreeListModel -> Word32 -> IO (Ptr TreeListRow)
gtk_tree_list_model_get_child_row Ptr TreeListModel
self' Word32
position
    Maybe TreeListRow
maybeResult <- Ptr TreeListRow
-> (Ptr TreeListRow -> IO TreeListRow) -> IO (Maybe TreeListRow)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr TreeListRow
result ((Ptr TreeListRow -> IO TreeListRow) -> IO (Maybe TreeListRow))
-> (Ptr TreeListRow -> IO TreeListRow) -> IO (Maybe TreeListRow)
forall a b. (a -> b) -> a -> b
$ \Ptr TreeListRow
result' -> do
        TreeListRow
result'' <- ((ManagedPtr TreeListRow -> TreeListRow)
-> Ptr TreeListRow -> IO TreeListRow
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr TreeListRow -> TreeListRow
Gtk.TreeListRow.TreeListRow) Ptr TreeListRow
result'
        TreeListRow -> IO TreeListRow
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return TreeListRow
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe TreeListRow -> IO (Maybe TreeListRow)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TreeListRow
maybeResult
#if defined(ENABLE_OVERLOADING)
data TreeListModelGetChildRowMethodInfo
instance (signature ~ (Word32 -> m (Maybe Gtk.TreeListRow.TreeListRow)), MonadIO m, IsTreeListModel a) => O.OverloadedMethod TreeListModelGetChildRowMethodInfo a signature where
    overloadedMethod = treeListModelGetChildRow
instance O.OverloadedMethodInfo TreeListModelGetChildRowMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.TreeListModel.treeListModelGetChildRow",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-TreeListModel.html#v:treeListModelGetChildRow"
        })
#endif
foreign import ccall "gtk_tree_list_model_get_model" gtk_tree_list_model_get_model :: 
    Ptr TreeListModel ->                    
    IO (Ptr Gio.ListModel.ListModel)
treeListModelGetModel ::
    (B.CallStack.HasCallStack, MonadIO m, IsTreeListModel a) =>
    a
    
    -> m Gio.ListModel.ListModel
    
treeListModelGetModel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTreeListModel a) =>
a -> m ListModel
treeListModelGetModel a
self = IO ListModel -> m ListModel
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ListModel -> m ListModel) -> IO ListModel -> m ListModel
forall a b. (a -> b) -> a -> b
$ do
    Ptr TreeListModel
self' <- a -> IO (Ptr TreeListModel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr ListModel
result <- Ptr TreeListModel -> IO (Ptr ListModel)
gtk_tree_list_model_get_model Ptr TreeListModel
self'
    Text -> Ptr ListModel -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"treeListModelGetModel" Ptr ListModel
result
    ListModel
result' <- ((ManagedPtr ListModel -> ListModel)
-> Ptr ListModel -> IO ListModel
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr ListModel -> ListModel
Gio.ListModel.ListModel) Ptr ListModel
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    ListModel -> IO ListModel
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ListModel
result'
#if defined(ENABLE_OVERLOADING)
data TreeListModelGetModelMethodInfo
instance (signature ~ (m Gio.ListModel.ListModel), MonadIO m, IsTreeListModel a) => O.OverloadedMethod TreeListModelGetModelMethodInfo a signature where
    overloadedMethod = treeListModelGetModel
instance O.OverloadedMethodInfo TreeListModelGetModelMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.TreeListModel.treeListModelGetModel",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-TreeListModel.html#v:treeListModelGetModel"
        })
#endif
foreign import ccall "gtk_tree_list_model_get_passthrough" gtk_tree_list_model_get_passthrough :: 
    Ptr TreeListModel ->                    
    IO CInt
treeListModelGetPassthrough ::
    (B.CallStack.HasCallStack, MonadIO m, IsTreeListModel a) =>
    a
    
    -> m Bool
    
treeListModelGetPassthrough :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTreeListModel a) =>
a -> m Bool
treeListModelGetPassthrough 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 TreeListModel
self' <- a -> IO (Ptr TreeListModel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CInt
result <- Ptr TreeListModel -> IO CInt
gtk_tree_list_model_get_passthrough Ptr TreeListModel
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 TreeListModelGetPassthroughMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsTreeListModel a) => O.OverloadedMethod TreeListModelGetPassthroughMethodInfo a signature where
    overloadedMethod = treeListModelGetPassthrough
instance O.OverloadedMethodInfo TreeListModelGetPassthroughMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.TreeListModel.treeListModelGetPassthrough",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-TreeListModel.html#v:treeListModelGetPassthrough"
        })
#endif
foreign import ccall "gtk_tree_list_model_get_row" gtk_tree_list_model_get_row :: 
    Ptr TreeListModel ->                    
    Word32 ->                               
    IO (Ptr Gtk.TreeListRow.TreeListRow)
treeListModelGetRow ::
    (B.CallStack.HasCallStack, MonadIO m, IsTreeListModel a) =>
    a
    
    -> Word32
    
    -> m (Maybe Gtk.TreeListRow.TreeListRow)
    
treeListModelGetRow :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTreeListModel a) =>
a -> Word32 -> m (Maybe TreeListRow)
treeListModelGetRow a
self Word32
position = IO (Maybe TreeListRow) -> m (Maybe TreeListRow)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe TreeListRow) -> m (Maybe TreeListRow))
-> IO (Maybe TreeListRow) -> m (Maybe TreeListRow)
forall a b. (a -> b) -> a -> b
$ do
    Ptr TreeListModel
self' <- a -> IO (Ptr TreeListModel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr TreeListRow
result <- Ptr TreeListModel -> Word32 -> IO (Ptr TreeListRow)
gtk_tree_list_model_get_row Ptr TreeListModel
self' Word32
position
    Maybe TreeListRow
maybeResult <- Ptr TreeListRow
-> (Ptr TreeListRow -> IO TreeListRow) -> IO (Maybe TreeListRow)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr TreeListRow
result ((Ptr TreeListRow -> IO TreeListRow) -> IO (Maybe TreeListRow))
-> (Ptr TreeListRow -> IO TreeListRow) -> IO (Maybe TreeListRow)
forall a b. (a -> b) -> a -> b
$ \Ptr TreeListRow
result' -> do
        TreeListRow
result'' <- ((ManagedPtr TreeListRow -> TreeListRow)
-> Ptr TreeListRow -> IO TreeListRow
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr TreeListRow -> TreeListRow
Gtk.TreeListRow.TreeListRow) Ptr TreeListRow
result'
        TreeListRow -> IO TreeListRow
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return TreeListRow
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe TreeListRow -> IO (Maybe TreeListRow)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TreeListRow
maybeResult
#if defined(ENABLE_OVERLOADING)
data TreeListModelGetRowMethodInfo
instance (signature ~ (Word32 -> m (Maybe Gtk.TreeListRow.TreeListRow)), MonadIO m, IsTreeListModel a) => O.OverloadedMethod TreeListModelGetRowMethodInfo a signature where
    overloadedMethod = treeListModelGetRow
instance O.OverloadedMethodInfo TreeListModelGetRowMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.TreeListModel.treeListModelGetRow",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-TreeListModel.html#v:treeListModelGetRow"
        })
#endif
foreign import ccall "gtk_tree_list_model_set_autoexpand" gtk_tree_list_model_set_autoexpand :: 
    Ptr TreeListModel ->                    
    CInt ->                                 
    IO ()
treeListModelSetAutoexpand ::
    (B.CallStack.HasCallStack, MonadIO m, IsTreeListModel a) =>
    a
    
    -> Bool
    
    -> m ()
treeListModelSetAutoexpand :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTreeListModel a) =>
a -> Bool -> m ()
treeListModelSetAutoexpand a
self Bool
autoexpand = 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 TreeListModel
self' <- a -> IO (Ptr TreeListModel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    let autoexpand' :: CInt
autoexpand' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
autoexpand
    Ptr TreeListModel -> CInt -> IO ()
gtk_tree_list_model_set_autoexpand Ptr TreeListModel
self' CInt
autoexpand'
    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 TreeListModelSetAutoexpandMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsTreeListModel a) => O.OverloadedMethod TreeListModelSetAutoexpandMethodInfo a signature where
    overloadedMethod = treeListModelSetAutoexpand
instance O.OverloadedMethodInfo TreeListModelSetAutoexpandMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.TreeListModel.treeListModelSetAutoexpand",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-TreeListModel.html#v:treeListModelSetAutoexpand"
        })
#endif