{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- /No description available in the introspection data./

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

module GI.Gtk.Structs.TreePath
    ( 

-- * Exported types
    TreePath(..)                            ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [appendIndex]("GI.Gtk.Structs.TreePath#g:method:appendIndex"), [compare]("GI.Gtk.Structs.TreePath#g:method:compare"), [copy]("GI.Gtk.Structs.TreePath#g:method:copy"), [down]("GI.Gtk.Structs.TreePath#g:method:down"), [free]("GI.Gtk.Structs.TreePath#g:method:free"), [isAncestor]("GI.Gtk.Structs.TreePath#g:method:isAncestor"), [isDescendant]("GI.Gtk.Structs.TreePath#g:method:isDescendant"), [next]("GI.Gtk.Structs.TreePath#g:method:next"), [prependIndex]("GI.Gtk.Structs.TreePath#g:method:prependIndex"), [prev]("GI.Gtk.Structs.TreePath#g:method:prev"), [toString]("GI.Gtk.Structs.TreePath#g:method:toString"), [up]("GI.Gtk.Structs.TreePath#g:method:up").
-- 
-- ==== Getters
-- [getDepth]("GI.Gtk.Structs.TreePath#g:method:getDepth"), [getIndices]("GI.Gtk.Structs.TreePath#g:method:getIndices").
-- 
-- ==== Setters
-- /None/.

#if defined(ENABLE_OVERLOADING)
    ResolveTreePathMethod                   ,
#endif

-- ** appendIndex #method:appendIndex#

#if defined(ENABLE_OVERLOADING)
    TreePathAppendIndexMethodInfo           ,
#endif
    treePathAppendIndex                     ,


-- ** compare #method:compare#

#if defined(ENABLE_OVERLOADING)
    TreePathCompareMethodInfo               ,
#endif
    treePathCompare                         ,


-- ** copy #method:copy#

#if defined(ENABLE_OVERLOADING)
    TreePathCopyMethodInfo                  ,
#endif
    treePathCopy                            ,


-- ** down #method:down#

#if defined(ENABLE_OVERLOADING)
    TreePathDownMethodInfo                  ,
#endif
    treePathDown                            ,


-- ** free #method:free#

#if defined(ENABLE_OVERLOADING)
    TreePathFreeMethodInfo                  ,
#endif
    treePathFree                            ,


-- ** getDepth #method:getDepth#

#if defined(ENABLE_OVERLOADING)
    TreePathGetDepthMethodInfo              ,
#endif
    treePathGetDepth                        ,


-- ** getIndices #method:getIndices#

#if defined(ENABLE_OVERLOADING)
    TreePathGetIndicesMethodInfo            ,
#endif
    treePathGetIndices                      ,


-- ** isAncestor #method:isAncestor#

#if defined(ENABLE_OVERLOADING)
    TreePathIsAncestorMethodInfo            ,
#endif
    treePathIsAncestor                      ,


-- ** isDescendant #method:isDescendant#

#if defined(ENABLE_OVERLOADING)
    TreePathIsDescendantMethodInfo          ,
#endif
    treePathIsDescendant                    ,


-- ** new #method:new#

    treePathNew                             ,


-- ** newFirst #method:newFirst#

    treePathNewFirst                        ,


-- ** newFromIndices #method:newFromIndices#

    treePathNewFromIndices                  ,


-- ** newFromString #method:newFromString#

    treePathNewFromString                   ,


-- ** next #method:next#

#if defined(ENABLE_OVERLOADING)
    TreePathNextMethodInfo                  ,
#endif
    treePathNext                            ,


-- ** prependIndex #method:prependIndex#

#if defined(ENABLE_OVERLOADING)
    TreePathPrependIndexMethodInfo          ,
#endif
    treePathPrependIndex                    ,


-- ** prev #method:prev#

#if defined(ENABLE_OVERLOADING)
    TreePathPrevMethodInfo                  ,
#endif
    treePathPrev                            ,


-- ** toString #method:toString#

#if defined(ENABLE_OVERLOADING)
    TreePathToStringMethodInfo              ,
#endif
    treePathToString                        ,


-- ** up #method:up#

#if defined(ENABLE_OVERLOADING)
    TreePathUpMethodInfo                    ,
#endif
    treePathUp                              ,




    ) where

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

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.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


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

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

foreign import ccall "gtk_tree_path_get_type" c_gtk_tree_path_get_type :: 
    IO GType

type instance O.ParentTypes TreePath = '[]
instance O.HasParentTypes TreePath

instance B.Types.TypedObject TreePath where
    glibType :: IO GType
glibType = IO GType
c_gtk_tree_path_get_type

instance B.Types.GBoxed TreePath

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


#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList TreePath
type instance O.AttributeList TreePath = TreePathAttributeList
type TreePathAttributeList = ('[ ] :: [(Symbol, *)])
#endif

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

foreign import ccall "gtk_tree_path_new" gtk_tree_path_new :: 
    IO (Ptr TreePath)

-- | Creates a new t'GI.Gtk.Structs.TreePath.TreePath'-struct.
-- This refers to a row.
treePathNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m TreePath
    -- ^ __Returns:__ A newly created t'GI.Gtk.Structs.TreePath.TreePath'-struct.
treePathNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m TreePath
treePathNew  = IO TreePath -> m TreePath
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TreePath -> m TreePath) -> IO TreePath -> m TreePath
forall a b. (a -> b) -> a -> b
$ do
    Ptr TreePath
result <- IO (Ptr TreePath)
gtk_tree_path_new
    Text -> Ptr TreePath -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"treePathNew" Ptr TreePath
result
    TreePath
result' <- ((ManagedPtr TreePath -> TreePath) -> Ptr TreePath -> IO TreePath
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr TreePath -> TreePath
TreePath) Ptr TreePath
result
    TreePath -> IO TreePath
