{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- The GTree struct is an opaque data structure representing a
-- [balanced binary tree][glib-Balanced-Binary-Trees]. It should be
-- accessed only by using the following functions.

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

module GI.GLib.Structs.Tree
    ( 

-- * Exported types
    Tree(..)                                ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [destroy]("GI.GLib.Structs.Tree#g:method:destroy"), [height]("GI.GLib.Structs.Tree#g:method:height"), [insert]("GI.GLib.Structs.Tree#g:method:insert"), [insertNode]("GI.GLib.Structs.Tree#g:method:insertNode"), [lookup]("GI.GLib.Structs.Tree#g:method:lookup"), [lookupExtended]("GI.GLib.Structs.Tree#g:method:lookupExtended"), [lookupNode]("GI.GLib.Structs.Tree#g:method:lookupNode"), [lowerBound]("GI.GLib.Structs.Tree#g:method:lowerBound"), [nnodes]("GI.GLib.Structs.Tree#g:method:nnodes"), [nodeFirst]("GI.GLib.Structs.Tree#g:method:nodeFirst"), [nodeLast]("GI.GLib.Structs.Tree#g:method:nodeLast"), [ref]("GI.GLib.Structs.Tree#g:method:ref"), [remove]("GI.GLib.Structs.Tree#g:method:remove"), [removeAll]("GI.GLib.Structs.Tree#g:method:removeAll"), [replace]("GI.GLib.Structs.Tree#g:method:replace"), [replaceNode]("GI.GLib.Structs.Tree#g:method:replaceNode"), [steal]("GI.GLib.Structs.Tree#g:method:steal"), [unref]("GI.GLib.Structs.Tree#g:method:unref"), [upperBound]("GI.GLib.Structs.Tree#g:method:upperBound").
-- 
-- ==== Getters
-- /None/.
-- 
-- ==== Setters
-- /None/.

#if defined(ENABLE_OVERLOADING)
    ResolveTreeMethod                       ,
#endif

-- ** destroy #method:destroy#

#if defined(ENABLE_OVERLOADING)
    TreeDestroyMethodInfo                   ,
#endif
    treeDestroy                             ,


-- ** height #method:height#

#if defined(ENABLE_OVERLOADING)
    TreeHeightMethodInfo                    ,
#endif
    treeHeight                              ,


-- ** insert #method:insert#

#if defined(ENABLE_OVERLOADING)
    TreeInsertMethodInfo                    ,
#endif
    treeInsert                              ,


-- ** insertNode #method:insertNode#

#if defined(ENABLE_OVERLOADING)
    TreeInsertNodeMethodInfo                ,
#endif
    treeInsertNode                          ,


-- ** lookup #method:lookup#

#if defined(ENABLE_OVERLOADING)
    TreeLookupMethodInfo                    ,
#endif
    treeLookup                              ,


-- ** lookupExtended #method:lookupExtended#

#if defined(ENABLE_OVERLOADING)
    TreeLookupExtendedMethodInfo            ,
#endif
    treeLookupExtended                      ,


-- ** lookupNode #method:lookupNode#

#if defined(ENABLE_OVERLOADING)
    TreeLookupNodeMethodInfo                ,
#endif
    treeLookupNode                          ,


-- ** lowerBound #method:lowerBound#

#if defined(ENABLE_OVERLOADING)
    TreeLowerBoundMethodInfo                ,
#endif
    treeLowerBound                          ,


-- ** newFull #method:newFull#

    treeNewFull                             ,


-- ** nnodes #method:nnodes#

#if defined(ENABLE_OVERLOADING)
    TreeNnodesMethodInfo                    ,
#endif
    treeNnodes                              ,


-- ** nodeFirst #method:nodeFirst#

#if defined(ENABLE_OVERLOADING)
    TreeNodeFirstMethodInfo                 ,
#endif
    treeNodeFirst                           ,


-- ** nodeLast #method:nodeLast#

#if defined(ENABLE_OVERLOADING)
    TreeNodeLastMethodInfo                  ,
#endif
    treeNodeLast                            ,


-- ** ref #method:ref#

#if defined(ENABLE_OVERLOADING)
    TreeRefMethodInfo                       ,
#endif
    treeRef                                 ,


-- ** remove #method:remove#

#if defined(ENABLE_OVERLOADING)
    TreeRemoveMethodInfo                    ,
#endif
    treeRemove                              ,


-- ** removeAll #method:removeAll#

#if defined(ENABLE_OVERLOADING)
    TreeRemoveAllMethodInfo                 ,
#endif
    treeRemoveAll                           ,


-- ** replace #method:replace#

#if defined(ENABLE_OVERLOADING)
    TreeReplaceMethodInfo                   ,
#endif
    treeReplace                             ,


-- ** replaceNode #method:replaceNode#

#if defined(ENABLE_OVERLOADING)
    TreeReplaceNodeMethodInfo               ,
#endif
    treeReplaceNode                         ,


-- ** steal #method:steal#

#if defined(ENABLE_OVERLOADING)
    TreeStealMethodInfo                     ,
#endif
    treeSteal                               ,


-- ** unref #method:unref#

#if defined(ENABLE_OVERLOADING)
    TreeUnrefMethodInfo                     ,
#endif
    treeUnref                               ,


-- ** upperBound #method:upperBound#

#if defined(ENABLE_OVERLOADING)
    TreeUpperBoundMethodInfo                ,
#endif
    treeUpperBound                          ,




    ) 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 {-# SOURCE #-} qualified GI.GLib.Structs.TreeNode as GLib.TreeNode

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

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

foreign import ccall "g_tree_get_type" c_g_tree_get_type :: 
    IO GType

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

instance B.Types.TypedObject Tree where
    glibType :: IO GType
glibType = IO GType
c_g_tree_get_type

instance B.Types.GBoxed Tree

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


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

-- method Tree::new_full
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "key_compare_func"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "CompareDataFunc" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "qsort()-style comparison function"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeNotified
--           , argClosure = 1
--           , argDestroy = 3
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key_compare_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "data to pass to comparison function"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key_destroy_func"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "DestroyNotify" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a function to free the memory allocated for the key\n  used when removing the entry from the #GTree or %NULL if you don't\n  want to supply such a function"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value_destroy_func"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "DestroyNotify" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a function to free the memory allocated for the\n  value used when removing the entry from the #GTree or %NULL if you\n  don't want to supply such a function"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "Tree" })
-- throws : False
-- Skip return : False

foreign import ccall "g_tree_new_full" g_tree_new_full :: 
    FunPtr GLib.Callbacks.C_CompareDataFunc -> -- key_compare_func : TInterface (Name {namespace = "GLib", name = "CompareDataFunc"})
    Ptr () ->                               -- key_compare_data : TBasicType TPtr
    FunPtr GLib.Callbacks.C_DestroyNotify -> -- key_destroy_func : TInterface (Name {namespace = "GLib", name = "DestroyNotify"})
    FunPtr GLib.Callbacks.C_DestroyNotify -> -- value_destroy_func : TInterface (Name {namespace = "GLib", name = "DestroyNotify"})
    IO (Ptr Tree)

