{-# 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 a D-Bus property on a D-Bus interface.
-- 
-- /Since: 2.26/

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

module GI.Gio.Structs.DBusPropertyInfo
    ( 

-- * Exported types
    DBusPropertyInfo(..)                    ,
    newZeroDBusPropertyInfo                 ,
    noDBusPropertyInfo                      ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveDBusPropertyInfoMethod           ,
#endif


-- ** ref #method:ref#

#if defined(ENABLE_OVERLOADING)
    DBusPropertyInfoRefMethodInfo           ,
#endif
    dBusPropertyInfoRef                     ,


-- ** unref #method:unref#

#if defined(ENABLE_OVERLOADING)
    DBusPropertyInfoUnrefMethodInfo         ,
#endif
    dBusPropertyInfoUnref                   ,




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

    clearDBusPropertyInfoAnnotations        ,
#if defined(ENABLE_OVERLOADING)
    dBusPropertyInfo_annotations            ,
#endif
    getDBusPropertyInfoAnnotations          ,
    setDBusPropertyInfoAnnotations          ,


-- ** flags #attr:flags#
-- | Access control flags for the property.

#if defined(ENABLE_OVERLOADING)
    dBusPropertyInfo_flags                  ,
#endif
    getDBusPropertyInfoFlags                ,
    setDBusPropertyInfoFlags                ,


-- ** name #attr:name#
-- | The name of the D-Bus property, e.g. \"SupportedFilesystems\".

    clearDBusPropertyInfoName               ,
#if defined(ENABLE_OVERLOADING)
    dBusPropertyInfo_name                   ,
#endif
    getDBusPropertyInfoName                 ,
    setDBusPropertyInfoName                 ,


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

#if defined(ENABLE_OVERLOADING)
    dBusPropertyInfo_refCount               ,
#endif
    getDBusPropertyInfoRefCount             ,
    setDBusPropertyInfoRefCount             ,


-- ** signature #attr:signature#
-- | The D-Bus signature of the property (a single complete type).

    clearDBusPropertyInfoSignature          ,
#if defined(ENABLE_OVERLOADING)
    dBusPropertyInfo_signature              ,
#endif
    getDBusPropertyInfoSignature            ,
    setDBusPropertyInfoSignature            ,




    ) 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.Gio.Flags as Gio.Flags
import {-# SOURCE #-} qualified GI.Gio.Structs.DBusAnnotationInfo as Gio.DBusAnnotationInfo

-- | Memory-managed wrapper type.
newtype DBusPropertyInfo = DBusPropertyInfo (ManagedPtr DBusPropertyInfo)
    deriving (DBusPropertyInfo -> DBusPropertyInfo -> Bool
(DBusPropertyInfo -> DBusPropertyInfo -> Bool)
-> (DBusPropertyInfo -> DBusPropertyInfo -> Bool)
-> Eq DBusPropertyInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DBusPropertyInfo -> DBusPropertyInfo -> Bool
$c/= :: DBusPropertyInfo -> DBusPropertyInfo -> Bool
== :: DBusPropertyInfo -> DBusPropertyInfo -> Bool
$c== :: DBusPropertyInfo -> DBusPropertyInfo -> Bool
Eq)
foreign import ccall "g_dbus_property_info_get_type" c_g_dbus_property_info_get_type :: 
    IO GType

instance BoxedObject DBusPropertyInfo where
    boxedType :: DBusPropertyInfo -> IO GType
boxedType _ = IO GType
c_g_dbus_property_info_get_type

-- | Convert 'DBusPropertyInfo' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue DBusPropertyInfo where
    toGValue :: DBusPropertyInfo -> IO GValue
toGValue o :: DBusPropertyInfo
o = do
        GType
gtype <- IO GType
c_g_dbus_property_info_get_type
        DBusPropertyInfo
-> (Ptr DBusPropertyInfo -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr DBusPropertyInfo
o (GType
-> (GValue -> Ptr DBusPropertyInfo -> IO ())
-> Ptr DBusPropertyInfo
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr DBusPropertyInfo -> IO ()
forall a. GValue -> Ptr a -> IO ()
B.GValue.set_boxed)
        
    fromGValue :: GValue -> IO DBusPropertyInfo
fromGValue gv :: GValue
gv = do
        Ptr DBusPropertyInfo
ptr <- GValue -> IO (Ptr DBusPropertyInfo)
forall b. GValue -> IO (Ptr b)
B.GValue.get_boxed GValue
gv :: IO (Ptr DBusPropertyInfo)
        (ManagedPtr DBusPropertyInfo -> DBusPropertyInfo)
-> Ptr DBusPropertyInfo -> IO DBusPropertyInfo
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr DBusPropertyInfo -> DBusPropertyInfo
DBusPropertyInfo Ptr DBusPropertyInfo
ptr
        
    

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

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


-- | A convenience alias for `Nothing` :: `Maybe` `DBusPropertyInfo`.
noDBusPropertyInfo :: Maybe DBusPropertyInfo
noDBusPropertyInfo :: Maybe DBusPropertyInfo
noDBusPropertyInfo = Maybe DBusPropertyInfo
forall a. Maybe a
Nothing

-- | 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' dBusPropertyInfo #refCount
-- @
getDBusPropertyInfoRefCount :: MonadIO m => DBusPropertyInfo -> m Int32
getDBusPropertyInfoRefCount :: DBusPropertyInfo -> m Int32
getDBusPropertyInfoRefCount s :: DBusPropertyInfo
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
$ DBusPropertyInfo -> (Ptr DBusPropertyInfo -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr DBusPropertyInfo
s ((Ptr DBusPropertyInfo -> IO Int32) -> IO Int32)
-> (Ptr DBusPropertyInfo -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr DBusPropertyInfo
ptr -> do
    Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr DBusPropertyInfo
ptr Ptr DBusPropertyInfo -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 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' dBusPropertyInfo [ #refCount 'Data.GI.Base.Attributes.:=' value ]
-- @
setDBusPropertyInfoRefCount :: MonadIO m => DBusPropertyInfo -> Int32 -> m ()
setDBusPropertyInfoRefCount :: DBusPropertyInfo -> Int32 -> m ()
setDBusPropertyInfoRefCount s :: DBusPropertyInfo
s val :: 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
$ DBusPropertyInfo -> (Ptr DBusPropertyInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr DBusPropertyInfo
s ((Ptr DBusPropertyInfo -> IO ()) -> IO ())
-> (Ptr DBusPropertyInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr DBusPropertyInfo
ptr -> do
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr DBusPropertyInfo
ptr Ptr DBusPropertyInfo -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) (Int32
val :: Int32)

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

dBusPropertyInfo_refCount :: AttrLabelProxy "refCount"
dBusPropertyInfo_refCount = AttrLabelProxy

#endif


-- | Get the value of the “@name@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dBusPropertyInfo #name
-- @
getDBusPropertyInfoName :: MonadIO m => DBusPropertyInfo -> m (Maybe T.Text)
getDBusPropertyInfoName :: DBusPropertyInfo -> m (Maybe Text)
getDBusPropertyInfoName s :: DBusPropertyInfo
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
$ DBusPropertyInfo
-> (Ptr DBusPropertyInfo -> IO (Maybe Text)) -> IO (Maybe Text)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr DBusPropertyInfo
s ((Ptr DBusPropertyInfo -> IO (Maybe Text)) -> IO (Maybe Text))
-> (Ptr DBusPropertyInfo -> IO (Maybe Text)) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr DBusPropertyInfo
ptr -> do
    CString
val <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek (Ptr DBusPropertyInfo
ptr Ptr DBusPropertyInfo -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 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
$ \val' :: 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 “@name@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' dBusPropertyInfo [ #name 'Data.GI.Base.Attributes.:=' value ]
-- @
setDBusPropertyInfoName :: MonadIO m => DBusPropertyInfo -> CString -> m ()
setDBusPropertyInfoName :: DBusPropertyInfo -> CString -> m ()
setDBusPropertyInfoName s :: DBusPropertyInfo
s val :: 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
$ DBusPropertyInfo -> (Ptr DBusPropertyInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr DBusPropertyInfo
s ((Ptr DBusPropertyInfo -> IO ()) -> IO ())
-> (Ptr DBusPropertyInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr DBusPropertyInfo
ptr -> do
    Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr DBusPropertyInfo
ptr Ptr DBusPropertyInfo -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8) (CString
val :: CString)

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

#if defined(ENABLE_OVERLOADING)
data DBusPropertyInfoNameFieldInfo
instance AttrInfo DBusPropertyInfoNameFieldInfo where
    type AttrBaseTypeConstraint DBusPropertyInfoNameFieldInfo = (~) DBusPropertyInfo
    type AttrAllowedOps DBusPropertyInfoNameFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint DBusPropertyInfoNameFieldInfo = (~) CString
    type AttrTransferTypeConstraint DBusPropertyInfoNameFieldInfo = (~)CString
    type AttrTransferType DBusPropertyInfoNameFieldInfo = CString
    type AttrGetType DBusPropertyInfoNameFieldInfo = Maybe T.Text
    type AttrLabel DBusPropertyInfoNameFieldInfo = "name"
    type AttrOrigin DBusPropertyInfoNameFieldInfo = DBusPropertyInfo
    attrGet = getDBusPropertyInfoName
    attrSet = setDBusPropertyInfoName
    attrConstruct = undefined
    attrClear = clearDBusPropertyInfoName
    attrTransfer _ v = do
        return v

dBusPropertyInfo_name :: AttrLabelProxy "name"
dBusPropertyInfo_name = AttrLabelProxy

#endif


-- | Get the value of the “@signature@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dBusPropertyInfo #signature
-- @
getDBusPropertyInfoSignature :: MonadIO m => DBusPropertyInfo -> m (Maybe T.Text)
getDBusPropertyInfoSignature :: DBusPropertyInfo -> m (Maybe Text)
getDBusPropertyInfoSignature s :: DBusPropertyInfo
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
$ DBusPropertyInfo
-> (Ptr DBusPropertyInfo -> IO (Maybe Text)) -> IO (Maybe Text)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr DBusPropertyInfo
s ((Ptr DBusPropertyInfo -> IO (Maybe Text)) -> IO (Maybe Text))
-> (Ptr DBusPropertyInfo -> IO (Maybe Text)) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr DBusPropertyInfo
ptr -> do
    CString
val <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek (Ptr DBusPropertyInfo
ptr Ptr DBusPropertyInfo -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16) :: 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
$ \val' :: 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 “@signature@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' dBusPropertyInfo [ #signature 'Data.GI.Base.Attributes.:=' value ]
-- @
setDBusPropertyInfoSignature :: MonadIO m => DBusPropertyInfo -> CString -> m ()
setDBusPropertyInfoSignature :: DBusPropertyInfo -> CString -> m ()
setDBusPropertyInfoSignature s :: DBusPropertyInfo
s val :: 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
$ DBusPropertyInfo -> (Ptr DBusPropertyInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr DBusPropertyInfo
s ((Ptr DBusPropertyInfo -> IO ()) -> IO ())
-> (Ptr DBusPropertyInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr DBusPropertyInfo
ptr -> do
    Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr DBusPropertyInfo
ptr Ptr DBusPropertyInfo -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16) (CString
val :: CString)

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

#if defined(ENABLE_OVERLOADING)
data DBusPropertyInfoSignatureFieldInfo
instance AttrInfo DBusPropertyInfoSignatureFieldInfo where
    type AttrBaseTypeConstraint DBusPropertyInfoSignatureFieldInfo = (~) DBusPropertyInfo
    type AttrAllowedOps DBusPropertyInfoSignatureFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint DBusPropertyInfoSignatureFieldInfo = (~) CString
    type AttrTransferTypeConstraint DBusPropertyInfoSignatureFieldInfo = (~)CString
    type AttrTransferType DBusPropertyInfoSignatureFieldInfo = CString
    type AttrGetType DBusPropertyInfoSignatureFieldInfo = Maybe T.Text
    type AttrLabel DBusPropertyInfoSignatureFieldInfo = "signature"
    type AttrOrigin DBusPropertyInfoSignatureFieldInfo = DBusPropertyInfo
    attrGet = getDBusPropertyInfoSignature
    attrSet = setDBusPropertyInfoSignature
    attrConstruct = undefined
    attrClear = clearDBusPropertyInfoSignature
    attrTransfer _ v = do
        return v

dBusPropertyInfo_signature :: AttrLabelProxy "signature"
dBusPropertyInfo_signature = AttrLabelProxy

#endif


-- | Get the value of the “@flags@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dBusPropertyInfo #flags
-- @
getDBusPropertyInfoFlags :: MonadIO m => DBusPropertyInfo -> m [Gio.Flags.DBusPropertyInfoFlags]
getDBusPropertyInfoFlags :: DBusPropertyInfo -> m [DBusPropertyInfoFlags]
getDBusPropertyInfoFlags s :: DBusPropertyInfo
s = IO [DBusPropertyInfoFlags] -> m [DBusPropertyInfoFlags]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [DBusPropertyInfoFlags] -> m [DBusPropertyInfoFlags])
-> IO [DBusPropertyInfoFlags] -> m [DBusPropertyInfoFlags]
forall a b. (a -> b) -> a -> b
$ DBusPropertyInfo
-> (Ptr DBusPropertyInfo -> IO [DBusPropertyInfoFlags])
-> IO [DBusPropertyInfoFlags]
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr DBusPropertyInfo
s ((Ptr DBusPropertyInfo -> IO [DBusPropertyInfoFlags])
 -> IO [DBusPropertyInfoFlags])
-> (Ptr DBusPropertyInfo -> IO [DBusPropertyInfoFlags])
-> IO [DBusPropertyInfoFlags]
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr DBusPropertyInfo
ptr -> do
    CUInt
val <- Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr DBusPropertyInfo
ptr Ptr DBusPropertyInfo -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24) :: IO CUInt
    let val' :: [DBusPropertyInfoFlags]
val' = CUInt -> [DBusPropertyInfoFlags]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
val
    [DBusPropertyInfoFlags] -> IO [DBusPropertyInfoFlags]
forall (m :: * -> *) a. Monad m => a -> m a
return [DBusPropertyInfoFlags]
val'

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

#if defined(ENABLE_OVERLOADING)
data DBusPropertyInfoFlagsFieldInfo
instance AttrInfo DBusPropertyInfoFlagsFieldInfo where
    type AttrBaseTypeConstraint DBusPropertyInfoFlagsFieldInfo = (~) DBusPropertyInfo
    type AttrAllowedOps DBusPropertyInfoFlagsFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint DBusPropertyInfoFlagsFieldInfo = (~) [Gio.Flags.DBusPropertyInfoFlags]
    type AttrTransferTypeConstraint DBusPropertyInfoFlagsFieldInfo = (~)[Gio.Flags.DBusPropertyInfoFlags]
    type AttrTransferType DBusPropertyInfoFlagsFieldInfo = [Gio.Flags.DBusPropertyInfoFlags]
    type AttrGetType DBusPropertyInfoFlagsFieldInfo = [Gio.Flags.DBusPropertyInfoFlags]
    type AttrLabel DBusPropertyInfoFlagsFieldInfo = "flags"
    type AttrOrigin DBusPropertyInfoFlagsFieldInfo = DBusPropertyInfo
    attrGet = getDBusPropertyInfoFlags
    attrSet = setDBusPropertyInfoFlags
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

dBusPropertyInfo_flags :: AttrLabelProxy "flags"
dBusPropertyInfo_flags = 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' dBusPropertyInfo #annotations
-- @
getDBusPropertyInfoAnnotations :: MonadIO m => DBusPropertyInfo -> m (Maybe [Gio.DBusAnnotationInfo.DBusAnnotationInfo])
getDBusPropertyInfoAnnotations :: DBusPropertyInfo -> m (Maybe [DBusAnnotationInfo])
getDBusPropertyInfoAnnotations s :: DBusPropertyInfo
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
$ DBusPropertyInfo
-> (Ptr DBusPropertyInfo -> IO (Maybe [DBusAnnotationInfo]))
-> IO (Maybe [DBusAnnotationInfo])
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr DBusPropertyInfo
s ((Ptr DBusPropertyInfo -> IO (Maybe [DBusAnnotationInfo]))
 -> IO (Maybe [DBusAnnotationInfo]))
-> (Ptr DBusPropertyInfo -> IO (Maybe [DBusAnnotationInfo]))
-> IO (Maybe [DBusAnnotationInfo])
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr DBusPropertyInfo
ptr -> do
    Ptr (Ptr DBusAnnotationInfo)
val <- Ptr (Ptr (Ptr DBusAnnotationInfo))
-> IO (Ptr (Ptr DBusAnnotationInfo))
forall a. Storable a => Ptr a -> IO a
peek (Ptr DBusPropertyInfo
ptr Ptr DBusPropertyInfo -> Int -> Ptr (Ptr (Ptr DBusAnnotationInfo))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 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
$ \val' :: 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, BoxedObject 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' dBusPropertyInfo [ #annotations 'Data.GI.Base.Attributes.:=' value ]
-- @
setDBusPropertyInfoAnnotations :: MonadIO m => DBusPropertyInfo -> Ptr (Ptr Gio.DBusAnnotationInfo.DBusAnnotationInfo) -> m ()
setDBusPropertyInfoAnnotations :: DBusPropertyInfo -> Ptr (Ptr DBusAnnotationInfo) -> m ()
setDBusPropertyInfoAnnotations s :: DBusPropertyInfo
s val :: 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
$ DBusPropertyInfo -> (Ptr DBusPropertyInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr DBusPropertyInfo
s ((Ptr DBusPropertyInfo -> IO ()) -> IO ())
-> (Ptr DBusPropertyInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr DBusPropertyInfo
ptr -> do
    Ptr (Ptr (Ptr DBusAnnotationInfo))
-> Ptr (Ptr DBusAnnotationInfo) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr DBusPropertyInfo
ptr Ptr DBusPropertyInfo -> Int -> Ptr (Ptr (Ptr DBusAnnotationInfo))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 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
-- @
clearDBusPropertyInfoAnnotations :: MonadIO m => DBusPropertyInfo -> m ()
clearDBusPropertyInfoAnnotations :: DBusPropertyInfo -> m ()
clearDBusPropertyInfoAnnotations s :: DBusPropertyInfo
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ DBusPropertyInfo -> (Ptr DBusPropertyInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr DBusPropertyInfo
s ((Ptr DBusPropertyInfo -> IO ()) -> IO ())
-> (Ptr DBusPropertyInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr DBusPropertyInfo
ptr -> do
    Ptr (Ptr (Ptr DBusAnnotationInfo))
-> Ptr (Ptr DBusAnnotationInfo) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr DBusPropertyInfo
ptr Ptr DBusPropertyInfo -> Int -> Ptr (Ptr (Ptr DBusAnnotationInfo))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32) (Ptr (Ptr DBusAnnotationInfo)
forall a. Ptr a
FP.nullPtr :: Ptr (Ptr Gio.DBusAnnotationInfo.DBusAnnotationInfo))

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

dBusPropertyInfo_annotations :: AttrLabelProxy "annotations"
dBusPropertyInfo_annotations = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DBusPropertyInfo
type instance O.AttributeList DBusPropertyInfo = DBusPropertyInfoAttributeList
type DBusPropertyInfoAttributeList = ('[ '("refCount", DBusPropertyInfoRefCountFieldInfo), '("name", DBusPropertyInfoNameFieldInfo), '("signature", DBusPropertyInfoSignatureFieldInfo), '("flags", DBusPropertyInfoFlagsFieldInfo), '("annotations", DBusPropertyInfoAnnotationsFieldInfo)] :: [(Symbol, *)])
#endif

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

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

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

#if defined(ENABLE_OVERLOADING)
data DBusPropertyInfoRefMethodInfo
instance (signature ~ (m DBusPropertyInfo), MonadIO m) => O.MethodInfo DBusPropertyInfoRefMethodInfo DBusPropertyInfo signature where
    overloadedMethod = dBusPropertyInfoRef

#endif

-- method DBusPropertyInfo::unref
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusPropertyInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusPropertyInfo."
--                 , 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_property_info_unref" g_dbus_property_info_unref :: 
    Ptr DBusPropertyInfo ->                 -- info : TInterface (Name {namespace = "Gio", name = "DBusPropertyInfo"})
    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/
dBusPropertyInfoUnref ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    DBusPropertyInfo
    -- ^ /@info@/: A t'GI.Gio.Structs.DBusPropertyInfo.DBusPropertyInfo'.
    -> m ()
dBusPropertyInfoUnref :: DBusPropertyInfo -> m ()
dBusPropertyInfoUnref info :: DBusPropertyInfo
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 DBusPropertyInfo
info' <- DBusPropertyInfo -> IO (Ptr DBusPropertyInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr DBusPropertyInfo
info
    Ptr DBusPropertyInfo -> IO ()
g_dbus_property_info_unref Ptr DBusPropertyInfo
info'
    DBusPropertyInfo -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr DBusPropertyInfo
info
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DBusPropertyInfoUnrefMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo DBusPropertyInfoUnrefMethodInfo DBusPropertyInfo signature where
    overloadedMethod = dBusPropertyInfoUnref

#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveDBusPropertyInfoMethod (t :: Symbol) (o :: *) :: * where
    ResolveDBusPropertyInfoMethod "ref" o = DBusPropertyInfoRefMethodInfo
    ResolveDBusPropertyInfoMethod "unref" o = DBusPropertyInfoUnrefMethodInfo
    ResolveDBusPropertyInfoMethod l o = O.MethodResolutionFailed l o

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

#endif