{- |
Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
License    : LGPL-2.1
Maintainer : Iñaki García Etxebarria (garetxe@gmail.com)

The 'GI.GLib.Structs.Node.Node' struct represents one node in a [n-ary tree][glib-N-ary-Trees].
-}

module GI.GLib.Structs.Node
    ( 

-- * Exported types
    Node(..)                                ,
    newZeroNode                             ,
    noNode                                  ,


 -- * Methods
-- ** childIndex #method:childIndex#

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    NodeChildIndexMethodInfo                ,
#endif
    nodeChildIndex                          ,


-- ** childPosition #method:childPosition#

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    NodeChildPositionMethodInfo             ,
#endif
    nodeChildPosition                       ,


-- ** depth #method:depth#

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    NodeDepthMethodInfo                     ,
#endif
    nodeDepth                               ,


-- ** destroy #method:destroy#

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    NodeDestroyMethodInfo                   ,
#endif
    nodeDestroy                             ,


-- ** isAncestor #method:isAncestor#

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    NodeIsAncestorMethodInfo                ,
#endif
    nodeIsAncestor                          ,


-- ** maxHeight #method:maxHeight#

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    NodeMaxHeightMethodInfo                 ,
#endif
    nodeMaxHeight                           ,


-- ** nChildren #method:nChildren#

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    NodeNChildrenMethodInfo                 ,
#endif
    nodeNChildren                           ,


-- ** nNodes #method:nNodes#

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    NodeNNodesMethodInfo                    ,
#endif
    nodeNNodes                              ,


-- ** reverseChildren #method:reverseChildren#

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    NodeReverseChildrenMethodInfo           ,
#endif
    nodeReverseChildren                     ,


-- ** unlink #method:unlink#

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    NodeUnlinkMethodInfo                    ,
#endif
    nodeUnlink                              ,




 -- * Properties
-- ** children #attr:children#
{- | points to the first child of the 'GI.GLib.Structs.Node.Node'.  The other
           children are accessed by using the /@next@/ pointer of each
           child.
-}
    clearNodeChildren                       ,
    getNodeChildren                         ,
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    node_children                           ,
#endif
    setNodeChildren                         ,


-- ** data #attr:data#
{- | contains the actual data of the node.
-}
    clearNodeData                           ,
    getNodeData                             ,
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    node_data                               ,
#endif
    setNodeData                             ,


-- ** next #attr:next#
{- | points to the node\'s next sibling (a sibling is another
       'GI.GLib.Structs.Node.Node' with the same parent).
-}
    clearNodeNext                           ,
    getNodeNext                             ,
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    node_next                               ,
#endif
    setNodeNext                             ,


-- ** parent #attr:parent#
{- | points to the parent of the 'GI.GLib.Structs.Node.Node', or is 'Nothing' if the
         'GI.GLib.Structs.Node.Node' is the root of the tree.
-}
    clearNodeParent                         ,
    getNodeParent                           ,
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    node_parent                             ,
#endif
    setNodeParent                           ,


-- ** prev #attr:prev#
{- | points to the node\'s previous sibling.
-}
    clearNodePrev                           ,
    getNodePrev                             ,
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    node_prev                               ,
#endif
    setNodePrev                             ,




    ) 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.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
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 {-# SOURCE #-} qualified GI.GLib.Flags as GLib.Flags

-- | Memory-managed wrapper type.
newtype Node = Node (ManagedPtr Node)
instance WrappedPtr Node where
    wrappedPtrCalloc = callocBytes 40
    wrappedPtrCopy = \p -> withManagedPtr p (copyBytes 40 >=> wrapPtr Node)
    wrappedPtrFree = Just ptr_to_g_free

-- | Construct a `Node` struct initialized to zero.
newZeroNode :: MonadIO m => m Node
newZeroNode = liftIO $ wrappedPtrCalloc >>= wrapPtr Node

instance tag ~ 'AttrSet => Constructible Node tag where
    new _ attrs = do
        o <- newZeroNode
        GI.Attributes.set o attrs
        return o


-- | A convenience alias for `Nothing` :: `Maybe` `Node`.
noNode :: Maybe Node
noNode = Nothing

{- |
Get the value of the “@data@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' node #data
@
-}
getNodeData :: MonadIO m => Node -> m (Ptr ())
getNodeData s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO (Ptr ())
    return val

{- |
Set the value of the “@data@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' node [ #data 'Data.GI.Base.Attributes.:=' value ]
@
-}
setNodeData :: MonadIO m => Node -> Ptr () -> m ()
setNodeData s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 0) (val :: Ptr ())

{- |
Set the value of the “@data@” field to `Nothing`.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.clear' #data
@
-}
clearNodeData :: MonadIO m => Node -> m ()
clearNodeData s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 0) (FP.nullPtr :: Ptr ())

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data NodeDataFieldInfo
instance AttrInfo NodeDataFieldInfo where
    type AttrAllowedOps NodeDataFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint NodeDataFieldInfo = (~) (Ptr ())
    type AttrBaseTypeConstraint NodeDataFieldInfo = (~) Node
    type AttrGetType NodeDataFieldInfo = Ptr ()
    type AttrLabel NodeDataFieldInfo = "data"
    type AttrOrigin NodeDataFieldInfo = Node
    attrGet _ = getNodeData
    attrSet _ = setNodeData
    attrConstruct = undefined
    attrClear _ = clearNodeData

node_data :: AttrLabelProxy "data"
node_data = AttrLabelProxy

#endif


{- |
Get the value of the “@next@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' node #next
@
-}
getNodeNext :: MonadIO m => Node -> m (Maybe Node)
getNodeNext s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 8) :: IO (Ptr Node)
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- (newPtr Node) val'
        return val''
    return result

{- |
Set the value of the “@next@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' node [ #next 'Data.GI.Base.Attributes.:=' value ]
@
-}
setNodeNext :: MonadIO m => Node -> Ptr Node -> m ()
setNodeNext s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (val :: Ptr Node)

{- |
Set the value of the “@next@” field to `Nothing`.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.clear' #next
@
-}
clearNodeNext :: MonadIO m => Node -> m ()
clearNodeNext s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (FP.nullPtr :: Ptr Node)

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data NodeNextFieldInfo
instance AttrInfo NodeNextFieldInfo where
    type AttrAllowedOps NodeNextFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint NodeNextFieldInfo = (~) (Ptr Node)
    type AttrBaseTypeConstraint NodeNextFieldInfo = (~) Node
    type AttrGetType NodeNextFieldInfo = Maybe Node
    type AttrLabel NodeNextFieldInfo = "next"
    type AttrOrigin NodeNextFieldInfo = Node
    attrGet _ = getNodeNext
    attrSet _ = setNodeNext
    attrConstruct = undefined
    attrClear _ = clearNodeNext

node_next :: AttrLabelProxy "next"
node_next = AttrLabelProxy

#endif


{- |
Get the value of the “@prev@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' node #prev
@
-}
getNodePrev :: MonadIO m => Node -> m (Maybe Node)
getNodePrev s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 16) :: IO (Ptr Node)
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- (newPtr Node) val'
        return val''
    return result

{- |
Set the value of the “@prev@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' node [ #prev 'Data.GI.Base.Attributes.:=' value ]
@
-}
setNodePrev :: MonadIO m => Node -> Ptr Node -> m ()
setNodePrev s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 16) (val :: Ptr Node)

{- |
Set the value of the “@prev@” field to `Nothing`.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.clear' #prev
@
-}
clearNodePrev :: MonadIO m => Node -> m ()
clearNodePrev s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 16) (FP.nullPtr :: Ptr Node)

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data NodePrevFieldInfo
instance AttrInfo NodePrevFieldInfo where
    type AttrAllowedOps NodePrevFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint NodePrevFieldInfo = (~) (Ptr Node)
    type AttrBaseTypeConstraint NodePrevFieldInfo = (~) Node
    type AttrGetType NodePrevFieldInfo = Maybe Node
    type AttrLabel NodePrevFieldInfo = "prev"
    type AttrOrigin NodePrevFieldInfo = Node
    attrGet _ = getNodePrev
    attrSet _ = setNodePrev
    attrConstruct = undefined
    attrClear _ = clearNodePrev

node_prev :: AttrLabelProxy "prev"
node_prev = AttrLabelProxy

#endif


{- |
Get the value of the “@parent@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' node #parent
@
-}
getNodeParent :: MonadIO m => Node -> m (Maybe Node)
getNodeParent s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 24) :: IO (Ptr Node)
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- (newPtr Node) val'
        return val''
    return result

{- |
Set the value of the “@parent@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' node [ #parent 'Data.GI.Base.Attributes.:=' value ]
@
-}
setNodeParent :: MonadIO m => Node -> Ptr Node -> m ()
setNodeParent s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 24) (val :: Ptr Node)

{- |
Set the value of the “@parent@” field to `Nothing`.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.clear' #parent
@
-}
clearNodeParent :: MonadIO m => Node -> m ()
clearNodeParent s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 24) (FP.nullPtr :: Ptr Node)

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data NodeParentFieldInfo
instance AttrInfo NodeParentFieldInfo where
    type AttrAllowedOps NodeParentFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint NodeParentFieldInfo = (~) (Ptr Node)
    type AttrBaseTypeConstraint NodeParentFieldInfo = (~) Node
    type AttrGetType NodeParentFieldInfo = Maybe Node
    type AttrLabel NodeParentFieldInfo = "parent"
    type AttrOrigin NodeParentFieldInfo = Node
    attrGet _ = getNodeParent
    attrSet _ = setNodeParent
    attrConstruct = undefined
    attrClear _ = clearNodeParent

node_parent :: AttrLabelProxy "parent"
node_parent = AttrLabelProxy

#endif


{- |
Get the value of the “@children@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' node #children
@
-}
getNodeChildren :: MonadIO m => Node -> m (Maybe Node)
getNodeChildren s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 32) :: IO (Ptr Node)
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- (newPtr Node) val'
        return val''
    return result

{- |
Set the value of the “@children@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' node [ #children 'Data.GI.Base.Attributes.:=' value ]
@
-}
setNodeChildren :: MonadIO m => Node -> Ptr Node -> m ()
setNodeChildren s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 32) (val :: Ptr Node)

{- |
Set the value of the “@children@” field to `Nothing`.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.clear' #children
@
-}
clearNodeChildren :: MonadIO m => Node -> m ()
clearNodeChildren s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 32) (FP.nullPtr :: Ptr Node)

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data NodeChildrenFieldInfo
instance AttrInfo NodeChildrenFieldInfo where
    type AttrAllowedOps NodeChildrenFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint NodeChildrenFieldInfo = (~) (Ptr Node)
    type AttrBaseTypeConstraint NodeChildrenFieldInfo = (~) Node
    type AttrGetType NodeChildrenFieldInfo = Maybe Node
    type AttrLabel NodeChildrenFieldInfo = "children"
    type AttrOrigin NodeChildrenFieldInfo = Node
    attrGet _ = getNodeChildren
    attrSet _ = setNodeChildren
    attrConstruct = undefined
    attrClear _ = clearNodeChildren

node_children :: AttrLabelProxy "children"
node_children = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
instance O.HasAttributeList Node
type instance O.AttributeList Node = NodeAttributeList
type NodeAttributeList = ('[ '("data", NodeDataFieldInfo), '("next", NodeNextFieldInfo), '("prev", NodePrevFieldInfo), '("parent", NodeParentFieldInfo), '("children", NodeChildrenFieldInfo)] :: [(Symbol, *)])
#endif

-- method Node::child_index
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "node", argType = TInterface (Name {namespace = "GLib", name = "Node"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GNode", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "data", argType = TBasicType TPtr, direction = DirectionIn, mayBeNull = True, argDoc = Documentation {rawDocText = Just "the data to find", 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_node_child_index" g_node_child_index :: 
    Ptr Node ->                             -- node : TInterface (Name {namespace = "GLib", name = "Node"})
    Ptr () ->                               -- data : TBasicType TPtr
    IO Int32

{- |
Gets the position of the first child of a 'GI.GLib.Structs.Node.Node'
which contains the given data.
-}
nodeChildIndex ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Node
    {- ^ /@node@/: a 'GI.GLib.Structs.Node.Node' -}
    -> Ptr ()
    {- ^ /@data@/: the data to find -}
    -> m Int32
    {- ^ __Returns:__ the index of the child of /@node@/ which contains
    /@data@/, or -1 if the data is not found -}
nodeChildIndex node data_ = liftIO $ do
    node' <- unsafeManagedPtrGetPtr node
    result <- g_node_child_index node' data_
    touchManagedPtr node
    return result

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data NodeChildIndexMethodInfo
instance (signature ~ (Ptr () -> m Int32), MonadIO m) => O.MethodInfo NodeChildIndexMethodInfo Node signature where
    overloadedMethod _ = nodeChildIndex

#endif

-- method Node::child_position
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "node", argType = TInterface (Name {namespace = "GLib", name = "Node"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GNode", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "child", argType = TInterface (Name {namespace = "GLib", name = "Node"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a child of @node", 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_node_child_position" g_node_child_position :: 
    Ptr Node ->                             -- node : TInterface (Name {namespace = "GLib", name = "Node"})
    Ptr Node ->                             -- child : TInterface (Name {namespace = "GLib", name = "Node"})
    IO Int32

{- |
Gets the position of a 'GI.GLib.Structs.Node.Node' with respect to its siblings.
/@child@/ must be a child of /@node@/. The first child is numbered 0,
the second 1, and so on.
-}
nodeChildPosition ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Node
    {- ^ /@node@/: a 'GI.GLib.Structs.Node.Node' -}
    -> Node
    {- ^ /@child@/: a child of /@node@/ -}
    -> m Int32
    {- ^ __Returns:__ the position of /@child@/ with respect to its siblings -}
nodeChildPosition node child = liftIO $ do
    node' <- unsafeManagedPtrGetPtr node
    child' <- unsafeManagedPtrGetPtr child
    result <- g_node_child_position node' child'
    touchManagedPtr node
    touchManagedPtr child
    return result

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data NodeChildPositionMethodInfo
instance (signature ~ (Node -> m Int32), MonadIO m) => O.MethodInfo NodeChildPositionMethodInfo Node signature where
    overloadedMethod _ = nodeChildPosition

#endif

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

foreign import ccall "g_node_depth" g_node_depth :: 
    Ptr Node ->                             -- node : TInterface (Name {namespace = "GLib", name = "Node"})
    IO Word32

{- |
Gets the depth of a 'GI.GLib.Structs.Node.Node'.

If /@node@/ is 'Nothing' the depth is 0. The root node has a depth of 1.
For the children of the root node the depth is 2. And so on.
-}
nodeDepth ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Node
    {- ^ /@node@/: a 'GI.GLib.Structs.Node.Node' -}
    -> m Word32
    {- ^ __Returns:__ the depth of the 'GI.GLib.Structs.Node.Node' -}
nodeDepth node = liftIO $ do
    node' <- unsafeManagedPtrGetPtr node
    result <- g_node_depth node'
    touchManagedPtr node
    return result

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data NodeDepthMethodInfo
instance (signature ~ (m Word32), MonadIO m) => O.MethodInfo NodeDepthMethodInfo Node signature where
    overloadedMethod _ = nodeDepth

#endif

-- method Node::destroy
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "root", argType = TInterface (Name {namespace = "GLib", name = "Node"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "the root of the tree/subtree to destroy", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_node_destroy" g_node_destroy :: 
    Ptr Node ->                             -- root : TInterface (Name {namespace = "GLib", name = "Node"})
    IO ()

{- |
Removes /@root@/ and its children from the tree, freeing any memory
allocated.
-}
nodeDestroy ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Node
    {- ^ /@root@/: the root of the tree\/subtree to destroy -}
    -> m ()
nodeDestroy root = liftIO $ do
    root' <- unsafeManagedPtrGetPtr root
    g_node_destroy root'
    touchManagedPtr root
    return ()

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data NodeDestroyMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo NodeDestroyMethodInfo Node signature where
    overloadedMethod _ = nodeDestroy

#endif

-- method Node::is_ancestor
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "node", argType = TInterface (Name {namespace = "GLib", name = "Node"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GNode", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "descendant", argType = TInterface (Name {namespace = "GLib", name = "Node"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GNode", 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_node_is_ancestor" g_node_is_ancestor :: 
    Ptr Node ->                             -- node : TInterface (Name {namespace = "GLib", name = "Node"})
    Ptr Node ->                             -- descendant : TInterface (Name {namespace = "GLib", name = "Node"})
    IO CInt

{- |
Returns 'True' if /@node@/ is an ancestor of /@descendant@/.
This is true if node is the parent of /@descendant@/,
or if node is the grandparent of /@descendant@/ etc.
-}
nodeIsAncestor ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Node
    {- ^ /@node@/: a 'GI.GLib.Structs.Node.Node' -}
    -> Node
    {- ^ /@descendant@/: a 'GI.GLib.Structs.Node.Node' -}
    -> m Bool
    {- ^ __Returns:__ 'True' if /@node@/ is an ancestor of /@descendant@/ -}
nodeIsAncestor node descendant = liftIO $ do
    node' <- unsafeManagedPtrGetPtr node
    descendant' <- unsafeManagedPtrGetPtr descendant
    result <- g_node_is_ancestor node' descendant'
    let result' = (/= 0) result
    touchManagedPtr node
    touchManagedPtr descendant
    return result'

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data NodeIsAncestorMethodInfo
instance (signature ~ (Node -> m Bool), MonadIO m) => O.MethodInfo NodeIsAncestorMethodInfo Node signature where
    overloadedMethod _ = nodeIsAncestor

#endif

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

foreign import ccall "g_node_max_height" g_node_max_height :: 
    Ptr Node ->                             -- root : TInterface (Name {namespace = "GLib", name = "Node"})
    IO Word32

{- |
Gets the maximum height of all branches beneath a 'GI.GLib.Structs.Node.Node'.
This is the maximum distance from the 'GI.GLib.Structs.Node.Node' to all leaf nodes.

If /@root@/ is 'Nothing', 0 is returned. If /@root@/ has no children,
1 is returned. If /@root@/ has children, 2 is returned. And so on.
-}
nodeMaxHeight ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Node
    {- ^ /@root@/: a 'GI.GLib.Structs.Node.Node' -}
    -> m Word32
    {- ^ __Returns:__ the maximum height of the tree beneath /@root@/ -}
nodeMaxHeight root = liftIO $ do
    root' <- unsafeManagedPtrGetPtr root
    result <- g_node_max_height root'
    touchManagedPtr root
    return result

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data NodeMaxHeightMethodInfo
instance (signature ~ (m Word32), MonadIO m) => O.MethodInfo NodeMaxHeightMethodInfo Node signature where
    overloadedMethod _ = nodeMaxHeight

#endif

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

foreign import ccall "g_node_n_children" g_node_n_children :: 
    Ptr Node ->                             -- node : TInterface (Name {namespace = "GLib", name = "Node"})
    IO Word32

{- |
Gets the number of children of a 'GI.GLib.Structs.Node.Node'.
-}
nodeNChildren ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Node
    {- ^ /@node@/: a 'GI.GLib.Structs.Node.Node' -}
    -> m Word32
    {- ^ __Returns:__ the number of children of /@node@/ -}
nodeNChildren node = liftIO $ do
    node' <- unsafeManagedPtrGetPtr node
    result <- g_node_n_children node'
    touchManagedPtr node
    return result

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data NodeNChildrenMethodInfo
instance (signature ~ (m Word32), MonadIO m) => O.MethodInfo NodeNChildrenMethodInfo Node signature where
    overloadedMethod _ = nodeNChildren

#endif

-- method Node::n_nodes
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "root", argType = TInterface (Name {namespace = "GLib", name = "Node"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GNode", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "flags", argType = TInterface (Name {namespace = "GLib", name = "TraverseFlags"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "which types of children are to be counted, one of\n    %G_TRAVERSE_ALL, %G_TRAVERSE_LEAVES and %G_TRAVERSE_NON_LEAVES", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TUInt)
-- throws : False
-- Skip return : False

foreign import ccall "g_node_n_nodes" g_node_n_nodes :: 
    Ptr Node ->                             -- root : TInterface (Name {namespace = "GLib", name = "Node"})
    CUInt ->                                -- flags : TInterface (Name {namespace = "GLib", name = "TraverseFlags"})
    IO Word32

{- |
Gets the number of nodes in a tree.
-}
nodeNNodes ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Node
    {- ^ /@root@/: a 'GI.GLib.Structs.Node.Node' -}
    -> [GLib.Flags.TraverseFlags]
    {- ^ /@flags@/: which types of children are to be counted, one of
    'GI.GLib.Flags.TraverseFlagsAll', 'GI.GLib.Flags.TraverseFlagsLeaves' and 'GI.GLib.Flags.TraverseFlagsNonLeaves' -}
    -> m Word32
    {- ^ __Returns:__ the number of nodes in the tree -}
nodeNNodes root flags = liftIO $ do
    root' <- unsafeManagedPtrGetPtr root
    let flags' = gflagsToWord flags
    result <- g_node_n_nodes root' flags'
    touchManagedPtr root
    return result

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data NodeNNodesMethodInfo
instance (signature ~ ([GLib.Flags.TraverseFlags] -> m Word32), MonadIO m) => O.MethodInfo NodeNNodesMethodInfo Node signature where
    overloadedMethod _ = nodeNNodes

#endif

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

foreign import ccall "g_node_reverse_children" g_node_reverse_children :: 
    Ptr Node ->                             -- node : TInterface (Name {namespace = "GLib", name = "Node"})
    IO ()

{- |
Reverses the order of the children of a 'GI.GLib.Structs.Node.Node'.
(It doesn\'t change the order of the grandchildren.)
-}
nodeReverseChildren ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Node
    {- ^ /@node@/: a 'GI.GLib.Structs.Node.Node'. -}
    -> m ()
nodeReverseChildren node = liftIO $ do
    node' <- unsafeManagedPtrGetPtr node
    g_node_reverse_children node'
    touchManagedPtr node
    return ()

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data NodeReverseChildrenMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo NodeReverseChildrenMethodInfo Node signature where
    overloadedMethod _ = nodeReverseChildren

#endif

-- method Node::unlink
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "node", argType = TInterface (Name {namespace = "GLib", name = "Node"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "the #GNode to unlink, which becomes the root of a new tree", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_node_unlink" g_node_unlink :: 
    Ptr Node ->                             -- node : TInterface (Name {namespace = "GLib", name = "Node"})
    IO ()

{- |
Unlinks a 'GI.GLib.Structs.Node.Node' from a tree, resulting in two separate trees.
-}
nodeUnlink ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Node
    {- ^ /@node@/: the 'GI.GLib.Structs.Node.Node' to unlink, which becomes the root of a new tree -}
    -> m ()
nodeUnlink node = liftIO $ do
    node' <- unsafeManagedPtrGetPtr node
    g_node_unlink node'
    touchManagedPtr node
    return ()

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data NodeUnlinkMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo NodeUnlinkMethodInfo Node signature where
    overloadedMethod _ = nodeUnlink

#endif

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
type family ResolveNodeMethod (t :: Symbol) (o :: *) :: * where
    ResolveNodeMethod "childIndex" o = NodeChildIndexMethodInfo
    ResolveNodeMethod "childPosition" o = NodeChildPositionMethodInfo
    ResolveNodeMethod "depth" o = NodeDepthMethodInfo
    ResolveNodeMethod "destroy" o = NodeDestroyMethodInfo
    ResolveNodeMethod "isAncestor" o = NodeIsAncestorMethodInfo
    ResolveNodeMethod "maxHeight" o = NodeMaxHeightMethodInfo
    ResolveNodeMethod "nChildren" o = NodeNChildrenMethodInfo
    ResolveNodeMethod "nNodes" o = NodeNNodesMethodInfo
    ResolveNodeMethod "reverseChildren" o = NodeReverseChildrenMethodInfo
    ResolveNodeMethod "unlink" o = NodeUnlinkMethodInfo
    ResolveNodeMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveNodeMethod t Node, O.MethodInfo info Node p) => O.IsLabelProxy t (Node -> p) where
    fromLabelProxy _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)

#if MIN_VERSION_base(4,9,0)
instance (info ~ ResolveNodeMethod t Node, O.MethodInfo info Node p) => O.IsLabel t (Node -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#else
    fromLabel _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#endif
#endif

#endif