{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Information about nodes in a remote object hierarchy.
-- 
-- /Since: 2.26/

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

module GI.Gio.Structs.DBusNodeInfo
    ( 

-- * Exported types
    DBusNodeInfo(..)                        ,
    newZeroDBusNodeInfo                     ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [generateXml]("GI.Gio.Structs.DBusNodeInfo#g:method:generateXml"), [lookupInterface]("GI.Gio.Structs.DBusNodeInfo#g:method:lookupInterface"), [ref]("GI.Gio.Structs.DBusNodeInfo#g:method:ref"), [unref]("GI.Gio.Structs.DBusNodeInfo#g:method:unref").
-- 
-- ==== Getters
-- /None/.
-- 
-- ==== Setters
-- /None/.

#if defined(ENABLE_OVERLOADING)
    ResolveDBusNodeInfoMethod               ,
#endif

-- ** generateXml #method:generateXml#

#if defined(ENABLE_OVERLOADING)
    DBusNodeInfoGenerateXmlMethodInfo       ,
#endif
    dBusNodeInfoGenerateXml                 ,


-- ** lookupInterface #method:lookupInterface#

#if defined(ENABLE_OVERLOADING)
    DBusNodeInfoLookupInterfaceMethodInfo   ,
#endif
    dBusNodeInfoLookupInterface             ,


-- ** newForXml #method:newForXml#

    dBusNodeInfoNewForXml                   ,


-- ** ref #method:ref#

#if defined(ENABLE_OVERLOADING)
    DBusNodeInfoRefMethodInfo               ,
#endif
    dBusNodeInfoRef                         ,


-- ** unref #method:unref#

#if defined(ENABLE_OVERLOADING)
    DBusNodeInfoUnrefMethodInfo             ,
#endif
    dBusNodeInfoUnref                       ,




 -- * Properties


-- ** annotations #attr:annotations#
-- | A pointer to a 'P.Nothing'-terminated array of pointers to t'GI.Gio.Structs.DBusAnnotationInfo.DBusAnnotationInfo' structures or 'P.Nothing' if there are no annotations.

    clearDBusNodeInfoAnnotations            ,
#if defined(ENABLE_OVERLOADING)
    dBusNodeInfo_annotations                ,
#endif
    getDBusNodeInfoAnnotations              ,
    setDBusNodeInfoAnnotations              ,


-- ** interfaces #attr:interfaces#
-- | A pointer to a 'P.Nothing'-terminated array of pointers to t'GI.Gio.Structs.DBusInterfaceInfo.DBusInterfaceInfo' structures or 'P.Nothing' if there are no interfaces.

    clearDBusNodeInfoInterfaces             ,
#if defined(ENABLE_OVERLOADING)
    dBusNodeInfo_interfaces                 ,
#endif
    getDBusNodeInfoInterfaces               ,
    setDBusNodeInfoInterfaces               ,


-- ** nodes #attr:nodes#
-- | A pointer to a 'P.Nothing'-terminated array of pointers to t'GI.Gio.Structs.DBusNodeInfo.DBusNodeInfo' structures or 'P.Nothing' if there are no nodes.

    clearDBusNodeInfoNodes                  ,
#if defined(ENABLE_OVERLOADING)
    dBusNodeInfo_nodes                      ,
#endif
    getDBusNodeInfoNodes                    ,
    setDBusNodeInfoNodes                    ,


-- ** path #attr:path#
-- | The path of the node or 'P.Nothing' if omitted. Note that this may be a relative path. See the D-Bus specification for more details.

    clearDBusNodeInfoPath                   ,
#if defined(ENABLE_OVERLOADING)
    dBusNodeInfo_path                       ,
#endif
    getDBusNodeInfoPath                     ,
    setDBusNodeInfoPath                     ,


-- ** refCount #attr:refCount#
-- | The reference count or -1 if statically allocated.

#if defined(ENABLE_OVERLOADING)
    dBusNodeInfo_refCount                   ,
#endif
    getDBusNodeInfoRefCount                 ,
    setDBusNodeInfoRefCount                 ,




    ) where

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

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R

import qualified GI.GLib.Structs.String as GLib.String
import {-# SOURCE #-} qualified GI.Gio.Structs.DBusAnnotationInfo as Gio.DBusAnnotationInfo
import {-# SOURCE #-} qualified GI.Gio.Structs.DBusInterfaceInfo as Gio.DBusInterfaceInfo

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

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

foreign import ccall "g_dbus_node_info_get_type" c_g_dbus_node_info_get_type :: 
    IO GType

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

instance B.Types.TypedObject DBusNodeInfo where
    glibType :: IO GType
glibType = IO GType
c_g_dbus_node_info_get_type

instance B.Types.GBoxed DBusNodeInfo

-- | Convert 'DBusNodeInfo' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe DBusNodeInfo) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_g_dbus_node_info_get_type
    gvalueSet_ :: Ptr GValue -> Maybe DBusNodeInfo -> IO ()
gvalueSet_ Ptr GValue
gv Maybe DBusNodeInfo
P.Nothing = Ptr GValue -> Ptr DBusNodeInfo -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv (Ptr DBusNodeInfo
forall a. Ptr a
FP.nullPtr :: FP.Ptr DBusNodeInfo)
    gvalueSet_ Ptr GValue
gv (P.Just DBusNodeInfo
obj) = DBusNodeInfo -> (Ptr DBusNodeInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr DBusNodeInfo
obj (Ptr GValue -> Ptr DBusNodeInfo -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe DBusNodeInfo)
gvalueGet_ Ptr GValue
gv = do
        Ptr DBusNodeInfo
ptr <- Ptr GValue -> IO (Ptr DBusNodeInfo)
forall b. Ptr GValue -> IO (Ptr b)
B.GValue.get_boxed Ptr GValue
gv :: IO (Ptr DBusNodeInfo)
        if Ptr DBusNodeInfo
ptr Ptr DBusNodeInfo -> Ptr DBusNodeInfo -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr DBusNodeInfo
forall a. Ptr a
FP.nullPtr
        then DBusNodeInfo -> Maybe DBusNodeInfo
forall a. a -> Maybe a
P.Just (DBusNodeInfo -> Maybe DBusNodeInfo)
-> IO DBusNodeInfo -> IO (Maybe DBusNodeInfo)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr DBusNodeInfo -> DBusNodeInfo)
-> Ptr DBusNodeInfo -> IO DBusNodeInfo
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr DBusNodeInfo -> DBusNodeInfo
DBusNodeInfo Ptr DBusNodeInfo
ptr
        else Maybe DBusNodeInfo -> IO (Maybe DBusNodeInfo)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe DBusNodeInfo
forall a. Maybe a
P.Nothing
        
    

-- | Construct a `DBusNodeInfo` struct initialized to zero.
newZeroDBusNodeInfo :: MonadIO m => m DBusNodeInfo
newZeroDBusNodeInfo :: forall (m :: * -> *). MonadIO m => m DBusNodeInfo
newZeroDBusNodeInfo = IO DBusNodeInfo -> m DBusNodeInfo
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DBusNodeInfo -> m DBusNodeInfo)
-> IO DBusNodeInfo -> m DBusNodeInfo
forall a b. (a -> b) -> a -> b
$ Int -> IO (Ptr DBusNodeInfo)
forall a. GBoxed a => Int -> IO (Ptr a)
callocBoxedBytes Int
40 IO (Ptr DBusNodeInfo)
-> (Ptr DBusNodeInfo -> IO DBusNodeInfo) -> IO DBusNodeInfo
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr DBusNodeInfo -> DBusNodeInfo)
-> Ptr DBusNodeInfo -> IO DBusNodeInfo
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr DBusNodeInfo -> DBusNodeInfo
DBusNodeInfo

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