-- | Creates a new t'GI.GLib.Structs.Tree.Tree' like @/g_tree_new()/@ and allows to specify functions
-- to free the memory allocated for the key and value that get called when
-- removing the entry from the t'GI.GLib.Structs.Tree.Tree'.
treeNewFull ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GLib.Callbacks.CompareDataFunc
    -- ^ /@keyCompareFunc@/: @/qsort()/@-style comparison function
    -> GLib.Callbacks.DestroyNotify
    -- ^ /@keyDestroyFunc@/: a function to free the memory allocated for the key
    --   used when removing the entry from the t'GI.GLib.Structs.Tree.Tree' or 'P.Nothing' if you don\'t
    --   want to supply such a function
    -> m Tree
    -- ^ __Returns:__ a newly allocated t'GI.GLib.Structs.Tree.Tree'
treeNewFull :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
CompareDataFunc -> DestroyNotify -> m Tree
treeNewFull CompareDataFunc
keyCompareFunc DestroyNotify
keyDestroyFunc = IO Tree -> m Tree
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Tree -> m Tree) -> IO Tree -> m Tree
forall a b. (a -> b) -> a -> b
$ do
    FunPtr C_CompareDataFunc
keyCompareFunc' <- C_CompareDataFunc -> IO (FunPtr C_CompareDataFunc)
GLib.Callbacks.mk_CompareDataFunc (Maybe (Ptr (FunPtr C_CompareDataFunc))
-> C_CompareDataFunc -> C_CompareDataFunc
GLib.Callbacks.wrap_CompareDataFunc Maybe (Ptr (FunPtr C_CompareDataFunc))
forall a. Maybe a
Nothing (CompareDataFunc -> C_CompareDataFunc
GLib.Callbacks.drop_closures_CompareDataFunc CompareDataFunc
keyCompareFunc))
    Ptr (FunPtr DestroyNotify)
ptrkeyDestroyFunc <- IO (Ptr (FunPtr DestroyNotify))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr GLib.Callbacks.C_DestroyNotify))
    FunPtr DestroyNotify
keyDestroyFunc' <- DestroyNotify -> IO (FunPtr DestroyNotify)
GLib.Callbacks.mk_DestroyNotify (Maybe (Ptr (FunPtr DestroyNotify))
-> DestroyNotify -> DestroyNotify
GLib.Callbacks.wrap_DestroyNotify (Ptr (FunPtr DestroyNotify) -> Maybe (Ptr (FunPtr DestroyNotify))
forall a. a -> Maybe a
Just Ptr (FunPtr DestroyNotify)
ptrkeyDestroyFunc) DestroyNotify
keyDestroyFunc)
    Ptr (FunPtr DestroyNotify) -> FunPtr DestroyNotify -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr DestroyNotify)
ptrkeyDestroyFunc FunPtr DestroyNotify
keyDestroyFunc'
    let keyCompareData :: Ptr ()
keyCompareData = FunPtr C_CompareDataFunc -> Ptr ()
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr C_CompareDataFunc
keyCompareFunc'
    let valueDestroyFunc :: FunPtr (Ptr a -> IO ())
valueDestroyFunc = FunPtr (Ptr a -> IO ())
forall a. FunPtr (Ptr a -> IO ())
SP.safeFreeFunPtrPtr
    Ptr Tree
result <- FunPtr C_CompareDataFunc
-> Ptr ()
-> FunPtr DestroyNotify
-> FunPtr DestroyNotify
-> IO (Ptr Tree)
g_tree_new_full FunPtr C_CompareDataFunc
keyCompareFunc' Ptr ()
keyCompareData FunPtr DestroyNotify
keyDestroyFunc' FunPtr DestroyNotify
forall a. FunPtr (Ptr a -> IO ())
valueDestroyFunc
    Text -> Ptr Tree -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"treeNewFull" Ptr Tree
result
    Tree
result' <- ((ManagedPtr Tree -> Tree) -> Ptr Tree -> IO Tree
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Tree -> Tree
Tree) Ptr Tree
result
    Tree -> IO Tree
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Tree
result'

#if defined(ENABLE_OVERLOADING)
#endif

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

foreign import ccall "g_tree_destroy" g_tree_destroy :: 
    Ptr Tree ->                             -- tree : TInterface (Name {namespace = "GLib", name = "Tree"})
    IO ()

-- | Removes all keys and values from the t'GI.GLib.Structs.Tree.Tree' and decreases its
-- reference count by one. If keys and\/or values are dynamically
-- allocated, you should either free them first or create the t'GI.GLib.Structs.Tree.Tree'
-- using 'GI.GLib.Structs.Tree.treeNewFull'. In the latter case the destroy functions
-- you supplied will be called on all keys and values before destroying
-- the t'GI.GLib.Structs.Tree.Tree'.
treeDestroy ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Tree
    -- ^ /@tree@/: a t'GI.GLib.Structs.Tree.Tree'
    -> m ()
treeDestroy :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Tree -> m ()
treeDestroy Tree
tree = 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 Tree
tree' <- Tree -> IO (Ptr Tree)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Tree
tree
    Ptr Tree -> IO ()
g_tree_destroy Ptr Tree
tree'
    Tree -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Tree
tree
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TreeDestroyMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod TreeDestroyMethodInfo Tree signature where
    overloadedMethod = treeDestroy

instance O.OverloadedMethodInfo TreeDestroyMethodInfo Tree where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Tree.treeDestroy",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.27/docs/GI-GLib-Structs-Tree.html#v:treeDestroy"
        })


#endif

-- method Tree::height
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "tree"
--           , argType = TInterface Name { namespace = "GLib" , name = "Tree" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTree" , 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 "g_tree_height" g_tree_height :: 
    Ptr Tree ->                             -- tree : TInterface (Name {namespace = "GLib", name = "Tree"})
    IO Int32

-- | Gets the height of a t'GI.GLib.Structs.Tree.Tree'.
-- 
-- If the t'GI.GLib.Structs.Tree.Tree' contains no nodes, the height is 0.
-- If the t'GI.GLib.Structs.Tree.Tree' contains only one root node the height is 1.
-- If the root node has children the height is 2, etc.
treeHeight ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Tree
    -- ^ /@tree@/: a t'GI.GLib.Structs.Tree.Tree'
    -> m Int32
    -- ^ __Returns:__ the height of /@tree@/
treeHeight :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Tree -> m Int32
treeHeight Tree
tree = IO Int32 -> m Int32
forall a. IO a -> m a
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 Tree
tree' <- Tree -> IO (Ptr Tree)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Tree
tree
    Int32
result <- Ptr Tree -> IO Int32
g_tree_height Ptr Tree
tree'
    Tree -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Tree
tree
    Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data TreeHeightMethodInfo
instance (signature ~ (m Int32), MonadIO m) => O.OverloadedMethod TreeHeightMethodInfo Tree signature where
    overloadedMethod = treeHeight

instance O.OverloadedMethodInfo TreeHeightMethodInfo Tree where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Tree.treeHeight",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.27/docs/GI-GLib-Structs-Tree.html#v:treeHeight"
        })


#endif

