{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- 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
-- ** Overloaded methods #method:Overloaded methods#

#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                              ,


-- ** lookup #method:lookup#

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


-- ** lookupExtended #method:lookupExtended#

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


-- ** nnodes #method:nnodes#

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


-- ** remove #method:remove#

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


-- ** replace #method:replace#

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


-- ** steal #method:steal#

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


-- ** unref #method:unref#

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




    ) 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.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


-- | 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
/= :: Tree -> Tree -> Bool
$c/= :: Tree -> Tree -> Bool
== :: Tree -> Tree -> Bool
$c== :: Tree -> Tree -> Bool
Eq)

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

-- XXX Wrapping a foreign struct/union with no known destructor or size, leak?
instance BoxedPtr Tree where
    boxedPtrCopy :: Tree -> IO Tree
boxedPtrCopy = Tree -> IO Tree
forall (m :: * -> *) a. Monad m => a -> m a
return
    boxedPtrFree :: Tree -> IO ()
boxedPtrFree = \Tree
_x -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()


#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Tree
type instance O.AttributeList Tree = TreeAttributeList
type TreeAttributeList = ('[ ] :: [(Symbol, *)])
#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 @/g_tree_new_full()/@. 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 :: Tree -> m ()
treeDestroy Tree
tree = 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 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 (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TreeDestroyMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo TreeDestroyMethodInfo Tree signature where
    overloadedMethod = 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 :: Tree -> m Int32
treeHeight Tree
tree = 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 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 (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data TreeHeightMethodInfo
instance (signature ~ (m Int32), MonadIO m) => O.MethodInfo TreeHeightMethodInfo Tree signature where
    overloadedMethod = 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'.
-- 
-- 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.
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 :: Tree -> Ptr () -> Ptr () -> m ()
treeInsert Tree
tree Ptr ()
key Ptr ()
value = 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 Tree
tree' <- Tree -> IO (Ptr Tree)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Tree
tree
    Ptr Tree -> Ptr () -> Ptr () -> IO ()
g_tree_insert Ptr Tree
tree' Ptr ()
key Ptr ()
value
    Tree -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Tree
tree
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

#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 :: Tree -> Ptr () -> m (Ptr ())
treeLookup Tree
tree Ptr ()
key = IO (Ptr ()) -> m (Ptr ())
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 (m :: * -> *) a. Monad m => a -> m a
return Ptr ()
result

#if defined(ENABLE_OVERLOADING)
data TreeLookupMethodInfo
instance (signature ~ (Ptr () -> m (Ptr ())), MonadIO m) => O.MethodInfo TreeLookupMethodInfo Tree signature where
    overloadedMethod = 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 :: Tree -> Ptr () -> m (Bool, Ptr (), Ptr ())
treeLookupExtended Tree
tree Ptr ()
lookupKey = IO (Bool, Ptr (), Ptr ()) -> m (Bool, Ptr (), Ptr ())
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 (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.MethodInfo TreeLookupExtendedMethodInfo Tree signature where
    overloadedMethod = treeLookupExtended

#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 :: Tree -> m Int32
treeNnodes Tree
tree = 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 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 (m :: * -> *) a. Monad m => a -> m a
return Int32
result

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

#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 @/g_tree_new_full()/@, 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.
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 :: Tree -> Ptr () -> m Bool
treeRemove Tree
tree Ptr ()
key = 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 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 (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

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

#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' similar to 'GI.GLib.Structs.Tree.treeInsert'.
-- 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.
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 :: Tree -> Ptr () -> Ptr () -> m ()
treeReplace Tree
tree Ptr ()
key Ptr ()
value = 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 Tree
tree' <- Tree -> IO (Ptr Tree)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Tree
tree
    Ptr Tree -> Ptr () -> Ptr () -> IO ()
g_tree_replace Ptr Tree
tree' Ptr ()
key Ptr ()
value
    Tree -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Tree
tree
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

#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 :: Tree -> Ptr () -> m Bool
treeSteal Tree
tree Ptr ()
key = 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 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 (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TreeStealMethodInfo
instance (signature ~ (Ptr () -> m Bool), MonadIO m) => O.MethodInfo TreeStealMethodInfo Tree signature where
    overloadedMethod = 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 :: Tree -> m ()
treeUnref Tree
tree = 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 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 (m :: * -> *) a. Monad m => a -> m a
return ()

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

#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 "lookup" o = TreeLookupMethodInfo
    ResolveTreeMethod "lookupExtended" o = TreeLookupExtendedMethodInfo
    ResolveTreeMethod "nnodes" o = TreeNnodesMethodInfo
    ResolveTreeMethod "remove" o = TreeRemoveMethodInfo
    ResolveTreeMethod "replace" o = TreeReplaceMethodInfo
    ResolveTreeMethod "steal" o = TreeStealMethodInfo
    ResolveTreeMethod "unref" o = TreeUnrefMethodInfo
    ResolveTreeMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveTreeMethod t Tree, O.MethodInfo 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

#endif