-- | Get the value of the “@ref_count@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dBusNodeInfo #refCount
-- @
getDBusNodeInfoRefCount :: MonadIO m => DBusNodeInfo -> m Int32
getDBusNodeInfoRefCount :: forall (m :: * -> *). MonadIO m => DBusNodeInfo -> m Int32
getDBusNodeInfoRefCount DBusNodeInfo
s = 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
$ DBusNodeInfo -> (Ptr DBusNodeInfo -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr DBusNodeInfo
s ((Ptr DBusNodeInfo -> IO Int32) -> IO Int32)
-> (Ptr DBusNodeInfo -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \Ptr DBusNodeInfo
ptr -> do
    Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr DBusNodeInfo
ptr Ptr DBusNodeInfo -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) :: IO Int32
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val

-- | Set the value of the “@ref_count@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' dBusNodeInfo [ #refCount 'Data.GI.Base.Attributes.:=' value ]
-- @
setDBusNodeInfoRefCount :: MonadIO m => DBusNodeInfo -> Int32 -> m ()
setDBusNodeInfoRefCount :: forall (m :: * -> *). MonadIO m => DBusNodeInfo -> Int32 -> m ()
setDBusNodeInfoRefCount DBusNodeInfo
s Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ DBusNodeInfo -> (Ptr DBusNodeInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr DBusNodeInfo
s ((Ptr DBusNodeInfo -> IO ()) -> IO ())
-> (Ptr DBusNodeInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr DBusNodeInfo
ptr -> do
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr DBusNodeInfo
ptr Ptr DBusNodeInfo -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (Int32
val :: Int32)

#if defined(ENABLE_OVERLOADING)
data DBusNodeInfoRefCountFieldInfo
instance AttrInfo DBusNodeInfoRefCountFieldInfo where
    type AttrBaseTypeConstraint DBusNodeInfoRefCountFieldInfo = (~) DBusNodeInfo
    type AttrAllowedOps DBusNodeInfoRefCountFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint DBusNodeInfoRefCountFieldInfo = (~) Int32
    type AttrTransferTypeConstraint DBusNodeInfoRefCountFieldInfo = (~)Int32
    type AttrTransferType DBusNodeInfoRefCountFieldInfo = Int32
    type AttrGetType DBusNodeInfoRefCountFieldInfo = Int32
    type AttrLabel DBusNodeInfoRefCountFieldInfo = "ref_count"
    type AttrOrigin DBusNodeInfoRefCountFieldInfo = DBusNodeInfo
    attrGet = getDBusNodeInfoRefCount
    attrSet = setDBusNodeInfoRefCount
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

dBusNodeInfo_refCount :: AttrLabelProxy "refCount"
dBusNodeInfo_refCount = AttrLabelProxy

#endif


-- | Get the value of the “@path@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dBusNodeInfo #path
-- @
getDBusNodeInfoPath :: MonadIO m => DBusNodeInfo -> m (Maybe T.Text)
getDBusNodeInfoPath :: forall (m :: * -> *). MonadIO m => DBusNodeInfo -> m (Maybe Text)
getDBusNodeInfoPath DBusNodeInfo
s = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ DBusNodeInfo
-> (Ptr DBusNodeInfo -> IO (Maybe Text)) -> IO (Maybe Text)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr DBusNodeInfo
s ((Ptr DBusNodeInfo -> IO (Maybe Text)) -> IO (Maybe Text))
-> (Ptr DBusNodeInfo -> IO (Maybe Text)) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \Ptr DBusNodeInfo
ptr -> do
    CString
val <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek (Ptr DBusNodeInfo
ptr Ptr DBusNodeInfo -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) :: IO CString
    Maybe Text
result <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull CString
val ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
val' -> do
        Text
val'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
val'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
val''
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
result

-- | Set the value of the “@path@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' dBusNodeInfo [ #path 'Data.GI.Base.Attributes.:=' value ]
-- @
setDBusNodeInfoPath :: MonadIO m => DBusNodeInfo -> CString -> m ()
setDBusNodeInfoPath :: forall (m :: * -> *). MonadIO m => DBusNodeInfo -> CString -> m ()
setDBusNodeInfoPath DBusNodeInfo
s CString
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ DBusNodeInfo -> (Ptr DBusNodeInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr DBusNodeInfo
s ((Ptr DBusNodeInfo -> IO ()) -> IO ())
-> (Ptr DBusNodeInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr DBusNodeInfo
ptr -> do
    Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr DBusNodeInfo
ptr Ptr DBusNodeInfo -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (CString
val :: CString)

-- | Set the value of the “@path@” 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' #path
-- @
clearDBusNodeInfoPath :: MonadIO m => DBusNodeInfo -> m ()
clearDBusNodeInfoPath :: forall (m :: * -> *). MonadIO m => DBusNodeInfo -> m ()
clearDBusNodeInfoPath DBusNodeInfo
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ DBusNodeInfo -> (Ptr DBusNodeInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr DBusNodeInfo
s ((Ptr DBusNodeInfo -> IO ()) -> IO ())
-> (Ptr DBusNodeInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr DBusNodeInfo
ptr -> do
    Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr DBusNodeInfo
ptr Ptr DBusNodeInfo -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (CString
forall a. Ptr a
FP.nullPtr :: CString)

#if defined(ENABLE_OVERLOADING)
data DBusNodeInfoPathFieldInfo
instance AttrInfo DBusNodeInfoPathFieldInfo where
    type AttrBaseTypeConstraint DBusNodeInfoPathFieldInfo = (~) DBusNodeInfo
    type AttrAllowedOps DBusNodeInfoPathFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint DBusNodeInfoPathFieldInfo = (~) CString
    type AttrTransferTypeConstraint DBusNodeInfoPathFieldInfo = (~)CString
    type AttrTransferType DBusNodeInfoPathFieldInfo = CString
    type AttrGetType DBusNodeInfoPathFieldInfo = Maybe T.Text
    type AttrLabel DBusNodeInfoPathFieldInfo = "path"
    type AttrOrigin DBusNodeInfoPathFieldInfo = DBusNodeInfo
    attrGet = getDBusNodeInfoPath
    attrSet = setDBusNodeInfoPath
    attrConstruct = undefined
    attrClear = clearDBusNodeInfoPath
    attrTransfer _ v = do
        return v

dBusNodeInfo_path :: AttrLabelProxy "path"
dBusNodeInfo_path = AttrLabelProxy

#endif


-- | Get the value of the “@interfaces@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dBusNodeInfo #interfaces
-- @
getDBusNodeInfoInterfaces :: MonadIO m => DBusNodeInfo -> m (Maybe [Gio.DBusInterfaceInfo.DBusInterfaceInfo])
getDBusNodeInfoInterfaces :: forall (m :: * -> *).
MonadIO m =>
DBusNodeInfo -> m (Maybe [DBusInterfaceInfo])
getDBusNodeInfoInterfaces DBusNodeInfo
s = IO (Maybe [DBusInterfaceInfo]) -> m (Maybe [DBusInterfaceInfo])
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe [DBusInterfaceInfo]) -> m (Maybe [DBusInterfaceInfo]))
-> IO (Maybe [DBusInterfaceInfo]) -> m (Maybe [DBusInterfaceInfo])
forall a b. (a -> b) -> a -> b
$ DBusNodeInfo
-> (Ptr DBusNodeInfo -> IO (Maybe [DBusInterfaceInfo]))
-> IO (Maybe [DBusInterfaceInfo])
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr DBusNodeInfo
s ((Ptr DBusNodeInfo -> IO (Maybe [DBusInterfaceInfo]))
 -> IO (Maybe [DBusInterfaceInfo]))
-> (Ptr DBusNodeInfo -> IO (Maybe [DBusInterfaceInfo]))
-> IO (Maybe [DBusInterfaceInfo])
forall a b. (a -> b) -> a -> b
$ \Ptr DBusNodeInfo
ptr -> do
    Ptr (Ptr DBusInterfaceInfo)
val <- Ptr (Ptr (Ptr DBusInterfaceInfo))
-> IO (Ptr (Ptr DBusInterfaceInfo))
forall a. Storable a => Ptr a -> IO a
peek (Ptr DBusNodeInfo
ptr Ptr DBusNodeInfo -> Int -> Ptr (Ptr (Ptr DBusInterfaceInfo))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) :: IO (Ptr (Ptr Gio.DBusInterfaceInfo.DBusInterfaceInfo))
    Maybe [DBusInterfaceInfo]
result <- Ptr (Ptr DBusInterfaceInfo)
-> (Ptr (Ptr DBusInterfaceInfo) -> IO [DBusInterfaceInfo])
-> IO (Maybe [DBusInterfaceInfo])
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull Ptr (Ptr DBusInterfaceInfo)
val ((Ptr (Ptr DBusInterfaceInfo) -> IO [DBusInterfaceInfo])
 -> IO (Maybe [DBusInterfaceInfo]))
-> (Ptr (Ptr DBusInterfaceInfo) -> IO [DBusInterfaceInfo])
-> IO (Maybe [DBusInterfaceInfo])
forall a b. (a -> b) -> a -> b
$ \Ptr (Ptr DBusInterfaceInfo)
val' -> do
        [Ptr DBusInterfaceInfo]
val'' <- Ptr (Ptr DBusInterfaceInfo) -> IO [Ptr DBusInterfaceInfo]
forall a. Ptr (Ptr a) -> IO [Ptr a]
unpackZeroTerminatedPtrArray Ptr (Ptr DBusInterfaceInfo)
val'
        [DBusInterfaceInfo]
val''' <- (Ptr DBusInterfaceInfo -> IO DBusInterfaceInfo)
-> [Ptr DBusInterfaceInfo] -> IO [DBusInterfaceInfo]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((ManagedPtr DBusInterfaceInfo -> DBusInterfaceInfo)
-> Ptr DBusInterfaceInfo -> IO DBusInterfaceInfo
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr DBusInterfaceInfo -> DBusInterfaceInfo
Gio.DBusInterfaceInfo.DBusInterfaceInfo) [Ptr DBusInterfaceInfo]
val''
        [DBusInterfaceInfo] -> IO [DBusInterfaceInfo]
forall (m :: * -> *) a. Monad m => a -> m a
return [DBusInterfaceInfo]
val'''
    Maybe [DBusInterfaceInfo] -> IO (Maybe [DBusInterfaceInfo])
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe [DBusInterfaceInfo]
result

-- | Set the value of the “@interfaces@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' dBusNodeInfo [ #interfaces 'Data.GI.Base.Attributes.:=' value ]
-- @
setDBusNodeInfoInterfaces :: MonadIO m => DBusNodeInfo -> Ptr (Ptr Gio.DBusInterfaceInfo.DBusInterfaceInfo) -> m ()
setDBusNodeInfoInterfaces :: forall (m :: * -> *).
MonadIO m =>
DBusNodeInfo -> Ptr (Ptr DBusInterfaceInfo) -> m ()
setDBusNodeInfoInterfaces DBusNodeInfo
s Ptr (Ptr DBusInterfaceInfo)
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ DBusNodeInfo -> (Ptr DBusNodeInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr DBusNodeInfo
s ((Ptr DBusNodeInfo -> IO ()) -> IO ())
-> (Ptr DBusNodeInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr DBusNodeInfo
ptr -> do
    Ptr (Ptr (Ptr DBusInterfaceInfo))
-> Ptr (Ptr DBusInterfaceInfo) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr DBusNodeInfo
ptr Ptr DBusNodeInfo -> Int -> Ptr (Ptr (Ptr DBusInterfaceInfo))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) (Ptr (Ptr DBusInterfaceInfo)
val :: Ptr (Ptr Gio.DBusInterfaceInfo.DBusInterfaceInfo))

-- | Set the value of the “@interfaces@” 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' #interfaces
-- @
clearDBusNodeInfoInterfaces :: MonadIO m => DBusNodeInfo -> m ()
clearDBusNodeInfoInterfaces :: forall (m :: * -> *). MonadIO m => DBusNodeInfo -> m ()
clearDBusNodeInfoInterfaces DBusNodeInfo
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ DBusNodeInfo -> (Ptr DBusNodeInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr DBusNodeInfo
s ((Ptr DBusNodeInfo -> IO ()) -> IO ())
-> (Ptr DBusNodeInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr DBusNodeInfo
ptr -> do
    Ptr (Ptr (Ptr DBusInterfaceInfo))
-> Ptr (Ptr DBusInterfaceInfo) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr DBusNodeInfo
ptr Ptr DBusNodeInfo -> Int -> Ptr (Ptr (Ptr DBusInterfaceInfo))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) (Ptr (Ptr DBusInterfaceInfo)
forall a. Ptr a
FP.nullPtr :: Ptr (Ptr Gio.DBusInterfaceInfo.DBusInterfaceInfo))

#if defined(ENABLE_OVERLOADING)
data DBusNodeInfoInterfacesFieldInfo
instance AttrInfo DBusNodeInfoInterfacesFieldInfo where
    type AttrBaseTypeConstraint DBusNodeInfoInterfacesFieldInfo = (~) DBusNodeInfo
    type AttrAllowedOps DBusNodeInfoInterfacesFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint DBusNodeInfoInterfacesFieldInfo = (~) (Ptr (Ptr Gio.DBusInterfaceInfo.DBusInterfaceInfo))
    type AttrTransferTypeConstraint DBusNodeInfoInterfacesFieldInfo = (~)(Ptr (Ptr Gio.DBusInterfaceInfo.DBusInterfaceInfo))
    type AttrTransferType DBusNodeInfoInterfacesFieldInfo = (Ptr (Ptr Gio.DBusInterfaceInfo.DBusInterfaceInfo))
    type AttrGetType DBusNodeInfoInterfacesFieldInfo = Maybe [Gio.DBusInterfaceInfo.DBusInterfaceInfo]
    type AttrLabel DBusNodeInfoInterfacesFieldInfo = "interfaces"
    type AttrOrigin DBusNodeInfoInterfacesFieldInfo = DBusNodeInfo
    attrGet = getDBusNodeInfoInterfaces
    attrSet = setDBusNodeInfoInterfaces
    attrConstruct = undefined
    attrClear = clearDBusNodeInfoInterfaces
    attrTransfer _ v = do
        return v

dBusNodeInfo_interfaces :: AttrLabelProxy "interfaces"
dBusNodeInfo_interfaces = AttrLabelProxy

#endif


-- | Get the value of the “@nodes@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dBusNodeInfo #nodes
-- @
getDBusNodeInfoNodes :: MonadIO m => DBusNodeInfo -> m (Maybe [DBusNodeInfo])
getDBusNodeInfoNodes :: forall (m :: * -> *).
MonadIO m =>
DBusNodeInfo -> m (Maybe [DBusNodeInfo])
getDBusNodeInfoNodes DBusNodeInfo
s = IO (Maybe [DBusNodeInfo]) -> m (Maybe [DBusNodeInfo])
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe [DBusNodeInfo]) -> m (Maybe [DBusNodeInfo]))
-> IO (Maybe [DBusNodeInfo]) -> m (Maybe [DBusNodeInfo])
forall a b. (a -> b) -> a -> b
$ DBusNodeInfo
-> (Ptr DBusNodeInfo -> IO (Maybe [DBusNodeInfo]))
-> IO (Maybe [DBusNodeInfo])
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr DBusNodeInfo
s ((Ptr DBusNodeInfo -> IO (Maybe [DBusNodeInfo]))
 -> IO (Maybe [DBusNodeInfo]))
-> (Ptr DBusNodeInfo -> IO (Maybe [DBusNodeInfo]))
-> IO (Maybe [DBusNodeInfo])
forall a b. (a -> b) -> a -> b
$ \Ptr DBusNodeInfo
ptr -> do
    Ptr (Ptr DBusNodeInfo)
val <- Ptr (Ptr (Ptr DBusNodeInfo)) -> IO (Ptr (Ptr DBusNodeInfo))
forall a. Storable a => Ptr a -> IO a
peek (Ptr DBusNodeInfo
ptr Ptr DBusNodeInfo -> Int -> Ptr (Ptr (Ptr DBusNodeInfo))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24) :: IO (Ptr (Ptr DBusNodeInfo))
    Maybe [DBusNodeInfo]
result <- Ptr (Ptr DBusNodeInfo)
-> (Ptr (Ptr DBusNodeInfo) -> IO [DBusNodeInfo])
-> IO (Maybe [DBusNodeInfo])
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull Ptr (Ptr DBusNodeInfo)
val ((Ptr (Ptr DBusNodeInfo) -> IO [DBusNodeInfo])
 -> IO (Maybe [DBusNodeInfo]))
-> (Ptr (Ptr DBusNodeInfo) -> IO [DBusNodeInfo])
-> IO (Maybe [DBusNodeInfo])
forall a b. (a -> b) -> a -> b
$ \Ptr (Ptr DBusNodeInfo)
val' -> do
        [Ptr DBusNodeInfo]
val'' <- Ptr (Ptr DBusNodeInfo) -> IO [Ptr DBusNodeInfo]
forall a. Ptr (Ptr a) -> IO [Ptr a]
unpackZeroTerminatedPtrArray Ptr (Ptr DBusNodeInfo)
val'
        [DBusNodeInfo]
val''' <- (Ptr DBusNodeInfo -> IO DBusNodeInfo)
-> [Ptr DBusNodeInfo] -> IO [DBusNodeInfo]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((ManagedPtr DBusNodeInfo -> DBusNodeInfo)
-> Ptr DBusNodeInfo -> IO DBusNodeInfo
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr DBusNodeInfo -> DBusNodeInfo
DBusNodeInfo) [Ptr DBusNodeInfo]
val''
        [DBusNodeInfo] -> IO [DBusNodeInfo]
forall (m :: * -> *) a. Monad m => a -> m a
return [DBusNodeInfo]
val'''
    Maybe [DBusNodeInfo] -> IO (Maybe [DBusNodeInfo])
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe [DBusNodeInfo]
result

-- | Set the value of the “@nodes@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' dBusNodeInfo [ #nodes 'Data.GI.Base.Attributes.:=' value ]
-- @
setDBusNodeInfoNodes :: MonadIO m => DBusNodeInfo -> Ptr (Ptr DBusNodeInfo) -> m ()
setDBusNodeInfoNodes :: forall (m :: * -> *).
MonadIO m =>
DBusNodeInfo -> Ptr (Ptr DBusNodeInfo) -> m ()
setDBusNodeInfoNodes DBusNodeInfo
s Ptr (Ptr DBusNodeInfo)
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ DBusNodeInfo -> (Ptr DBusNodeInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr DBusNodeInfo
s ((Ptr DBusNodeInfo -> IO ()) -> IO ())
-> (Ptr DBusNodeInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr DBusNodeInfo
ptr -> do
    Ptr (Ptr (Ptr DBusNodeInfo)) -> Ptr (Ptr DBusNodeInfo) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr DBusNodeInfo
ptr Ptr DBusNodeInfo -> Int -> Ptr (Ptr (Ptr DBusNodeInfo))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24) (Ptr (Ptr DBusNodeInfo)
val :: Ptr (Ptr DBusNodeInfo))

-- | Set the value of the “@nodes@” 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' #nodes
-- @
clearDBusNodeInfoNodes :: MonadIO m => DBusNodeInfo -> m ()
clearDBusNodeInfoNodes :: forall (m :: * -> *). MonadIO m => DBusNodeInfo -> m ()
clearDBusNodeInfoNodes DBusNodeInfo
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ DBusNodeInfo -> (Ptr DBusNodeInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr DBusNodeInfo
s ((Ptr DBusNodeInfo -> IO ()) -> IO ())
-> (Ptr DBusNodeInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr DBusNodeInfo
ptr -> do
    Ptr (Ptr (Ptr DBusNodeInfo)) -> Ptr (Ptr DBusNodeInfo) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr DBusNodeInfo
ptr Ptr DBusNodeInfo -> Int -> Ptr (Ptr (Ptr DBusNodeInfo))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24) (Ptr (Ptr DBusNodeInfo)
forall a. Ptr a
FP.nullPtr :: Ptr (Ptr DBusNodeInfo))

#if defined(ENABLE_OVERLOADING)
data DBusNodeInfoNodesFieldInfo
instance AttrInfo DBusNodeInfoNodesFieldInfo where
    type AttrBaseTypeConstraint DBusNodeInfoNodesFieldInfo = (~) DBusNodeInfo
    type AttrAllowedOps DBusNodeInfoNodesFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint DBusNodeInfoNodesFieldInfo = (~) (Ptr (Ptr DBusNodeInfo))
    type AttrTransferTypeConstraint DBusNodeInfoNodesFieldInfo = (~)(Ptr (Ptr DBusNodeInfo))
    type AttrTransferType DBusNodeInfoNodesFieldInfo = (Ptr (Ptr DBusNodeInfo))
    type AttrGetType DBusNodeInfoNodesFieldInfo = Maybe [DBusNodeInfo]
    type AttrLabel DBusNodeInfoNodesFieldInfo = "nodes"
    type AttrOrigin DBusNodeInfoNodesFieldInfo = DBusNodeInfo
    attrGet = getDBusNodeInfoNodes
    attrSet = setDBusNodeInfoNodes
    attrConstruct = undefined
    attrClear = clearDBusNodeInfoNodes
    attrTransfer _ v = do
        return v

dBusNodeInfo_nodes :: AttrLabelProxy "nodes"
dBusNodeInfo_nodes = AttrLabelProxy

#endif


-- | Get the value of the “@annotations@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dBusNodeInfo #annotations
-- @
getDBusNodeInfoAnnotations :: MonadIO m => DBusNodeInfo -> m (Maybe [Gio.DBusAnnotationInfo.DBusAnnotationInfo])
getDBusNodeInfoAnnotations :: forall (m :: * -> *).
MonadIO m =>
DBusNodeInfo -> m (Maybe [DBusAnnotationInfo])
getDBusNodeInfoAnnotations DBusNodeInfo
s = IO (Maybe [DBusAnnotationInfo]) -> m (Maybe [DBusAnnotationInfo])
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe [DBusAnnotationInfo]) -> m (Maybe [DBusAnnotationInfo]))
-> IO (Maybe [DBusAnnotationInfo])
-> m (Maybe [DBusAnnotationInfo])
forall a b. (a -> b) -> a -> b
$ DBusNodeInfo
-> (Ptr DBusNodeInfo -> IO (Maybe [DBusAnnotationInfo]))
-> IO (Maybe [DBusAnnotationInfo])
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr DBusNodeInfo
s ((Ptr DBusNodeInfo -> IO (Maybe [DBusAnnotationInfo]))
 -> IO (Maybe [DBusAnnotationInfo]))
-> (Ptr DBusNodeInfo -> IO (Maybe [DBusAnnotationInfo]))
-> IO (Maybe [DBusAnnotationInfo])
forall a b. (a -> b) -> a -> b
$ \Ptr DBusNodeInfo
ptr -> do
    Ptr (Ptr DBusAnnotationInfo)
val <- Ptr (Ptr (Ptr DBusAnnotationInfo))
-> IO (Ptr (Ptr DBusAnnotationInfo))
forall a. Storable a => Ptr a -> IO a
peek (Ptr DBusNodeInfo
ptr Ptr DBusNodeInfo -> Int -> Ptr (Ptr (Ptr DBusAnnotationInfo))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32) :: IO (Ptr (Ptr Gio.DBusAnnotationInfo.DBusAnnotationInfo))
    Maybe [DBusAnnotationInfo]
result <- Ptr (Ptr DBusAnnotationInfo)
-> (Ptr (Ptr DBusAnnotationInfo) -> IO [DBusAnnotationInfo])
-> IO (Maybe [DBusAnnotationInfo])
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull Ptr (Ptr DBusAnnotationInfo)
val ((Ptr (Ptr DBusAnnotationInfo) -> IO [DBusAnnotationInfo])
 -> IO (Maybe [DBusAnnotationInfo]))
-> (Ptr (Ptr DBusAnnotationInfo) -> IO [DBusAnnotationInfo])
-> IO (Maybe [DBusAnnotationInfo])
forall a b. (a -> b) -> a -> b
$ \Ptr (Ptr DBusAnnotationInfo)
val' -> do
        [Ptr DBusAnnotationInfo]
val'' <- Ptr (Ptr DBusAnnotationInfo) -> IO [Ptr DBusAnnotationInfo]
forall a. Ptr (Ptr a) -> IO [Ptr a]
unpackZeroTerminatedPtrArray Ptr (Ptr DBusAnnotationInfo)
val'
        [DBusAnnotationInfo]
val''' <- (Ptr DBusAnnotationInfo -> IO DBusAnnotationInfo)
-> [Ptr DBusAnnotationInfo] -> IO [DBusAnnotationInfo]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((ManagedPtr DBusAnnotationInfo -> DBusAnnotationInfo)
-> Ptr DBusAnnotationInfo -> IO DBusAnnotationInfo
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr DBusAnnotationInfo -> DBusAnnotationInfo
Gio.DBusAnnotationInfo.DBusAnnotationInfo) [Ptr DBusAnnotationInfo]
val''
        [DBusAnnotationInfo] -> IO [DBusAnnotationInfo]
forall (m :: * -> *) a. Monad m => a -> m a
return [DBusAnnotationInfo]
val'''
    Maybe [DBusAnnotationInfo] -> IO (Maybe [DBusAnnotationInfo])
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe [DBusAnnotationInfo]
result

-- | Set the value of the “@annotations@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' dBusNodeInfo [ #annotations 'Data.GI.Base.Attributes.:=' value ]
-- @
setDBusNodeInfoAnnotations :: MonadIO m => DBusNodeInfo -> Ptr (Ptr Gio.DBusAnnotationInfo.DBusAnnotationInfo) -> m ()
setDBusNodeInfoAnnotations :: forall (m :: * -> *).
MonadIO m =>
DBusNodeInfo -> Ptr (Ptr DBusAnnotationInfo) -> m ()
setDBusNodeInfoAnnotations DBusNodeInfo
s Ptr (Ptr DBusAnnotationInfo)
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ DBusNodeInfo -> (Ptr DBusNodeInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr DBusNodeInfo
s ((Ptr DBusNodeInfo -> IO ()) -> IO ())
-> (Ptr DBusNodeInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr DBusNodeInfo
ptr -> do
    Ptr (Ptr (Ptr DBusAnnotationInfo))
-> Ptr (Ptr DBusAnnotationInfo) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr DBusNodeInfo
ptr Ptr DBusNodeInfo -> Int -> Ptr (Ptr (Ptr DBusAnnotationInfo))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32) (Ptr (Ptr DBusAnnotationInfo)
val :: Ptr (Ptr Gio.DBusAnnotationInfo.DBusAnnotationInfo))

-- | Set the value of the “@annotations@” 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' #annotations
-- @
clearDBusNodeInfoAnnotations :: MonadIO m => DBusNodeInfo -> m ()
clearDBusNodeInfoAnnotations :: forall (m :: * -> *). MonadIO m => DBusNodeInfo -> m ()
clearDBusNodeInfoAnnotations DBusNodeInfo
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ DBusNodeInfo -> (Ptr DBusNodeInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr DBusNodeInfo
s ((Ptr DBusNodeInfo -> IO ()) -> IO ())
-> (Ptr DBusNodeInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr DBusNodeInfo
ptr -> do
    Ptr (Ptr (Ptr DBusAnnotationInfo))
-> Ptr (Ptr DBusAnnotationInfo) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr DBusNodeInfo
ptr Ptr DBusNodeInfo -> Int -> Ptr (Ptr (Ptr DBusAnnotationInfo))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32) (Ptr (Ptr DBusAnnotationInfo)
forall a. Ptr a
FP.nullPtr :: Ptr (Ptr Gio.DBusAnnotationInfo.DBusAnnotationInfo))

#if defined(ENABLE_OVERLOADING)
data DBusNodeInfoAnnotationsFieldInfo
instance AttrInfo DBusNodeInfoAnnotationsFieldInfo where
    type AttrBaseTypeConstraint DBusNodeInfoAnnotationsFieldInfo = (~) DBusNodeInfo
    type AttrAllowedOps DBusNodeInfoAnnotationsFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint DBusNodeInfoAnnotationsFieldInfo = (~) (Ptr (Ptr Gio.DBusAnnotationInfo.DBusAnnotationInfo))
    type AttrTransferTypeConstraint DBusNodeInfoAnnotationsFieldInfo = (~)(Ptr (Ptr Gio.DBusAnnotationInfo.DBusAnnotationInfo))
    type AttrTransferType DBusNodeInfoAnnotationsFieldInfo = (Ptr (Ptr Gio.DBusAnnotationInfo.DBusAnnotationInfo))
    type AttrGetType DBusNodeInfoAnnotationsFieldInfo = Maybe [Gio.DBusAnnotationInfo.DBusAnnotationInfo]
    type AttrLabel DBusNodeInfoAnnotationsFieldInfo = "annotations"
    type AttrOrigin DBusNodeInfoAnnotationsFieldInfo = DBusNodeInfo
    attrGet = getDBusNodeInfoAnnotations
    attrSet = setDBusNodeInfoAnnotations
    attrConstruct = undefined
    attrClear = clearDBusNodeInfoAnnotations
    attrTransfer _ v = do
        return v

dBusNodeInfo_annotations :: AttrLabelProxy "annotations"
dBusNodeInfo_annotations = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DBusNodeInfo
type instance O.AttributeList DBusNodeInfo = DBusNodeInfoAttributeList
type DBusNodeInfoAttributeList = ('[ '("refCount", DBusNodeInfoRefCountFieldInfo), '("path", DBusNodeInfoPathFieldInfo), '("interfaces", DBusNodeInfoInterfacesFieldInfo), '("nodes", DBusNodeInfoNodesFieldInfo), '("annotations", DBusNodeInfoAnnotationsFieldInfo)] :: [(Symbol, *)])
#endif

-- method DBusNodeInfo::new_for_xml
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "xml_data"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Valid D-Bus introspection XML."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gio" , name = "DBusNodeInfo" })
-- throws : True
-- Skip return : False

foreign import ccall "g_dbus_node_info_new_for_xml" g_dbus_node_info_new_for_xml :: 
    CString ->                              -- xml_data : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr DBusNodeInfo)

-- | Parses /@xmlData@/ and returns a t'GI.Gio.Structs.DBusNodeInfo.DBusNodeInfo' representing the data.
-- 
-- The introspection XML must contain exactly one top-level
-- \<node> element.
-- 
-- Note that this routine is using a
-- [GMarkup][glib-Simple-XML-Subset-Parser.description]-based
-- parser that only accepts a subset of valid XML documents.
-- 
-- /Since: 2.26/
dBusNodeInfoNewForXml ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@xmlData@/: Valid D-Bus introspection XML.
    -> m DBusNodeInfo
    -- ^ __Returns:__ A t'GI.Gio.Structs.DBusNodeInfo.DBusNodeInfo' structure or 'P.Nothing' if /@error@/ is set. Free
    -- with 'GI.Gio.Structs.DBusNodeInfo.dBusNodeInfoUnref'. /(Can throw 'Data.GI.Base.GError.GError')/
dBusNodeInfoNewForXml :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> m DBusNodeInfo
dBusNodeInfoNewForXml Text
xmlData = IO DBusNodeInfo -> m DBusNodeInfo
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DBusNodeInfo -> m DBusNodeInfo)
-> IO DBusNodeInfo -> m DBusNodeInfo
forall a b. (a -> b) -> a -> b
$ do
    CString
xmlData' <- Text -> IO CString
textToCString Text
xmlData
    IO DBusNodeInfo -> IO () -> IO DBusNodeInfo
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr DBusNodeInfo
result <- (Ptr (Ptr GError) -> IO (Ptr DBusNodeInfo))
-> IO (Ptr DBusNodeInfo)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr DBusNodeInfo))
 -> IO (Ptr DBusNodeInfo))