-- method Tree::insert
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "tree"
--           , argType = TInterface Name { namespace = "GLib" , name = "Tree" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTree" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the key to insert" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the value corresponding to the key"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_tree_insert" g_tree_insert :: 
    Ptr Tree ->                             -- tree : TInterface (Name {namespace = "GLib", name = "Tree"})
    Ptr () ->                               -- key : TBasicType TPtr
    Ptr () ->                               -- value : TBasicType TPtr
    IO ()

-- | Inserts a key\/value pair into a t'GI.GLib.Structs.Tree.Tree'.
-- 
-- Inserts a new key and value into a t'GI.GLib.Structs.Tree.Tree' as 'GI.GLib.Structs.Tree.treeInsertNode' does,
-- only this function does not return the inserted or set node.
treeInsert ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Tree
    -- ^ /@tree@/: a t'GI.GLib.Structs.Tree.Tree'
    -> Ptr ()
    -- ^ /@key@/: the key to insert
    -> Ptr ()
    -- ^ /@value@/: the value corresponding to the key
    -> m ()
treeInsert :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Tree -> Ptr () -> Ptr () -> m ()
treeInsert Tree
tree Ptr ()
key Ptr ()
value = 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 Tree
tree' <- Tree -> IO (Ptr Tree)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Tree
tree
    Ptr Tree -> Ptr () -> DestroyNotify
g_tree_insert Ptr Tree
tree' Ptr ()
key Ptr ()
value
    Tree -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Tree
tree
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TreeInsertMethodInfo
instance (signature ~ (Ptr () -> Ptr () -> m ()), MonadIO m) => O.OverloadedMethod TreeInsertMethodInfo Tree signature where
    overloadedMethod = treeInsert

instance O.OverloadedMethodInfo TreeInsertMethodInfo Tree where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Tree.treeInsert",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.27/docs/GI-GLib-Structs-Tree.html#v:treeInsert"
        })


#endif

-- method Tree::insert_node
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "tree"
--           , argType = TInterface Name { namespace = "GLib" , name = "Tree" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTree" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the key to insert" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the value corresponding to the key"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "TreeNode" })
-- throws : False
-- Skip return : False

foreign import ccall "g_tree_insert_node" g_tree_insert_node :: 
    Ptr Tree ->                             -- tree : TInterface (Name {namespace = "GLib", name = "Tree"})
    Ptr () ->                               -- key : TBasicType TPtr
    Ptr () ->                               -- value : TBasicType TPtr
    IO (Ptr GLib.TreeNode.TreeNode)

-- | Inserts a key\/value pair into a t'GI.GLib.Structs.Tree.Tree'.
-- 
-- If the given key already exists in the t'GI.GLib.Structs.Tree.Tree' its corresponding value
-- is set to the new value. If you supplied a /@valueDestroyFunc@/ when
-- creating the t'GI.GLib.Structs.Tree.Tree', the old value is freed using that function. If
-- you supplied a /@keyDestroyFunc@/ when creating the t'GI.GLib.Structs.Tree.Tree', the passed
-- key is freed using that function.
-- 
-- The tree is automatically \'balanced\' as new key\/value pairs are added,
-- so that the distance from the root to every leaf is as small as possible.
-- The cost of maintaining a balanced tree while inserting new key\/value
-- result in a O(n log(n)) operation where most of the other operations
-- are O(log(n)).
-- 
-- /Since: 2.68/
treeInsertNode ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Tree
    -- ^ /@tree@/: a t'GI.GLib.Structs.Tree.Tree'
    -> Ptr ()
    -- ^ /@key@/: the key to insert
    -> Ptr ()
    -- ^ /@value@/: the value corresponding to the key
    -> m GLib.TreeNode.TreeNode
    -- ^ __Returns:__ the inserted (or set) node.
treeInsertNode :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Tree -> Ptr () -> Ptr () -> m TreeNode
treeInsertNode Tree
tree Ptr ()
key Ptr ()
value = IO TreeNode -> m TreeNode
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TreeNode -> m TreeNode) -> IO TreeNode -> m TreeNode
forall a b. (a -> b) -> a -> b
$ do
    Ptr Tree
tree' <- Tree -> IO (Ptr Tree)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Tree
tree
    Ptr TreeNode
result <- Ptr Tree -> Ptr () -> Ptr () -> IO (Ptr TreeNode)
g_tree_insert_node Ptr Tree
tree' Ptr ()
key Ptr ()
value
    Text -> Ptr TreeNode -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"treeInsertNode" Ptr TreeNode
result
    TreeNode
result' <- ((ManagedPtr TreeNode -> TreeNode) -> Ptr TreeNode -> IO TreeNode
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr TreeNode -> TreeNode
GLib.TreeNode.TreeNode) Ptr TreeNode
result
    Tree -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Tree
tree
    TreeNode -> IO TreeNode
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return TreeNode
result'

#if defined(ENABLE_OVERLOADING)
data TreeInsertNodeMethodInfo
instance (signature ~ (Ptr () -> Ptr () -> m GLib.TreeNode.TreeNode), MonadIO m) => O.OverloadedMethod TreeInsertNodeMethodInfo Tree signature where
    overloadedMethod = treeInsertNode

instance O.OverloadedMethodInfo TreeInsertNodeMethodInfo Tree where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Tree.treeInsertNode",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.27/docs/GI-GLib-Structs-Tree.html#v:treeInsertNode"
        })


#endif

-- method Tree::lookup
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "tree"
--           , argType = TInterface Name { namespace = "GLib" , name = "Tree" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTree" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the key to look up" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TPtr)
-- throws : False
-- Skip return : False

foreign import ccall "g_tree_lookup" g_tree_lookup :: 
    Ptr Tree ->                             -- tree : TInterface (Name {namespace = "GLib", name = "Tree"})
    Ptr () ->                               -- key : TBasicType TPtr
    IO (Ptr ())

-- | Gets the value corresponding to the given key. Since a t'GI.GLib.Structs.Tree.Tree' is
-- automatically balanced as key\/value pairs are added, key lookup
-- is O(log n) (where n is the number of key\/value pairs in the tree).
treeLookup ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Tree
    -- ^ /@tree@/: a t'GI.GLib.Structs.Tree.Tree'
    -> Ptr ()
    -- ^ /@key@/: the key to look up
    -> m (Ptr ())
    -- ^ __Returns:__ the value corresponding to the key, or 'P.Nothing'
    --     if the key was not found
treeLookup :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Tree -> Ptr () -> m (Ptr ())
treeLookup Tree
tree Ptr ()
key = IO (Ptr ()) -> m (Ptr ())
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Ptr ()) -> m (Ptr ())) -> IO (Ptr ()) -> m (Ptr ())
forall a b. (a -> b) -> a -> b
$ do
    Ptr Tree
tree' <- Tree -> IO (Ptr Tree)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Tree
tree
    Ptr ()
result <- Ptr Tree -> Ptr () -> IO (Ptr ())
g_tree_lookup Ptr Tree
tree' Ptr ()
key
    Tree -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Tree
tree
    Ptr () -> IO (Ptr ())
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ()
result