forall (m :: * -> *) a. Monad m => a -> m a
return TreePath
result'

#if defined(ENABLE_OVERLOADING)
#endif

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

foreign import ccall "gtk_tree_path_new_first" gtk_tree_path_new_first :: 
    IO (Ptr TreePath)

-- | Creates a new t'GI.Gtk.Structs.TreePath.TreePath'-struct.
-- 
-- The string representation of this path is “0”.
treePathNewFirst ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m TreePath
    -- ^ __Returns:__ A new t'GI.Gtk.Structs.TreePath.TreePath'-struct
treePathNewFirst :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m TreePath
treePathNewFirst  = IO TreePath -> m TreePath
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TreePath -> m TreePath) -> IO TreePath -> m TreePath
forall a b. (a -> b) -> a -> b
$ do
    Ptr TreePath
result <- IO (Ptr TreePath)
gtk_tree_path_new_first
    Text -> Ptr TreePath -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"treePathNewFirst" Ptr TreePath
result
    TreePath
result' <- ((ManagedPtr TreePath -> TreePath) -> Ptr TreePath -> IO TreePath
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr TreePath -> TreePath
TreePath) Ptr TreePath
result
    TreePath -> IO TreePath
forall (m :: * -> *) a. Monad m => a -> m a
return TreePath
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method TreePath::new_from_indices
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "indices"
--           , argType = TCArray False (-1) 1 (TBasicType TInt)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "array of indices" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "length"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "length of @indices array"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "length"
--              , argType = TBasicType TUInt64
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "length of @indices array"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "TreePath" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_tree_path_new_from_indicesv" gtk_tree_path_new_from_indicesv :: 
    Ptr Int32 ->                            -- indices : TCArray False (-1) 1 (TBasicType TInt)
    Word64 ->                               -- length : TBasicType TUInt64
    IO (Ptr TreePath)

-- | Creates a new path with the given /@indices@/ array of /@length@/.
treePathNewFromIndices ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    [Int32]
    -- ^ /@indices@/: array of indices
    -> m TreePath
    -- ^ __Returns:__ A newly created t'GI.Gtk.Structs.TreePath.TreePath'-struct
treePathNewFromIndices :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
[Int32] -> m TreePath
treePathNewFromIndices [Int32]
indices = IO TreePath -> m TreePath
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TreePath -> m TreePath) -> IO TreePath -> m TreePath
forall a b. (a -> b) -> a -> b
$ do
    let length_ :: Word64
length_ = Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word64) -> Int -> Word64
forall a b. (a -> b) -> a -> b
$ [Int32] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
P.length [Int32]
indices
    Ptr Int32
indices' <- [Int32] -> IO (Ptr Int32)
forall a. Storable a => [a] -> IO (Ptr a)
packStorableArray [Int32]
indices
    Ptr TreePath