-> (Ptr (Ptr GError) -> IO (Ptr DBusNodeInfo))
-> IO (Ptr DBusNodeInfo)
forall a b. (a -> b) -> a -> b
$ CString -> Ptr (Ptr GError) -> IO (Ptr DBusNodeInfo)
g_dbus_node_info_new_for_xml CString
xmlData'
        Text -> Ptr DBusNodeInfo -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"dBusNodeInfoNewForXml" Ptr DBusNodeInfo
result
        DBusNodeInfo
result' <- ((ManagedPtr DBusNodeInfo -> DBusNodeInfo)
-> Ptr DBusNodeInfo -> IO DBusNodeInfo
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr DBusNodeInfo -> DBusNodeInfo
DBusNodeInfo) Ptr DBusNodeInfo
result
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
xmlData'
        DBusNodeInfo -> IO DBusNodeInfo
forall (m :: * -> *) a. Monad m => a -> m a
return DBusNodeInfo
result'
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
xmlData'
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method DBusNodeInfo::generate_xml
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusNodeInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusNodeInfo." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "indent"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Indentation level." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "string_builder"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "String" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GString to to append XML data to."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_node_info_generate_xml" g_dbus_node_info_generate_xml :: 
    Ptr DBusNodeInfo ->                     -- info : TInterface (Name {namespace = "Gio", name = "DBusNodeInfo"})
    Word32 ->                               -- indent : TBasicType TUInt
    Ptr GLib.String.String ->               -- string_builder : TInterface (Name {namespace = "GLib", name = "String"})
    IO ()