#if defined(ENABLE_OVERLOADING)
data TreeLookupMethodInfo
instance (signature ~ (Ptr () -> m (Ptr ())), MonadIO m) => O.OverloadedMethod TreeLookupMethodInfo Tree signature where
    overloadedMethod = treeLookup

instance O.OverloadedMethodInfo TreeLookupMethodInfo Tree where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Tree.treeLookup",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.27/docs/GI-GLib-Structs-Tree.html#v:treeLookup"
        })


#endif

-- method Tree::lookup_extended
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "tree"
--           , argType = TInterface Name { namespace = "GLib" , name = "Tree" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTree" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "lookup_key"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the key to look up" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "orig_key"
--           , argType = TBasicType TPtr
--           , direction = DirectionOut
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "returns the original key"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TPtr
--           , direction = DirectionOut
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "returns the value associated with the key"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_tree_lookup_extended" g_tree_lookup_extended :: 
    Ptr Tree ->                             -- tree : TInterface (Name {namespace = "GLib", name = "Tree"})
    Ptr () ->                               -- lookup_key : TBasicType TPtr
    Ptr (Ptr ()) ->                         -- orig_key : TBasicType TPtr
    Ptr (Ptr ()) ->                         -- value : TBasicType TPtr
    IO CInt

-- | Looks up a key in the t'GI.GLib.Structs.Tree.Tree', returning the original key and the
-- associated value. This is useful if you need to free the memory
-- allocated for the original key, for example before calling
-- 'GI.GLib.Structs.Tree.treeRemove'.
treeLookupExtended ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Tree
    -- ^ /@tree@/: a t'GI.GLib.Structs.Tree.Tree'
    -> Ptr ()
    -- ^ /@lookupKey@/: the key to look up
    -> m ((Bool, Ptr (), Ptr ()))
    -- ^ __Returns:__ 'P.True' if the key was found in the t'GI.GLib.Structs.Tree.Tree'
treeLookupExtended :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Tree -> Ptr () -> m (Bool, Ptr (), Ptr ())
treeLookupExtended Tree
tree Ptr ()
lookupKey = IO (Bool, Ptr (), Ptr ()) -> m (Bool, Ptr (), Ptr ())
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Ptr (), Ptr ()) -> m (Bool, Ptr (), Ptr ()))
-> IO (Bool, Ptr (), Ptr ()) -> m (Bool, Ptr (), Ptr ())
forall a b. (a -> b) -> a -> b
$ do
    Ptr Tree
tree' <- Tree -> IO (Ptr Tree)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Tree
tree
    Ptr (Ptr ())
origKey <- IO (Ptr (Ptr ()))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (Ptr ()))
    Ptr (Ptr ())
value <- IO (Ptr (Ptr ()))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (Ptr ()))
    CInt
result <- Ptr Tree -> Ptr () -> Ptr (Ptr ()) -> Ptr (Ptr ()) -> IO CInt
g_tree_lookup_extended Ptr Tree
tree' Ptr ()
lookupKey Ptr (Ptr ())
origKey Ptr (Ptr ())
value
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Ptr ()
origKey' <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr ())
origKey
    Ptr ()
value' <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr ())
value
    Tree -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Tree
tree
    Ptr (Ptr ()) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr ())
origKey
    Ptr (Ptr ()) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr ())
value
    (Bool, Ptr (), Ptr ()) -> IO (Bool, Ptr (), Ptr ())
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', Ptr ()
origKey', Ptr ()
value')

#if defined(ENABLE_OVERLOADING)
data TreeLookupExtendedMethodInfo
instance (signature ~ (Ptr () -> m ((Bool, Ptr (), Ptr ()))), MonadIO m) => O.OverloadedMethod TreeLookupExtendedMethodInfo Tree signature where
    overloadedMethod = treeLookupExtended

instance O.OverloadedMethodInfo TreeLookupExtendedMethodInfo Tree where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Tree.treeLookupExtended",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.27/docs/GI-GLib-Structs-Tree.html#v:treeLookupExtended"
        })


#endif

-- method Tree::lookup_node
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "tree"
--           , argType = TInterface Name { namespace = "GLib" , name = "Tree" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTree" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the key to look up" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "TreeNode" })
-- throws : False
-- Skip return : False

foreign import ccall "g_tree_lookup_node" g_tree_lookup_node :: 
    Ptr Tree ->                             -- tree : TInterface (Name {namespace = "GLib", name = "Tree"})
    Ptr () ->                               -- key : TBasicType TPtr
    IO (Ptr GLib.TreeNode.TreeNode)

-- | Gets the tree node corresponding to the given key. Since a t'GI.GLib.Structs.Tree.Tree' is
-- automatically balanced as key\/value pairs are added, key lookup
-- is O(log n) (where n is the number of key\/value pairs in the tree).
-- 
-- /Since: 2.68/
treeLookupNode ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Tree
    -- ^ /@tree@/: a t'GI.GLib.Structs.Tree.Tree'
    -> Ptr ()
    -- ^ /@key@/: the key to look up
    -> m (Maybe GLib.TreeNode.TreeNode)
    -- ^ __Returns:__ the tree node corresponding to
    --          the key, or 'P.Nothing' if the key was not found
treeLookupNode :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Tree -> Ptr () -> m (Maybe TreeNode)
treeLookupNode Tree
tree Ptr ()
key = IO (Maybe TreeNode) -> m (Maybe TreeNode)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe TreeNode) -> m (Maybe TreeNode))
-> IO (Maybe TreeNode) -> m (Maybe TreeNode)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Tree
tree' <- Tree -> IO (Ptr Tree)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Tree
tree
    Ptr TreeNode
result <- Ptr Tree -> Ptr () -> IO (Ptr TreeNode)
g_tree_lookup_node Ptr Tree
tree' Ptr ()
key
    Maybe TreeNode
maybeResult <- Ptr TreeNode
-> (Ptr TreeNode -> IO TreeNode) -> IO (Maybe TreeNode)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr TreeNode
result ((Ptr TreeNode -> IO TreeNode) -> IO (Maybe TreeNode))
-> (Ptr TreeNode -> IO TreeNode) -> IO (Maybe TreeNode)
forall a b. (a -> b) -> a -> b
$ \Ptr TreeNode
result' -> do
        TreeNode
result'' <- ((ManagedPtr TreeNode -> TreeNode) -> Ptr TreeNode -> IO TreeNode
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr TreeNode -> TreeNode
GLib.TreeNode.TreeNode) Ptr TreeNode
result'
        TreeNode -> IO TreeNode
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return TreeNode
result''
    Tree -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Tree
tree
    Maybe TreeNode -> IO (Maybe TreeNode)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TreeNode
maybeResult

#if defined(ENABLE_OVERLOADING)
data TreeLookupNodeMethodInfo
instance (signature ~ (Ptr () -> m (Maybe GLib.TreeNode.TreeNode)), MonadIO m) => O.OverloadedMethod TreeLookupNodeMethodInfo Tree signature where
    overloadedMethod = treeLookupNode

instance O.OverloadedMethodInfo TreeLookupNodeMethodInfo Tree where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Tree.treeLookupNode",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.27/docs/GI-GLib-Structs-Tree.html#v:treeLookupNode"
        })


#endif