result <- Ptr Int32 -> Word64 -> IO (Ptr TreePath)
gtk_tree_path_new_from_indicesv Ptr Int32
indices' Word64
length_
    Text -> Ptr TreePath -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"treePathNewFromIndices" Ptr TreePath
result
    TreePath
result' <- ((ManagedPtr TreePath -> TreePath) -> Ptr TreePath -> IO TreePath
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr TreePath -> TreePath
TreePath) Ptr TreePath
result
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
indices'
    TreePath -> IO TreePath
forall (m :: * -> *) a. Monad m => a -> m a
return TreePath
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method TreePath::new_from_string
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "path"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The string representation of a path"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "TreePath" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_tree_path_new_from_string" gtk_tree_path_new_from_string :: 
    CString ->                              -- path : TBasicType TUTF8
    IO (Ptr TreePath)

-- | Creates a new t'GI.Gtk.Structs.TreePath.TreePath'-struct initialized to /@path@/.
-- 
-- /@path@/ is expected to be a colon separated list of numbers.
-- For example, the string “10:4:0” would create a path of depth
-- 3 pointing to the 11th child of the root node, the 5th
-- child of that 11th child, and the 1st child of that 5th child.
-- If an invalid path string is passed in, 'P.Nothing' is returned.
treePathNewFromString ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@path@/: The string representation of a path
    -> m (Maybe TreePath)
    -- ^ __Returns:__ A newly-created t'GI.Gtk.Structs.TreePath.TreePath'-struct, or 'P.Nothing'
treePathNewFromString :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> m (Maybe TreePath)
treePathNewFromString Text
path = IO (Maybe TreePath) -> m (Maybe TreePath)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe TreePath) -> m (Maybe TreePath))
-> IO (Maybe TreePath) -> m (Maybe TreePath)
forall a b. (a -> b) -> a -> b
$ do
    CString
path' <- Text -> IO CString
textToCString Text
path
    Ptr TreePath
result <- CString -> IO (Ptr TreePath)
gtk_tree_path_new_from_string CString
path'
    Maybe TreePath
maybeResult <- Ptr TreePath
-> (Ptr TreePath -> IO TreePath) -> IO (Maybe TreePath)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr TreePath
result ((Ptr TreePath -> IO TreePath) -> IO (Maybe TreePath))
-> (Ptr TreePath -> IO TreePath) -> IO (Maybe TreePath)
forall a b. (a -> b) -> a -> b
$ \Ptr TreePath
result' -> do
        TreePath
result'' <- ((ManagedPtr TreePath -> TreePath) -> Ptr TreePath -> IO TreePath
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr TreePath -> TreePath
TreePath) Ptr TreePath
result'
        TreePath -> IO TreePath
forall (m :: * -> *) a. Monad m => a -> m a
return TreePath
result''
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
path'
    Maybe TreePath -> IO (Maybe TreePath)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TreePath
maybeResult

#if defined(ENABLE_OVERLOADING)
#endif

-- method TreePath::append_index
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TreePath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTreePath-struct"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "index_"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the index" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_tree_path_append_index" gtk_tree_path_append_index :: 
    Ptr TreePath ->                         -- path : TInterface (Name {namespace = "Gtk", name = "TreePath"})
    Int32 ->                                -- index_ : TBasicType TInt
    IO ()

-- | Appends a new index to a path.
-- 
-- As a result, the depth of the path is increased.
treePathAppendIndex ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TreePath
    -- ^ /@path@/: a t'GI.Gtk.Structs.TreePath.TreePath'-struct
    -> Int32
    -- ^ /@index_@/: the index
    -> m ()
treePathAppendIndex :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
TreePath -> Int32 -> m ()
treePathAppendIndex TreePath
path Int32
index_ = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr TreePath
path' <- TreePath -> IO (Ptr TreePath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TreePath
path
    Ptr TreePath -> Int32 -> IO ()
gtk_tree_path_append_index Ptr TreePath
path' Int32
index_
    TreePath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TreePath
path
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TreePathAppendIndexMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m) => O.OverloadedMethod TreePathAppendIndexMethodInfo TreePath signature where
    overloadedMethod = treePathAppendIndex