-- | Appends an XML representation of /@info@/ (and its children) to /@stringBuilder@/.
-- 
-- This function is typically used for generating introspection XML documents at run-time for
-- handling the @org.freedesktop.DBus.Introspectable.Introspect@  method.
-- 
-- /Since: 2.26/
dBusNodeInfoGenerateXml ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    DBusNodeInfo
    -- ^ /@info@/: A t'GI.Gio.Structs.DBusNodeInfo.DBusNodeInfo'.
    -> Word32
    -- ^ /@indent@/: Indentation level.
    -> GLib.String.String
    -- ^ /@stringBuilder@/: A t'GI.GLib.Structs.String.String' to to append XML data to.
    -> m ()
dBusNodeInfoGenerateXml :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
DBusNodeInfo -> Word32 -> String -> m ()
dBusNodeInfoGenerateXml DBusNodeInfo
info Word32
indent String
stringBuilder = 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 DBusNodeInfo
info' <- DBusNodeInfo -> IO (Ptr DBusNodeInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr DBusNodeInfo
info
    Ptr String
stringBuilder' <- String -> IO (Ptr String)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr String
stringBuilder
    Ptr DBusNodeInfo -> Word32 -> Ptr String -> IO ()
g_dbus_node_info_generate_xml Ptr DBusNodeInfo
info' Word32
indent Ptr String
stringBuilder'
    DBusNodeInfo -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr DBusNodeInfo