-- method Tree::lower_bound
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "tree"
--           , argType = TInterface Name { namespace = "GLib" , name = "Tree" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTree" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the key to calculate the lower bound for"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "TreeNode" })
-- throws : False
-- Skip return : False

foreign import ccall "g_tree_lower_bound" g_tree_lower_bound :: 
    Ptr Tree ->                             -- tree : TInterface (Name {namespace = "GLib", name = "Tree"})
    Ptr () ->                               -- key : TBasicType TPtr
    IO (Ptr GLib.TreeNode.TreeNode)

-- | Gets the lower bound node corresponding to the given key,
-- or 'P.Nothing' if the tree is empty or all the nodes in the tree
-- have keys that are strictly lower than the searched key.
-- 
-- The lower bound is the first node that has its key greater
-- than or equal to the searched key.
-- 
-- /Since: 2.68/
treeLowerBound ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Tree
    -- ^ /@tree@/: a t'GI.GLib.Structs.Tree.Tree'
    -> Ptr ()
    -- ^ /@key@/: the key to calculate the lower bound for
    -> m (Maybe GLib.TreeNode.TreeNode)
    -- ^ __Returns:__ the tree node corresponding to
    --          the lower bound, or 'P.Nothing' if the tree is empty or has only
    --          keys strictly lower than the searched key.
treeLowerBound :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Tree -> Ptr () -> m (Maybe TreeNode)
treeLowerBound Tree
tree Ptr ()
key = IO (Maybe TreeNode) -> m (Maybe TreeNode)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe TreeNode) -> m (Maybe TreeNode))
-> IO (Maybe TreeNode) -> m (Maybe TreeNode)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Tree
tree' <- Tree -> IO (Ptr Tree)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Tree
tree
    Ptr TreeNode
result <- Ptr Tree -> Ptr () -> IO (Ptr TreeNode)
g_tree_lower_bound Ptr Tree
tree' Ptr ()
key
    Maybe TreeNode
maybeResult <- Ptr TreeNode
-> (Ptr TreeNode -> IO TreeNode) -> IO (Maybe TreeNode)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr TreeNode
result ((Ptr TreeNode -> IO TreeNode) -> IO (Maybe TreeNode))
-> (Ptr TreeNode -> IO TreeNode) -> IO (Maybe TreeNode)
forall a b. (a -> b) -> a -> b
$ \Ptr TreeNode
result' -> do
        TreeNode
result'' <- ((ManagedPtr TreeNode -> TreeNode) -> Ptr TreeNode -> IO TreeNode
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr TreeNode -> TreeNode
GLib.TreeNode.TreeNode) Ptr TreeNode
result'
        TreeNode -> IO TreeNode
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return TreeNode
result''
    Tree -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Tree
tree
    Maybe TreeNode -> IO (Maybe TreeNode)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TreeNode
maybeResult

#if defined(ENABLE_OVERLOADING)
data TreeLowerBoundMethodInfo
instance (signature ~ (Ptr () -> m (Maybe GLib.TreeNode.TreeNode)), MonadIO m) => O.OverloadedMethod TreeLowerBoundMethodInfo Tree signature where
    overloadedMethod = treeLowerBound

instance O.OverloadedMethodInfo TreeLowerBoundMethodInfo Tree where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Tree.treeLowerBound",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.27/docs/GI-GLib-Structs-Tree.html#v:treeLowerBound"
        })


#endif

-- method Tree::nnodes
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "tree"
--           , argType = TInterface Name { namespace = "GLib" , name = "Tree" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTree" , 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 "g_tree_nnodes" g_tree_nnodes :: 
    Ptr Tree ->                             -- tree : TInterface (Name {namespace = "GLib", name = "Tree"})
    IO Int32

-- | Gets the number of nodes in a t'GI.GLib.Structs.Tree.Tree'.
treeNnodes ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Tree
    -- ^ /@tree@/: a t'GI.GLib.Structs.Tree.Tree'
    -> m Int32
    -- ^ __Returns:__ the number of nodes in /@tree@/
treeNnodes :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Tree -> m Int32
treeNnodes Tree
tree = IO Int32 -> m Int32
forall a. IO a -> m a
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 Tree
tree' <- Tree -> IO (Ptr Tree)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Tree
tree
    Int32
result <- Ptr Tree -> IO Int32
g_tree_nnodes Ptr Tree
tree'
    Tree -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Tree
tree
    Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data TreeNnodesMethodInfo
instance (signature ~ (m Int32), MonadIO m) => O.OverloadedMethod TreeNnodesMethodInfo Tree signature where
    overloadedMethod = treeNnodes

instance O.OverloadedMethodInfo TreeNnodesMethodInfo Tree where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Tree.treeNnodes",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.27/docs/GI-GLib-Structs-Tree.html#v:treeNnodes"
        })


#endif

-- method Tree::node_first
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "tree"
--           , argType = TInterface Name { namespace = "GLib" , name = "Tree" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTree" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "TreeNode" })
-- throws : False
-- Skip return : False

foreign import ccall "g_tree_node_first" g_tree_node_first :: 
    Ptr Tree ->                             -- tree : TInterface (Name {namespace = "GLib", name = "Tree"})
    IO (Ptr GLib.TreeNode.TreeNode)

-- | Returns the first in-order node of the tree, or 'P.Nothing'
-- for an empty tree.
-- 
-- /Since: 2.68/
treeNodeFirst ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Tree
    -- ^ /@tree@/: a t'GI.GLib.Structs.Tree.Tree'
    -> m (Maybe GLib.TreeNode.TreeNode)
    -- ^ __Returns:__ the first node in the tree
treeNodeFirst :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Tree -> m (Maybe TreeNode)
treeNodeFirst Tree
tree = IO (Maybe TreeNode) -> m (Maybe TreeNode)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe TreeNode) -> m (Maybe TreeNode))
-> IO (Maybe TreeNode) -> m (Maybe TreeNode)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Tree
tree' <- Tree -> IO (Ptr Tree)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Tree
tree
    Ptr TreeNode
result <- Ptr Tree -> IO (Ptr TreeNode)
g_tree_node_first Ptr Tree
tree'
    Maybe TreeNode
maybeResult <- Ptr TreeNode
-> (Ptr TreeNode -> IO TreeNode) -> IO (Maybe TreeNode)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr TreeNode
result ((Ptr TreeNode -> IO TreeNode) -> IO (Maybe TreeNode))
-> (Ptr TreeNode -> IO TreeNode) -> IO (Maybe TreeNode)
forall a b. (a -> b) -> a -> b
$ \Ptr TreeNode
result' -> do
        TreeNode
result'' <- ((ManagedPtr TreeNode -> TreeNode) -> Ptr TreeNode -> IO TreeNode
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr TreeNode -> TreeNode
GLib.TreeNode.TreeNode) Ptr TreeNode
result'
        TreeNode -> IO TreeNode
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return TreeNode
result''
    Tree -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Tree
tree
    Maybe TreeNode -> IO (Maybe TreeNode)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TreeNode
maybeResult