instance O.OverloadedMethodInfo TreePathAppendIndexMethodInfo TreePath where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Structs.TreePath.treePathAppendIndex",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Structs-TreePath.html#v:treePathAppendIndex"
        }


#endif

-- method TreePath::compare
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "a"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TreePath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTreePath-struct"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "b"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TreePath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTreePath-struct to compare with"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_tree_path_compare" gtk_tree_path_compare :: 
    Ptr TreePath ->                         -- a : TInterface (Name {namespace = "Gtk", name = "TreePath"})
    Ptr TreePath ->                         -- b : TInterface (Name {namespace = "Gtk", name = "TreePath"})
    IO Int32

-- | Compares two paths.
-- 
-- If /@a@/ appears before /@b@/ in a tree, then -1 is returned.
-- If /@b@/ appears before /@a@/, then 1 is returned.
-- If the two nodes are equal, then 0 is returned.
treePathCompare ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TreePath
    -- ^ /@a@/: a t'GI.Gtk.Structs.TreePath.TreePath'-struct
    -> TreePath
    -- ^ /@b@/: a t'GI.Gtk.Structs.TreePath.TreePath'-struct to compare with
    -> m Int32
    -- ^ __Returns:__ the relative positions of /@a@/ and /@b@/
treePathCompare :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
TreePath -> TreePath -> m Int32
treePathCompare TreePath
a TreePath
b = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr TreePath
a' <- TreePath -> IO (Ptr TreePath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TreePath
a
    Ptr TreePath
b' <- TreePath -> IO (Ptr TreePath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TreePath
b
    Int32
result <- Ptr TreePath -> Ptr TreePath -> IO Int32
gtk_tree_path_compare Ptr TreePath
a' Ptr TreePath
b'
    TreePath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TreePath
a
    TreePath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TreePath
b
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data TreePathCompareMethodInfo
instance (signature ~ (TreePath -> m Int32), MonadIO m) => O.OverloadedMethod TreePathCompareMethodInfo TreePath signature where
    overloadedMethod = treePathCompare

instance O.OverloadedMethodInfo TreePathCompareMethodInfo TreePath where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Structs.TreePath.treePathCompare",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Structs-TreePath.html#v:treePathCompare"
        }


#endif

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

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

-- | Creates a new t'GI.Gtk.Structs.TreePath.TreePath'-struct as a copy of /@path@/.
treePathCopy ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TreePath
    -- ^ /@path@/: a t'GI.Gtk.Structs.TreePath.TreePath'-struct
    -> m TreePath
    -- ^ __Returns:__ a new t'GI.Gtk.Structs.TreePath.TreePath'-struct
treePathCopy :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
TreePath -> m TreePath
treePathCopy TreePath
path = IO TreePath -> m TreePath
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TreePath -> m TreePath) -> IO TreePath -> m TreePath
forall a b. (a -> b) -> a -> b
$ do
    Ptr TreePath
path' <- TreePath -> IO (Ptr TreePath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TreePath
path
    Ptr TreePath
result <- Ptr TreePath -> IO (Ptr TreePath)
gtk_tree_path_copy Ptr TreePath
path'
    Text -> Ptr TreePath -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"treePathCopy" Ptr TreePath
result
    TreePath
result' <- ((ManagedPtr TreePath -> TreePath) -> Ptr TreePath -> IO TreePath
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr TreePath -> TreePath
TreePath) Ptr TreePath
result
    TreePath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TreePath
path
    TreePath -> IO TreePath
forall (m :: * -> *) a. Monad m => a -> m a
return TreePath
result'

#if defined(ENABLE_OVERLOADING)
data TreePathCopyMethodInfo
instance (signature ~ (m TreePath), MonadIO m) => O.OverloadedMethod TreePathCopyMethodInfo TreePath signature where
    overloadedMethod = treePathCopy

instance O.OverloadedMethodInfo TreePathCopyMethodInfo TreePath where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Structs.TreePath.treePathCopy",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Structs-TreePath.html#v:treePathCopy"
        }


#endif

-- method TreePath::down
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TreePath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTreePath-struct"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

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

-- | Moves /@path@/ to point to the first child of the current path.
treePathDown ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TreePath
    -- ^ /@path@/: a t'GI.Gtk.Structs.TreePath.TreePath'-struct
    -> m ()