info
    String -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr String
stringBuilder
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DBusNodeInfoGenerateXmlMethodInfo
instance (signature ~ (Word32 -> GLib.String.String -> m ()), MonadIO m) => O.OverloadedMethod DBusNodeInfoGenerateXmlMethodInfo DBusNodeInfo signature where
    overloadedMethod = dBusNodeInfoGenerateXml

instance O.OverloadedMethodInfo DBusNodeInfoGenerateXmlMethodInfo DBusNodeInfo where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Structs.DBusNodeInfo.dBusNodeInfoGenerateXml",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Structs-DBusNodeInfo.html#v:dBusNodeInfoGenerateXml"
        }


#endif

-- method DBusNodeInfo::lookup_interface
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusNodeInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusNodeInfo." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A D-Bus interface name."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Gio" , name = "DBusInterfaceInfo" })
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_node_info_lookup_interface" g_dbus_node_info_lookup_interface :: 
    Ptr DBusNodeInfo ->                     -- info : TInterface (Name {namespace = "Gio", name = "DBusNodeInfo"})
    CString ->                              -- name : TBasicType TUTF8
    IO (Ptr Gio.DBusInterfaceInfo.DBusInterfaceInfo)

-- | Looks up information about an interface.
-- 
-- The cost of this function is O(n) in number of interfaces.
-- 
-- /Since: 2.26/
dBusNodeInfoLookupInterface ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    DBusNodeInfo
    -- ^ /@info@/: A t'GI.Gio.Structs.DBusNodeInfo.DBusNodeInfo'.
    -> T.Text
    -- ^ /@name@/: A D-Bus interface name.
    -> m Gio.DBusInterfaceInfo.DBusInterfaceInfo
    -- ^ __Returns:__ A t'GI.Gio.Structs.DBusInterfaceInfo.DBusInterfaceInfo' or 'P.Nothing' if not found. Do not free, it is owned by /@info@/.