#if defined(ENABLE_OVERLOADING)
data TreeNodeFirstMethodInfo
instance (signature ~ (m (Maybe GLib.TreeNode.TreeNode)), MonadIO m) => O.OverloadedMethod TreeNodeFirstMethodInfo Tree signature where
    overloadedMethod = treeNodeFirst

instance O.OverloadedMethodInfo TreeNodeFirstMethodInfo Tree where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Tree.treeNodeFirst",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.27/docs/GI-GLib-Structs-Tree.html#v:treeNodeFirst"
        })


#endif

-- method Tree::node_last
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "tree"
--           , argType = TInterface Name { namespace = "GLib" , name = "Tree" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTree" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "TreeNode" })
-- throws : False
-- Skip return : False

foreign import ccall "g_tree_node_last" g_tree_node_last :: 
    Ptr Tree ->                             -- tree : TInterface (Name {namespace = "GLib", name = "Tree"})
    IO (Ptr GLib.TreeNode.TreeNode)

-- | Returns the last in-order node of the tree, or 'P.Nothing'
-- for an empty tree.
-- 
-- /Since: 2.68/
treeNodeLast ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Tree
    -- ^ /@tree@/: a t'GI.GLib.Structs.Tree.Tree'
    -> m (Maybe GLib.TreeNode.TreeNode)
    -- ^ __Returns:__ the last node in the tree
treeNodeLast :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Tree -> m (Maybe TreeNode)
treeNodeLast Tree
tree = IO (Maybe TreeNode) -> m (Maybe TreeNode)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe TreeNode) -> m (Maybe TreeNode))
-> IO (Maybe TreeNode) -> m (Maybe TreeNode)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Tree
tree' <- Tree -> IO (Ptr Tree)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Tree
tree
    Ptr TreeNode
result <- Ptr Tree -> IO (Ptr TreeNode)
g_tree_node_last Ptr Tree
tree'
    Maybe TreeNode
maybeResult <- Ptr TreeNode
-> (Ptr TreeNode -> IO TreeNode) -> IO (Maybe TreeNode)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr TreeNode
result ((Ptr TreeNode -> IO TreeNode) -> IO (Maybe TreeNode))
-> (Ptr TreeNode -> IO TreeNode) -> IO (Maybe TreeNode)
forall a b. (a -> b) -> a -> b
$ \Ptr TreeNode
result' -> do
        TreeNode
result'' <- ((ManagedPtr TreeNode -> TreeNode) -> Ptr TreeNode -> IO TreeNode
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr TreeNode -> TreeNode
GLib.TreeNode.TreeNode) Ptr TreeNode
result'
        TreeNode -> IO TreeNode
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return TreeNode
result''
    Tree -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Tree
tree
    Maybe TreeNode -> IO (Maybe TreeNode)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TreeNode
maybeResult

#if defined(ENABLE_OVERLOADING)
data TreeNodeLastMethodInfo
instance (signature ~ (m (Maybe GLib.TreeNode.TreeNode)), MonadIO m) => O.OverloadedMethod TreeNodeLastMethodInfo Tree signature where
    overloadedMethod = treeNodeLast

instance O.OverloadedMethodInfo TreeNodeLastMethodInfo Tree where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Tree.treeNodeLast",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.27/docs/GI-GLib-Structs-Tree.html#v:treeNodeLast"
        })


#endif

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

foreign import ccall "g_tree_ref" g_tree_ref :: 
    Ptr Tree ->                             -- tree : TInterface (Name {namespace = "GLib", name = "Tree"})
    IO (Ptr Tree)

-- | Increments the reference count of /@tree@/ by one.
-- 
-- It is safe to call this function from any thread.
-- 
-- /Since: 2.22/
treeRef ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Tree
    -- ^ /@tree@/: a t'GI.GLib.Structs.Tree.Tree'
    -> m Tree
    -- ^ __Returns:__ the passed in t'GI.GLib.Structs.Tree.Tree'
treeRef :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Tree -> m Tree
treeRef Tree
tree = IO Tree -> m Tree
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Tree -> m Tree) -> IO Tree -> m Tree
forall a b. (a -> b) -> a -> b
$ do
    Ptr Tree
tree' <- Tree -> IO (Ptr Tree)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Tree
tree
    Ptr Tree
result <- Ptr Tree -> IO (Ptr Tree)
g_tree_ref Ptr Tree
tree'
    Text -> Ptr Tree -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"treeRef" Ptr Tree
result
    Tree
result' <- ((ManagedPtr Tree -> Tree) -> Ptr Tree -> IO Tree
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Tree -> Tree
Tree) Ptr Tree
result
    Tree -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Tree
tree
    Tree -> IO Tree
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Tree
result'

#if defined(ENABLE_OVERLOADING)
data TreeRefMethodInfo
instance (signature ~ (m Tree), MonadIO m) => O.OverloadedMethod TreeRefMethodInfo Tree signature where
    overloadedMethod = treeRef

instance O.OverloadedMethodInfo TreeRefMethodInfo Tree where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Tree.treeRef",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.27/docs/GI-GLib-Structs-Tree.html#v:treeRef"
        })


#endif

-- method Tree::remove
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "tree"
--           , argType = TInterface Name { namespace = "GLib" , name = "Tree" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTree" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the key to remove" , 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 "g_tree_remove" g_tree_remove :: 
    Ptr Tree ->                             -- tree : TInterface (Name {namespace = "GLib", name = "Tree"})
    Ptr () ->                               -- key : TBasicType TPtr
    IO CInt

-- | Removes a key\/value pair from a t'GI.GLib.Structs.Tree.Tree'.
-- 
-- If the t'GI.GLib.Structs.Tree.Tree' was created using 'GI.GLib.Structs.Tree.treeNewFull', the key and value
-- are freed using the supplied destroy functions, otherwise you have to
-- make sure that any dynamically allocated values are freed yourself.
-- If the key does not exist in the t'GI.GLib.Structs.Tree.Tree', the function does nothing.
-- 
-- The cost of maintaining a balanced tree while removing a key\/value
-- result in a O(n log(n)) operation where most of the other operations
-- are O(log(n)).
treeRemove ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Tree
    -- ^ /@tree@/: a t'GI.GLib.Structs.Tree.Tree'
    -> Ptr ()
    -- ^ /@key@/: the key to remove
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the key was found (prior to 2.8, this function
    --     returned nothing)
treeRemove :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Tree -> Ptr () -> m Bool
treeRemove Tree
tree Ptr ()
key = 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 Tree
tree' <- Tree -> IO (Ptr Tree)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Tree
tree
    CInt
result <- Ptr Tree -> Ptr () -> IO CInt
g_tree_remove Ptr Tree
tree' Ptr ()
key
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Tree -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Tree
tree
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TreeRemoveMethodInfo
instance (signature ~ (Ptr () -> m Bool), MonadIO m) => O.OverloadedMethod TreeRemoveMethodInfo Tree signature where
    overloadedMethod = treeRemove

instance O.OverloadedMethodInfo TreeRemoveMethodInfo Tree where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Tree.treeRemove",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.27/docs/GI-GLib-Structs-Tree.html#v:treeRemove"
        })


#endif

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

foreign import ccall "g_tree_remove_all" g_tree_remove_all :: 
    Ptr Tree ->                             -- tree : TInterface (Name {namespace = "GLib", name = "Tree"})
    IO ()