treePathDown :: forall (m :: * -> *). (HasCallStack, MonadIO m) => TreePath -> m ()
treePathDown TreePath
path = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr TreePath
path' <- TreePath -> IO (Ptr TreePath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TreePath
path
    Ptr TreePath -> IO ()
gtk_tree_path_down Ptr TreePath
path'
    TreePath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TreePath
path
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TreePathDownMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod TreePathDownMethodInfo TreePath signature where
    overloadedMethod = treePathDown

instance O.OverloadedMethodInfo TreePathDownMethodInfo TreePath where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Structs.TreePath.treePathDown",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Structs-TreePath.html#v:treePathDown"
        }


#endif

-- method TreePath::free
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TreePath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTreePath-struct"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

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

-- | Frees /@path@/. If /@path@/ is 'P.Nothing', it simply returns.
treePathFree ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TreePath
    -- ^ /@path@/: a t'GI.Gtk.Structs.TreePath.TreePath'-struct
    -> m ()
treePathFree :: forall (m :: * -> *). (HasCallStack, MonadIO m) => TreePath -> m ()
treePathFree TreePath
path = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr TreePath
path' <- TreePath -> IO (Ptr TreePath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TreePath
path
    Ptr TreePath -> IO ()
gtk_tree_path_free Ptr TreePath
path'
    TreePath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TreePath
path
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TreePathFreeMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod TreePathFreeMethodInfo TreePath signature where
    overloadedMethod = treePathFree

instance O.OverloadedMethodInfo TreePathFreeMethodInfo TreePath where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Structs.TreePath.treePathFree",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Structs-TreePath.html#v:treePathFree"
        }


#endif

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

foreign import ccall "gtk_tree_path_get_depth" gtk_tree_path_get_depth :: 
    Ptr TreePath ->                         -- path : TInterface (Name {namespace = "Gtk", name = "TreePath"})
    IO Int32

-- | Returns the current depth of /@path@/.
treePathGetDepth ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TreePath
    -- ^ /@path@/: a t'GI.Gtk.Structs.TreePath.TreePath'-struct
    -> m Int32
    -- ^ __Returns:__ The depth of /@path@/
treePathGetDepth :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
TreePath -> m Int32
treePathGetDepth TreePath
path = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr TreePath
path' <- TreePath -> IO (Ptr TreePath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TreePath
path
    Int32
result <- Ptr TreePath -> IO Int32
gtk_tree_path_get_depth Ptr TreePath
path'
    TreePath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TreePath
path
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data TreePathGetDepthMethodInfo
instance (signature ~ (m Int32), MonadIO m) => O.OverloadedMethod TreePathGetDepthMethodInfo TreePath signature where
    overloadedMethod = treePathGetDepth

instance O.OverloadedMethodInfo TreePathGetDepthMethodInfo TreePath where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Structs.TreePath.treePathGetDepth",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Structs-TreePath.html#v:treePathGetDepth"
        }


#endif

-- method TreePath::get_indices
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TreePath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTreePath-struct"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "depth"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "return location for number of elements\n    returned in the integer array, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "depth"
--              , argType = TBasicType TInt
--              , direction = DirectionOut
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText =
--                        Just
--                          "return location for number of elements\n    returned in the integer array, or %NULL"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferEverything
--              }
--          ]
-- returnType: Just (TCArray False (-1) 1 (TBasicType TInt))
-- throws : False
-- Skip return : False

foreign import ccall "gtk_tree_path_get_indices_with_depth" gtk_tree_path_get_indices_with_depth :: 
    Ptr TreePath ->                         -- path : TInterface (Name {namespace = "Gtk", name = "TreePath"})
    Ptr Int32 ->                            -- depth : TBasicType TInt
    IO (Ptr Int32)

-- | Returns the current indices of /@path@/.
-- 
-- This is an array of integers, each representing a node in a tree.
-- It also returns the number of elements in the array.
-- The array should not be freed.
treePathGetIndices ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TreePath
    -- ^ /@path@/: a t'GI.Gtk.Structs.TreePath.TreePath'-struct
    -> m [Int32]
    -- ^ __Returns:__ The current
    --     indices, or 'P.Nothing'