dBusNodeInfoLookupInterface :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
DBusNodeInfo -> Text -> m DBusInterfaceInfo
dBusNodeInfoLookupInterface DBusNodeInfo
info Text
name = IO DBusInterfaceInfo -> m DBusInterfaceInfo
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DBusInterfaceInfo -> m DBusInterfaceInfo)
-> IO DBusInterfaceInfo -> m DBusInterfaceInfo
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusNodeInfo
info' <- DBusNodeInfo -> IO (Ptr DBusNodeInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr DBusNodeInfo
info
    CString
name' <- Text -> IO CString
textToCString Text
name
    Ptr DBusInterfaceInfo
result <- Ptr DBusNodeInfo -> CString -> IO (Ptr DBusInterfaceInfo)
g_dbus_node_info_lookup_interface Ptr DBusNodeInfo
info' CString
name'
    Text -> Ptr DBusInterfaceInfo -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"dBusNodeInfoLookupInterface" Ptr DBusInterfaceInfo
result
    DBusInterfaceInfo
result' <- ((ManagedPtr DBusInterfaceInfo -> DBusInterfaceInfo)
-> Ptr DBusInterfaceInfo -> IO DBusInterfaceInfo
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr DBusInterfaceInfo -> DBusInterfaceInfo
Gio.DBusInterfaceInfo.DBusInterfaceInfo) Ptr DBusInterfaceInfo
result
    DBusNodeInfo -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr DBusNodeInfo