-- | Removes all nodes from a t'GI.GLib.Structs.Tree.Tree' and destroys their keys and values,
-- then resets the t'GI.GLib.Structs.Tree.Tree'’s root to 'P.Nothing'.
-- 
-- /Since: 2.70/
treeRemoveAll ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Tree
    -- ^ /@tree@/: a t'GI.GLib.Structs.Tree.Tree'
    -> m ()
treeRemoveAll :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Tree -> m ()
treeRemoveAll Tree
tree = 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 Tree
tree' <- Tree -> IO (Ptr Tree)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Tree
tree
    Ptr Tree -> IO ()
g_tree_remove_all Ptr Tree
tree'
    Tree -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Tree
tree
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TreeRemoveAllMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod TreeRemoveAllMethodInfo Tree signature where
    overloadedMethod = treeRemoveAll

instance O.OverloadedMethodInfo TreeRemoveAllMethodInfo Tree where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Tree.treeRemoveAll",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.27/docs/GI-GLib-Structs-Tree.html#v:treeRemoveAll"
        })


#endif

-- method Tree::replace
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "tree"
--           , argType = TInterface Name { namespace = "GLib" , name = "Tree" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTree" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the key to insert" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the value corresponding to the key"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_tree_replace" g_tree_replace :: 
    Ptr Tree ->                             -- tree : TInterface (Name {namespace = "GLib", name = "Tree"})
    Ptr () ->                               -- key : TBasicType TPtr
    Ptr () ->                               -- value : TBasicType TPtr
    IO ()

-- | Inserts a new key and value into a t'GI.GLib.Structs.Tree.Tree' as 'GI.GLib.Structs.Tree.treeReplaceNode' does,
-- only this function does not return the inserted or set node.
treeReplace ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Tree
    -- ^ /@tree@/: a t'GI.GLib.Structs.Tree.Tree'
    -> Ptr ()
    -- ^ /@key@/: the key to insert
    -> Ptr ()
    -- ^ /@value@/: the value corresponding to the key
    -> m ()
treeReplace :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Tree -> Ptr () -> Ptr () -> m ()
treeReplace Tree
tree Ptr ()
key Ptr ()
value = 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 Tree
tree' <- Tree -> IO (Ptr Tree)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Tree
tree
    Ptr Tree -> Ptr () -> DestroyNotify
g_tree_replace Ptr Tree
tree' Ptr ()
key Ptr ()
value
    Tree -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Tree
tree
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TreeReplaceMethodInfo
instance (signature ~ (Ptr () -> Ptr () -> m ()), MonadIO m) => O.OverloadedMethod TreeReplaceMethodInfo Tree signature where
    overloadedMethod = treeReplace

instance O.OverloadedMethodInfo TreeReplaceMethodInfo Tree where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Tree.treeReplace",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.27/docs/GI-GLib-Structs-Tree.html#v:treeReplace"
        })


#endif

-- method Tree::replace_node
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "tree"
--           , argType = TInterface Name { namespace = "GLib" , name = "Tree" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTree" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the key to insert" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the value corresponding to the key"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "TreeNode" })
-- throws : False
-- Skip return : False

foreign import ccall "g_tree_replace_node" g_tree_replace_node :: 
    Ptr Tree ->                             -- tree : TInterface (Name {namespace = "GLib", name = "Tree"})
    Ptr () ->                               -- key : TBasicType TPtr
    Ptr () ->                               -- value : TBasicType TPtr
    IO (Ptr GLib.TreeNode.TreeNode)

-- | Inserts a new key and value into a t'GI.GLib.Structs.Tree.Tree' similar to 'GI.GLib.Structs.Tree.treeInsertNode'.
-- The difference is that if the key already exists in the t'GI.GLib.Structs.Tree.Tree', it gets
-- replaced by the new key. If you supplied a /@valueDestroyFunc@/ when
-- creating the t'GI.GLib.Structs.Tree.Tree', the old value is freed using that function. If you
-- supplied a /@keyDestroyFunc@/ when creating the t'GI.GLib.Structs.Tree.Tree', the old key is
-- freed using that function.
-- 
-- The tree is automatically \'balanced\' as new key\/value pairs are added,
-- so that the distance from the root to every leaf is as small as possible.
-- 
-- /Since: 2.68/
treeReplaceNode ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Tree
    -- ^ /@tree@/: a t'GI.GLib.Structs.Tree.Tree'
    -> Ptr ()
    -- ^ /@key@/: the key to insert
    -> Ptr ()
    -- ^ /@value@/: the value corresponding to the key
    -> m GLib.TreeNode.TreeNode
    -- ^ __Returns:__ the inserted (or set) node.
treeReplaceNode :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Tree -> Ptr () -> Ptr () -> m TreeNode
treeReplaceNode Tree
tree Ptr ()
key Ptr ()
value = IO TreeNode -> m TreeNode
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TreeNode -> m TreeNode) -> IO TreeNode -> m TreeNode
forall a b. (a -> b) -> a -> b
$ do
    Ptr Tree
tree' <- Tree -> IO (Ptr Tree)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Tree
tree
    Ptr TreeNode
result <- Ptr Tree -> Ptr () -> Ptr () -> IO (Ptr TreeNode)
g_tree_replace_node Ptr Tree
tree' Ptr ()
key Ptr ()
value
    Text -> Ptr TreeNode -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"treeReplaceNode" Ptr TreeNode
result
    TreeNode
result' <- ((ManagedPtr TreeNode -> TreeNode) -> Ptr TreeNode -> IO TreeNode
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr TreeNode -> TreeNode
GLib.TreeNode.TreeNode) Ptr TreeNode
result
    Tree -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Tree
tree
    TreeNode -> IO TreeNode
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return TreeNode
result'

#if defined(ENABLE_OVERLOADING)
data TreeReplaceNodeMethodInfo
instance (signature ~ (Ptr () -> Ptr () -> m GLib.TreeNode.TreeNode), MonadIO m) => O.OverloadedMethod TreeReplaceNodeMethodInfo Tree signature where
    overloadedMethod = treeReplaceNode

instance O.OverloadedMethodInfo TreeReplaceNodeMethodInfo Tree where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Tree.treeReplaceNode",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.27/docs/GI-GLib-Structs-Tree.html#v:treeReplaceNode"
        })


#endif