treePathGetIndices :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
TreePath -> m [Int32]
treePathGetIndices TreePath
path = IO [Int32] -> m [Int32]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Int32] -> m [Int32]) -> IO [Int32] -> m [Int32]
forall a b. (a -> b) -> a -> b
$ do
    Ptr TreePath
path' <- TreePath -> IO (Ptr TreePath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TreePath
path
    Ptr Int32
depth <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Int32
result <- Ptr TreePath -> Ptr Int32 -> IO (Ptr Int32)
gtk_tree_path_get_indices_with_depth Ptr TreePath
path' Ptr Int32
depth
    Int32
depth' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
depth
    Text -> Ptr Int32 -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"treePathGetIndices" Ptr Int32
result
    [Int32]
result' <- (Int32 -> Ptr Int32 -> IO [Int32]
forall a b. (Integral a, Storable b) => a -> Ptr b -> IO [b]
unpackStorableArrayWithLength Int32
depth') Ptr Int32
result
    TreePath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TreePath
path
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
depth
    [Int32] -> IO [Int32]
forall (m :: * -> *) a. Monad m => a -> m a
return [Int32]
result'

#if defined(ENABLE_OVERLOADING)
data TreePathGetIndicesMethodInfo
instance (signature ~ (m [Int32]), MonadIO m) => O.OverloadedMethod TreePathGetIndicesMethodInfo TreePath signature where
    overloadedMethod = treePathGetIndices

instance O.OverloadedMethodInfo TreePathGetIndicesMethodInfo TreePath where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Structs.TreePath.treePathGetIndices",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Structs-TreePath.html#v:treePathGetIndices"
        }


#endif

-- method TreePath::is_ancestor
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TreePath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTreePath-struct"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "descendant"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TreePath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "another #GtkTreePath-struct"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_tree_path_is_ancestor" gtk_tree_path_is_ancestor :: 
    Ptr TreePath ->                         -- path : TInterface (Name {namespace = "Gtk", name = "TreePath"})
    Ptr TreePath ->                         -- descendant : TInterface (Name {namespace = "Gtk", name = "TreePath"})
    IO CInt

-- | Returns 'P.True' if /@descendant@/ is a descendant of /@path@/.
treePathIsAncestor ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TreePath
    -- ^ /@path@/: a t'GI.Gtk.Structs.TreePath.TreePath'-struct
    -> TreePath
    -- ^ /@descendant@/: another t'GI.Gtk.Structs.TreePath.TreePath'-struct
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@descendant@/ is contained inside /@path@/
treePathIsAncestor :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
TreePath -> TreePath -> m Bool
treePathIsAncestor TreePath
path TreePath
descendant = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr TreePath
path' <- TreePath -> IO (Ptr TreePath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TreePath
path
    Ptr TreePath
descendant' <- TreePath -> IO (Ptr TreePath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TreePath
descendant
    CInt
result <- Ptr TreePath -> Ptr TreePath -> IO CInt
gtk_tree_path_is_ancestor Ptr TreePath
path' Ptr TreePath
descendant'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    TreePath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TreePath
path
    TreePath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TreePath
descendant
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TreePathIsAncestorMethodInfo
instance (signature ~ (TreePath -> m Bool), MonadIO m) => O.OverloadedMethod TreePathIsAncestorMethodInfo TreePath signature where
    overloadedMethod = treePathIsAncestor

instance O.OverloadedMethodInfo TreePathIsAncestorMethodInfo TreePath where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Structs.TreePath.treePathIsAncestor",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Structs-TreePath.html#v:treePathIsAncestor"
        }


#endif

-- method TreePath::is_descendant
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TreePath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTreePath-struct"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "ancestor"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TreePath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "another #GtkTreePath-struct"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_tree_path_is_descendant" gtk_tree_path_is_descendant :: 
    Ptr TreePath ->                         -- path : TInterface (Name {namespace = "Gtk", name = "TreePath"})
    Ptr TreePath ->                         -- ancestor : TInterface (Name {namespace = "Gtk", name = "TreePath"})
    IO CInt

-- | Returns 'P.True' if /@path@/ is a descendant of /@ancestor@/.
treePathIsDescendant ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TreePath
    -- ^ /@path@/: a t'GI.Gtk.Structs.TreePath.TreePath'-struct
    -> TreePath
    -- ^ /@ancestor@/: another t'GI.Gtk.Structs.TreePath.TreePath'-struct
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@ancestor@/ contains /@path@/ somewhere below it
treePathIsDescendant :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
TreePath -> TreePath -> m Bool
treePathIsDescendant TreePath
path TreePath
ancestor = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr TreePath
path' <- TreePath -> IO (Ptr TreePath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TreePath
path
    Ptr TreePath
ancestor' <- TreePath -> IO (Ptr TreePath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TreePath
ancestor
    CInt
result <- Ptr TreePath -> Ptr TreePath -> IO CInt
gtk_tree_path_is_descendant Ptr TreePath
path' Ptr TreePath
ancestor'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    TreePath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TreePath
path
    TreePath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TreePath
ancestor
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TreePathIsDescendantMethodInfo
instance (signature ~ (TreePath -> m Bool), MonadIO m) => O.OverloadedMethod TreePathIsDescendantMethodInfo TreePath signature where
    overloadedMethod = treePathIsDescendant

instance O.OverloadedMethodInfo TreePathIsDescendantMethodInfo TreePath where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Structs.TreePath.treePathIsDescendant",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Structs-TreePath.html#v:treePathIsDescendant"
        }


#endif

-- method TreePath::next
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TreePath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTreePath-struct"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

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

-- | Moves the /@path@/ to point to the next node at the current depth.
treePathNext ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TreePath
    -- ^ /@path@/: a t'GI.Gtk.Structs.TreePath.TreePath'-struct
    -> m ()
treePathNext :: forall (m :: * -> *). (HasCallStack, MonadIO m) => TreePath -> m ()
treePathNext TreePath
path = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr TreePath
path' <- TreePath -> IO (Ptr TreePath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TreePath
path
    Ptr TreePath -> IO ()
gtk_tree_path_next Ptr TreePath
path'
    TreePath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TreePath
path
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TreePathNextMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod TreePathNextMethodInfo TreePath signature where
    overloadedMethod = treePathNext

instance O.OverloadedMethodInfo TreePathNextMethodInfo TreePath where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Structs.TreePath.treePathNext",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Structs-TreePath.html#v:treePathNext"
        }


#endif

-- method TreePath::prepend_index
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TreePath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTreePath-struct"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "index_"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the index" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_tree_path_prepend_index" gtk_tree_path_prepend_index :: 
    Ptr TreePath ->                         -- path : TInterface (Name {namespace = "Gtk", name = "TreePath"})
    Int32 ->                                -- index_ : TBasicType TInt
    IO ()

-- | Prepends a new index to a path.
-- 
-- As a result, the depth of the path is increased.
treePathPrependIndex ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TreePath
    -- ^ /@path@/: a t'GI.Gtk.Structs.TreePath.TreePath'-struct
    -> Int32
    -- ^ /@index_@/: the index
    -> m ()
treePathPrependIndex :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
TreePath -> Int32 -> m ()
treePathPrependIndex TreePath
path Int32
index_ = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr TreePath
path' <- TreePath -> IO (Ptr TreePath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TreePath
path
    Ptr TreePath -> Int32 -> IO ()
gtk_tree_path_prepend_index Ptr TreePath
path' Int32
index_
    TreePath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TreePath
path
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TreePathPrependIndexMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m) => O.OverloadedMethod TreePathPrependIndexMethodInfo TreePath signature where
    overloadedMethod = treePathPrependIndex

instance O.OverloadedMethodInfo TreePathPrependIndexMethodInfo TreePath where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Structs.TreePath.treePathPrependIndex",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Structs-TreePath.html#v:treePathPrependIndex"
        }


#endif

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

foreign import ccall "gtk_tree_path_prev" gtk_tree_path_prev :: 
    Ptr TreePath ->                         -- path : TInterface (Name {namespace = "Gtk", name = "TreePath"})
    IO CInt

-- | Moves the /@path@/ to point to the previous node at the
-- current depth, if it exists.
treePathPrev ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TreePath
    -- ^ /@path@/: a t'GI.Gtk.Structs.TreePath.TreePath'-struct
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@path@/ has a previous node, and
    --     the move was made
treePathPrev :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
TreePath -> m Bool
treePathPrev TreePath
path = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr TreePath
path' <- TreePath -> IO (Ptr TreePath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TreePath
path
    CInt