info
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
    DBusInterfaceInfo -> IO DBusInterfaceInfo
forall (m :: * -> *) a. Monad m => a -> m a
return DBusInterfaceInfo
result'

#if defined(ENABLE_OVERLOADING)
data DBusNodeInfoLookupInterfaceMethodInfo
instance (signature ~ (T.Text -> m Gio.DBusInterfaceInfo.DBusInterfaceInfo), MonadIO m) => O.OverloadedMethod DBusNodeInfoLookupInterfaceMethodInfo DBusNodeInfo signature where
    overloadedMethod = dBusNodeInfoLookupInterface

instance O.OverloadedMethodInfo DBusNodeInfoLookupInterfaceMethodInfo DBusNodeInfo where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Structs.DBusNodeInfo.dBusNodeInfoLookupInterface",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Structs-DBusNodeInfo.html#v:dBusNodeInfoLookupInterface"
        }


#endif

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

foreign import ccall "g_dbus_node_info_ref" g_dbus_node_info_ref :: 
    Ptr DBusNodeInfo ->                     -- info : TInterface (Name {namespace = "Gio", name = "DBusNodeInfo"})
    IO (Ptr DBusNodeInfo)

-- | If /@info@/ is statically allocated does nothing. Otherwise increases
-- the reference count.
-- 
-- /Since: 2.26/
dBusNodeInfoRef ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    DBusNodeInfo
    -- ^ /@info@/: A t'GI.Gio.Structs.DBusNodeInfo.DBusNodeInfo'
    -> m DBusNodeInfo
    -- ^ __Returns:__ The same /@info@/.
dBusNodeInfoRef :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
DBusNodeInfo -> m DBusNodeInfo
dBusNodeInfoRef DBusNodeInfo
info = IO DBusNodeInfo -> m DBusNodeInfo
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DBusNodeInfo -> m DBusNodeInfo)
-> IO DBusNodeInfo -> m DBusNodeInfo
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusNodeInfo
info' <- DBusNodeInfo -> IO (Ptr DBusNodeInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr DBusNodeInfo
info
    Ptr DBusNodeInfo
result <- Ptr DBusNodeInfo -> IO (Ptr DBusNodeInfo)
g_dbus_node_info_ref Ptr DBusNodeInfo
info'
    Text -> Ptr DBusNodeInfo -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"dBusNodeInfoRef" Ptr DBusNodeInfo
result
    DBusNodeInfo
result' <- ((ManagedPtr DBusNodeInfo -> DBusNodeInfo)
-> Ptr DBusNodeInfo -> IO DBusNodeInfo
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr DBusNodeInfo -> DBusNodeInfo
DBusNodeInfo) Ptr DBusNodeInfo
result
    DBusNodeInfo -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr DBusNodeInfo
info
    DBusNodeInfo -> IO DBusNodeInfo
forall (m :: * -> *) a. Monad m => a -> m a
return DBusNodeInfo
result'

#if defined(ENABLE_OVERLOADING)
data DBusNodeInfoRefMethodInfo
instance (signature ~ (m DBusNodeInfo), MonadIO m) => O.OverloadedMethod DBusNodeInfoRefMethodInfo DBusNodeInfo signature where
    overloadedMethod = dBusNodeInfoRef

instance O.OverloadedMethodInfo DBusNodeInfoRefMethodInfo DBusNodeInfo where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Structs.DBusNodeInfo.dBusNodeInfoRef",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Structs-DBusNodeInfo.html#v:dBusNodeInfoRef"
        }


#endif

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

foreign import ccall "g_dbus_node_info_unref" g_dbus_node_info_unref :: 
    Ptr DBusNodeInfo ->                     -- info : TInterface (Name {namespace = "Gio", name = "DBusNodeInfo"})
    IO ()

-- | If /@info@/ is statically allocated, does nothing. Otherwise decreases
-- the reference count of /@info@/. When its reference count drops to 0,
-- the memory used is freed.
-- 
-- /Since: 2.26/
dBusNodeInfoUnref ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    DBusNodeInfo
    -- ^ /@info@/: A t'GI.Gio.Structs.DBusNodeInfo.DBusNodeInfo'.
    -> m ()
dBusNodeInfoUnref :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
DBusNodeInfo -> m ()
dBusNodeInfoUnref DBusNodeInfo
info = 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 DBusNodeInfo
info' <- DBusNodeInfo -> IO (Ptr DBusNodeInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr DBusNodeInfo
info
    Ptr DBusNodeInfo -> IO ()
g_dbus_node_info_unref Ptr DBusNodeInfo
info'
    DBusNodeInfo -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr DBusNodeInfo
info
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DBusNodeInfoUnrefMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod DBusNodeInfoUnrefMethodInfo DBusNodeInfo signature where
    overloadedMethod = dBusNodeInfoUnref

instance O.OverloadedMethodInfo DBusNodeInfoUnrefMethodInfo DBusNodeInfo where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Structs.DBusNodeInfo.dBusNodeInfoUnref",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Structs-DBusNodeInfo.html#v:dBusNodeInfoUnref"
        }


#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveDBusNodeInfoMethod (t :: Symbol) (o :: *) :: * where
    ResolveDBusNodeInfoMethod "generateXml" o = DBusNodeInfoGenerateXmlMethodInfo
    ResolveDBusNodeInfoMethod "lookupInterface" o = DBusNodeInfoLookupInterfaceMethodInfo
    ResolveDBusNodeInfoMethod "ref" o = DBusNodeInfoRefMethodInfo
    ResolveDBusNodeInfoMethod "unref" o = DBusNodeInfoUnrefMethodInfo
    ResolveDBusNodeInfoMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveDBusNodeInfoMethod t DBusNodeInfo, O.OverloadedMethod info DBusNodeInfo p) => OL.IsLabel t (DBusNodeInfo -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveDBusNodeInfoMethod t DBusNodeInfo, O.OverloadedMethod info DBusNodeInfo p, R.HasField t DBusNodeInfo p) => R.HasField t DBusNodeInfo p where
    getField = O.overloadedMethod @info

#endif

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

#endif