-- method Tree::steal
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "tree"
--           , argType = TInterface Name { namespace = "GLib" , name = "Tree" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTree" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the key to remove" , 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 "g_tree_steal" g_tree_steal :: 
    Ptr Tree ->                             -- tree : TInterface (Name {namespace = "GLib", name = "Tree"})
    Ptr () ->                               -- key : TBasicType TPtr
    IO CInt

-- | Removes a key and its associated value from a t'GI.GLib.Structs.Tree.Tree' without calling
-- the key and value destroy functions.
-- 
-- If the key does not exist in the t'GI.GLib.Structs.Tree.Tree', the function does nothing.
treeSteal ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Tree
    -- ^ /@tree@/: a t'GI.GLib.Structs.Tree.Tree'
    -> Ptr ()
    -- ^ /@key@/: the key to remove
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the key was found (prior to 2.8, this function
    --     returned nothing)
treeSteal :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Tree -> Ptr () -> m Bool
treeSteal Tree
tree Ptr ()
key = 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 Tree
tree' <- Tree -> IO (Ptr Tree)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Tree
tree
    CInt
result <- Ptr Tree -> Ptr () -> IO CInt
g_tree_steal Ptr Tree
tree' Ptr ()
key
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Tree -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Tree
tree
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TreeStealMethodInfo
instance (signature ~ (Ptr () -> m Bool), MonadIO m) => O.OverloadedMethod TreeStealMethodInfo Tree signature where
    overloadedMethod = treeSteal

instance O.OverloadedMethodInfo TreeStealMethodInfo Tree where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Tree.treeSteal",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.27/docs/GI-GLib-Structs-Tree.html#v:treeSteal"
        })


#endif

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

foreign import ccall "g_tree_unref" g_tree_unref :: 
    Ptr Tree ->                             -- tree : TInterface (Name {namespace = "GLib", name = "Tree"})
    IO ()

-- | Decrements the reference count of /@tree@/ by one.
-- If the reference count drops to 0, all keys and values will
-- be destroyed (if destroy functions were specified) and all
-- memory allocated by /@tree@/ will be released.
-- 
-- It is safe to call this function from any thread.
-- 
-- /Since: 2.22/
treeUnref ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Tree
    -- ^ /@tree@/: a t'GI.GLib.Structs.Tree.Tree'
    -> m ()
treeUnref :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Tree -> m ()
treeUnref Tree
tree = 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 Tree
tree' <- Tree -> IO (Ptr Tree)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Tree
tree
    Ptr Tree -> IO ()
g_tree_unref Ptr Tree
tree'
    Tree -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Tree
tree
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TreeUnrefMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod TreeUnrefMethodInfo Tree signature where
    overloadedMethod = treeUnref

instance O.OverloadedMethodInfo TreeUnrefMethodInfo Tree where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Tree.treeUnref",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.27/docs/GI-GLib-Structs-Tree.html#v:treeUnref"
        })


#endif

-- method Tree::upper_bound
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "tree"
--           , argType = TInterface Name { namespace = "GLib" , name = "Tree" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTree" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the key to calculate the upper bound for"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "TreeNode" })
-- throws : False
-- Skip return : False

foreign import ccall "g_tree_upper_bound" g_tree_upper_bound :: 
    Ptr Tree ->                             -- tree : TInterface (Name {namespace = "GLib", name = "Tree"})
    Ptr () ->                               -- key : TBasicType TPtr
    IO (Ptr GLib.TreeNode.TreeNode)

-- | Gets the upper bound node corresponding to the given key,
-- or 'P.Nothing' if the tree is empty or all the nodes in the tree
-- have keys that are lower than or equal to the searched key.
-- 
-- The upper bound is the first node that has its key strictly greater
-- than the searched key.
-- 
-- /Since: 2.68/
treeUpperBound ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Tree
    -- ^ /@tree@/: a t'GI.GLib.Structs.Tree.Tree'
    -> Ptr ()
    -- ^ /@key@/: the key to calculate the upper bound for
    -> m (Maybe GLib.TreeNode.TreeNode)
    -- ^ __Returns:__ the tree node corresponding to the
    --          upper bound, or 'P.Nothing' if the tree is empty or has only keys
    --          lower than or equal to the searched key.
treeUpperBound :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Tree -> Ptr () -> m (Maybe TreeNode)
treeUpperBound Tree
tree Ptr ()
key = IO (Maybe TreeNode) -> m (Maybe TreeNode)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe TreeNode) -> m (Maybe TreeNode))
-> IO (Maybe TreeNode) -> m (Maybe TreeNode)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Tree
tree' <- Tree -> IO (Ptr Tree)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Tree
tree
    Ptr TreeNode
result <- Ptr Tree -> Ptr () -> IO (Ptr TreeNode)
g_tree_upper_bound Ptr Tree
tree' Ptr ()
key
    Maybe TreeNode
maybeResult <- Ptr TreeNode
-> (Ptr TreeNode -> IO TreeNode) -> IO (Maybe TreeNode)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr TreeNode
result ((Ptr TreeNode -> IO TreeNode) -> IO (Maybe TreeNode))
-> (Ptr TreeNode -> IO TreeNode) -> IO (Maybe TreeNode)
forall a b. (a -> b) -> a -> b
$ \Ptr TreeNode
result' -> do
        TreeNode
result'' <- ((ManagedPtr TreeNode -> TreeNode) -> Ptr TreeNode -> IO TreeNode
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr TreeNode -> TreeNode
GLib.TreeNode.TreeNode) Ptr TreeNode
result'
        TreeNode -> IO TreeNode
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return TreeNode
result''
    Tree -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Tree
tree
    Maybe TreeNode -> IO (Maybe TreeNode)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TreeNode
maybeResult

#if defined(ENABLE_OVERLOADING)
data TreeUpperBoundMethodInfo
instance (signature ~ (Ptr () -> m (Maybe GLib.TreeNode.TreeNode)), MonadIO m) => O.OverloadedMethod TreeUpperBoundMethodInfo Tree signature where
    overloadedMethod = treeUpperBound

instance O.OverloadedMethodInfo TreeUpperBoundMethodInfo Tree where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Tree.treeUpperBound",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.27/docs/GI-GLib-Structs-Tree.html#v:treeUpperBound"
        })


#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveTreeMethod (t :: Symbol) (o :: *) :: * where
    ResolveTreeMethod "destroy" o = TreeDestroyMethodInfo
    ResolveTreeMethod "height" o = TreeHeightMethodInfo
    ResolveTreeMethod "insert" o = TreeInsertMethodInfo
    ResolveTreeMethod "insertNode" o = TreeInsertNodeMethodInfo
    ResolveTreeMethod "lookup" o = TreeLookupMethodInfo
    ResolveTreeMethod "lookupExtended" o = TreeLookupExtendedMethodInfo
    ResolveTreeMethod "lookupNode" o = TreeLookupNodeMethodInfo
    ResolveTreeMethod "lowerBound" o = TreeLowerBoundMethodInfo
    ResolveTreeMethod "nnodes" o = TreeNnodesMethodInfo
    ResolveTreeMethod "nodeFirst" o = TreeNodeFirstMethodInfo
    ResolveTreeMethod "nodeLast" o = TreeNodeLastMethodInfo
    ResolveTreeMethod "ref" o = TreeRefMethodInfo
    ResolveTreeMethod "remove" o = TreeRemoveMethodInfo
    ResolveTreeMethod "removeAll" o = TreeRemoveAllMethodInfo
    ResolveTreeMethod "replace" o = TreeReplaceMethodInfo
    ResolveTreeMethod "replaceNode" o = TreeReplaceNodeMethodInfo
    ResolveTreeMethod "steal" o = TreeStealMethodInfo
    ResolveTreeMethod "unref" o = TreeUnrefMethodInfo
    ResolveTreeMethod "upperBound" o = TreeUpperBoundMethodInfo
    ResolveTreeMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif