{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- The t'GI.GLib.Structs.Node.Node' struct represents one node in a [n-ary tree][glib-N-ary-Trees].

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

module GI.GLib.Structs.Node
    ( 

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


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolveNodeMethod                       ,
#endif


-- ** childIndex #method:childIndex#

#if defined(ENABLE_OVERLOADING)
    NodeChildIndexMethodInfo                ,
#endif
    nodeChildIndex                          ,


-- ** childPosition #method:childPosition#

#if defined(ENABLE_OVERLOADING)
    NodeChildPositionMethodInfo             ,
#endif
    nodeChildPosition                       ,


-- ** depth #method:depth#

#if defined(ENABLE_OVERLOADING)
    NodeDepthMethodInfo                     ,
#endif
    nodeDepth                               ,


-- ** destroy #method:destroy#

#if defined(ENABLE_OVERLOADING)
    NodeDestroyMethodInfo                   ,
#endif
    nodeDestroy                             ,


-- ** isAncestor #method:isAncestor#

#if defined(ENABLE_OVERLOADING)
    NodeIsAncestorMethodInfo                ,
#endif
    nodeIsAncestor                          ,


-- ** maxHeight #method:maxHeight#

#if defined(ENABLE_OVERLOADING)
    NodeMaxHeightMethodInfo                 ,
#endif
    nodeMaxHeight                           ,


-- ** nChildren #method:nChildren#

#if defined(ENABLE_OVERLOADING)
    NodeNChildrenMethodInfo                 ,
#endif
    nodeNChildren                           ,


-- ** nNodes #method:nNodes#

#if defined(ENABLE_OVERLOADING)
    NodeNNodesMethodInfo                    ,
#endif
    nodeNNodes                              ,


-- ** reverseChildren #method:reverseChildren#

#if defined(ENABLE_OVERLOADING)
    NodeReverseChildrenMethodInfo           ,
#endif
    nodeReverseChildren                     ,


-- ** unlink #method:unlink#

#if defined(ENABLE_OVERLOADING)
    NodeUnlinkMethodInfo                    ,
#endif
    nodeUnlink                              ,




 -- * Properties
-- ** children #attr:children#
-- | points to the first child of the t'GI.GLib.Structs.Node.Node'.  The other
--            children are accessed by using the /@next@/ pointer of each
--            child.

    clearNodeChildren                       ,
    getNodeChildren                         ,
#if defined(ENABLE_OVERLOADING)
    node_children                           ,
#endif
    setNodeChildren                         ,


-- ** data #attr:data#
-- | contains the actual data of the node.

    clearNodeData                           ,
    getNodeData                             ,
#if defined(ENABLE_OVERLOADING)
    node_data                               ,
#endif
    setNodeData                             ,


-- ** next #attr:next#
-- | points to the node\'s next sibling (a sibling is another
--        t'GI.GLib.Structs.Node.Node' with the same parent).

    clearNodeNext                           ,
    getNodeNext                             ,
#if defined(ENABLE_OVERLOADING)
    node_next                               ,
#endif
    setNodeNext                             ,


-- ** parent #attr:parent#
-- | points to the parent of the t'GI.GLib.Structs.Node.Node', or is 'P.Nothing' if the
--          t'GI.GLib.Structs.Node.Node' is the root of the tree.

    clearNodeParent                         ,
    getNodeParent                           ,
#if defined(ENABLE_OVERLOADING)
    node_parent                             ,
#endif
    setNodeParent                           ,


-- ** prev #attr:prev#
-- | points to the node\'s previous sibling.

    clearNodePrev                           ,
    getNodePrev                             ,
#if defined(ENABLE_OVERLOADING)
    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.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 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 {-# SOURCE #-} qualified GI.GLib.Flags as GLib.Flags

-- | Memory-managed wrapper type.
newtype Node = Node (ManagedPtr Node)
    deriving (Node -> Node -> Bool
(Node -> Node -> Bool) -> (Node -> Node -> Bool) -> Eq Node
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Node -> Node -> Bool
$c/= :: Node -> Node -> Bool
== :: Node -> Node -> Bool
$c== :: Node -> Node -> Bool
Eq)
instance WrappedPtr Node where
    wrappedPtrCalloc :: IO (Ptr Node)
wrappedPtrCalloc = Int -> IO (Ptr Node)
forall a. Int -> IO (Ptr a)
callocBytes 40
    wrappedPtrCopy :: Node -> IO Node
wrappedPtrCopy = \p :: Node
p -> Node -> (Ptr Node -> IO Node) -> IO Node
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Node
p (Int -> Ptr Node -> IO (Ptr Node)
forall a. WrappedPtr a => Int -> Ptr a -> IO (Ptr a)
copyBytes 40 (Ptr Node -> IO (Ptr Node))
-> (Ptr Node -> IO Node) -> Ptr Node -> IO Node
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr Node -> Node) -> Ptr Node -> IO Node
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr Node -> Node
Node)
    wrappedPtrFree :: Maybe (GDestroyNotify Node)
wrappedPtrFree = GDestroyNotify Node -> Maybe (GDestroyNotify Node)
forall a. a -> Maybe a
Just GDestroyNotify Node
forall a. FunPtr (Ptr a -> IO ())
ptr_to_g_free

-- | Construct a `Node` struct initialized to zero.
newZeroNode :: MonadIO m => m Node
newZeroNode :: m Node
newZeroNode = IO Node -> m Node
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Node -> m Node) -> IO Node -> m Node
forall a b. (a -> b) -> a -> b
$ IO (Ptr Node)
forall a. WrappedPtr a => IO (Ptr a)
wrappedPtrCalloc IO (Ptr Node) -> (Ptr Node -> IO Node) -> IO Node
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr Node -> Node) -> Ptr Node -> IO Node
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr Node -> Node
Node

instance tag ~ 'AttrSet => Constructible Node tag where
    new :: (ManagedPtr Node -> Node) -> [AttrOp Node tag] -> m Node
new _ attrs :: [AttrOp Node tag]
attrs = do
        Node
o <- m Node
forall (m :: * -> *). MonadIO m => m Node
newZeroNode
        Node -> [AttrOp Node 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set Node
o [AttrOp Node tag]
[AttrOp Node 'AttrSet]
attrs
        Node -> m Node
forall (m :: * -> *) a. Monad m => a -> m a
return Node
o


-- | A convenience alias for `Nothing` :: `Maybe` `Node`.
noNode :: Maybe Node
noNode :: Maybe Node
noNode = Maybe Node
forall a. Maybe a
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 :: Node -> m (Ptr ())
getNodeData s :: Node
s = 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
$ Node -> (Ptr Node -> IO (Ptr ())) -> IO (Ptr ())
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Node
s ((Ptr Node -> IO (Ptr ())) -> IO (Ptr ()))
-> (Ptr Node -> IO (Ptr ())) -> IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Node
ptr -> do
    Ptr ()
val <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek (Ptr Node
ptr Ptr Node -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) :: IO (Ptr ())
    Ptr () -> IO (Ptr ())
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ()
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 :: Node -> Ptr () -> m ()
setNodeData s :: Node
s val :: Ptr ()
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Node -> (Ptr Node -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Node
s ((Ptr Node -> IO ()) -> IO ()) -> (Ptr Node -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Node
ptr -> do
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Node
ptr Ptr Node -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) (Ptr ()
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 :: Node -> m ()
clearNodeData s :: Node
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Node -> (Ptr Node -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Node
s ((Ptr Node -> IO ()) -> IO ()) -> (Ptr Node -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Node
ptr -> do
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Node
ptr Ptr Node -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) (Ptr ()
forall a. Ptr a
FP.nullPtr :: Ptr ())

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

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 :: Node -> m (Maybe Node)
getNodeNext s :: Node
s = IO (Maybe Node) -> m (Maybe Node)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Node) -> m (Maybe Node))
-> IO (Maybe Node) -> m (Maybe Node)
forall a b. (a -> b) -> a -> b
$ Node -> (Ptr Node -> IO (Maybe Node)) -> IO (Maybe Node)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Node
s ((Ptr Node -> IO (Maybe Node)) -> IO (Maybe Node))
-> (Ptr Node -> IO (Maybe Node)) -> IO (Maybe Node)
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Node
ptr -> do
    Ptr Node
val <- Ptr (Ptr Node) -> IO (Ptr Node)
forall a. Storable a => Ptr a -> IO a
peek (Ptr Node
ptr Ptr Node -> Int -> Ptr (Ptr Node)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8) :: IO (Ptr Node)
    Maybe Node
result <- Ptr Node -> (Ptr Node -> IO Node) -> IO (Maybe Node)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull Ptr Node
val ((Ptr Node -> IO Node) -> IO (Maybe Node))
-> (Ptr Node -> IO Node) -> IO (Maybe Node)
forall a b. (a -> b) -> a -> b
$ \val' :: Ptr Node
val' -> do
        Node
val'' <- ((ManagedPtr Node -> Node) -> Ptr Node -> IO Node
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr Node -> Node
Node) Ptr Node
val'
        Node -> IO Node
forall (m :: * -> *) a. Monad m => a -> m a
return Node
val''
    Maybe Node -> IO (Maybe Node)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Node
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 :: Node -> Ptr Node -> m ()
setNodeNext s :: Node
s val :: Ptr Node
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Node -> (Ptr Node -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Node
s ((Ptr Node -> IO ()) -> IO ()) -> (Ptr Node -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Node
ptr -> do
    Ptr (Ptr Node) -> Ptr Node -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Node
ptr Ptr Node -> Int -> Ptr (Ptr Node)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8) (Ptr Node
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 :: Node -> m ()
clearNodeNext s :: Node
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Node -> (Ptr Node -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Node
s ((Ptr Node -> IO ()) -> IO ()) -> (Ptr Node -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Node
ptr -> do
    Ptr (Ptr Node) -> Ptr Node -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Node
ptr Ptr Node -> Int -> Ptr (Ptr Node)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8) (Ptr Node
forall a. Ptr a
FP.nullPtr :: Ptr Node)

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

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 :: Node -> m (Maybe Node)
getNodePrev s :: Node
s = IO (Maybe Node) -> m (Maybe Node)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Node) -> m (Maybe Node))
-> IO (Maybe Node) -> m (Maybe Node)
forall a b. (a -> b) -> a -> b
$ Node -> (Ptr Node -> IO (Maybe Node)) -> IO (Maybe Node)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Node
s ((Ptr Node -> IO (Maybe Node)) -> IO (Maybe Node))
-> (Ptr Node -> IO (Maybe Node)) -> IO (Maybe Node)
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Node
ptr -> do
    Ptr Node
val <- Ptr (Ptr Node) -> IO (Ptr Node)
forall a. Storable a => Ptr a -> IO a
peek (Ptr Node
ptr Ptr Node -> Int -> Ptr (Ptr Node)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16) :: IO (Ptr Node)
    Maybe Node
result <- Ptr Node -> (Ptr Node -> IO Node) -> IO (Maybe Node)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull Ptr Node
val ((Ptr Node -> IO Node) -> IO (Maybe Node))
-> (Ptr Node -> IO Node) -> IO (Maybe Node)
forall a b. (a -> b) -> a -> b
$ \val' :: Ptr Node
val' -> do
        Node
val'' <- ((ManagedPtr Node -> Node) -> Ptr Node -> IO Node
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr Node -> Node
Node) Ptr Node
val'
        Node -> IO Node
forall (m :: * -> *) a. Monad m => a -> m a
return Node
val''
    Maybe Node -> IO (Maybe Node)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Node
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 :: Node -> Ptr Node -> m ()
setNodePrev s :: Node
s val :: Ptr Node
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Node -> (Ptr Node -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Node
s ((Ptr Node -> IO ()) -> IO ()) -> (Ptr Node -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Node
ptr -> do
    Ptr (Ptr Node) -> Ptr Node -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Node
ptr Ptr Node -> Int -> Ptr (Ptr Node)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16) (Ptr Node
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 :: Node -> m ()
clearNodePrev s :: Node
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Node -> (Ptr Node -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Node
s ((Ptr Node -> IO ()) -> IO ()) -> (Ptr Node -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Node
ptr -> do
    Ptr (Ptr Node) -> Ptr Node -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Node
ptr Ptr Node -> Int -> Ptr (Ptr Node)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16) (Ptr Node
forall a. Ptr a
FP.nullPtr :: Ptr Node)

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

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 :: Node -> m (Maybe Node)
getNodeParent s :: Node
s = IO (Maybe Node) -> m (Maybe Node)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Node) -> m (Maybe Node))
-> IO (Maybe Node) -> m (Maybe Node)
forall a b. (a -> b) -> a -> b
$ Node -> (Ptr Node -> IO (Maybe Node)) -> IO (Maybe Node)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Node
s ((Ptr Node -> IO (Maybe Node)) -> IO (Maybe Node))
-> (Ptr Node -> IO (Maybe Node)) -> IO (Maybe Node)
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Node
ptr -> do
    Ptr Node
val <- Ptr (Ptr Node) -> IO (Ptr Node)
forall a. Storable a => Ptr a -> IO a
peek (Ptr Node
ptr Ptr Node -> Int -> Ptr (Ptr Node)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24) :: IO (Ptr Node)
    Maybe Node
result <- Ptr Node -> (Ptr Node -> IO Node) -> IO (Maybe Node)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull Ptr Node
val ((Ptr Node -> IO Node) -> IO (Maybe Node))
-> (Ptr Node -> IO Node) -> IO (Maybe Node)
forall a b. (a -> b) -> a -> b
$ \val' :: Ptr Node
val' -> do
        Node
val'' <- ((ManagedPtr Node -> Node) -> Ptr Node -> IO Node
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr Node -> Node
Node) Ptr Node
val'
        Node -> IO Node
forall (m :: * -> *) a. Monad m => a -> m a
return Node
val''
    Maybe Node -> IO (Maybe Node)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Node
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 :: Node -> Ptr Node -> m ()
setNodeParent s :: Node
s val :: Ptr Node
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Node -> (Ptr Node -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Node
s ((Ptr Node -> IO ()) -> IO ()) -> (Ptr Node -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Node
ptr -> do
    Ptr (Ptr Node) -> Ptr Node -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Node
ptr Ptr Node -> Int -> Ptr (Ptr Node)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24) (Ptr Node
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 :: Node -> m ()
clearNodeParent s :: Node
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Node -> (Ptr Node -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Node
s ((Ptr Node -> IO ()) -> IO ()) -> (Ptr Node -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Node
ptr -> do
    Ptr (Ptr Node) -> Ptr Node -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Node
ptr Ptr Node -> Int -> Ptr (Ptr Node)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24) (Ptr Node
forall a. Ptr a
FP.nullPtr :: Ptr Node)

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

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 :: Node -> m (Maybe Node)
getNodeChildren s :: Node
s = IO (Maybe Node) -> m (Maybe Node)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Node) -> m (Maybe Node))
-> IO (Maybe Node) -> m (Maybe Node)
forall a b. (a -> b) -> a -> b
$ Node -> (Ptr Node -> IO (Maybe Node)) -> IO (Maybe Node)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Node
s ((Ptr Node -> IO (Maybe Node)) -> IO (Maybe Node))
-> (Ptr Node -> IO (Maybe Node)) -> IO (Maybe Node)
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Node
ptr -> do
    Ptr Node
val <- Ptr (Ptr Node) -> IO (Ptr Node)
forall a. Storable a => Ptr a -> IO a
peek (Ptr Node
ptr Ptr Node -> Int -> Ptr (Ptr Node)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32) :: IO (Ptr Node)
    Maybe Node
result <- Ptr Node -> (Ptr Node -> IO Node) -> IO (Maybe Node)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull Ptr Node
val ((Ptr Node -> IO Node) -> IO (Maybe Node))
-> (Ptr Node -> IO Node) -> IO (Maybe Node)
forall a b. (a -> b) -> a -> b
$ \val' :: Ptr Node
val' -> do
        Node
val'' <- ((ManagedPtr Node -> Node) -> Ptr Node -> IO Node
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr Node -> Node
Node) Ptr Node
val'
        Node -> IO Node
forall (m :: * -> *) a. Monad m => a -> m a
return Node
val''
    Maybe Node -> IO (Maybe Node)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Node
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 :: Node -> Ptr Node -> m ()
setNodeChildren s :: Node
s val :: Ptr Node
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Node -> (Ptr Node -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Node
s ((Ptr Node -> IO ()) -> IO ()) -> (Ptr Node -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Node
ptr -> do
    Ptr (Ptr Node) -> Ptr Node -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Node
ptr Ptr Node -> Int -> Ptr (Ptr Node)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32) (Ptr Node
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 :: Node -> m ()
clearNodeChildren s :: Node
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Node -> (Ptr Node -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Node
s ((Ptr Node -> IO ()) -> IO ()) -> (Ptr Node -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Node
ptr -> do
    Ptr (Ptr Node) -> Ptr Node -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Node
ptr Ptr Node -> Int -> Ptr (Ptr Node)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32) (Ptr Node
forall a. Ptr a
FP.nullPtr :: Ptr Node)

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

node_children :: AttrLabelProxy "children"
node_children = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
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 t'GI.GLib.Structs.Node.Node'
-- which contains the given data.
nodeChildIndex ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Node
    -- ^ /@node@/: a t'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 -> Ptr () -> m Int32
nodeChildIndex node :: Node
node data_ :: Ptr ()
data_ = 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 Node
node' <- Node -> IO (Ptr Node)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Node
node
    Int32
result <- Ptr Node -> Ptr () -> IO Int32
g_node_child_index Ptr Node
node' Ptr ()
data_
    Node -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Node
node
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
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 t'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 t'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 -> Node -> m Int32
nodeChildPosition node :: Node
node child :: Node
child = 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 Node
node' <- Node -> IO (Ptr Node)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Node
node
    Ptr Node
child' <- Node -> IO (Ptr Node)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Node
child
    Int32
result <- Ptr Node -> Ptr Node -> IO Int32
g_node_child_position Ptr Node
node' Ptr Node
child'
    Node -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Node
node
    Node -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Node
child
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
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 t'GI.GLib.Structs.Node.Node'.
-- 
-- If /@node@/ is 'P.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 t'GI.GLib.Structs.Node.Node'
    -> m Word32
    -- ^ __Returns:__ the depth of the t'GI.GLib.Structs.Node.Node'
nodeDepth :: Node -> m Word32
nodeDepth node :: Node
node = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr Node
node' <- Node -> IO (Ptr Node)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Node
node
    Word32
result <- Ptr Node -> IO Word32
g_node_depth Ptr Node
node'
    Node -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Node
node
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
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 :: Node -> m ()
nodeDestroy root :: Node
root = 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 Node
root' <- Node -> IO (Ptr Node)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Node
root
    Ptr Node -> IO ()
g_node_destroy Ptr Node
root'
    Node -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Node
root
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
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 'P.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 t'GI.GLib.Structs.Node.Node'
    -> Node
    -- ^ /@descendant@/: a t'GI.GLib.Structs.Node.Node'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@node@/ is an ancestor of /@descendant@/
nodeIsAncestor :: Node -> Node -> m Bool
nodeIsAncestor node :: Node
node descendant :: Node
descendant = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Node
node' <- Node -> IO (Ptr Node)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Node
node
    Ptr Node
descendant' <- Node -> IO (Ptr Node)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Node
descendant
    CInt
result <- Ptr Node -> Ptr Node -> IO CInt
g_node_is_ancestor Ptr Node
node' Ptr Node
descendant'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    Node -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Node
node
    Node -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Node
descendant
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
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 t'GI.GLib.Structs.Node.Node'.
-- This is the maximum distance from the t'GI.GLib.Structs.Node.Node' to all leaf nodes.
-- 
-- If /@root@/ is 'P.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 t'GI.GLib.Structs.Node.Node'
    -> m Word32
    -- ^ __Returns:__ the maximum height of the tree beneath /@root@/
nodeMaxHeight :: Node -> m Word32
nodeMaxHeight root :: Node
root = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr Node
root' <- Node -> IO (Ptr Node)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Node
root
    Word32
result <- Ptr Node -> IO Word32
g_node_max_height Ptr Node
root'
    Node -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Node
root
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
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 t'GI.GLib.Structs.Node.Node'.
nodeNChildren ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Node
    -- ^ /@node@/: a t'GI.GLib.Structs.Node.Node'
    -> m Word32
    -- ^ __Returns:__ the number of children of /@node@/
nodeNChildren :: Node -> m Word32
nodeNChildren node :: Node
node = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr Node
node' <- Node -> IO (Ptr Node)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Node
node
    Word32
result <- Ptr Node -> IO Word32
g_node_n_children Ptr Node
node'
    Node -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Node
node
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
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 t'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 :: Node -> [TraverseFlags] -> m Word32
nodeNNodes root :: Node
root flags :: [TraverseFlags]
flags = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr Node
root' <- Node -> IO (Ptr Node)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Node
root
    let flags' :: CUInt
flags' = [TraverseFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [TraverseFlags]
flags
    Word32
result <- Ptr Node -> CUInt -> IO Word32
g_node_n_nodes Ptr Node
root' CUInt
flags'
    Node -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Node
root
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
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 t'GI.GLib.Structs.Node.Node'.
-- (It doesn\'t change the order of the grandchildren.)
nodeReverseChildren ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Node
    -- ^ /@node@/: a t'GI.GLib.Structs.Node.Node'.
    -> m ()
nodeReverseChildren :: Node -> m ()
nodeReverseChildren node :: Node
node = 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 Node
node' <- Node -> IO (Ptr Node)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Node
node
    Ptr Node -> IO ()
g_node_reverse_children Ptr Node
node'
    Node -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Node
node
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
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 t'GI.GLib.Structs.Node.Node' from a tree, resulting in two separate trees.
nodeUnlink ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Node
    -- ^ /@node@/: the t'GI.GLib.Structs.Node.Node' to unlink, which becomes the root of a new tree
    -> m ()
nodeUnlink :: Node -> m ()
nodeUnlink node :: Node
node = 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 Node
node' <- Node -> IO (Ptr Node)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Node
node
    Ptr Node -> IO ()
g_node_unlink Ptr Node
node'
    Node -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Node
node
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

#endif

#if defined(ENABLE_OVERLOADING)
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) => OL.IsLabel t (Node -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#endif