result <- Ptr TreePath -> IO CInt
gtk_tree_path_prev Ptr TreePath
path'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    TreePath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TreePath
path
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TreePathPrevMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.OverloadedMethod TreePathPrevMethodInfo TreePath signature where
    overloadedMethod = treePathPrev

instance O.OverloadedMethodInfo TreePathPrevMethodInfo TreePath where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Structs.TreePath.treePathPrev",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Structs-TreePath.html#v:treePathPrev"
        }


#endif

-- method TreePath::to_string
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TreePath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GtkTreePath-struct"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_tree_path_to_string" gtk_tree_path_to_string :: 
    Ptr TreePath ->                         -- path : TInterface (Name {namespace = "Gtk", name = "TreePath"})
    IO CString

-- | Generates a string representation of the path.
-- 
-- This string is a “:” separated list of numbers.
-- For example, “4:10:0:3” would be an acceptable
-- return value for this string. If the path has
-- depth 0, 'P.Nothing' is returned.
treePathToString ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TreePath
    -- ^ /@path@/: A t'GI.Gtk.Structs.TreePath.TreePath'-struct
    -> m (Maybe T.Text)
    -- ^ __Returns:__ A newly-allocated string.
    --     Must be freed with 'GI.GLib.Functions.free'.
treePathToString :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
TreePath -> m (Maybe Text)
treePathToString TreePath
path = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    Ptr TreePath
path' <- TreePath -> IO (Ptr TreePath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TreePath
path
    CString
result <- Ptr TreePath -> IO CString
gtk_tree_path_to_string Ptr TreePath
path'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    TreePath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TreePath
path
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data TreePathToStringMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m) => O.OverloadedMethod TreePathToStringMethodInfo TreePath signature where
    overloadedMethod = treePathToString

instance O.OverloadedMethodInfo TreePathToStringMethodInfo TreePath where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Structs.TreePath.treePathToString",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Structs-TreePath.html#v:treePathToString"
        }


#endif

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

foreign import ccall "gtk_tree_path_up" gtk_tree_path_up :: 
    Ptr TreePath ->                         -- path : TInterface (Name {namespace = "Gtk", name = "TreePath"})
    IO CInt

-- | Moves the /@path@/ to point to its parent node, if it has a parent.
treePathUp ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TreePath
    -- ^ /@path@/: a t'GI.Gtk.Structs.TreePath.TreePath'-struct
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@path@/ has a parent, and the move was made
treePathUp :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
TreePath -> m Bool
treePathUp TreePath
path = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr TreePath
path' <- TreePath -> IO (Ptr TreePath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TreePath
path
    CInt
result <- Ptr TreePath -> IO CInt
gtk_tree_path_up Ptr TreePath
path'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    TreePath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TreePath
path
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TreePathUpMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.OverloadedMethod TreePathUpMethodInfo TreePath signature where
    overloadedMethod = treePathUp

instance O.OverloadedMethodInfo TreePathUpMethodInfo TreePath where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Structs.TreePath.treePathUp",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Structs-TreePath.html#v:treePathUp"
        }


#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveTreePathMethod (t :: Symbol) (o :: *) :: * where
    ResolveTreePathMethod "appendIndex" o = TreePathAppendIndexMethodInfo
    ResolveTreePathMethod "compare" o = TreePathCompareMethodInfo
    ResolveTreePathMethod "copy" o = TreePathCopyMethodInfo
    ResolveTreePathMethod "down" o = TreePathDownMethodInfo
    ResolveTreePathMethod "free" o = TreePathFreeMethodInfo
    ResolveTreePathMethod "isAncestor" o = TreePathIsAncestorMethodInfo
    ResolveTreePathMethod "isDescendant" o = TreePathIsDescendantMethodInfo
    ResolveTreePathMethod "next" o = TreePathNextMethodInfo
    ResolveTreePathMethod "prependIndex" o = TreePathPrependIndexMethodInfo
    ResolveTreePathMethod "prev" o = TreePathPrevMethodInfo
    ResolveTreePathMethod "toString" o = TreePathToStringMethodInfo
    ResolveTreePathMethod "up" o = TreePathUpMethodInfo
    ResolveTreePathMethod "getDepth" o = TreePathGetDepthMethodInfo
    ResolveTreePathMethod "getIndices" o = TreePathGetIndicesMethodInfo
    ResolveTreePathMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif