{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- t'GI.Gio.Objects.DBusProxy.DBusProxy' is a base class used for proxies to access a D-Bus
-- interface on a remote object. A t'GI.Gio.Objects.DBusProxy.DBusProxy' can be constructed for
-- both well-known and unique names.
-- 
-- By default, t'GI.Gio.Objects.DBusProxy.DBusProxy' will cache all properties (and listen to
-- changes) of the remote object, and proxy all signals that get
-- emitted. This behaviour can be changed by passing suitable
-- t'GI.Gio.Flags.DBusProxyFlags' when the proxy is created. If the proxy is for a
-- well-known name, the property cache is flushed when the name owner
-- vanishes and reloaded when a name owner appears.
-- 
-- The unique name owner of the proxy\'s name is tracked and can be read from
-- t'GI.Gio.Objects.DBusProxy.DBusProxy':@/g-name-owner/@. Connect to the [notify]("GI.GObject.Objects.Object#signal:notify") signal to
-- get notified of changes. Additionally, only signals and property
-- changes emitted from the current name owner are considered and
-- calls are always sent to the current name owner. This avoids a
-- number of race conditions when the name is lost by one owner and
-- claimed by another. However, if no name owner currently exists,
-- then calls will be sent to the well-known name which may result in
-- the message bus launching an owner (unless
-- 'GI.Gio.Flags.DBusProxyFlagsDoNotAutoStart' is set).
-- 
-- The generic [gPropertiesChanged]("GI.Gio.Objects.DBusProxy#signal:gPropertiesChanged") and
-- [gSignal]("GI.Gio.Objects.DBusProxy#signal:gSignal") signals are not very convenient to work with.
-- Therefore, the recommended way of working with proxies is to subclass
-- t'GI.Gio.Objects.DBusProxy.DBusProxy', and have more natural properties and signals in your derived
-- class. This [example][gdbus-example-gdbus-codegen] shows how this can
-- easily be done using the [gdbus-codegen][gdbus-codegen] tool.
-- 
-- A t'GI.Gio.Objects.DBusProxy.DBusProxy' instance can be used from multiple threads but note
-- that all signals (e.g. [gSignal]("GI.Gio.Objects.DBusProxy#signal:gSignal"), [gPropertiesChanged]("GI.Gio.Objects.DBusProxy#signal:gPropertiesChanged")
-- and [notify]("GI.GObject.Objects.Object#signal:notify")) are emitted in the
-- [thread-default main context][g-main-context-push-thread-default]
-- of the thread where the instance was constructed.
-- 
-- An example using a proxy for a well-known name can be found in
-- <https://git.gnome.org/browse/glib/tree/gio/tests/gdbus-example-watch-proxy.c gdbus-example-watch-proxy.c>
-- 
-- /Since: 2.26/

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

module GI.Gio.Objects.DBusProxy
    ( 

-- * Exported types
    DBusProxy(..)                           ,
    IsDBusProxy                             ,
    toDBusProxy                             ,
    noDBusProxy                             ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveDBusProxyMethod                  ,
#endif


-- ** call #method:call#

#if defined(ENABLE_OVERLOADING)
    DBusProxyCallMethodInfo                 ,
#endif
    dBusProxyCall                           ,


-- ** callFinish #method:callFinish#

#if defined(ENABLE_OVERLOADING)
    DBusProxyCallFinishMethodInfo           ,
#endif
    dBusProxyCallFinish                     ,


-- ** callSync #method:callSync#

#if defined(ENABLE_OVERLOADING)
    DBusProxyCallSyncMethodInfo             ,
#endif
    dBusProxyCallSync                       ,


-- ** callWithUnixFdList #method:callWithUnixFdList#

#if defined(ENABLE_OVERLOADING)
    DBusProxyCallWithUnixFdListMethodInfo   ,
#endif
    dBusProxyCallWithUnixFdList             ,


-- ** callWithUnixFdListFinish #method:callWithUnixFdListFinish#

#if defined(ENABLE_OVERLOADING)
    DBusProxyCallWithUnixFdListFinishMethodInfo,
#endif
    dBusProxyCallWithUnixFdListFinish       ,


-- ** callWithUnixFdListSync #method:callWithUnixFdListSync#

#if defined(ENABLE_OVERLOADING)
    DBusProxyCallWithUnixFdListSyncMethodInfo,
#endif
    dBusProxyCallWithUnixFdListSync         ,


-- ** getCachedProperty #method:getCachedProperty#

#if defined(ENABLE_OVERLOADING)
    DBusProxyGetCachedPropertyMethodInfo    ,
#endif
    dBusProxyGetCachedProperty              ,


-- ** getCachedPropertyNames #method:getCachedPropertyNames#

#if defined(ENABLE_OVERLOADING)
    DBusProxyGetCachedPropertyNamesMethodInfo,
#endif
    dBusProxyGetCachedPropertyNames         ,


-- ** getConnection #method:getConnection#

#if defined(ENABLE_OVERLOADING)
    DBusProxyGetConnectionMethodInfo        ,
#endif
    dBusProxyGetConnection                  ,


-- ** getDefaultTimeout #method:getDefaultTimeout#

#if defined(ENABLE_OVERLOADING)
    DBusProxyGetDefaultTimeoutMethodInfo    ,
#endif
    dBusProxyGetDefaultTimeout              ,


-- ** getFlags #method:getFlags#

#if defined(ENABLE_OVERLOADING)
    DBusProxyGetFlagsMethodInfo             ,
#endif
    dBusProxyGetFlags                       ,


-- ** getInterfaceInfo #method:getInterfaceInfo#

#if defined(ENABLE_OVERLOADING)
    DBusProxyGetInterfaceInfoMethodInfo     ,
#endif
    dBusProxyGetInterfaceInfo               ,


-- ** getInterfaceName #method:getInterfaceName#

#if defined(ENABLE_OVERLOADING)
    DBusProxyGetInterfaceNameMethodInfo     ,
#endif
    dBusProxyGetInterfaceName               ,


-- ** getName #method:getName#

#if defined(ENABLE_OVERLOADING)
    DBusProxyGetNameMethodInfo              ,
#endif
    dBusProxyGetName                        ,


-- ** getNameOwner #method:getNameOwner#

#if defined(ENABLE_OVERLOADING)
    DBusProxyGetNameOwnerMethodInfo         ,
#endif
    dBusProxyGetNameOwner                   ,


-- ** getObjectPath #method:getObjectPath#

#if defined(ENABLE_OVERLOADING)
    DBusProxyGetObjectPathMethodInfo        ,
#endif
    dBusProxyGetObjectPath                  ,


-- ** new #method:new#

    dBusProxyNew                            ,


-- ** newFinish #method:newFinish#

    dBusProxyNewFinish                      ,


-- ** newForBus #method:newForBus#

    dBusProxyNewForBus                      ,


-- ** newForBusFinish #method:newForBusFinish#

    dBusProxyNewForBusFinish                ,


-- ** newForBusSync #method:newForBusSync#

    dBusProxyNewForBusSync                  ,


-- ** newSync #method:newSync#

    dBusProxyNewSync                        ,


-- ** setCachedProperty #method:setCachedProperty#

#if defined(ENABLE_OVERLOADING)
    DBusProxySetCachedPropertyMethodInfo    ,
#endif
    dBusProxySetCachedProperty              ,


-- ** setDefaultTimeout #method:setDefaultTimeout#

#if defined(ENABLE_OVERLOADING)
    DBusProxySetDefaultTimeoutMethodInfo    ,
#endif
    dBusProxySetDefaultTimeout              ,


-- ** setInterfaceInfo #method:setInterfaceInfo#

#if defined(ENABLE_OVERLOADING)
    DBusProxySetInterfaceInfoMethodInfo     ,
#endif
    dBusProxySetInterfaceInfo               ,




 -- * Properties
-- ** gBusType #attr:gBusType#
-- | If this property is not 'GI.Gio.Enums.BusTypeNone', then
-- t'GI.Gio.Objects.DBusProxy.DBusProxy':@/g-connection/@ must be 'P.Nothing' and will be set to the
-- t'GI.Gio.Objects.DBusConnection.DBusConnection' obtained by calling 'GI.Gio.Functions.busGet' with the value
-- of this property.
-- 
-- /Since: 2.26/

#if defined(ENABLE_OVERLOADING)
    DBusProxyGBusTypePropertyInfo           ,
#endif
    constructDBusProxyGBusType              ,
#if defined(ENABLE_OVERLOADING)
    dBusProxyGBusType                       ,
#endif


-- ** gConnection #attr:gConnection#
-- | The t'GI.Gio.Objects.DBusConnection.DBusConnection' the proxy is for.
-- 
-- /Since: 2.26/

#if defined(ENABLE_OVERLOADING)
    DBusProxyGConnectionPropertyInfo        ,
#endif
    constructDBusProxyGConnection           ,
#if defined(ENABLE_OVERLOADING)
    dBusProxyGConnection                    ,
#endif
    getDBusProxyGConnection                 ,


-- ** gDefaultTimeout #attr:gDefaultTimeout#
-- | The timeout to use if -1 (specifying default timeout) is passed
-- as /@timeoutMsec@/ in the 'GI.Gio.Objects.DBusProxy.dBusProxyCall' and
-- 'GI.Gio.Objects.DBusProxy.dBusProxyCallSync' functions.
-- 
-- This allows applications to set a proxy-wide timeout for all
-- remote method invocations on the proxy. If this property is -1,
-- the default timeout (typically 25 seconds) is used. If set to
-- @/G_MAXINT/@, then no timeout is used.
-- 
-- /Since: 2.26/

#if defined(ENABLE_OVERLOADING)
    DBusProxyGDefaultTimeoutPropertyInfo    ,
#endif
    constructDBusProxyGDefaultTimeout       ,
#if defined(ENABLE_OVERLOADING)
    dBusProxyGDefaultTimeout                ,
#endif
    getDBusProxyGDefaultTimeout             ,
    setDBusProxyGDefaultTimeout             ,


-- ** gFlags #attr:gFlags#
-- | Flags from the t'GI.Gio.Flags.DBusProxyFlags' enumeration.
-- 
-- /Since: 2.26/

#if defined(ENABLE_OVERLOADING)
    DBusProxyGFlagsPropertyInfo             ,
#endif
    constructDBusProxyGFlags                ,
#if defined(ENABLE_OVERLOADING)
    dBusProxyGFlags                         ,
#endif
    getDBusProxyGFlags                      ,


-- ** gInterfaceInfo #attr:gInterfaceInfo#
-- | Ensure that interactions with this proxy conform to the given
-- interface. This is mainly to ensure that malformed data received
-- from the other peer is ignored. The given t'GI.Gio.Structs.DBusInterfaceInfo.DBusInterfaceInfo' is
-- said to be the \"expected interface\".
-- 
-- The checks performed are:
-- 
-- * When completing a method call, if the type signature of
-- the reply message isn\'t what\'s expected, the reply is
-- discarded and the t'GError' is set to 'GI.Gio.Enums.IOErrorEnumInvalidArgument'.
-- * Received signals that have a type signature mismatch are dropped and
-- a warning is logged via @/g_warning()/@.
-- * Properties received via the initial @GetAll()@ call or via the
-- @::PropertiesChanged@ signal (on the
-- <http://dbus.freedesktop.org/doc/dbus-specification.html#standard-interfaces-properties org.freedesktop.DBus.Properties>
-- interface) or set using 'GI.Gio.Objects.DBusProxy.dBusProxySetCachedProperty'
-- with a type signature mismatch are ignored and a warning is
-- logged via @/g_warning()/@.
-- 
-- 
-- Note that these checks are never done on methods, signals and
-- properties that are not referenced in the given
-- t'GI.Gio.Structs.DBusInterfaceInfo.DBusInterfaceInfo', since extending a D-Bus interface on the
-- service-side is not considered an ABI break.
-- 
-- /Since: 2.26/

#if defined(ENABLE_OVERLOADING)
    DBusProxyGInterfaceInfoPropertyInfo     ,
#endif
    clearDBusProxyGInterfaceInfo            ,
    constructDBusProxyGInterfaceInfo        ,
#if defined(ENABLE_OVERLOADING)
    dBusProxyGInterfaceInfo                 ,
#endif
    getDBusProxyGInterfaceInfo              ,
    setDBusProxyGInterfaceInfo              ,


-- ** gInterfaceName #attr:gInterfaceName#
-- | The D-Bus interface name the proxy is for.
-- 
-- /Since: 2.26/

#if defined(ENABLE_OVERLOADING)
    DBusProxyGInterfaceNamePropertyInfo     ,
#endif
    constructDBusProxyGInterfaceName        ,
#if defined(ENABLE_OVERLOADING)
    dBusProxyGInterfaceName                 ,
#endif
    getDBusProxyGInterfaceName              ,


-- ** gName #attr:gName#
-- | The well-known or unique name that the proxy is for.
-- 
-- /Since: 2.26/

#if defined(ENABLE_OVERLOADING)
    DBusProxyGNamePropertyInfo              ,
#endif
    constructDBusProxyGName                 ,
#if defined(ENABLE_OVERLOADING)
    dBusProxyGName                          ,
#endif
    getDBusProxyGName                       ,


-- ** gNameOwner #attr:gNameOwner#
-- | The unique name that owns t'GI.Gio.Objects.DBusProxy.DBusProxy':@/g-name/@ or 'P.Nothing' if no-one
-- currently owns that name. You may connect to [notify]("GI.GObject.Objects.Object#signal:notify") signal to
-- track changes to this property.
-- 
-- /Since: 2.26/

#if defined(ENABLE_OVERLOADING)
    DBusProxyGNameOwnerPropertyInfo         ,
#endif
#if defined(ENABLE_OVERLOADING)
    dBusProxyGNameOwner                     ,
#endif
    getDBusProxyGNameOwner                  ,


-- ** gObjectPath #attr:gObjectPath#
-- | The object path the proxy is for.
-- 
-- /Since: 2.26/

#if defined(ENABLE_OVERLOADING)
    DBusProxyGObjectPathPropertyInfo        ,
#endif
    constructDBusProxyGObjectPath           ,
#if defined(ENABLE_OVERLOADING)
    dBusProxyGObjectPath                    ,
#endif
    getDBusProxyGObjectPath                 ,




 -- * Signals
-- ** gPropertiesChanged #signal:gPropertiesChanged#

    C_DBusProxyGPropertiesChangedCallback   ,
    DBusProxyGPropertiesChangedCallback     ,
#if defined(ENABLE_OVERLOADING)
    DBusProxyGPropertiesChangedSignalInfo   ,
#endif
    afterDBusProxyGPropertiesChanged        ,
    genClosure_DBusProxyGPropertiesChanged  ,
    mk_DBusProxyGPropertiesChangedCallback  ,
    noDBusProxyGPropertiesChangedCallback   ,
    onDBusProxyGPropertiesChanged           ,
    wrap_DBusProxyGPropertiesChangedCallback,


-- ** gSignal #signal:gSignal#

    C_DBusProxyGSignalCallback              ,
    DBusProxyGSignalCallback                ,
#if defined(ENABLE_OVERLOADING)
    DBusProxyGSignalSignalInfo              ,
#endif
    afterDBusProxyGSignal                   ,
    genClosure_DBusProxyGSignal             ,
    mk_DBusProxyGSignalCallback             ,
    noDBusProxyGSignalCallback              ,
    onDBusProxyGSignal                      ,
    wrap_DBusProxyGSignalCallback           ,




    ) 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 qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Callbacks as Gio.Callbacks
import {-# SOURCE #-} qualified GI.Gio.Enums as Gio.Enums
import {-# SOURCE #-} qualified GI.Gio.Flags as Gio.Flags
import {-# SOURCE #-} qualified GI.Gio.Interfaces.AsyncInitable as Gio.AsyncInitable
import {-# SOURCE #-} qualified GI.Gio.Interfaces.AsyncResult as Gio.AsyncResult
import {-# SOURCE #-} qualified GI.Gio.Interfaces.DBusInterface as Gio.DBusInterface
import {-# SOURCE #-} qualified GI.Gio.Interfaces.Initable as Gio.Initable
import {-# SOURCE #-} qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
import {-# SOURCE #-} qualified GI.Gio.Objects.DBusConnection as Gio.DBusConnection
import {-# SOURCE #-} qualified GI.Gio.Objects.UnixFDList as Gio.UnixFDList
import {-# SOURCE #-} qualified GI.Gio.Structs.DBusInterfaceInfo as Gio.DBusInterfaceInfo

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

instance GObject DBusProxy where
    gobjectType :: IO GType
gobjectType = IO GType
c_g_dbus_proxy_get_type
    

-- | Convert 'DBusProxy' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue DBusProxy where
    toGValue :: DBusProxy -> IO GValue
toGValue o :: DBusProxy
o = do
        GType
gtype <- IO GType
c_g_dbus_proxy_get_type
        DBusProxy -> (Ptr DBusProxy -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr DBusProxy
o (GType
-> (GValue -> Ptr DBusProxy -> IO ()) -> Ptr DBusProxy -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr DBusProxy -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
        
    fromGValue :: GValue -> IO DBusProxy
fromGValue gv :: GValue
gv = do
        Ptr DBusProxy
ptr <- GValue -> IO (Ptr DBusProxy)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr DBusProxy)
        (ManagedPtr DBusProxy -> DBusProxy)
-> Ptr DBusProxy -> IO DBusProxy
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr DBusProxy -> DBusProxy
DBusProxy Ptr DBusProxy
ptr
        
    

-- | Type class for types which can be safely cast to `DBusProxy`, for instance with `toDBusProxy`.
class (GObject o, O.IsDescendantOf DBusProxy o) => IsDBusProxy o
instance (GObject o, O.IsDescendantOf DBusProxy o) => IsDBusProxy o

instance O.HasParentTypes DBusProxy
type instance O.ParentTypes DBusProxy = '[GObject.Object.Object, Gio.AsyncInitable.AsyncInitable, Gio.DBusInterface.DBusInterface, Gio.Initable.Initable]

-- | Cast to `DBusProxy`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toDBusProxy :: (MonadIO m, IsDBusProxy o) => o -> m DBusProxy
toDBusProxy :: o -> m DBusProxy
toDBusProxy = IO DBusProxy -> m DBusProxy
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DBusProxy -> m DBusProxy)
-> (o -> IO DBusProxy) -> o -> m DBusProxy
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr DBusProxy -> DBusProxy) -> o -> IO DBusProxy
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr DBusProxy -> DBusProxy
DBusProxy

-- | A convenience alias for `Nothing` :: `Maybe` `DBusProxy`.
noDBusProxy :: Maybe DBusProxy
noDBusProxy :: Maybe DBusProxy
noDBusProxy = Maybe DBusProxy
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolveDBusProxyMethod (t :: Symbol) (o :: *) :: * where
    ResolveDBusProxyMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveDBusProxyMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveDBusProxyMethod "call" o = DBusProxyCallMethodInfo
    ResolveDBusProxyMethod "callFinish" o = DBusProxyCallFinishMethodInfo
    ResolveDBusProxyMethod "callSync" o = DBusProxyCallSyncMethodInfo
    ResolveDBusProxyMethod "callWithUnixFdList" o = DBusProxyCallWithUnixFdListMethodInfo
    ResolveDBusProxyMethod "callWithUnixFdListFinish" o = DBusProxyCallWithUnixFdListFinishMethodInfo
    ResolveDBusProxyMethod "callWithUnixFdListSync" o = DBusProxyCallWithUnixFdListSyncMethodInfo
    ResolveDBusProxyMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveDBusProxyMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveDBusProxyMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveDBusProxyMethod "init" o = Gio.Initable.InitableInitMethodInfo
    ResolveDBusProxyMethod "initAsync" o = Gio.AsyncInitable.AsyncInitableInitAsyncMethodInfo
    ResolveDBusProxyMethod "initFinish" o = Gio.AsyncInitable.AsyncInitableInitFinishMethodInfo
    ResolveDBusProxyMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveDBusProxyMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveDBusProxyMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveDBusProxyMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveDBusProxyMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveDBusProxyMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveDBusProxyMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveDBusProxyMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveDBusProxyMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveDBusProxyMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveDBusProxyMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveDBusProxyMethod "getCachedProperty" o = DBusProxyGetCachedPropertyMethodInfo
    ResolveDBusProxyMethod "getCachedPropertyNames" o = DBusProxyGetCachedPropertyNamesMethodInfo
    ResolveDBusProxyMethod "getConnection" o = DBusProxyGetConnectionMethodInfo
    ResolveDBusProxyMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveDBusProxyMethod "getDefaultTimeout" o = DBusProxyGetDefaultTimeoutMethodInfo
    ResolveDBusProxyMethod "getFlags" o = DBusProxyGetFlagsMethodInfo
    ResolveDBusProxyMethod "getInfo" o = Gio.DBusInterface.DBusInterfaceGetInfoMethodInfo
    ResolveDBusProxyMethod "getInterfaceInfo" o = DBusProxyGetInterfaceInfoMethodInfo
    ResolveDBusProxyMethod "getInterfaceName" o = DBusProxyGetInterfaceNameMethodInfo
    ResolveDBusProxyMethod "getName" o = DBusProxyGetNameMethodInfo
    ResolveDBusProxyMethod "getNameOwner" o = DBusProxyGetNameOwnerMethodInfo
    ResolveDBusProxyMethod "getObject" o = Gio.DBusInterface.DBusInterfaceGetObjectMethodInfo
    ResolveDBusProxyMethod "getObjectPath" o = DBusProxyGetObjectPathMethodInfo
    ResolveDBusProxyMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveDBusProxyMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveDBusProxyMethod "setCachedProperty" o = DBusProxySetCachedPropertyMethodInfo
    ResolveDBusProxyMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveDBusProxyMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveDBusProxyMethod "setDefaultTimeout" o = DBusProxySetDefaultTimeoutMethodInfo
    ResolveDBusProxyMethod "setInterfaceInfo" o = DBusProxySetInterfaceInfoMethodInfo
    ResolveDBusProxyMethod "setObject" o = Gio.DBusInterface.DBusInterfaceSetObjectMethodInfo
    ResolveDBusProxyMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveDBusProxyMethod l o = O.MethodResolutionFailed l o

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

#endif

-- signal DBusProxy::g-properties-changed
-- | Emitted when one or more D-Bus properties on /@proxy@/ changes. The
-- local cache has already been updated when this signal fires. Note
-- that both /@changedProperties@/ and /@invalidatedProperties@/ are
-- guaranteed to never be 'P.Nothing' (either may be empty though).
-- 
-- If the proxy has the flag
-- 'GI.Gio.Flags.DBusProxyFlagsGetInvalidatedProperties' set, then
-- /@invalidatedProperties@/ will always be empty.
-- 
-- This signal corresponds to the
-- @PropertiesChanged@ D-Bus signal on the
-- @org.freedesktop.DBus.Properties@ interface.
-- 
-- /Since: 2.26/
type DBusProxyGPropertiesChangedCallback =
    GVariant
    -- ^ /@changedProperties@/: A t'GVariant' containing the properties that changed (type: @a{sv}@)
    -> [T.Text]
    -- ^ /@invalidatedProperties@/: A 'P.Nothing' terminated array of properties that was invalidated
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `DBusProxyGPropertiesChangedCallback`@.
noDBusProxyGPropertiesChangedCallback :: Maybe DBusProxyGPropertiesChangedCallback
noDBusProxyGPropertiesChangedCallback :: Maybe DBusProxyGPropertiesChangedCallback
noDBusProxyGPropertiesChangedCallback = Maybe DBusProxyGPropertiesChangedCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_DBusProxyGPropertiesChangedCallback =
    Ptr () ->                               -- object
    Ptr GVariant ->
    Ptr CString ->
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_DBusProxyGPropertiesChangedCallback`.
foreign import ccall "wrapper"
    mk_DBusProxyGPropertiesChangedCallback :: C_DBusProxyGPropertiesChangedCallback -> IO (FunPtr C_DBusProxyGPropertiesChangedCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_DBusProxyGPropertiesChanged :: MonadIO m => DBusProxyGPropertiesChangedCallback -> m (GClosure C_DBusProxyGPropertiesChangedCallback)
genClosure_DBusProxyGPropertiesChanged :: DBusProxyGPropertiesChangedCallback
-> m (GClosure C_DBusProxyGPropertiesChangedCallback)
genClosure_DBusProxyGPropertiesChanged cb :: DBusProxyGPropertiesChangedCallback
cb = IO (GClosure C_DBusProxyGPropertiesChangedCallback)
-> m (GClosure C_DBusProxyGPropertiesChangedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_DBusProxyGPropertiesChangedCallback)
 -> m (GClosure C_DBusProxyGPropertiesChangedCallback))
-> IO (GClosure C_DBusProxyGPropertiesChangedCallback)
-> m (GClosure C_DBusProxyGPropertiesChangedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DBusProxyGPropertiesChangedCallback
cb' = DBusProxyGPropertiesChangedCallback
-> C_DBusProxyGPropertiesChangedCallback
wrap_DBusProxyGPropertiesChangedCallback DBusProxyGPropertiesChangedCallback
cb
    C_DBusProxyGPropertiesChangedCallback
-> IO (FunPtr C_DBusProxyGPropertiesChangedCallback)
mk_DBusProxyGPropertiesChangedCallback C_DBusProxyGPropertiesChangedCallback
cb' IO (FunPtr C_DBusProxyGPropertiesChangedCallback)
-> (FunPtr C_DBusProxyGPropertiesChangedCallback
    -> IO (GClosure C_DBusProxyGPropertiesChangedCallback))
-> IO (GClosure C_DBusProxyGPropertiesChangedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_DBusProxyGPropertiesChangedCallback
-> IO (GClosure C_DBusProxyGPropertiesChangedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `DBusProxyGPropertiesChangedCallback` into a `C_DBusProxyGPropertiesChangedCallback`.
wrap_DBusProxyGPropertiesChangedCallback ::
    DBusProxyGPropertiesChangedCallback ->
    C_DBusProxyGPropertiesChangedCallback
wrap_DBusProxyGPropertiesChangedCallback :: DBusProxyGPropertiesChangedCallback
-> C_DBusProxyGPropertiesChangedCallback
wrap_DBusProxyGPropertiesChangedCallback _cb :: DBusProxyGPropertiesChangedCallback
_cb _ changedProperties :: Ptr GVariant
changedProperties invalidatedProperties :: Ptr CString
invalidatedProperties _ = do
    GVariant
changedProperties' <- Ptr GVariant -> IO GVariant
B.GVariant.newGVariantFromPtr Ptr GVariant
changedProperties
    [Text]
invalidatedProperties' <- HasCallStack => Ptr CString -> IO [Text]
Ptr CString -> IO [Text]
unpackZeroTerminatedUTF8CArray Ptr CString
invalidatedProperties
    DBusProxyGPropertiesChangedCallback
_cb  GVariant
changedProperties' [Text]
invalidatedProperties'


-- | Connect a signal handler for the [gPropertiesChanged](#signal:gPropertiesChanged) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' dBusProxy #gPropertiesChanged callback
-- @
-- 
-- 
onDBusProxyGPropertiesChanged :: (IsDBusProxy a, MonadIO m) => a -> DBusProxyGPropertiesChangedCallback -> m SignalHandlerId
onDBusProxyGPropertiesChanged :: a -> DBusProxyGPropertiesChangedCallback -> m SignalHandlerId
onDBusProxyGPropertiesChanged obj :: a
obj cb :: DBusProxyGPropertiesChangedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DBusProxyGPropertiesChangedCallback
cb' = DBusProxyGPropertiesChangedCallback
-> C_DBusProxyGPropertiesChangedCallback
wrap_DBusProxyGPropertiesChangedCallback DBusProxyGPropertiesChangedCallback
cb
    FunPtr C_DBusProxyGPropertiesChangedCallback
cb'' <- C_DBusProxyGPropertiesChangedCallback
-> IO (FunPtr C_DBusProxyGPropertiesChangedCallback)
mk_DBusProxyGPropertiesChangedCallback C_DBusProxyGPropertiesChangedCallback
cb'
    a
-> Text
-> FunPtr C_DBusProxyGPropertiesChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "g-properties-changed" FunPtr C_DBusProxyGPropertiesChangedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [gPropertiesChanged](#signal:gPropertiesChanged) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' dBusProxy #gPropertiesChanged callback
-- @
-- 
-- 
afterDBusProxyGPropertiesChanged :: (IsDBusProxy a, MonadIO m) => a -> DBusProxyGPropertiesChangedCallback -> m SignalHandlerId
afterDBusProxyGPropertiesChanged :: a -> DBusProxyGPropertiesChangedCallback -> m SignalHandlerId
afterDBusProxyGPropertiesChanged obj :: a
obj cb :: DBusProxyGPropertiesChangedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DBusProxyGPropertiesChangedCallback
cb' = DBusProxyGPropertiesChangedCallback
-> C_DBusProxyGPropertiesChangedCallback
wrap_DBusProxyGPropertiesChangedCallback DBusProxyGPropertiesChangedCallback
cb
    FunPtr C_DBusProxyGPropertiesChangedCallback
cb'' <- C_DBusProxyGPropertiesChangedCallback
-> IO (FunPtr C_DBusProxyGPropertiesChangedCallback)
mk_DBusProxyGPropertiesChangedCallback C_DBusProxyGPropertiesChangedCallback
cb'
    a
-> Text
-> FunPtr C_DBusProxyGPropertiesChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "g-properties-changed" FunPtr C_DBusProxyGPropertiesChangedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data DBusProxyGPropertiesChangedSignalInfo
instance SignalInfo DBusProxyGPropertiesChangedSignalInfo where
    type HaskellCallbackType DBusProxyGPropertiesChangedSignalInfo = DBusProxyGPropertiesChangedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_DBusProxyGPropertiesChangedCallback cb
        cb'' <- mk_DBusProxyGPropertiesChangedCallback cb'
        connectSignalFunPtr obj "g-properties-changed" cb'' connectMode detail

#endif

-- signal DBusProxy::g-signal
-- | Emitted when a signal from the remote object and interface that /@proxy@/ is for, has been received.
-- 
-- /Since: 2.26/
type DBusProxyGSignalCallback =
    Maybe T.Text
    -- ^ /@senderName@/: The sender of the signal or 'P.Nothing' if the connection is not a bus connection.
    -> T.Text
    -- ^ /@signalName@/: The name of the signal.
    -> GVariant
    -- ^ /@parameters@/: A t'GVariant' tuple with parameters for the signal.
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `DBusProxyGSignalCallback`@.
noDBusProxyGSignalCallback :: Maybe DBusProxyGSignalCallback
noDBusProxyGSignalCallback :: Maybe DBusProxyGSignalCallback
noDBusProxyGSignalCallback = Maybe DBusProxyGSignalCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_DBusProxyGSignalCallback =
    Ptr () ->                               -- object
    CString ->
    CString ->
    Ptr GVariant ->
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_DBusProxyGSignalCallback`.
foreign import ccall "wrapper"
    mk_DBusProxyGSignalCallback :: C_DBusProxyGSignalCallback -> IO (FunPtr C_DBusProxyGSignalCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_DBusProxyGSignal :: MonadIO m => DBusProxyGSignalCallback -> m (GClosure C_DBusProxyGSignalCallback)
genClosure_DBusProxyGSignal :: DBusProxyGSignalCallback -> m (GClosure C_DBusProxyGSignalCallback)
genClosure_DBusProxyGSignal cb :: DBusProxyGSignalCallback
cb = IO (GClosure C_DBusProxyGSignalCallback)
-> m (GClosure C_DBusProxyGSignalCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_DBusProxyGSignalCallback)
 -> m (GClosure C_DBusProxyGSignalCallback))
-> IO (GClosure C_DBusProxyGSignalCallback)
-> m (GClosure C_DBusProxyGSignalCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DBusProxyGSignalCallback
cb' = DBusProxyGSignalCallback -> C_DBusProxyGSignalCallback
wrap_DBusProxyGSignalCallback DBusProxyGSignalCallback
cb
    C_DBusProxyGSignalCallback
-> IO (FunPtr C_DBusProxyGSignalCallback)
mk_DBusProxyGSignalCallback C_DBusProxyGSignalCallback
cb' IO (FunPtr C_DBusProxyGSignalCallback)
-> (FunPtr C_DBusProxyGSignalCallback
    -> IO (GClosure C_DBusProxyGSignalCallback))
-> IO (GClosure C_DBusProxyGSignalCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_DBusProxyGSignalCallback
-> IO (GClosure C_DBusProxyGSignalCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `DBusProxyGSignalCallback` into a `C_DBusProxyGSignalCallback`.
wrap_DBusProxyGSignalCallback ::
    DBusProxyGSignalCallback ->
    C_DBusProxyGSignalCallback
wrap_DBusProxyGSignalCallback :: DBusProxyGSignalCallback -> C_DBusProxyGSignalCallback
wrap_DBusProxyGSignalCallback _cb :: DBusProxyGSignalCallback
_cb _ senderName :: CString
senderName signalName :: CString
signalName parameters :: Ptr GVariant
parameters _ = do
    Maybe Text
maybeSenderName <-
        if CString
senderName CString -> CString -> Bool
forall a. Eq a => a -> a -> Bool
== CString
forall a. Ptr a
nullPtr
        then Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
forall a. Maybe a
Nothing
        else do
            Text
senderName' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
senderName
            Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Text -> IO (Maybe Text)) -> Maybe Text -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ Text -> Maybe Text
forall a. a -> Maybe a
Just Text
senderName'
    Text
signalName' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
signalName
    GVariant
parameters' <- Ptr GVariant -> IO GVariant
B.GVariant.newGVariantFromPtr Ptr GVariant
parameters
    DBusProxyGSignalCallback
_cb  Maybe Text
maybeSenderName Text
signalName' GVariant
parameters'


-- | Connect a signal handler for the [gSignal](#signal:gSignal) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' dBusProxy #gSignal callback
-- @
-- 
-- 
onDBusProxyGSignal :: (IsDBusProxy a, MonadIO m) => a -> DBusProxyGSignalCallback -> m SignalHandlerId
onDBusProxyGSignal :: a -> DBusProxyGSignalCallback -> m SignalHandlerId
onDBusProxyGSignal obj :: a
obj cb :: DBusProxyGSignalCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DBusProxyGSignalCallback
cb' = DBusProxyGSignalCallback -> C_DBusProxyGSignalCallback
wrap_DBusProxyGSignalCallback DBusProxyGSignalCallback
cb
    FunPtr C_DBusProxyGSignalCallback
cb'' <- C_DBusProxyGSignalCallback
-> IO (FunPtr C_DBusProxyGSignalCallback)
mk_DBusProxyGSignalCallback C_DBusProxyGSignalCallback
cb'
    a
-> Text
-> FunPtr C_DBusProxyGSignalCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "g-signal" FunPtr C_DBusProxyGSignalCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [gSignal](#signal:gSignal) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' dBusProxy #gSignal callback
-- @
-- 
-- 
afterDBusProxyGSignal :: (IsDBusProxy a, MonadIO m) => a -> DBusProxyGSignalCallback -> m SignalHandlerId
afterDBusProxyGSignal :: a -> DBusProxyGSignalCallback -> m SignalHandlerId
afterDBusProxyGSignal obj :: a
obj cb :: DBusProxyGSignalCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DBusProxyGSignalCallback
cb' = DBusProxyGSignalCallback -> C_DBusProxyGSignalCallback
wrap_DBusProxyGSignalCallback DBusProxyGSignalCallback
cb
    FunPtr C_DBusProxyGSignalCallback
cb'' <- C_DBusProxyGSignalCallback
-> IO (FunPtr C_DBusProxyGSignalCallback)
mk_DBusProxyGSignalCallback C_DBusProxyGSignalCallback
cb'
    a
-> Text
-> FunPtr C_DBusProxyGSignalCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "g-signal" FunPtr C_DBusProxyGSignalCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data DBusProxyGSignalSignalInfo
instance SignalInfo DBusProxyGSignalSignalInfo where
    type HaskellCallbackType DBusProxyGSignalSignalInfo = DBusProxyGSignalCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_DBusProxyGSignalCallback cb
        cb'' <- mk_DBusProxyGSignalCallback cb'
        connectSignalFunPtr obj "g-signal" cb'' connectMode detail

#endif

-- VVV Prop "g-bus-type"
   -- Type: TInterface (Name {namespace = "Gio", name = "BusType"})
   -- Flags: [PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Construct a `GValueConstruct` with valid value for the “@g-bus-type@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDBusProxyGBusType :: (IsDBusProxy o) => Gio.Enums.BusType -> IO (GValueConstruct o)
constructDBusProxyGBusType :: BusType -> IO (GValueConstruct o)
constructDBusProxyGBusType val :: BusType
val = String -> BusType -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum "g-bus-type" BusType
val

#if defined(ENABLE_OVERLOADING)
data DBusProxyGBusTypePropertyInfo
instance AttrInfo DBusProxyGBusTypePropertyInfo where
    type AttrAllowedOps DBusProxyGBusTypePropertyInfo = '[ 'AttrConstruct]
    type AttrBaseTypeConstraint DBusProxyGBusTypePropertyInfo = IsDBusProxy
    type AttrSetTypeConstraint DBusProxyGBusTypePropertyInfo = (~) Gio.Enums.BusType
    type AttrTransferTypeConstraint DBusProxyGBusTypePropertyInfo = (~) Gio.Enums.BusType
    type AttrTransferType DBusProxyGBusTypePropertyInfo = Gio.Enums.BusType
    type AttrGetType DBusProxyGBusTypePropertyInfo = ()
    type AttrLabel DBusProxyGBusTypePropertyInfo = "g-bus-type"
    type AttrOrigin DBusProxyGBusTypePropertyInfo = DBusProxy
    attrGet = undefined
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructDBusProxyGBusType
    attrClear = undefined
#endif

-- VVV Prop "g-connection"
   -- Type: TInterface (Name {namespace = "Gio", name = "DBusConnection"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@g-connection@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dBusProxy #gConnection
-- @
getDBusProxyGConnection :: (MonadIO m, IsDBusProxy o) => o -> m (Maybe Gio.DBusConnection.DBusConnection)
getDBusProxyGConnection :: o -> m (Maybe DBusConnection)
getDBusProxyGConnection obj :: o
obj = IO (Maybe DBusConnection) -> m (Maybe DBusConnection)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe DBusConnection) -> m (Maybe DBusConnection))
-> IO (Maybe DBusConnection) -> m (Maybe DBusConnection)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr DBusConnection -> DBusConnection)
-> IO (Maybe DBusConnection)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj "g-connection" ManagedPtr DBusConnection -> DBusConnection
Gio.DBusConnection.DBusConnection

-- | Construct a `GValueConstruct` with valid value for the “@g-connection@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDBusProxyGConnection :: (IsDBusProxy o, Gio.DBusConnection.IsDBusConnection a) => a -> IO (GValueConstruct o)
constructDBusProxyGConnection :: a -> IO (GValueConstruct o)
constructDBusProxyGConnection val :: a
val = String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject "g-connection" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)

#if defined(ENABLE_OVERLOADING)
data DBusProxyGConnectionPropertyInfo
instance AttrInfo DBusProxyGConnectionPropertyInfo where
    type AttrAllowedOps DBusProxyGConnectionPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DBusProxyGConnectionPropertyInfo = IsDBusProxy
    type AttrSetTypeConstraint DBusProxyGConnectionPropertyInfo = Gio.DBusConnection.IsDBusConnection
    type AttrTransferTypeConstraint DBusProxyGConnectionPropertyInfo = Gio.DBusConnection.IsDBusConnection
    type AttrTransferType DBusProxyGConnectionPropertyInfo = Gio.DBusConnection.DBusConnection
    type AttrGetType DBusProxyGConnectionPropertyInfo = (Maybe Gio.DBusConnection.DBusConnection)
    type AttrLabel DBusProxyGConnectionPropertyInfo = "g-connection"
    type AttrOrigin DBusProxyGConnectionPropertyInfo = DBusProxy
    attrGet = getDBusProxyGConnection
    attrSet = undefined
    attrTransfer _ v = do
        unsafeCastTo Gio.DBusConnection.DBusConnection v
    attrConstruct = constructDBusProxyGConnection
    attrClear = undefined
#endif

-- VVV Prop "g-default-timeout"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@g-default-timeout@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dBusProxy #gDefaultTimeout
-- @
getDBusProxyGDefaultTimeout :: (MonadIO m, IsDBusProxy o) => o -> m Int32
getDBusProxyGDefaultTimeout :: o -> m Int32
getDBusProxyGDefaultTimeout obj :: o
obj = 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
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj "g-default-timeout"

-- | Set the value of the “@g-default-timeout@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' dBusProxy [ #gDefaultTimeout 'Data.GI.Base.Attributes.:=' value ]
-- @
setDBusProxyGDefaultTimeout :: (MonadIO m, IsDBusProxy o) => o -> Int32 -> m ()
setDBusProxyGDefaultTimeout :: o -> Int32 -> m ()
setDBusProxyGDefaultTimeout obj :: o
obj 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
$ o -> String -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj "g-default-timeout" Int32
val

-- | Construct a `GValueConstruct` with valid value for the “@g-default-timeout@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDBusProxyGDefaultTimeout :: (IsDBusProxy o) => Int32 -> IO (GValueConstruct o)
constructDBusProxyGDefaultTimeout :: Int32 -> IO (GValueConstruct o)
constructDBusProxyGDefaultTimeout val :: Int32
val = String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 "g-default-timeout" Int32
val

#if defined(ENABLE_OVERLOADING)
data DBusProxyGDefaultTimeoutPropertyInfo
instance AttrInfo DBusProxyGDefaultTimeoutPropertyInfo where
    type AttrAllowedOps DBusProxyGDefaultTimeoutPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint DBusProxyGDefaultTimeoutPropertyInfo = IsDBusProxy
    type AttrSetTypeConstraint DBusProxyGDefaultTimeoutPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint DBusProxyGDefaultTimeoutPropertyInfo = (~) Int32
    type AttrTransferType DBusProxyGDefaultTimeoutPropertyInfo = Int32
    type AttrGetType DBusProxyGDefaultTimeoutPropertyInfo = Int32
    type AttrLabel DBusProxyGDefaultTimeoutPropertyInfo = "g-default-timeout"
    type AttrOrigin DBusProxyGDefaultTimeoutPropertyInfo = DBusProxy
    attrGet = getDBusProxyGDefaultTimeout
    attrSet = setDBusProxyGDefaultTimeout
    attrTransfer _ v = do
        return v
    attrConstruct = constructDBusProxyGDefaultTimeout
    attrClear = undefined
#endif

-- VVV Prop "g-flags"
   -- Type: TInterface (Name {namespace = "Gio", name = "DBusProxyFlags"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@g-flags@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dBusProxy #gFlags
-- @
getDBusProxyGFlags :: (MonadIO m, IsDBusProxy o) => o -> m [Gio.Flags.DBusProxyFlags]
getDBusProxyGFlags :: o -> m [DBusProxyFlags]
getDBusProxyGFlags obj :: o
obj = IO [DBusProxyFlags] -> m [DBusProxyFlags]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [DBusProxyFlags] -> m [DBusProxyFlags])
-> IO [DBusProxyFlags] -> m [DBusProxyFlags]
forall a b. (a -> b) -> a -> b
$ o -> String -> IO [DBusProxyFlags]
forall a b.
(GObject a, IsGFlag b, BoxedFlags b) =>
a -> String -> IO [b]
B.Properties.getObjectPropertyFlags o
obj "g-flags"

-- | Construct a `GValueConstruct` with valid value for the “@g-flags@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDBusProxyGFlags :: (IsDBusProxy o) => [Gio.Flags.DBusProxyFlags] -> IO (GValueConstruct o)
constructDBusProxyGFlags :: [DBusProxyFlags] -> IO (GValueConstruct o)
constructDBusProxyGFlags val :: [DBusProxyFlags]
val = String -> [DBusProxyFlags] -> IO (GValueConstruct o)
forall a o.
(IsGFlag a, BoxedFlags a) =>
String -> [a] -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyFlags "g-flags" [DBusProxyFlags]
val

#if defined(ENABLE_OVERLOADING)
data DBusProxyGFlagsPropertyInfo
instance AttrInfo DBusProxyGFlagsPropertyInfo where
    type AttrAllowedOps DBusProxyGFlagsPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint DBusProxyGFlagsPropertyInfo = IsDBusProxy
    type AttrSetTypeConstraint DBusProxyGFlagsPropertyInfo = (~) [Gio.Flags.DBusProxyFlags]
    type AttrTransferTypeConstraint DBusProxyGFlagsPropertyInfo = (~) [Gio.Flags.DBusProxyFlags]
    type AttrTransferType DBusProxyGFlagsPropertyInfo = [Gio.Flags.DBusProxyFlags]
    type AttrGetType DBusProxyGFlagsPropertyInfo = [Gio.Flags.DBusProxyFlags]
    type AttrLabel DBusProxyGFlagsPropertyInfo = "g-flags"
    type AttrOrigin DBusProxyGFlagsPropertyInfo = DBusProxy
    attrGet = getDBusProxyGFlags
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructDBusProxyGFlags
    attrClear = undefined
#endif

-- VVV Prop "g-interface-info"
   -- Type: TInterface (Name {namespace = "Gio", name = "DBusInterfaceInfo"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@g-interface-info@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dBusProxy #gInterfaceInfo
-- @
getDBusProxyGInterfaceInfo :: (MonadIO m, IsDBusProxy o) => o -> m (Maybe Gio.DBusInterfaceInfo.DBusInterfaceInfo)
getDBusProxyGInterfaceInfo :: o -> m (Maybe DBusInterfaceInfo)
getDBusProxyGInterfaceInfo obj :: o
obj = 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
$ o
-> String
-> (ManagedPtr DBusInterfaceInfo -> DBusInterfaceInfo)
-> IO (Maybe DBusInterfaceInfo)
forall a b.
(GObject a, BoxedObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyBoxed o
obj "g-interface-info" ManagedPtr DBusInterfaceInfo -> DBusInterfaceInfo
Gio.DBusInterfaceInfo.DBusInterfaceInfo

-- | Set the value of the “@g-interface-info@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' dBusProxy [ #gInterfaceInfo 'Data.GI.Base.Attributes.:=' value ]
-- @
setDBusProxyGInterfaceInfo :: (MonadIO m, IsDBusProxy o) => o -> Gio.DBusInterfaceInfo.DBusInterfaceInfo -> m ()
setDBusProxyGInterfaceInfo :: o -> DBusInterfaceInfo -> m ()
setDBusProxyGInterfaceInfo obj :: o
obj val :: 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
$ o -> String -> Maybe DBusInterfaceInfo -> IO ()
forall a b.
(GObject a, BoxedObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyBoxed o
obj "g-interface-info" (DBusInterfaceInfo -> Maybe DBusInterfaceInfo
forall a. a -> Maybe a
Just DBusInterfaceInfo
val)

-- | Construct a `GValueConstruct` with valid value for the “@g-interface-info@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDBusProxyGInterfaceInfo :: (IsDBusProxy o) => Gio.DBusInterfaceInfo.DBusInterfaceInfo -> IO (GValueConstruct o)
constructDBusProxyGInterfaceInfo :: DBusInterfaceInfo -> IO (GValueConstruct o)
constructDBusProxyGInterfaceInfo val :: DBusInterfaceInfo
val = String -> Maybe DBusInterfaceInfo -> IO (GValueConstruct o)
forall a o.
BoxedObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBoxed "g-interface-info" (DBusInterfaceInfo -> Maybe DBusInterfaceInfo
forall a. a -> Maybe a
Just DBusInterfaceInfo
val)

-- | Set the value of the “@g-interface-info@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #gInterfaceInfo
-- @
clearDBusProxyGInterfaceInfo :: (MonadIO m, IsDBusProxy o) => o -> m ()
clearDBusProxyGInterfaceInfo :: o -> m ()
clearDBusProxyGInterfaceInfo obj :: o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe DBusInterfaceInfo -> IO ()
forall a b.
(GObject a, BoxedObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyBoxed o
obj "g-interface-info" (Maybe DBusInterfaceInfo
forall a. Maybe a
Nothing :: Maybe Gio.DBusInterfaceInfo.DBusInterfaceInfo)

#if defined(ENABLE_OVERLOADING)
data DBusProxyGInterfaceInfoPropertyInfo
instance AttrInfo DBusProxyGInterfaceInfoPropertyInfo where
    type AttrAllowedOps DBusProxyGInterfaceInfoPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DBusProxyGInterfaceInfoPropertyInfo = IsDBusProxy
    type AttrSetTypeConstraint DBusProxyGInterfaceInfoPropertyInfo = (~) Gio.DBusInterfaceInfo.DBusInterfaceInfo
    type AttrTransferTypeConstraint DBusProxyGInterfaceInfoPropertyInfo = (~) Gio.DBusInterfaceInfo.DBusInterfaceInfo
    type AttrTransferType DBusProxyGInterfaceInfoPropertyInfo = Gio.DBusInterfaceInfo.DBusInterfaceInfo
    type AttrGetType DBusProxyGInterfaceInfoPropertyInfo = (Maybe Gio.DBusInterfaceInfo.DBusInterfaceInfo)
    type AttrLabel DBusProxyGInterfaceInfoPropertyInfo = "g-interface-info"
    type AttrOrigin DBusProxyGInterfaceInfoPropertyInfo = DBusProxy
    attrGet = getDBusProxyGInterfaceInfo
    attrSet = setDBusProxyGInterfaceInfo
    attrTransfer _ v = do
        return v
    attrConstruct = constructDBusProxyGInterfaceInfo
    attrClear = clearDBusProxyGInterfaceInfo
#endif

-- VVV Prop "g-interface-name"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@g-interface-name@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dBusProxy #gInterfaceName
-- @
getDBusProxyGInterfaceName :: (MonadIO m, IsDBusProxy o) => o -> m (Maybe T.Text)
getDBusProxyGInterfaceName :: o -> m (Maybe Text)
getDBusProxyGInterfaceName obj :: o
obj = 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
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj "g-interface-name"

-- | Construct a `GValueConstruct` with valid value for the “@g-interface-name@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDBusProxyGInterfaceName :: (IsDBusProxy o) => T.Text -> IO (GValueConstruct o)
constructDBusProxyGInterfaceName :: Text -> IO (GValueConstruct o)
constructDBusProxyGInterfaceName val :: Text
val = String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString "g-interface-name" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

#if defined(ENABLE_OVERLOADING)
data DBusProxyGInterfaceNamePropertyInfo
instance AttrInfo DBusProxyGInterfaceNamePropertyInfo where
    type AttrAllowedOps DBusProxyGInterfaceNamePropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DBusProxyGInterfaceNamePropertyInfo = IsDBusProxy
    type AttrSetTypeConstraint DBusProxyGInterfaceNamePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint DBusProxyGInterfaceNamePropertyInfo = (~) T.Text
    type AttrTransferType DBusProxyGInterfaceNamePropertyInfo = T.Text
    type AttrGetType DBusProxyGInterfaceNamePropertyInfo = (Maybe T.Text)
    type AttrLabel DBusProxyGInterfaceNamePropertyInfo = "g-interface-name"
    type AttrOrigin DBusProxyGInterfaceNamePropertyInfo = DBusProxy
    attrGet = getDBusProxyGInterfaceName
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructDBusProxyGInterfaceName
    attrClear = undefined
#endif

-- VVV Prop "g-name"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@g-name@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dBusProxy #gName
-- @
getDBusProxyGName :: (MonadIO m, IsDBusProxy o) => o -> m (Maybe T.Text)
getDBusProxyGName :: o -> m (Maybe Text)
getDBusProxyGName obj :: o
obj = 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
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj "g-name"

-- | Construct a `GValueConstruct` with valid value for the “@g-name@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDBusProxyGName :: (IsDBusProxy o) => T.Text -> IO (GValueConstruct o)
constructDBusProxyGName :: Text -> IO (GValueConstruct o)
constructDBusProxyGName val :: Text
val = String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString "g-name" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

#if defined(ENABLE_OVERLOADING)
data DBusProxyGNamePropertyInfo
instance AttrInfo DBusProxyGNamePropertyInfo where
    type AttrAllowedOps DBusProxyGNamePropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DBusProxyGNamePropertyInfo = IsDBusProxy
    type AttrSetTypeConstraint DBusProxyGNamePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint DBusProxyGNamePropertyInfo = (~) T.Text
    type AttrTransferType DBusProxyGNamePropertyInfo = T.Text
    type AttrGetType DBusProxyGNamePropertyInfo = (Maybe T.Text)
    type AttrLabel DBusProxyGNamePropertyInfo = "g-name"
    type AttrOrigin DBusProxyGNamePropertyInfo = DBusProxy
    attrGet = getDBusProxyGName
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructDBusProxyGName
    attrClear = undefined
#endif

-- VVV Prop "g-name-owner"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@g-name-owner@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dBusProxy #gNameOwner
-- @
getDBusProxyGNameOwner :: (MonadIO m, IsDBusProxy o) => o -> m (Maybe T.Text)
getDBusProxyGNameOwner :: o -> m (Maybe Text)
getDBusProxyGNameOwner obj :: o
obj = 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
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj "g-name-owner"

#if defined(ENABLE_OVERLOADING)
data DBusProxyGNameOwnerPropertyInfo
instance AttrInfo DBusProxyGNameOwnerPropertyInfo where
    type AttrAllowedOps DBusProxyGNameOwnerPropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DBusProxyGNameOwnerPropertyInfo = IsDBusProxy
    type AttrSetTypeConstraint DBusProxyGNameOwnerPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DBusProxyGNameOwnerPropertyInfo = (~) ()
    type AttrTransferType DBusProxyGNameOwnerPropertyInfo = ()
    type AttrGetType DBusProxyGNameOwnerPropertyInfo = (Maybe T.Text)
    type AttrLabel DBusProxyGNameOwnerPropertyInfo = "g-name-owner"
    type AttrOrigin DBusProxyGNameOwnerPropertyInfo = DBusProxy
    attrGet = getDBusProxyGNameOwner
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

-- VVV Prop "g-object-path"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@g-object-path@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dBusProxy #gObjectPath
-- @
getDBusProxyGObjectPath :: (MonadIO m, IsDBusProxy o) => o -> m (Maybe T.Text)
getDBusProxyGObjectPath :: o -> m (Maybe Text)
getDBusProxyGObjectPath obj :: o
obj = 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
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj "g-object-path"

-- | Construct a `GValueConstruct` with valid value for the “@g-object-path@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDBusProxyGObjectPath :: (IsDBusProxy o) => T.Text -> IO (GValueConstruct o)
constructDBusProxyGObjectPath :: Text -> IO (GValueConstruct o)
constructDBusProxyGObjectPath val :: Text
val = String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString "g-object-path" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

#if defined(ENABLE_OVERLOADING)
data DBusProxyGObjectPathPropertyInfo
instance AttrInfo DBusProxyGObjectPathPropertyInfo where
    type AttrAllowedOps DBusProxyGObjectPathPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DBusProxyGObjectPathPropertyInfo = IsDBusProxy
    type AttrSetTypeConstraint DBusProxyGObjectPathPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint DBusProxyGObjectPathPropertyInfo = (~) T.Text
    type AttrTransferType DBusProxyGObjectPathPropertyInfo = T.Text
    type AttrGetType DBusProxyGObjectPathPropertyInfo = (Maybe T.Text)
    type AttrLabel DBusProxyGObjectPathPropertyInfo = "g-object-path"
    type AttrOrigin DBusProxyGObjectPathPropertyInfo = DBusProxy
    attrGet = getDBusProxyGObjectPath
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructDBusProxyGObjectPath
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DBusProxy
type instance O.AttributeList DBusProxy = DBusProxyAttributeList
type DBusProxyAttributeList = ('[ '("gBusType", DBusProxyGBusTypePropertyInfo), '("gConnection", DBusProxyGConnectionPropertyInfo), '("gDefaultTimeout", DBusProxyGDefaultTimeoutPropertyInfo), '("gFlags", DBusProxyGFlagsPropertyInfo), '("gInterfaceInfo", DBusProxyGInterfaceInfoPropertyInfo), '("gInterfaceName", DBusProxyGInterfaceNamePropertyInfo), '("gName", DBusProxyGNamePropertyInfo), '("gNameOwner", DBusProxyGNameOwnerPropertyInfo), '("gObjectPath", DBusProxyGObjectPathPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
dBusProxyGBusType :: AttrLabelProxy "gBusType"
dBusProxyGBusType = AttrLabelProxy

dBusProxyGConnection :: AttrLabelProxy "gConnection"
dBusProxyGConnection = AttrLabelProxy

dBusProxyGDefaultTimeout :: AttrLabelProxy "gDefaultTimeout"
dBusProxyGDefaultTimeout = AttrLabelProxy

dBusProxyGFlags :: AttrLabelProxy "gFlags"
dBusProxyGFlags = AttrLabelProxy

dBusProxyGInterfaceInfo :: AttrLabelProxy "gInterfaceInfo"
dBusProxyGInterfaceInfo = AttrLabelProxy

dBusProxyGInterfaceName :: AttrLabelProxy "gInterfaceName"
dBusProxyGInterfaceName = AttrLabelProxy

dBusProxyGName :: AttrLabelProxy "gName"
dBusProxyGName = AttrLabelProxy

dBusProxyGNameOwner :: AttrLabelProxy "gNameOwner"
dBusProxyGNameOwner = AttrLabelProxy

dBusProxyGObjectPath :: AttrLabelProxy "gObjectPath"
dBusProxyGObjectPath = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList DBusProxy = DBusProxySignalList
type DBusProxySignalList = ('[ '("gPropertiesChanged", DBusProxyGPropertiesChangedSignalInfo), '("gSignal", DBusProxyGSignalSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

-- method DBusProxy::new_finish
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "res"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncResult" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A #GAsyncResult obtained from the #GAsyncReadyCallback function passed to g_dbus_proxy_new()."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "DBusProxy" })
-- throws : True
-- Skip return : False

foreign import ccall "g_dbus_proxy_new_finish" g_dbus_proxy_new_finish :: 
    Ptr Gio.AsyncResult.AsyncResult ->      -- res : TInterface (Name {namespace = "Gio", name = "AsyncResult"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr DBusProxy)

-- | Finishes creating a t'GI.Gio.Objects.DBusProxy.DBusProxy'.
-- 
-- /Since: 2.26/
dBusProxyNewFinish ::
    (B.CallStack.HasCallStack, MonadIO m, Gio.AsyncResult.IsAsyncResult a) =>
    a
    -- ^ /@res@/: A t'GI.Gio.Interfaces.AsyncResult.AsyncResult' obtained from the t'GI.Gio.Callbacks.AsyncReadyCallback' function passed to 'GI.Gio.Objects.DBusProxy.dBusProxyNew'.
    -> m DBusProxy
    -- ^ __Returns:__ A t'GI.Gio.Objects.DBusProxy.DBusProxy' or 'P.Nothing' if /@error@/ is set.
    --    Free with 'GI.GObject.Objects.Object.objectUnref'. /(Can throw 'Data.GI.Base.GError.GError')/
dBusProxyNewFinish :: a -> m DBusProxy
dBusProxyNewFinish res :: a
res = IO DBusProxy -> m DBusProxy
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DBusProxy -> m DBusProxy) -> IO DBusProxy -> m DBusProxy
forall a b. (a -> b) -> a -> b
$ do
    Ptr AsyncResult
res' <- a -> IO (Ptr AsyncResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
res
    IO DBusProxy -> IO () -> IO DBusProxy
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr DBusProxy
result <- (Ptr (Ptr GError) -> IO (Ptr DBusProxy)) -> IO (Ptr DBusProxy)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr DBusProxy)) -> IO (Ptr DBusProxy))
-> (Ptr (Ptr GError) -> IO (Ptr DBusProxy)) -> IO (Ptr DBusProxy)
forall a b. (a -> b) -> a -> b
$ Ptr AsyncResult -> Ptr (Ptr GError) -> IO (Ptr DBusProxy)
g_dbus_proxy_new_finish Ptr AsyncResult
res'
        Text -> Ptr DBusProxy -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusProxyNewFinish" Ptr DBusProxy
result
        DBusProxy
result' <- ((ManagedPtr DBusProxy -> DBusProxy)
-> Ptr DBusProxy -> IO DBusProxy
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr DBusProxy -> DBusProxy
DBusProxy) Ptr DBusProxy
result
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
res
        DBusProxy -> IO DBusProxy
forall (m :: * -> *) a. Monad m => a -> m a
return DBusProxy
result'
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method DBusProxy::new_for_bus_finish
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "res"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncResult" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A #GAsyncResult obtained from the #GAsyncReadyCallback function passed to g_dbus_proxy_new_for_bus()."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "DBusProxy" })
-- throws : True
-- Skip return : False

foreign import ccall "g_dbus_proxy_new_for_bus_finish" g_dbus_proxy_new_for_bus_finish :: 
    Ptr Gio.AsyncResult.AsyncResult ->      -- res : TInterface (Name {namespace = "Gio", name = "AsyncResult"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr DBusProxy)

-- | Finishes creating a t'GI.Gio.Objects.DBusProxy.DBusProxy'.
-- 
-- /Since: 2.26/
dBusProxyNewForBusFinish ::
    (B.CallStack.HasCallStack, MonadIO m, Gio.AsyncResult.IsAsyncResult a) =>
    a
    -- ^ /@res@/: A t'GI.Gio.Interfaces.AsyncResult.AsyncResult' obtained from the t'GI.Gio.Callbacks.AsyncReadyCallback' function passed to 'GI.Gio.Objects.DBusProxy.dBusProxyNewForBus'.
    -> m DBusProxy
    -- ^ __Returns:__ A t'GI.Gio.Objects.DBusProxy.DBusProxy' or 'P.Nothing' if /@error@/ is set.
    --    Free with 'GI.GObject.Objects.Object.objectUnref'. /(Can throw 'Data.GI.Base.GError.GError')/
dBusProxyNewForBusFinish :: a -> m DBusProxy
dBusProxyNewForBusFinish res :: a
res = IO DBusProxy -> m DBusProxy
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DBusProxy -> m DBusProxy) -> IO DBusProxy -> m DBusProxy
forall a b. (a -> b) -> a -> b
$ do
    Ptr AsyncResult
res' <- a -> IO (Ptr AsyncResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
res
    IO DBusProxy -> IO () -> IO DBusProxy
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr DBusProxy
result <- (Ptr (Ptr GError) -> IO (Ptr DBusProxy)) -> IO (Ptr DBusProxy)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr DBusProxy)) -> IO (Ptr DBusProxy))
-> (Ptr (Ptr GError) -> IO (Ptr DBusProxy)) -> IO (Ptr DBusProxy)
forall a b. (a -> b) -> a -> b
$ Ptr AsyncResult -> Ptr (Ptr GError) -> IO (Ptr DBusProxy)
g_dbus_proxy_new_for_bus_finish Ptr AsyncResult
res'
        Text -> Ptr DBusProxy -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusProxyNewForBusFinish" Ptr DBusProxy
result
        DBusProxy
result' <- ((ManagedPtr DBusProxy -> DBusProxy)
-> Ptr DBusProxy -> IO DBusProxy
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr DBusProxy -> DBusProxy
DBusProxy) Ptr DBusProxy
result
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
res
        DBusProxy -> IO DBusProxy
forall (m :: * -> *) a. Monad m => a -> m a
return DBusProxy
result'
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method DBusProxy::new_for_bus_sync
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "bus_type"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "BusType" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GBusType." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusProxyFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Flags used when constructing the proxy."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusInterfaceInfo" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A #GDBusInterfaceInfo specifying the minimal interface\n       that @proxy conforms to or %NULL."
--                 , 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 bus name (well-known or unique)."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "object_path"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An object path." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "interface_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
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GCancellable or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "DBusProxy" })
-- throws : True
-- Skip return : False

foreign import ccall "g_dbus_proxy_new_for_bus_sync" g_dbus_proxy_new_for_bus_sync :: 
    CInt ->                                 -- bus_type : TInterface (Name {namespace = "Gio", name = "BusType"})
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gio", name = "DBusProxyFlags"})
    Ptr Gio.DBusInterfaceInfo.DBusInterfaceInfo -> -- info : TInterface (Name {namespace = "Gio", name = "DBusInterfaceInfo"})
    CString ->                              -- name : TBasicType TUTF8
    CString ->                              -- object_path : TBasicType TUTF8
    CString ->                              -- interface_name : TBasicType TUTF8
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr DBusProxy)

-- | Like 'GI.Gio.Objects.DBusProxy.dBusProxyNewSync' but takes a t'GI.Gio.Enums.BusType' instead of a t'GI.Gio.Objects.DBusConnection.DBusConnection'.
-- 
-- t'GI.Gio.Objects.DBusProxy.DBusProxy' is used in this [example][gdbus-wellknown-proxy].
-- 
-- /Since: 2.26/
dBusProxyNewForBusSync ::
    (B.CallStack.HasCallStack, MonadIO m, Gio.Cancellable.IsCancellable a) =>
    Gio.Enums.BusType
    -- ^ /@busType@/: A t'GI.Gio.Enums.BusType'.
    -> [Gio.Flags.DBusProxyFlags]
    -- ^ /@flags@/: Flags used when constructing the proxy.
    -> Maybe (Gio.DBusInterfaceInfo.DBusInterfaceInfo)
    -- ^ /@info@/: A t'GI.Gio.Structs.DBusInterfaceInfo.DBusInterfaceInfo' specifying the minimal interface
    --        that /@proxy@/ conforms to or 'P.Nothing'.
    -> T.Text
    -- ^ /@name@/: A bus name (well-known or unique).
    -> T.Text
    -- ^ /@objectPath@/: An object path.
    -> T.Text
    -- ^ /@interfaceName@/: A D-Bus interface name.
    -> Maybe (a)
    -- ^ /@cancellable@/: A t'GI.Gio.Objects.Cancellable.Cancellable' or 'P.Nothing'.
    -> m DBusProxy
    -- ^ __Returns:__ A t'GI.Gio.Objects.DBusProxy.DBusProxy' or 'P.Nothing' if error is set.
    --    Free with 'GI.GObject.Objects.Object.objectUnref'. /(Can throw 'Data.GI.Base.GError.GError')/
dBusProxyNewForBusSync :: BusType
-> [DBusProxyFlags]
-> Maybe DBusInterfaceInfo
-> Text
-> Text
-> Text
-> Maybe a
-> m DBusProxy
dBusProxyNewForBusSync busType :: BusType
busType flags :: [DBusProxyFlags]
flags info :: Maybe DBusInterfaceInfo
info name :: Text
name objectPath :: Text
objectPath interfaceName :: Text
interfaceName cancellable :: Maybe a
cancellable = IO DBusProxy -> m DBusProxy
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DBusProxy -> m DBusProxy) -> IO DBusProxy -> m DBusProxy
forall a b. (a -> b) -> a -> b
$ do
    let busType' :: CInt
busType' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (BusType -> Int) -> BusType -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BusType -> Int
forall a. Enum a => a -> Int
fromEnum) BusType
busType
    let flags' :: CUInt
flags' = [DBusProxyFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [DBusProxyFlags]
flags
    Ptr DBusInterfaceInfo
maybeInfo <- case Maybe DBusInterfaceInfo
info of
        Nothing -> Ptr DBusInterfaceInfo -> IO (Ptr DBusInterfaceInfo)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr DBusInterfaceInfo
forall a. Ptr a
nullPtr
        Just jInfo :: DBusInterfaceInfo
jInfo -> do
            Ptr DBusInterfaceInfo
jInfo' <- DBusInterfaceInfo -> IO (Ptr DBusInterfaceInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr DBusInterfaceInfo
jInfo
            Ptr DBusInterfaceInfo -> IO (Ptr DBusInterfaceInfo)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr DBusInterfaceInfo
jInfo'
    CString
name' <- Text -> IO CString
textToCString Text
name
    CString
objectPath' <- Text -> IO CString
textToCString Text
objectPath
    CString
interfaceName' <- Text -> IO CString
textToCString Text
interfaceName
    Ptr Cancellable
maybeCancellable <- case Maybe a
cancellable of
        Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just jCancellable :: a
jCancellable -> do
            Ptr Cancellable
jCancellable' <- a -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    IO DBusProxy -> IO () -> IO DBusProxy
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr DBusProxy
result <- (Ptr (Ptr GError) -> IO (Ptr DBusProxy)) -> IO (Ptr DBusProxy)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr DBusProxy)) -> IO (Ptr DBusProxy))
-> (Ptr (Ptr GError) -> IO (Ptr DBusProxy)) -> IO (Ptr DBusProxy)
forall a b. (a -> b) -> a -> b
$ CInt
-> CUInt
-> Ptr DBusInterfaceInfo
-> CString
-> CString
-> CString
-> Ptr Cancellable
-> Ptr (Ptr GError)
-> IO (Ptr DBusProxy)
g_dbus_proxy_new_for_bus_sync CInt
busType' CUInt
flags' Ptr DBusInterfaceInfo
maybeInfo CString
name' CString
objectPath' CString
interfaceName' Ptr Cancellable
maybeCancellable
        Text -> Ptr DBusProxy -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusProxyNewForBusSync" Ptr DBusProxy
result
        DBusProxy
result' <- ((ManagedPtr DBusProxy -> DBusProxy)
-> Ptr DBusProxy -> IO DBusProxy
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr DBusProxy -> DBusProxy
DBusProxy) Ptr DBusProxy
result
        Maybe DBusInterfaceInfo -> (DBusInterfaceInfo -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe DBusInterfaceInfo
info DBusInterfaceInfo -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        Maybe a -> (a -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe a
cancellable a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
objectPath'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
interfaceName'
        DBusProxy -> IO DBusProxy
forall (m :: * -> *) a. Monad m => a -> m a
return DBusProxy
result'
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
objectPath'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
interfaceName'
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method DBusProxy::new_sync
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "connection"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusConnection."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusProxyFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Flags used when constructing the proxy."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusInterfaceInfo" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A #GDBusInterfaceInfo specifying the minimal interface that @proxy conforms to or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A bus name (well-known or unique) or %NULL if @connection is not a message bus connection."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "object_path"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An object path." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "interface_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
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GCancellable or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "DBusProxy" })
-- throws : True
-- Skip return : False

foreign import ccall "g_dbus_proxy_new_sync" g_dbus_proxy_new_sync :: 
    Ptr Gio.DBusConnection.DBusConnection -> -- connection : TInterface (Name {namespace = "Gio", name = "DBusConnection"})
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gio", name = "DBusProxyFlags"})
    Ptr Gio.DBusInterfaceInfo.DBusInterfaceInfo -> -- info : TInterface (Name {namespace = "Gio", name = "DBusInterfaceInfo"})
    CString ->                              -- name : TBasicType TUTF8
    CString ->                              -- object_path : TBasicType TUTF8
    CString ->                              -- interface_name : TBasicType TUTF8
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr DBusProxy)

-- | Creates a proxy for accessing /@interfaceName@/ on the remote object
-- at /@objectPath@/ owned by /@name@/ at /@connection@/ and synchronously
-- loads D-Bus properties unless the
-- 'GI.Gio.Flags.DBusProxyFlagsDoNotLoadProperties' flag is used.
-- 
-- If the 'GI.Gio.Flags.DBusProxyFlagsDoNotConnectSignals' flag is not set, also sets up
-- match rules for signals. Connect to the [gSignal]("GI.Gio.Objects.DBusProxy#signal:gSignal") signal
-- to handle signals from the remote object.
-- 
-- If both 'GI.Gio.Flags.DBusProxyFlagsDoNotLoadProperties' and
-- 'GI.Gio.Flags.DBusProxyFlagsDoNotConnectSignals' are set, this constructor is
-- guaranteed to return immediately without blocking.
-- 
-- If /@name@/ is a well-known name and the
-- 'GI.Gio.Flags.DBusProxyFlagsDoNotAutoStart' and 'GI.Gio.Flags.DBusProxyFlagsDoNotAutoStartAtConstruction'
-- flags aren\'t set and no name owner currently exists, the message bus
-- will be requested to launch a name owner for the name.
-- 
-- This is a synchronous failable constructor. See 'GI.Gio.Objects.DBusProxy.dBusProxyNew'
-- and 'GI.Gio.Objects.DBusProxy.dBusProxyNewFinish' for the asynchronous version.
-- 
-- t'GI.Gio.Objects.DBusProxy.DBusProxy' is used in this [example][gdbus-wellknown-proxy].
-- 
-- /Since: 2.26/
dBusProxyNewSync ::
    (B.CallStack.HasCallStack, MonadIO m, Gio.DBusConnection.IsDBusConnection a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@connection@/: A t'GI.Gio.Objects.DBusConnection.DBusConnection'.
    -> [Gio.Flags.DBusProxyFlags]
    -- ^ /@flags@/: Flags used when constructing the proxy.
    -> Maybe (Gio.DBusInterfaceInfo.DBusInterfaceInfo)
    -- ^ /@info@/: A t'GI.Gio.Structs.DBusInterfaceInfo.DBusInterfaceInfo' specifying the minimal interface that /@proxy@/ conforms to or 'P.Nothing'.
    -> Maybe (T.Text)
    -- ^ /@name@/: A bus name (well-known or unique) or 'P.Nothing' if /@connection@/ is not a message bus connection.
    -> T.Text
    -- ^ /@objectPath@/: An object path.
    -> T.Text
    -- ^ /@interfaceName@/: A D-Bus interface name.
    -> Maybe (b)
    -- ^ /@cancellable@/: A t'GI.Gio.Objects.Cancellable.Cancellable' or 'P.Nothing'.
    -> m DBusProxy
    -- ^ __Returns:__ A t'GI.Gio.Objects.DBusProxy.DBusProxy' or 'P.Nothing' if error is set.
    --    Free with 'GI.GObject.Objects.Object.objectUnref'. /(Can throw 'Data.GI.Base.GError.GError')/
dBusProxyNewSync :: a
-> [DBusProxyFlags]
-> Maybe DBusInterfaceInfo
-> Maybe Text
-> Text
-> Text
-> Maybe b
-> m DBusProxy
dBusProxyNewSync connection :: a
connection flags :: [DBusProxyFlags]
flags info :: Maybe DBusInterfaceInfo
info name :: Maybe Text
name objectPath :: Text
objectPath interfaceName :: Text
interfaceName cancellable :: Maybe b
cancellable = IO DBusProxy -> m DBusProxy
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DBusProxy -> m DBusProxy) -> IO DBusProxy -> m DBusProxy
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusConnection
connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    let flags' :: CUInt
flags' = [DBusProxyFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [DBusProxyFlags]
flags
    Ptr DBusInterfaceInfo
maybeInfo <- case Maybe DBusInterfaceInfo
info of
        Nothing -> Ptr DBusInterfaceInfo -> IO (Ptr DBusInterfaceInfo)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr DBusInterfaceInfo
forall a. Ptr a
nullPtr
        Just jInfo :: DBusInterfaceInfo
jInfo -> do
            Ptr DBusInterfaceInfo
jInfo' <- DBusInterfaceInfo -> IO (Ptr DBusInterfaceInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr DBusInterfaceInfo
jInfo
            Ptr DBusInterfaceInfo -> IO (Ptr DBusInterfaceInfo)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr DBusInterfaceInfo
jInfo'
    CString
maybeName <- case Maybe Text
name of
        Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just jName :: Text
jName -> do
            CString
jName' <- Text -> IO CString
textToCString Text
jName
            CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jName'
    CString
objectPath' <- Text -> IO CString
textToCString Text
objectPath
    CString
interfaceName' <- Text -> IO CString
textToCString Text
interfaceName
    Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
        Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just jCancellable :: b
jCancellable -> do
            Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    IO DBusProxy -> IO () -> IO DBusProxy
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr DBusProxy
result <- (Ptr (Ptr GError) -> IO (Ptr DBusProxy)) -> IO (Ptr DBusProxy)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr DBusProxy)) -> IO (Ptr DBusProxy))
-> (Ptr (Ptr GError) -> IO (Ptr DBusProxy)) -> IO (Ptr DBusProxy)
forall a b. (a -> b) -> a -> b
$ Ptr DBusConnection
-> CUInt
-> Ptr DBusInterfaceInfo
-> CString
-> CString
-> CString
-> Ptr Cancellable
-> Ptr (Ptr GError)
-> IO (Ptr DBusProxy)
g_dbus_proxy_new_sync Ptr DBusConnection
connection' CUInt
flags' Ptr DBusInterfaceInfo
maybeInfo CString
maybeName CString
objectPath' CString
interfaceName' Ptr Cancellable
maybeCancellable
        Text -> Ptr DBusProxy -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusProxyNewSync" Ptr DBusProxy
result
        DBusProxy
result' <- ((ManagedPtr DBusProxy -> DBusProxy)
-> Ptr DBusProxy -> IO DBusProxy
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr DBusProxy -> DBusProxy
DBusProxy) Ptr DBusProxy
result
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
connection
        Maybe DBusInterfaceInfo -> (DBusInterfaceInfo -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe DBusInterfaceInfo
info DBusInterfaceInfo -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeName
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
objectPath'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
interfaceName'
        DBusProxy -> IO DBusProxy
forall (m :: * -> *) a. Monad m => a -> m a
return DBusProxy
result'
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeName
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
objectPath'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
interfaceName'
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method DBusProxy::call
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "proxy"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusProxy" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusProxy." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "method_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Name of method to invoke."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "parameters"
--           , argType = TVariant
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A #GVariant tuple with parameters for the signal or %NULL if not passing parameters."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusCallFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Flags from the #GDBusCallFlags enumeration."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "timeout_msec"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The timeout in milliseconds (with %G_MAXINT meaning\n               \"infinite\") or -1 to use the proxy default timeout."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GCancellable or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "callback"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncReadyCallback" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A #GAsyncReadyCallback to call when the request is satisfied or %NULL if you don't\ncare about the result of the method invocation."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = 7
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The data to pass to @callback."
--                 , 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_proxy_call" g_dbus_proxy_call :: 
    Ptr DBusProxy ->                        -- proxy : TInterface (Name {namespace = "Gio", name = "DBusProxy"})
    CString ->                              -- method_name : TBasicType TUTF8
    Ptr GVariant ->                         -- parameters : TVariant
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gio", name = "DBusCallFlags"})
    Int32 ->                                -- timeout_msec : TBasicType TInt
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    FunPtr Gio.Callbacks.C_AsyncReadyCallback -> -- callback : TInterface (Name {namespace = "Gio", name = "AsyncReadyCallback"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    IO ()

-- | Asynchronously invokes the /@methodName@/ method on /@proxy@/.
-- 
-- If /@methodName@/ contains any dots, then /@name@/ is split into interface and
-- method name parts. This allows using /@proxy@/ for invoking methods on
-- other interfaces.
-- 
-- If the t'GI.Gio.Objects.DBusConnection.DBusConnection' associated with /@proxy@/ is closed then
-- the operation will fail with 'GI.Gio.Enums.IOErrorEnumClosed'. If
-- /@cancellable@/ is canceled, the operation will fail with
-- 'GI.Gio.Enums.IOErrorEnumCancelled'. If /@parameters@/ contains a value not
-- compatible with the D-Bus protocol, the operation fails with
-- 'GI.Gio.Enums.IOErrorEnumInvalidArgument'.
-- 
-- If the /@parameters@/ t'GVariant' is floating, it is consumed. This allows
-- convenient \'inline\' use of @/g_variant_new()/@, e.g.:
-- 
-- === /C code/
-- >
-- > g_dbus_proxy_call (proxy,
-- >                    "TwoStrings",
-- >                    g_variant_new ("(ss)",
-- >                                   "Thing One",
-- >                                   "Thing Two"),
-- >                    G_DBUS_CALL_FLAGS_NONE,
-- >                    -1,
-- >                    NULL,
-- >                    (GAsyncReadyCallback) two_strings_done,
-- >                    &data);
-- 
-- 
-- If /@proxy@/ has an expected interface (see
-- t'GI.Gio.Objects.DBusProxy.DBusProxy':@/g-interface-info/@) and /@methodName@/ is referenced by it,
-- then the return value is checked against the return type.
-- 
-- This is an asynchronous method. When the operation is finished,
-- /@callback@/ will be invoked in the
-- [thread-default main context][g-main-context-push-thread-default]
-- of the thread you are calling this method from.
-- You can then call 'GI.Gio.Objects.DBusProxy.dBusProxyCallFinish' to get the result of
-- the operation. See 'GI.Gio.Objects.DBusProxy.dBusProxyCallSync' for the synchronous
-- version of this method.
-- 
-- If /@callback@/ is 'P.Nothing' then the D-Bus method call message will be sent with
-- the 'GI.Gio.Flags.DBusMessageFlagsNoReplyExpected' flag set.
-- 
-- /Since: 2.26/
dBusProxyCall ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusProxy a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@proxy@/: A t'GI.Gio.Objects.DBusProxy.DBusProxy'.
    -> T.Text
    -- ^ /@methodName@/: Name of method to invoke.
    -> Maybe (GVariant)
    -- ^ /@parameters@/: A t'GVariant' tuple with parameters for the signal or 'P.Nothing' if not passing parameters.
    -> [Gio.Flags.DBusCallFlags]
    -- ^ /@flags@/: Flags from the t'GI.Gio.Flags.DBusCallFlags' enumeration.
    -> Int32
    -- ^ /@timeoutMsec@/: The timeout in milliseconds (with @/G_MAXINT/@ meaning
    --                \"infinite\") or -1 to use the proxy default timeout.
    -> Maybe (b)
    -- ^ /@cancellable@/: A t'GI.Gio.Objects.Cancellable.Cancellable' or 'P.Nothing'.
    -> Maybe (Gio.Callbacks.AsyncReadyCallback)
    -- ^ /@callback@/: A t'GI.Gio.Callbacks.AsyncReadyCallback' to call when the request is satisfied or 'P.Nothing' if you don\'t
    -- care about the result of the method invocation.
    -> m ()
dBusProxyCall :: a
-> Text
-> Maybe GVariant
-> [DBusCallFlags]
-> Int32
-> Maybe b
-> Maybe AsyncReadyCallback
-> m ()
dBusProxyCall proxy :: a
proxy methodName :: Text
methodName parameters :: Maybe GVariant
parameters flags :: [DBusCallFlags]
flags timeoutMsec :: Int32
timeoutMsec cancellable :: Maybe b
cancellable callback :: Maybe AsyncReadyCallback
callback = 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 DBusProxy
proxy' <- a -> IO (Ptr DBusProxy)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
proxy
    CString
methodName' <- Text -> IO CString
textToCString Text
methodName
    Ptr GVariant
maybeParameters <- case Maybe GVariant
parameters of
        Nothing -> Ptr GVariant -> IO (Ptr GVariant)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GVariant
forall a. Ptr a
nullPtr
        Just jParameters :: GVariant
jParameters -> do
            Ptr GVariant
jParameters' <- GVariant -> IO (Ptr GVariant)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GVariant
jParameters
            Ptr GVariant -> IO (Ptr GVariant)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GVariant
jParameters'
    let flags' :: CUInt
flags' = [DBusCallFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [DBusCallFlags]
flags
    Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
        Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just jCancellable :: b
jCancellable -> do
            Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    FunPtr C_AsyncReadyCallback
maybeCallback <- case Maybe AsyncReadyCallback
callback of
        Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_AsyncReadyCallback
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
        Just jCallback :: AsyncReadyCallback
jCallback -> do
            Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
            FunPtr C_AsyncReadyCallback
jCallback' <- C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
Gio.Callbacks.mk_AsyncReadyCallback (Maybe (Ptr (FunPtr C_AsyncReadyCallback))
-> AsyncReadyCallback_WithClosures -> C_AsyncReadyCallback
Gio.Callbacks.wrap_AsyncReadyCallback (Ptr (FunPtr C_AsyncReadyCallback)
-> Maybe (Ptr (FunPtr C_AsyncReadyCallback))
forall a. a -> Maybe a
Just Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback) (AsyncReadyCallback -> AsyncReadyCallback_WithClosures
Gio.Callbacks.drop_closures_AsyncReadyCallback AsyncReadyCallback
jCallback))
            Ptr (FunPtr C_AsyncReadyCallback)
-> FunPtr C_AsyncReadyCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback FunPtr C_AsyncReadyCallback
jCallback'
            FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
jCallback'
    let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
    Ptr DBusProxy
-> CString
-> Ptr GVariant
-> CUInt
-> Int32
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> IO ()
g_dbus_proxy_call Ptr DBusProxy
proxy' CString
methodName' Ptr GVariant
maybeParameters CUInt
flags' Int32
timeoutMsec Ptr Cancellable
maybeCancellable FunPtr C_AsyncReadyCallback
maybeCallback Ptr ()
forall a. Ptr a
userData
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
proxy
    Maybe GVariant -> (GVariant -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe GVariant
parameters GVariant -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
methodName'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DBusProxyCallMethodInfo
instance (signature ~ (T.Text -> Maybe (GVariant) -> [Gio.Flags.DBusCallFlags] -> Int32 -> Maybe (b) -> Maybe (Gio.Callbacks.AsyncReadyCallback) -> m ()), MonadIO m, IsDBusProxy a, Gio.Cancellable.IsCancellable b) => O.MethodInfo DBusProxyCallMethodInfo a signature where
    overloadedMethod = dBusProxyCall

#endif

-- method DBusProxy::call_finish
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "proxy"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusProxy" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusProxy." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "res"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncResult" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A #GAsyncResult obtained from the #GAsyncReadyCallback passed to g_dbus_proxy_call()."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just TVariant
-- throws : True
-- Skip return : False

foreign import ccall "g_dbus_proxy_call_finish" g_dbus_proxy_call_finish :: 
    Ptr DBusProxy ->                        -- proxy : TInterface (Name {namespace = "Gio", name = "DBusProxy"})
    Ptr Gio.AsyncResult.AsyncResult ->      -- res : TInterface (Name {namespace = "Gio", name = "AsyncResult"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr GVariant)

-- | Finishes an operation started with 'GI.Gio.Objects.DBusProxy.dBusProxyCall'.
-- 
-- /Since: 2.26/
dBusProxyCallFinish ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusProxy a, Gio.AsyncResult.IsAsyncResult b) =>
    a
    -- ^ /@proxy@/: A t'GI.Gio.Objects.DBusProxy.DBusProxy'.
    -> b
    -- ^ /@res@/: A t'GI.Gio.Interfaces.AsyncResult.AsyncResult' obtained from the t'GI.Gio.Callbacks.AsyncReadyCallback' passed to 'GI.Gio.Objects.DBusProxy.dBusProxyCall'.
    -> m GVariant
    -- ^ __Returns:__ 'P.Nothing' if /@error@/ is set. Otherwise a t'GVariant' tuple with
    -- return values. Free with 'GI.GLib.Structs.Variant.variantUnref'. /(Can throw 'Data.GI.Base.GError.GError')/
dBusProxyCallFinish :: a -> b -> m GVariant
dBusProxyCallFinish proxy :: a
proxy res :: b
res = IO GVariant -> m GVariant
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GVariant -> m GVariant) -> IO GVariant -> m GVariant
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusProxy
proxy' <- a -> IO (Ptr DBusProxy)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
proxy
    Ptr AsyncResult
res' <- b -> IO (Ptr AsyncResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
res
    IO GVariant -> IO () -> IO GVariant
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr GVariant
result <- (Ptr (Ptr GError) -> IO (Ptr GVariant)) -> IO (Ptr GVariant)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr GVariant)) -> IO (Ptr GVariant))
-> (Ptr (Ptr GError) -> IO (Ptr GVariant)) -> IO (Ptr GVariant)
forall a b. (a -> b) -> a -> b
$ Ptr DBusProxy
-> Ptr AsyncResult -> Ptr (Ptr GError) -> IO (Ptr GVariant)
g_dbus_proxy_call_finish Ptr DBusProxy
proxy' Ptr AsyncResult
res'
        Text -> Ptr GVariant -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusProxyCallFinish" Ptr GVariant
result
        GVariant
result' <- Ptr GVariant -> IO GVariant
B.GVariant.wrapGVariantPtr Ptr GVariant
result
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
proxy
        b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
res
        GVariant -> IO GVariant
forall (m :: * -> *) a. Monad m => a -> m a
return GVariant
result'
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data DBusProxyCallFinishMethodInfo
instance (signature ~ (b -> m GVariant), MonadIO m, IsDBusProxy a, Gio.AsyncResult.IsAsyncResult b) => O.MethodInfo DBusProxyCallFinishMethodInfo a signature where
    overloadedMethod = dBusProxyCallFinish

#endif

-- method DBusProxy::call_sync
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "proxy"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusProxy" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusProxy." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "method_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Name of method to invoke."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "parameters"
--           , argType = TVariant
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A #GVariant tuple with parameters for the signal\n             or %NULL if not passing parameters."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusCallFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Flags from the #GDBusCallFlags enumeration."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "timeout_msec"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The timeout in milliseconds (with %G_MAXINT meaning\n               \"infinite\") or -1 to use the proxy default timeout."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GCancellable or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just TVariant
-- throws : True
-- Skip return : False

foreign import ccall "g_dbus_proxy_call_sync" g_dbus_proxy_call_sync :: 
    Ptr DBusProxy ->                        -- proxy : TInterface (Name {namespace = "Gio", name = "DBusProxy"})
    CString ->                              -- method_name : TBasicType TUTF8
    Ptr GVariant ->                         -- parameters : TVariant
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gio", name = "DBusCallFlags"})
    Int32 ->                                -- timeout_msec : TBasicType TInt
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr GVariant)

-- | Synchronously invokes the /@methodName@/ method on /@proxy@/.
-- 
-- If /@methodName@/ contains any dots, then /@name@/ is split into interface and
-- method name parts. This allows using /@proxy@/ for invoking methods on
-- other interfaces.
-- 
-- If the t'GI.Gio.Objects.DBusConnection.DBusConnection' associated with /@proxy@/ is disconnected then
-- the operation will fail with 'GI.Gio.Enums.IOErrorEnumClosed'. If
-- /@cancellable@/ is canceled, the operation will fail with
-- 'GI.Gio.Enums.IOErrorEnumCancelled'. If /@parameters@/ contains a value not
-- compatible with the D-Bus protocol, the operation fails with
-- 'GI.Gio.Enums.IOErrorEnumInvalidArgument'.
-- 
-- If the /@parameters@/ t'GVariant' is floating, it is consumed. This allows
-- convenient \'inline\' use of @/g_variant_new()/@, e.g.:
-- 
-- === /C code/
-- >
-- > g_dbus_proxy_call_sync (proxy,
-- >                         "TwoStrings",
-- >                         g_variant_new ("(ss)",
-- >                                        "Thing One",
-- >                                        "Thing Two"),
-- >                         G_DBUS_CALL_FLAGS_NONE,
-- >                         -1,
-- >                         NULL,
-- >                         &error);
-- 
-- 
-- The calling thread is blocked until a reply is received. See
-- 'GI.Gio.Objects.DBusProxy.dBusProxyCall' for the asynchronous version of this
-- method.
-- 
-- If /@proxy@/ has an expected interface (see
-- t'GI.Gio.Objects.DBusProxy.DBusProxy':@/g-interface-info/@) and /@methodName@/ is referenced by it,
-- then the return value is checked against the return type.
-- 
-- /Since: 2.26/
dBusProxyCallSync ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusProxy a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@proxy@/: A t'GI.Gio.Objects.DBusProxy.DBusProxy'.
    -> T.Text
    -- ^ /@methodName@/: Name of method to invoke.
    -> Maybe (GVariant)
    -- ^ /@parameters@/: A t'GVariant' tuple with parameters for the signal
    --              or 'P.Nothing' if not passing parameters.
    -> [Gio.Flags.DBusCallFlags]
    -- ^ /@flags@/: Flags from the t'GI.Gio.Flags.DBusCallFlags' enumeration.
    -> Int32
    -- ^ /@timeoutMsec@/: The timeout in milliseconds (with @/G_MAXINT/@ meaning
    --                \"infinite\") or -1 to use the proxy default timeout.
    -> Maybe (b)
    -- ^ /@cancellable@/: A t'GI.Gio.Objects.Cancellable.Cancellable' or 'P.Nothing'.
    -> m GVariant
    -- ^ __Returns:__ 'P.Nothing' if /@error@/ is set. Otherwise a t'GVariant' tuple with
    -- return values. Free with 'GI.GLib.Structs.Variant.variantUnref'. /(Can throw 'Data.GI.Base.GError.GError')/
dBusProxyCallSync :: a
-> Text
-> Maybe GVariant
-> [DBusCallFlags]
-> Int32
-> Maybe b
-> m GVariant
dBusProxyCallSync proxy :: a
proxy methodName :: Text
methodName parameters :: Maybe GVariant
parameters flags :: [DBusCallFlags]
flags timeoutMsec :: Int32
timeoutMsec cancellable :: Maybe b
cancellable = IO GVariant -> m GVariant
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GVariant -> m GVariant) -> IO GVariant -> m GVariant
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusProxy
proxy' <- a -> IO (Ptr DBusProxy)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
proxy
    CString
methodName' <- Text -> IO CString
textToCString Text
methodName
    Ptr GVariant
maybeParameters <- case Maybe GVariant
parameters of
        Nothing -> Ptr GVariant -> IO (Ptr GVariant)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GVariant
forall a. Ptr a
nullPtr
        Just jParameters :: GVariant
jParameters -> do
            Ptr GVariant
jParameters' <- GVariant -> IO (Ptr GVariant)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GVariant
jParameters
            Ptr GVariant -> IO (Ptr GVariant)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GVariant
jParameters'
    let flags' :: CUInt
flags' = [DBusCallFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [DBusCallFlags]
flags
    Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
        Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just jCancellable :: b
jCancellable -> do
            Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    IO GVariant -> IO () -> IO GVariant
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr GVariant
result <- (Ptr (Ptr GError) -> IO (Ptr GVariant)) -> IO (Ptr GVariant)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr GVariant)) -> IO (Ptr GVariant))
-> (Ptr (Ptr GError) -> IO (Ptr GVariant)) -> IO (Ptr GVariant)
forall a b. (a -> b) -> a -> b
$ Ptr DBusProxy
-> CString
-> Ptr GVariant
-> CUInt
-> Int32
-> Ptr Cancellable
-> Ptr (Ptr GError)
-> IO (Ptr GVariant)
g_dbus_proxy_call_sync Ptr DBusProxy
proxy' CString
methodName' Ptr GVariant
maybeParameters CUInt
flags' Int32
timeoutMsec Ptr Cancellable
maybeCancellable
        Text -> Ptr GVariant -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusProxyCallSync" Ptr GVariant
result
        GVariant
result' <- Ptr GVariant -> IO GVariant
B.GVariant.wrapGVariantPtr Ptr GVariant
result
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
proxy
        Maybe GVariant -> (GVariant -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe GVariant
parameters GVariant -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
methodName'
        GVariant -> IO GVariant
forall (m :: * -> *) a. Monad m => a -> m a
return GVariant
result'
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
methodName'
     )

#if defined(ENABLE_OVERLOADING)
data DBusProxyCallSyncMethodInfo
instance (signature ~ (T.Text -> Maybe (GVariant) -> [Gio.Flags.DBusCallFlags] -> Int32 -> Maybe (b) -> m GVariant), MonadIO m, IsDBusProxy a, Gio.Cancellable.IsCancellable b) => O.MethodInfo DBusProxyCallSyncMethodInfo a signature where
    overloadedMethod = dBusProxyCallSync

#endif

-- method DBusProxy::call_with_unix_fd_list
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "proxy"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusProxy" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusProxy." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "method_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Name of method to invoke."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "parameters"
--           , argType = TVariant
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A #GVariant tuple with parameters for the signal or %NULL if not passing parameters."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusCallFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Flags from the #GDBusCallFlags enumeration."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "timeout_msec"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The timeout in milliseconds (with %G_MAXINT meaning\n               \"infinite\") or -1 to use the proxy default timeout."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "fd_list"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "UnixFDList" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GUnixFDList or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GCancellable or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "callback"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncReadyCallback" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A #GAsyncReadyCallback to call when the request is satisfied or %NULL if you don't\ncare about the result of the method invocation."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = 8
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The data to pass to @callback."
--                 , 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_proxy_call_with_unix_fd_list" g_dbus_proxy_call_with_unix_fd_list :: 
    Ptr DBusProxy ->                        -- proxy : TInterface (Name {namespace = "Gio", name = "DBusProxy"})
    CString ->                              -- method_name : TBasicType TUTF8
    Ptr GVariant ->                         -- parameters : TVariant
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gio", name = "DBusCallFlags"})
    Int32 ->                                -- timeout_msec : TBasicType TInt
    Ptr Gio.UnixFDList.UnixFDList ->        -- fd_list : TInterface (Name {namespace = "Gio", name = "UnixFDList"})
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    FunPtr Gio.Callbacks.C_AsyncReadyCallback -> -- callback : TInterface (Name {namespace = "Gio", name = "AsyncReadyCallback"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    IO ()

-- | Like 'GI.Gio.Objects.DBusProxy.dBusProxyCall' but also takes a t'GI.Gio.Objects.UnixFDList.UnixFDList' object.
-- 
-- This method is only available on UNIX.
-- 
-- /Since: 2.30/
dBusProxyCallWithUnixFdList ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusProxy a, Gio.UnixFDList.IsUnixFDList b, Gio.Cancellable.IsCancellable c) =>
    a
    -- ^ /@proxy@/: A t'GI.Gio.Objects.DBusProxy.DBusProxy'.
    -> T.Text
    -- ^ /@methodName@/: Name of method to invoke.
    -> Maybe (GVariant)
    -- ^ /@parameters@/: A t'GVariant' tuple with parameters for the signal or 'P.Nothing' if not passing parameters.
    -> [Gio.Flags.DBusCallFlags]
    -- ^ /@flags@/: Flags from the t'GI.Gio.Flags.DBusCallFlags' enumeration.
    -> Int32
    -- ^ /@timeoutMsec@/: The timeout in milliseconds (with @/G_MAXINT/@ meaning
    --                \"infinite\") or -1 to use the proxy default timeout.
    -> Maybe (b)
    -- ^ /@fdList@/: A t'GI.Gio.Objects.UnixFDList.UnixFDList' or 'P.Nothing'.
    -> Maybe (c)
    -- ^ /@cancellable@/: A t'GI.Gio.Objects.Cancellable.Cancellable' or 'P.Nothing'.
    -> Maybe (Gio.Callbacks.AsyncReadyCallback)
    -- ^ /@callback@/: A t'GI.Gio.Callbacks.AsyncReadyCallback' to call when the request is satisfied or 'P.Nothing' if you don\'t
    -- care about the result of the method invocation.
    -> m ()
dBusProxyCallWithUnixFdList :: a
-> Text
-> Maybe GVariant
-> [DBusCallFlags]
-> Int32
-> Maybe b
-> Maybe c
-> Maybe AsyncReadyCallback
-> m ()
dBusProxyCallWithUnixFdList proxy :: a
proxy methodName :: Text
methodName parameters :: Maybe GVariant
parameters flags :: [DBusCallFlags]
flags timeoutMsec :: Int32
timeoutMsec fdList :: Maybe b
fdList cancellable :: Maybe c
cancellable callback :: Maybe AsyncReadyCallback
callback = 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 DBusProxy
proxy' <- a -> IO (Ptr DBusProxy)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
proxy
    CString
methodName' <- Text -> IO CString
textToCString Text
methodName
    Ptr GVariant
maybeParameters <- case Maybe GVariant
parameters of
        Nothing -> Ptr GVariant -> IO (Ptr GVariant)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GVariant
forall a. Ptr a
nullPtr
        Just jParameters :: GVariant
jParameters -> do
            Ptr GVariant
jParameters' <- GVariant -> IO (Ptr GVariant)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GVariant
jParameters
            Ptr GVariant -> IO (Ptr GVariant)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GVariant
jParameters'
    let flags' :: CUInt
flags' = [DBusCallFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [DBusCallFlags]
flags
    Ptr UnixFDList
maybeFdList <- case Maybe b
fdList of
        Nothing -> Ptr UnixFDList -> IO (Ptr UnixFDList)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr UnixFDList
forall a. Ptr a
nullPtr
        Just jFdList :: b
jFdList -> do
            Ptr UnixFDList
jFdList' <- b -> IO (Ptr UnixFDList)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jFdList
            Ptr UnixFDList -> IO (Ptr UnixFDList)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr UnixFDList
jFdList'
    Ptr Cancellable
maybeCancellable <- case Maybe c
cancellable of
        Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just jCancellable :: c
jCancellable -> do
            Ptr Cancellable
jCancellable' <- c -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    FunPtr C_AsyncReadyCallback
maybeCallback <- case Maybe AsyncReadyCallback
callback of
        Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_AsyncReadyCallback
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
        Just jCallback :: AsyncReadyCallback
jCallback -> do
            Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
            FunPtr C_AsyncReadyCallback
jCallback' <- C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
Gio.Callbacks.mk_AsyncReadyCallback (Maybe (Ptr (FunPtr C_AsyncReadyCallback))
-> AsyncReadyCallback_WithClosures -> C_AsyncReadyCallback
Gio.Callbacks.wrap_AsyncReadyCallback (Ptr (FunPtr C_AsyncReadyCallback)
-> Maybe (Ptr (FunPtr C_AsyncReadyCallback))
forall a. a -> Maybe a
Just Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback) (AsyncReadyCallback -> AsyncReadyCallback_WithClosures
Gio.Callbacks.drop_closures_AsyncReadyCallback AsyncReadyCallback
jCallback))
            Ptr (FunPtr C_AsyncReadyCallback)
-> FunPtr C_AsyncReadyCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback FunPtr C_AsyncReadyCallback
jCallback'
            FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
jCallback'
    let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
    Ptr DBusProxy
-> CString
-> Ptr GVariant
-> CUInt
-> Int32
-> Ptr UnixFDList
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> IO ()
g_dbus_proxy_call_with_unix_fd_list Ptr DBusProxy
proxy' CString
methodName' Ptr GVariant
maybeParameters CUInt
flags' Int32
timeoutMsec Ptr UnixFDList
maybeFdList Ptr Cancellable
maybeCancellable FunPtr C_AsyncReadyCallback
maybeCallback Ptr ()
forall a. Ptr a
userData
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
proxy
    Maybe GVariant -> (GVariant -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe GVariant
parameters GVariant -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
fdList b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Maybe c -> (c -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe c
cancellable c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
methodName'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DBusProxyCallWithUnixFdListMethodInfo
instance (signature ~ (T.Text -> Maybe (GVariant) -> [Gio.Flags.DBusCallFlags] -> Int32 -> Maybe (b) -> Maybe (c) -> Maybe (Gio.Callbacks.AsyncReadyCallback) -> m ()), MonadIO m, IsDBusProxy a, Gio.UnixFDList.IsUnixFDList b, Gio.Cancellable.IsCancellable c) => O.MethodInfo DBusProxyCallWithUnixFdListMethodInfo a signature where
    overloadedMethod = dBusProxyCallWithUnixFdList

#endif

-- method DBusProxy::call_with_unix_fd_list_finish
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "proxy"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusProxy" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusProxy." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "out_fd_list"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "UnixFDList" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Return location for a #GUnixFDList or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "res"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncResult" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A #GAsyncResult obtained from the #GAsyncReadyCallback passed to g_dbus_proxy_call_with_unix_fd_list()."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just TVariant
-- throws : True
-- Skip return : False

foreign import ccall "g_dbus_proxy_call_with_unix_fd_list_finish" g_dbus_proxy_call_with_unix_fd_list_finish :: 
    Ptr DBusProxy ->                        -- proxy : TInterface (Name {namespace = "Gio", name = "DBusProxy"})
    Ptr (Ptr Gio.UnixFDList.UnixFDList) ->  -- out_fd_list : TInterface (Name {namespace = "Gio", name = "UnixFDList"})
    Ptr Gio.AsyncResult.AsyncResult ->      -- res : TInterface (Name {namespace = "Gio", name = "AsyncResult"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr GVariant)

-- | Finishes an operation started with 'GI.Gio.Objects.DBusProxy.dBusProxyCallWithUnixFdList'.
-- 
-- /Since: 2.30/
dBusProxyCallWithUnixFdListFinish ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusProxy a, Gio.AsyncResult.IsAsyncResult b) =>
    a
    -- ^ /@proxy@/: A t'GI.Gio.Objects.DBusProxy.DBusProxy'.
    -> b
    -- ^ /@res@/: A t'GI.Gio.Interfaces.AsyncResult.AsyncResult' obtained from the t'GI.Gio.Callbacks.AsyncReadyCallback' passed to 'GI.Gio.Objects.DBusProxy.dBusProxyCallWithUnixFdList'.
    -> m ((GVariant, Gio.UnixFDList.UnixFDList))
    -- ^ __Returns:__ 'P.Nothing' if /@error@/ is set. Otherwise a t'GVariant' tuple with
    -- return values. Free with 'GI.GLib.Structs.Variant.variantUnref'. /(Can throw 'Data.GI.Base.GError.GError')/
dBusProxyCallWithUnixFdListFinish :: a -> b -> m (GVariant, UnixFDList)
dBusProxyCallWithUnixFdListFinish proxy :: a
proxy res :: b
res = IO (GVariant, UnixFDList) -> m (GVariant, UnixFDList)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GVariant, UnixFDList) -> m (GVariant, UnixFDList))
-> IO (GVariant, UnixFDList) -> m (GVariant, UnixFDList)
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusProxy
proxy' <- a -> IO (Ptr DBusProxy)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
proxy
    Ptr (Ptr UnixFDList)
outFdList <- IO (Ptr (Ptr UnixFDList))
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr (Ptr Gio.UnixFDList.UnixFDList))
    Ptr AsyncResult
res' <- b -> IO (Ptr AsyncResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
res
    IO (GVariant, UnixFDList) -> IO () -> IO (GVariant, UnixFDList)
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr GVariant
result <- (Ptr (Ptr GError) -> IO (Ptr GVariant)) -> IO (Ptr GVariant)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr GVariant)) -> IO (Ptr GVariant))
-> (Ptr (Ptr GError) -> IO (Ptr GVariant)) -> IO (Ptr GVariant)
forall a b. (a -> b) -> a -> b
$ Ptr DBusProxy
-> Ptr (Ptr UnixFDList)
-> Ptr AsyncResult
-> Ptr (Ptr GError)
-> IO (Ptr GVariant)
g_dbus_proxy_call_with_unix_fd_list_finish Ptr DBusProxy
proxy' Ptr (Ptr UnixFDList)
outFdList Ptr AsyncResult
res'
        Text -> Ptr GVariant -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusProxyCallWithUnixFdListFinish" Ptr GVariant
result
        GVariant
result' <- Ptr GVariant -> IO GVariant
B.GVariant.wrapGVariantPtr Ptr GVariant
result
        Ptr UnixFDList
outFdList' <- Ptr (Ptr UnixFDList) -> IO (Ptr UnixFDList)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr UnixFDList)
outFdList
        UnixFDList
outFdList'' <- ((ManagedPtr UnixFDList -> UnixFDList)
-> Ptr UnixFDList -> IO UnixFDList
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr UnixFDList -> UnixFDList
Gio.UnixFDList.UnixFDList) Ptr UnixFDList
outFdList'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
proxy
        b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
res
        Ptr (Ptr UnixFDList) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr UnixFDList)
outFdList
        (GVariant, UnixFDList) -> IO (GVariant, UnixFDList)
forall (m :: * -> *) a. Monad m => a -> m a
return (GVariant
result', UnixFDList
outFdList'')
     ) (do
        Ptr (Ptr UnixFDList) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr UnixFDList)
outFdList
     )

#if defined(ENABLE_OVERLOADING)
data DBusProxyCallWithUnixFdListFinishMethodInfo
instance (signature ~ (b -> m ((GVariant, Gio.UnixFDList.UnixFDList))), MonadIO m, IsDBusProxy a, Gio.AsyncResult.IsAsyncResult b) => O.MethodInfo DBusProxyCallWithUnixFdListFinishMethodInfo a signature where
    overloadedMethod = dBusProxyCallWithUnixFdListFinish

#endif

-- method DBusProxy::call_with_unix_fd_list_sync
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "proxy"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusProxy" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusProxy." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "method_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Name of method to invoke."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "parameters"
--           , argType = TVariant
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A #GVariant tuple with parameters for the signal\n             or %NULL if not passing parameters."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusCallFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Flags from the #GDBusCallFlags enumeration."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "timeout_msec"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The timeout in milliseconds (with %G_MAXINT meaning\n               \"infinite\") or -1 to use the proxy default timeout."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "fd_list"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "UnixFDList" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GUnixFDList or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "out_fd_list"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "UnixFDList" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Return location for a #GUnixFDList or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GCancellable or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just TVariant
-- throws : True
-- Skip return : False

foreign import ccall "g_dbus_proxy_call_with_unix_fd_list_sync" g_dbus_proxy_call_with_unix_fd_list_sync :: 
    Ptr DBusProxy ->                        -- proxy : TInterface (Name {namespace = "Gio", name = "DBusProxy"})
    CString ->                              -- method_name : TBasicType TUTF8
    Ptr GVariant ->                         -- parameters : TVariant
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gio", name = "DBusCallFlags"})
    Int32 ->                                -- timeout_msec : TBasicType TInt
    Ptr Gio.UnixFDList.UnixFDList ->        -- fd_list : TInterface (Name {namespace = "Gio", name = "UnixFDList"})
    Ptr (Ptr Gio.UnixFDList.UnixFDList) ->  -- out_fd_list : TInterface (Name {namespace = "Gio", name = "UnixFDList"})
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr GVariant)

-- | Like 'GI.Gio.Objects.DBusProxy.dBusProxyCallSync' but also takes and returns t'GI.Gio.Objects.UnixFDList.UnixFDList' objects.
-- 
-- This method is only available on UNIX.
-- 
-- /Since: 2.30/
dBusProxyCallWithUnixFdListSync ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusProxy a, Gio.UnixFDList.IsUnixFDList b, Gio.Cancellable.IsCancellable c) =>
    a
    -- ^ /@proxy@/: A t'GI.Gio.Objects.DBusProxy.DBusProxy'.
    -> T.Text
    -- ^ /@methodName@/: Name of method to invoke.
    -> Maybe (GVariant)
    -- ^ /@parameters@/: A t'GVariant' tuple with parameters for the signal
    --              or 'P.Nothing' if not passing parameters.
    -> [Gio.Flags.DBusCallFlags]
    -- ^ /@flags@/: Flags from the t'GI.Gio.Flags.DBusCallFlags' enumeration.
    -> Int32
    -- ^ /@timeoutMsec@/: The timeout in milliseconds (with @/G_MAXINT/@ meaning
    --                \"infinite\") or -1 to use the proxy default timeout.
    -> Maybe (b)
    -- ^ /@fdList@/: A t'GI.Gio.Objects.UnixFDList.UnixFDList' or 'P.Nothing'.
    -> Maybe (c)
    -- ^ /@cancellable@/: A t'GI.Gio.Objects.Cancellable.Cancellable' or 'P.Nothing'.
    -> m ((GVariant, Gio.UnixFDList.UnixFDList))
    -- ^ __Returns:__ 'P.Nothing' if /@error@/ is set. Otherwise a t'GVariant' tuple with
    -- return values. Free with 'GI.GLib.Structs.Variant.variantUnref'. /(Can throw 'Data.GI.Base.GError.GError')/
dBusProxyCallWithUnixFdListSync :: a
-> Text
-> Maybe GVariant
-> [DBusCallFlags]
-> Int32
-> Maybe b
-> Maybe c
-> m (GVariant, UnixFDList)
dBusProxyCallWithUnixFdListSync proxy :: a
proxy methodName :: Text
methodName parameters :: Maybe GVariant
parameters flags :: [DBusCallFlags]
flags timeoutMsec :: Int32
timeoutMsec fdList :: Maybe b
fdList cancellable :: Maybe c
cancellable = IO (GVariant, UnixFDList) -> m (GVariant, UnixFDList)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GVariant, UnixFDList) -> m (GVariant, UnixFDList))
-> IO (GVariant, UnixFDList) -> m (GVariant, UnixFDList)
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusProxy
proxy' <- a -> IO (Ptr DBusProxy)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
proxy
    CString
methodName' <- Text -> IO CString
textToCString Text
methodName
    Ptr GVariant
maybeParameters <- case Maybe GVariant
parameters of
        Nothing -> Ptr GVariant -> IO (Ptr GVariant)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GVariant
forall a. Ptr a
nullPtr
        Just jParameters :: GVariant
jParameters -> do
            Ptr GVariant
jParameters' <- GVariant -> IO (Ptr GVariant)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GVariant
jParameters
            Ptr GVariant -> IO (Ptr GVariant)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GVariant
jParameters'
    let flags' :: CUInt
flags' = [DBusCallFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [DBusCallFlags]
flags
    Ptr UnixFDList
maybeFdList <- case Maybe b
fdList of
        Nothing -> Ptr UnixFDList -> IO (Ptr UnixFDList)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr UnixFDList
forall a. Ptr a
nullPtr
        Just jFdList :: b
jFdList -> do
            Ptr UnixFDList
jFdList' <- b -> IO (Ptr UnixFDList)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jFdList
            Ptr UnixFDList -> IO (Ptr UnixFDList)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr UnixFDList
jFdList'
    Ptr (Ptr UnixFDList)
outFdList <- IO (Ptr (Ptr UnixFDList))
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr (Ptr Gio.UnixFDList.UnixFDList))
    Ptr Cancellable
maybeCancellable <- case Maybe c
cancellable of
        Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just jCancellable :: c
jCancellable -> do
            Ptr Cancellable
jCancellable' <- c -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    IO (GVariant, UnixFDList) -> IO () -> IO (GVariant, UnixFDList)
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr GVariant
result <- (Ptr (Ptr GError) -> IO (Ptr GVariant)) -> IO (Ptr GVariant)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr GVariant)) -> IO (Ptr GVariant))
-> (Ptr (Ptr GError) -> IO (Ptr GVariant)) -> IO (Ptr GVariant)
forall a b. (a -> b) -> a -> b
$ Ptr DBusProxy
-> CString
-> Ptr GVariant
-> CUInt
-> Int32
-> Ptr UnixFDList
-> Ptr (Ptr UnixFDList)
-> Ptr Cancellable
-> Ptr (Ptr GError)
-> IO (Ptr GVariant)
g_dbus_proxy_call_with_unix_fd_list_sync Ptr DBusProxy
proxy' CString
methodName' Ptr GVariant
maybeParameters CUInt
flags' Int32
timeoutMsec Ptr UnixFDList
maybeFdList Ptr (Ptr UnixFDList)
outFdList Ptr Cancellable
maybeCancellable
        Text -> Ptr GVariant -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusProxyCallWithUnixFdListSync" Ptr GVariant
result
        GVariant
result' <- Ptr GVariant -> IO GVariant
B.GVariant.wrapGVariantPtr Ptr GVariant
result
        Ptr UnixFDList
outFdList' <- Ptr (Ptr UnixFDList) -> IO (Ptr UnixFDList)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr UnixFDList)
outFdList
        UnixFDList
outFdList'' <- ((ManagedPtr UnixFDList -> UnixFDList)
-> Ptr UnixFDList -> IO UnixFDList
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr UnixFDList -> UnixFDList
Gio.UnixFDList.UnixFDList) Ptr UnixFDList
outFdList'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
proxy
        Maybe GVariant -> (GVariant -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe GVariant
parameters GVariant -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
fdList b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        Maybe c -> (c -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe c
cancellable c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
methodName'
        Ptr (Ptr UnixFDList) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr UnixFDList)
outFdList
        (GVariant, UnixFDList) -> IO (GVariant, UnixFDList)
forall (m :: * -> *) a. Monad m => a -> m a
return (GVariant
result', UnixFDList
outFdList'')
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
methodName'
        Ptr (Ptr UnixFDList) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr UnixFDList)
outFdList
     )

#if defined(ENABLE_OVERLOADING)
data DBusProxyCallWithUnixFdListSyncMethodInfo
instance (signature ~ (T.Text -> Maybe (GVariant) -> [Gio.Flags.DBusCallFlags] -> Int32 -> Maybe (b) -> Maybe (c) -> m ((GVariant, Gio.UnixFDList.UnixFDList))), MonadIO m, IsDBusProxy a, Gio.UnixFDList.IsUnixFDList b, Gio.Cancellable.IsCancellable c) => O.MethodInfo DBusProxyCallWithUnixFdListSyncMethodInfo a signature where
    overloadedMethod = dBusProxyCallWithUnixFdListSync

#endif

-- method DBusProxy::get_cached_property
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "proxy"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusProxy" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusProxy." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "property_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Property name." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just TVariant
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_proxy_get_cached_property" g_dbus_proxy_get_cached_property :: 
    Ptr DBusProxy ->                        -- proxy : TInterface (Name {namespace = "Gio", name = "DBusProxy"})
    CString ->                              -- property_name : TBasicType TUTF8
    IO (Ptr GVariant)

-- | Looks up the value for a property from the cache. This call does no
-- blocking IO.
-- 
-- If /@proxy@/ has an expected interface (see
-- t'GI.Gio.Objects.DBusProxy.DBusProxy':@/g-interface-info/@) and /@propertyName@/ is referenced by
-- it, then /@value@/ is checked against the type of the property.
-- 
-- /Since: 2.26/
dBusProxyGetCachedProperty ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusProxy a) =>
    a
    -- ^ /@proxy@/: A t'GI.Gio.Objects.DBusProxy.DBusProxy'.
    -> T.Text
    -- ^ /@propertyName@/: Property name.
    -> m (Maybe GVariant)
    -- ^ __Returns:__ A reference to the t'GVariant' instance
    --    that holds the value for /@propertyName@/ or 'P.Nothing' if the value is not in
    --    the cache. The returned reference must be freed with 'GI.GLib.Structs.Variant.variantUnref'.
dBusProxyGetCachedProperty :: a -> Text -> m (Maybe GVariant)
dBusProxyGetCachedProperty proxy :: a
proxy propertyName :: Text
propertyName = IO (Maybe GVariant) -> m (Maybe GVariant)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe GVariant) -> m (Maybe GVariant))
-> IO (Maybe GVariant) -> m (Maybe GVariant)
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusProxy
proxy' <- a -> IO (Ptr DBusProxy)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
proxy
    CString
propertyName' <- Text -> IO CString
textToCString Text
propertyName
    Ptr GVariant
result <- Ptr DBusProxy -> CString -> IO (Ptr GVariant)
g_dbus_proxy_get_cached_property Ptr DBusProxy
proxy' CString
propertyName'
    Maybe GVariant
maybeResult <- Ptr GVariant
-> (Ptr GVariant -> IO GVariant) -> IO (Maybe GVariant)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr GVariant
result ((Ptr GVariant -> IO GVariant) -> IO (Maybe GVariant))
-> (Ptr GVariant -> IO GVariant) -> IO (Maybe GVariant)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr GVariant
result' -> do
        GVariant
result'' <- Ptr GVariant -> IO GVariant
B.GVariant.wrapGVariantPtr Ptr GVariant
result'
        GVariant -> IO GVariant
forall (m :: * -> *) a. Monad m => a -> m a
return GVariant
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
proxy
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
propertyName'
    Maybe GVariant -> IO (Maybe GVariant)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe GVariant
maybeResult

#if defined(ENABLE_OVERLOADING)
data DBusProxyGetCachedPropertyMethodInfo
instance (signature ~ (T.Text -> m (Maybe GVariant)), MonadIO m, IsDBusProxy a) => O.MethodInfo DBusProxyGetCachedPropertyMethodInfo a signature where
    overloadedMethod = dBusProxyGetCachedProperty

#endif

-- method DBusProxy::get_cached_property_names
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "proxy"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusProxy" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusProxy." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TCArray True (-1) (-1) (TBasicType TUTF8))
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_proxy_get_cached_property_names" g_dbus_proxy_get_cached_property_names :: 
    Ptr DBusProxy ->                        -- proxy : TInterface (Name {namespace = "Gio", name = "DBusProxy"})
    IO (Ptr CString)

-- | Gets the names of all cached properties on /@proxy@/.
-- 
-- /Since: 2.26/
dBusProxyGetCachedPropertyNames ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusProxy a) =>
    a
    -- ^ /@proxy@/: A t'GI.Gio.Objects.DBusProxy.DBusProxy'.
    -> m (Maybe [T.Text])
    -- ^ __Returns:__ A
    --          'P.Nothing'-terminated array of strings or 'P.Nothing' if
    --          /@proxy@/ has no cached properties. Free the returned array with
    --          'GI.GLib.Functions.strfreev'.
dBusProxyGetCachedPropertyNames :: a -> m (Maybe [Text])
dBusProxyGetCachedPropertyNames proxy :: a
proxy = 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
$ do
    Ptr DBusProxy
proxy' <- a -> IO (Ptr DBusProxy)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
proxy
    Ptr CString
result <- Ptr DBusProxy -> IO (Ptr CString)
g_dbus_proxy_get_cached_property_names Ptr DBusProxy
proxy'
    Maybe [Text]
maybeResult <- Ptr CString -> (Ptr CString -> IO [Text]) -> IO (Maybe [Text])
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr CString
result ((Ptr CString -> IO [Text]) -> IO (Maybe [Text]))
-> (Ptr CString -> IO [Text]) -> IO (Maybe [Text])
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr CString
result' -> do
        [Text]
result'' <- HasCallStack => Ptr CString -> IO [Text]
Ptr CString -> IO [Text]
unpackZeroTerminatedUTF8CArray Ptr CString
result'
        (CString -> IO ()) -> Ptr CString -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
result'
        Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
result'
        [Text] -> IO [Text]
forall (m :: * -> *) a. Monad m => a -> m a
return [Text]
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
proxy
    Maybe [Text] -> IO (Maybe [Text])
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe [Text]
maybeResult

#if defined(ENABLE_OVERLOADING)
data DBusProxyGetCachedPropertyNamesMethodInfo
instance (signature ~ (m (Maybe [T.Text])), MonadIO m, IsDBusProxy a) => O.MethodInfo DBusProxyGetCachedPropertyNamesMethodInfo a signature where
    overloadedMethod = dBusProxyGetCachedPropertyNames

#endif

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

foreign import ccall "g_dbus_proxy_get_connection" g_dbus_proxy_get_connection :: 
    Ptr DBusProxy ->                        -- proxy : TInterface (Name {namespace = "Gio", name = "DBusProxy"})
    IO (Ptr Gio.DBusConnection.DBusConnection)

-- | Gets the connection /@proxy@/ is for.
-- 
-- /Since: 2.26/
dBusProxyGetConnection ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusProxy a) =>
    a
    -- ^ /@proxy@/: A t'GI.Gio.Objects.DBusProxy.DBusProxy'.
    -> m Gio.DBusConnection.DBusConnection
    -- ^ __Returns:__ A t'GI.Gio.Objects.DBusConnection.DBusConnection' owned by /@proxy@/. Do not free.
dBusProxyGetConnection :: a -> m DBusConnection
dBusProxyGetConnection proxy :: a
proxy = IO DBusConnection -> m DBusConnection
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DBusConnection -> m DBusConnection)
-> IO DBusConnection -> m DBusConnection
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusProxy
proxy' <- a -> IO (Ptr DBusProxy)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
proxy
    Ptr DBusConnection
result <- Ptr DBusProxy -> IO (Ptr DBusConnection)
g_dbus_proxy_get_connection Ptr DBusProxy
proxy'
    Text -> Ptr DBusConnection -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusProxyGetConnection" Ptr DBusConnection
result
    DBusConnection
result' <- ((ManagedPtr DBusConnection -> DBusConnection)
-> Ptr DBusConnection -> IO DBusConnection
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr DBusConnection -> DBusConnection
Gio.DBusConnection.DBusConnection) Ptr DBusConnection
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
proxy
    DBusConnection -> IO DBusConnection
forall (m :: * -> *) a. Monad m => a -> m a
return DBusConnection
result'

#if defined(ENABLE_OVERLOADING)
data DBusProxyGetConnectionMethodInfo
instance (signature ~ (m Gio.DBusConnection.DBusConnection), MonadIO m, IsDBusProxy a) => O.MethodInfo DBusProxyGetConnectionMethodInfo a signature where
    overloadedMethod = dBusProxyGetConnection

#endif

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

foreign import ccall "g_dbus_proxy_get_default_timeout" g_dbus_proxy_get_default_timeout :: 
    Ptr DBusProxy ->                        -- proxy : TInterface (Name {namespace = "Gio", name = "DBusProxy"})
    IO Int32

-- | Gets the timeout to use if -1 (specifying default timeout) is
-- passed as /@timeoutMsec@/ in the 'GI.Gio.Objects.DBusProxy.dBusProxyCall' and
-- 'GI.Gio.Objects.DBusProxy.dBusProxyCallSync' functions.
-- 
-- See the t'GI.Gio.Objects.DBusProxy.DBusProxy':@/g-default-timeout/@ property for more details.
-- 
-- /Since: 2.26/
dBusProxyGetDefaultTimeout ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusProxy a) =>
    a
    -- ^ /@proxy@/: A t'GI.Gio.Objects.DBusProxy.DBusProxy'.
    -> m Int32
    -- ^ __Returns:__ Timeout to use for /@proxy@/.
dBusProxyGetDefaultTimeout :: a -> m Int32
dBusProxyGetDefaultTimeout proxy :: a
proxy = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusProxy
proxy' <- a -> IO (Ptr DBusProxy)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
proxy
    Int32
result <- Ptr DBusProxy -> IO Int32
g_dbus_proxy_get_default_timeout Ptr DBusProxy
proxy'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
proxy
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data DBusProxyGetDefaultTimeoutMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsDBusProxy a) => O.MethodInfo DBusProxyGetDefaultTimeoutMethodInfo a signature where
    overloadedMethod = dBusProxyGetDefaultTimeout

#endif

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

foreign import ccall "g_dbus_proxy_get_flags" g_dbus_proxy_get_flags :: 
    Ptr DBusProxy ->                        -- proxy : TInterface (Name {namespace = "Gio", name = "DBusProxy"})
    IO CUInt

-- | Gets the flags that /@proxy@/ was constructed with.
-- 
-- /Since: 2.26/
dBusProxyGetFlags ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusProxy a) =>
    a
    -- ^ /@proxy@/: A t'GI.Gio.Objects.DBusProxy.DBusProxy'.
    -> m [Gio.Flags.DBusProxyFlags]
    -- ^ __Returns:__ Flags from the t'GI.Gio.Flags.DBusProxyFlags' enumeration.
dBusProxyGetFlags :: a -> m [DBusProxyFlags]
dBusProxyGetFlags proxy :: a
proxy = IO [DBusProxyFlags] -> m [DBusProxyFlags]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [DBusProxyFlags] -> m [DBusProxyFlags])
-> IO [DBusProxyFlags] -> m [DBusProxyFlags]
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusProxy
proxy' <- a -> IO (Ptr DBusProxy)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
proxy
    CUInt
result <- Ptr DBusProxy -> IO CUInt
g_dbus_proxy_get_flags Ptr DBusProxy
proxy'
    let result' :: [DBusProxyFlags]
result' = CUInt -> [DBusProxyFlags]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
proxy
    [DBusProxyFlags] -> IO [DBusProxyFlags]
forall (m :: * -> *) a. Monad m => a -> m a
return [DBusProxyFlags]
result'

#if defined(ENABLE_OVERLOADING)
data DBusProxyGetFlagsMethodInfo
instance (signature ~ (m [Gio.Flags.DBusProxyFlags]), MonadIO m, IsDBusProxy a) => O.MethodInfo DBusProxyGetFlagsMethodInfo a signature where
    overloadedMethod = dBusProxyGetFlags

#endif

-- method DBusProxy::get_interface_info
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "proxy"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusProxy" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusProxy" , 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_proxy_get_interface_info" g_dbus_proxy_get_interface_info :: 
    Ptr DBusProxy ->                        -- proxy : TInterface (Name {namespace = "Gio", name = "DBusProxy"})
    IO (Ptr Gio.DBusInterfaceInfo.DBusInterfaceInfo)

-- | Returns the t'GI.Gio.Structs.DBusInterfaceInfo.DBusInterfaceInfo', if any, specifying the interface
-- that /@proxy@/ conforms to. See the t'GI.Gio.Objects.DBusProxy.DBusProxy':@/g-interface-info/@
-- property for more details.
-- 
-- /Since: 2.26/
dBusProxyGetInterfaceInfo ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusProxy a) =>
    a
    -- ^ /@proxy@/: A t'GI.Gio.Objects.DBusProxy.DBusProxy'
    -> m (Maybe Gio.DBusInterfaceInfo.DBusInterfaceInfo)
    -- ^ __Returns:__ A t'GI.Gio.Structs.DBusInterfaceInfo.DBusInterfaceInfo' or 'P.Nothing'.
    --    Do not unref the returned object, it is owned by /@proxy@/.
dBusProxyGetInterfaceInfo :: a -> m (Maybe DBusInterfaceInfo)
dBusProxyGetInterfaceInfo proxy :: a
proxy = 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
$ do
    Ptr DBusProxy
proxy' <- a -> IO (Ptr DBusProxy)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
proxy
    Ptr DBusInterfaceInfo
result <- Ptr DBusProxy -> IO (Ptr DBusInterfaceInfo)
g_dbus_proxy_get_interface_info Ptr DBusProxy
proxy'
    Maybe DBusInterfaceInfo
maybeResult <- Ptr DBusInterfaceInfo
-> (Ptr DBusInterfaceInfo -> IO DBusInterfaceInfo)
-> IO (Maybe DBusInterfaceInfo)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr DBusInterfaceInfo
result ((Ptr DBusInterfaceInfo -> IO DBusInterfaceInfo)
 -> IO (Maybe DBusInterfaceInfo))
-> (Ptr DBusInterfaceInfo -> IO DBusInterfaceInfo)
-> IO (Maybe DBusInterfaceInfo)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr DBusInterfaceInfo
result' -> do
        DBusInterfaceInfo
result'' <- ((ManagedPtr DBusInterfaceInfo -> DBusInterfaceInfo)
-> Ptr DBusInterfaceInfo -> IO DBusInterfaceInfo
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr DBusInterfaceInfo -> DBusInterfaceInfo
Gio.DBusInterfaceInfo.DBusInterfaceInfo) Ptr DBusInterfaceInfo
result'
        DBusInterfaceInfo -> IO DBusInterfaceInfo
forall (m :: * -> *) a. Monad m => a -> m a
return DBusInterfaceInfo
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
proxy
    Maybe DBusInterfaceInfo -> IO (Maybe DBusInterfaceInfo)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe DBusInterfaceInfo
maybeResult

#if defined(ENABLE_OVERLOADING)
data DBusProxyGetInterfaceInfoMethodInfo
instance (signature ~ (m (Maybe Gio.DBusInterfaceInfo.DBusInterfaceInfo)), MonadIO m, IsDBusProxy a) => O.MethodInfo DBusProxyGetInterfaceInfoMethodInfo a signature where
    overloadedMethod = dBusProxyGetInterfaceInfo

#endif

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

foreign import ccall "g_dbus_proxy_get_interface_name" g_dbus_proxy_get_interface_name :: 
    Ptr DBusProxy ->                        -- proxy : TInterface (Name {namespace = "Gio", name = "DBusProxy"})
    IO CString

-- | Gets the D-Bus interface name /@proxy@/ is for.
-- 
-- /Since: 2.26/
dBusProxyGetInterfaceName ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusProxy a) =>
    a
    -- ^ /@proxy@/: A t'GI.Gio.Objects.DBusProxy.DBusProxy'.
    -> m T.Text
    -- ^ __Returns:__ A string owned by /@proxy@/. Do not free.
dBusProxyGetInterfaceName :: a -> m Text
dBusProxyGetInterfaceName proxy :: a
proxy = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusProxy
proxy' <- a -> IO (Ptr DBusProxy)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
proxy
    CString
result <- Ptr DBusProxy -> IO CString
g_dbus_proxy_get_interface_name Ptr DBusProxy
proxy'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusProxyGetInterfaceName" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
proxy
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data DBusProxyGetInterfaceNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDBusProxy a) => O.MethodInfo DBusProxyGetInterfaceNameMethodInfo a signature where
    overloadedMethod = dBusProxyGetInterfaceName

#endif

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

foreign import ccall "g_dbus_proxy_get_name" g_dbus_proxy_get_name :: 
    Ptr DBusProxy ->                        -- proxy : TInterface (Name {namespace = "Gio", name = "DBusProxy"})
    IO CString

-- | Gets the name that /@proxy@/ was constructed for.
-- 
-- /Since: 2.26/
dBusProxyGetName ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusProxy a) =>
    a
    -- ^ /@proxy@/: A t'GI.Gio.Objects.DBusProxy.DBusProxy'.
    -> m T.Text
    -- ^ __Returns:__ A string owned by /@proxy@/. Do not free.
dBusProxyGetName :: a -> m Text
dBusProxyGetName proxy :: a
proxy = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusProxy
proxy' <- a -> IO (Ptr DBusProxy)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
proxy
    CString
result <- Ptr DBusProxy -> IO CString
g_dbus_proxy_get_name Ptr DBusProxy
proxy'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusProxyGetName" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
proxy
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data DBusProxyGetNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDBusProxy a) => O.MethodInfo DBusProxyGetNameMethodInfo a signature where
    overloadedMethod = dBusProxyGetName

#endif

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

foreign import ccall "g_dbus_proxy_get_name_owner" g_dbus_proxy_get_name_owner :: 
    Ptr DBusProxy ->                        -- proxy : TInterface (Name {namespace = "Gio", name = "DBusProxy"})
    IO CString

-- | The unique name that owns the name that /@proxy@/ is for or 'P.Nothing' if
-- no-one currently owns that name. You may connect to the
-- [notify]("GI.GObject.Objects.Object#signal:notify") signal to track changes to the
-- t'GI.Gio.Objects.DBusProxy.DBusProxy':@/g-name-owner/@ property.
-- 
-- /Since: 2.26/
dBusProxyGetNameOwner ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusProxy a) =>
    a
    -- ^ /@proxy@/: A t'GI.Gio.Objects.DBusProxy.DBusProxy'.
    -> m (Maybe T.Text)
    -- ^ __Returns:__ The name owner or 'P.Nothing' if no name
    --    owner exists. Free with 'GI.GLib.Functions.free'.
dBusProxyGetNameOwner :: a -> m (Maybe Text)
dBusProxyGetNameOwner proxy :: a
proxy = 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
$ do
    Ptr DBusProxy
proxy' <- a -> IO (Ptr DBusProxy)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
proxy
    CString
result <- Ptr DBusProxy -> IO CString
g_dbus_proxy_get_name_owner Ptr DBusProxy
proxy'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \result' :: CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
proxy
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data DBusProxyGetNameOwnerMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsDBusProxy a) => O.MethodInfo DBusProxyGetNameOwnerMethodInfo a signature where
    overloadedMethod = dBusProxyGetNameOwner

#endif

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

foreign import ccall "g_dbus_proxy_get_object_path" g_dbus_proxy_get_object_path :: 
    Ptr DBusProxy ->                        -- proxy : TInterface (Name {namespace = "Gio", name = "DBusProxy"})
    IO CString

-- | Gets the object path /@proxy@/ is for.
-- 
-- /Since: 2.26/
dBusProxyGetObjectPath ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusProxy a) =>
    a
    -- ^ /@proxy@/: A t'GI.Gio.Objects.DBusProxy.DBusProxy'.
    -> m T.Text
    -- ^ __Returns:__ A string owned by /@proxy@/. Do not free.
dBusProxyGetObjectPath :: a -> m Text
dBusProxyGetObjectPath proxy :: a
proxy = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusProxy
proxy' <- a -> IO (Ptr DBusProxy)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
proxy
    CString
result <- Ptr DBusProxy -> IO CString
g_dbus_proxy_get_object_path Ptr DBusProxy
proxy'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusProxyGetObjectPath" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
proxy
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data DBusProxyGetObjectPathMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDBusProxy a) => O.MethodInfo DBusProxyGetObjectPathMethodInfo a signature where
    overloadedMethod = dBusProxyGetObjectPath

#endif

-- method DBusProxy::set_cached_property
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "proxy"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusProxy" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusProxy" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "property_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Property name." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TVariant
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "Value for the property or %NULL to remove it from the cache."
--                 , 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_proxy_set_cached_property" g_dbus_proxy_set_cached_property :: 
    Ptr DBusProxy ->                        -- proxy : TInterface (Name {namespace = "Gio", name = "DBusProxy"})
    CString ->                              -- property_name : TBasicType TUTF8
    Ptr GVariant ->                         -- value : TVariant
    IO ()

-- | If /@value@/ is not 'P.Nothing', sets the cached value for the property with
-- name /@propertyName@/ to the value in /@value@/.
-- 
-- If /@value@/ is 'P.Nothing', then the cached value is removed from the
-- property cache.
-- 
-- If /@proxy@/ has an expected interface (see
-- t'GI.Gio.Objects.DBusProxy.DBusProxy':@/g-interface-info/@) and /@propertyName@/ is referenced by
-- it, then /@value@/ is checked against the type of the property.
-- 
-- If the /@value@/ t'GVariant' is floating, it is consumed. This allows
-- convenient \'inline\' use of @/g_variant_new()/@, e.g.
-- 
-- === /C code/
-- >
-- > g_dbus_proxy_set_cached_property (proxy,
-- >                                   "SomeProperty",
-- >                                   g_variant_new ("(si)",
-- >                                                 "A String",
-- >                                                 42));
-- 
-- 
-- Normally you will not need to use this method since /@proxy@/
-- is tracking changes using the
-- @org.freedesktop.DBus.Properties.PropertiesChanged@
-- D-Bus signal. However, for performance reasons an object may
-- decide to not use this signal for some properties and instead
-- use a proprietary out-of-band mechanism to transmit changes.
-- 
-- As a concrete example, consider an object with a property
-- @ChatroomParticipants@ which is an array of strings. Instead of
-- transmitting the same (long) array every time the property changes,
-- it is more efficient to only transmit the delta using e.g. signals
-- @ChatroomParticipantJoined(String name)@ and
-- @ChatroomParticipantParted(String name)@.
-- 
-- /Since: 2.26/
dBusProxySetCachedProperty ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusProxy a) =>
    a
    -- ^ /@proxy@/: A t'GI.Gio.Objects.DBusProxy.DBusProxy'
    -> T.Text
    -- ^ /@propertyName@/: Property name.
    -> Maybe (GVariant)
    -- ^ /@value@/: Value for the property or 'P.Nothing' to remove it from the cache.
    -> m ()
dBusProxySetCachedProperty :: a -> Text -> Maybe GVariant -> m ()
dBusProxySetCachedProperty proxy :: a
proxy propertyName :: Text
propertyName value :: Maybe GVariant
value = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusProxy
proxy' <- a -> IO (Ptr DBusProxy)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
proxy
    CString
propertyName' <- Text -> IO CString
textToCString Text
propertyName
    Ptr GVariant
maybeValue <- case Maybe GVariant
value of
        Nothing -> Ptr GVariant -> IO (Ptr GVariant)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GVariant
forall a. Ptr a
nullPtr
        Just jValue :: GVariant
jValue -> do
            Ptr GVariant
jValue' <- GVariant -> IO (Ptr GVariant)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GVariant
jValue
            Ptr GVariant -> IO (Ptr GVariant)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GVariant
jValue'
    Ptr DBusProxy -> CString -> Ptr GVariant -> IO ()
g_dbus_proxy_set_cached_property Ptr DBusProxy
proxy' CString
propertyName' Ptr GVariant
maybeValue
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
proxy
    Maybe GVariant -> (GVariant -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe GVariant
value GVariant -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
propertyName'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DBusProxySetCachedPropertyMethodInfo
instance (signature ~ (T.Text -> Maybe (GVariant) -> m ()), MonadIO m, IsDBusProxy a) => O.MethodInfo DBusProxySetCachedPropertyMethodInfo a signature where
    overloadedMethod = dBusProxySetCachedProperty

#endif

-- method DBusProxy::set_default_timeout
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "proxy"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusProxy" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusProxy." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "timeout_msec"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Timeout in milliseconds."
--                 , 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_proxy_set_default_timeout" g_dbus_proxy_set_default_timeout :: 
    Ptr DBusProxy ->                        -- proxy : TInterface (Name {namespace = "Gio", name = "DBusProxy"})
    Int32 ->                                -- timeout_msec : TBasicType TInt
    IO ()

-- | Sets the timeout to use if -1 (specifying default timeout) is
-- passed as /@timeoutMsec@/ in the 'GI.Gio.Objects.DBusProxy.dBusProxyCall' and
-- 'GI.Gio.Objects.DBusProxy.dBusProxyCallSync' functions.
-- 
-- See the t'GI.Gio.Objects.DBusProxy.DBusProxy':@/g-default-timeout/@ property for more details.
-- 
-- /Since: 2.26/
dBusProxySetDefaultTimeout ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusProxy a) =>
    a
    -- ^ /@proxy@/: A t'GI.Gio.Objects.DBusProxy.DBusProxy'.
    -> Int32
    -- ^ /@timeoutMsec@/: Timeout in milliseconds.
    -> m ()
dBusProxySetDefaultTimeout :: a -> Int32 -> m ()
dBusProxySetDefaultTimeout proxy :: a
proxy timeoutMsec :: Int32
timeoutMsec = 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 DBusProxy
proxy' <- a -> IO (Ptr DBusProxy)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
proxy
    Ptr DBusProxy -> Int32 -> IO ()
g_dbus_proxy_set_default_timeout Ptr DBusProxy
proxy' Int32
timeoutMsec
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
proxy
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DBusProxySetDefaultTimeoutMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsDBusProxy a) => O.MethodInfo DBusProxySetDefaultTimeoutMethodInfo a signature where
    overloadedMethod = dBusProxySetDefaultTimeout

#endif

-- method DBusProxy::set_interface_info
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "proxy"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusProxy" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusProxy" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusInterfaceInfo" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "Minimum interface this proxy conforms to\n   or %NULL to unset."
--                 , 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_proxy_set_interface_info" g_dbus_proxy_set_interface_info :: 
    Ptr DBusProxy ->                        -- proxy : TInterface (Name {namespace = "Gio", name = "DBusProxy"})
    Ptr Gio.DBusInterfaceInfo.DBusInterfaceInfo -> -- info : TInterface (Name {namespace = "Gio", name = "DBusInterfaceInfo"})
    IO ()

-- | Ensure that interactions with /@proxy@/ conform to the given
-- interface. See the t'GI.Gio.Objects.DBusProxy.DBusProxy':@/g-interface-info/@ property for more
-- details.
-- 
-- /Since: 2.26/
dBusProxySetInterfaceInfo ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusProxy a) =>
    a
    -- ^ /@proxy@/: A t'GI.Gio.Objects.DBusProxy.DBusProxy'
    -> Maybe (Gio.DBusInterfaceInfo.DBusInterfaceInfo)
    -- ^ /@info@/: Minimum interface this proxy conforms to
    --    or 'P.Nothing' to unset.
    -> m ()
dBusProxySetInterfaceInfo :: a -> Maybe DBusInterfaceInfo -> m ()
dBusProxySetInterfaceInfo proxy :: a
proxy info :: Maybe DBusInterfaceInfo
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 DBusProxy
proxy' <- a -> IO (Ptr DBusProxy)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
proxy
    Ptr DBusInterfaceInfo
maybeInfo <- case Maybe DBusInterfaceInfo
info of
        Nothing -> Ptr DBusInterfaceInfo -> IO (Ptr DBusInterfaceInfo)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr DBusInterfaceInfo
forall a. Ptr a
nullPtr
        Just jInfo :: DBusInterfaceInfo
jInfo -> do
            Ptr DBusInterfaceInfo
jInfo' <- DBusInterfaceInfo -> IO (Ptr DBusInterfaceInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr DBusInterfaceInfo
jInfo
            Ptr DBusInterfaceInfo -> IO (Ptr DBusInterfaceInfo)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr DBusInterfaceInfo
jInfo'
    Ptr DBusProxy -> Ptr DBusInterfaceInfo -> IO ()
g_dbus_proxy_set_interface_info Ptr DBusProxy
proxy' Ptr DBusInterfaceInfo
maybeInfo
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
proxy
    Maybe DBusInterfaceInfo -> (DBusInterfaceInfo -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe DBusInterfaceInfo
info DBusInterfaceInfo -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DBusProxySetInterfaceInfoMethodInfo
instance (signature ~ (Maybe (Gio.DBusInterfaceInfo.DBusInterfaceInfo) -> m ()), MonadIO m, IsDBusProxy a) => O.MethodInfo DBusProxySetInterfaceInfoMethodInfo a signature where
    overloadedMethod = dBusProxySetInterfaceInfo

#endif

-- method DBusProxy::new
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "connection"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusConnection."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusProxyFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Flags used when constructing the proxy."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusInterfaceInfo" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A #GDBusInterfaceInfo specifying the minimal interface that @proxy conforms to or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A bus name (well-known or unique) or %NULL if @connection is not a message bus connection."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "object_path"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An object path." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "interface_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
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GCancellable or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "callback"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncReadyCallback" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "Callback function to invoke when the proxy is ready."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = 8
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "User data to pass to @callback."
--                 , 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_proxy_new" g_dbus_proxy_new :: 
    Ptr Gio.DBusConnection.DBusConnection -> -- connection : TInterface (Name {namespace = "Gio", name = "DBusConnection"})
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gio", name = "DBusProxyFlags"})
    Ptr Gio.DBusInterfaceInfo.DBusInterfaceInfo -> -- info : TInterface (Name {namespace = "Gio", name = "DBusInterfaceInfo"})
    CString ->                              -- name : TBasicType TUTF8
    CString ->                              -- object_path : TBasicType TUTF8
    CString ->                              -- interface_name : TBasicType TUTF8
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    FunPtr Gio.Callbacks.C_AsyncReadyCallback -> -- callback : TInterface (Name {namespace = "Gio", name = "AsyncReadyCallback"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    IO ()

-- | Creates a proxy for accessing /@interfaceName@/ on the remote object
-- at /@objectPath@/ owned by /@name@/ at /@connection@/ and asynchronously
-- loads D-Bus properties unless the
-- 'GI.Gio.Flags.DBusProxyFlagsDoNotLoadProperties' flag is used. Connect to
-- the [gPropertiesChanged]("GI.Gio.Objects.DBusProxy#signal:gPropertiesChanged") signal to get notified about
-- property changes.
-- 
-- If the 'GI.Gio.Flags.DBusProxyFlagsDoNotConnectSignals' flag is not set, also sets up
-- match rules for signals. Connect to the [gSignal]("GI.Gio.Objects.DBusProxy#signal:gSignal") signal
-- to handle signals from the remote object.
-- 
-- If both 'GI.Gio.Flags.DBusProxyFlagsDoNotLoadProperties' and
-- 'GI.Gio.Flags.DBusProxyFlagsDoNotConnectSignals' are set, this constructor is
-- guaranteed to complete immediately without blocking.
-- 
-- If /@name@/ is a well-known name and the
-- 'GI.Gio.Flags.DBusProxyFlagsDoNotAutoStart' and 'GI.Gio.Flags.DBusProxyFlagsDoNotAutoStartAtConstruction'
-- flags aren\'t set and no name owner currently exists, the message bus
-- will be requested to launch a name owner for the name.
-- 
-- This is a failable asynchronous constructor - when the proxy is
-- ready, /@callback@/ will be invoked and you can use
-- 'GI.Gio.Objects.DBusProxy.dBusProxyNewFinish' to get the result.
-- 
-- See 'GI.Gio.Objects.DBusProxy.dBusProxyNewSync' and for a synchronous version of this constructor.
-- 
-- t'GI.Gio.Objects.DBusProxy.DBusProxy' is used in this [example][gdbus-wellknown-proxy].
-- 
-- /Since: 2.26/
dBusProxyNew ::
    (B.CallStack.HasCallStack, MonadIO m, Gio.DBusConnection.IsDBusConnection a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@connection@/: A t'GI.Gio.Objects.DBusConnection.DBusConnection'.
    -> [Gio.Flags.DBusProxyFlags]
    -- ^ /@flags@/: Flags used when constructing the proxy.
    -> Maybe (Gio.DBusInterfaceInfo.DBusInterfaceInfo)
    -- ^ /@info@/: A t'GI.Gio.Structs.DBusInterfaceInfo.DBusInterfaceInfo' specifying the minimal interface that /@proxy@/ conforms to or 'P.Nothing'.
    -> Maybe (T.Text)
    -- ^ /@name@/: A bus name (well-known or unique) or 'P.Nothing' if /@connection@/ is not a message bus connection.
    -> T.Text
    -- ^ /@objectPath@/: An object path.
    -> T.Text
    -- ^ /@interfaceName@/: A D-Bus interface name.
    -> Maybe (b)
    -- ^ /@cancellable@/: A t'GI.Gio.Objects.Cancellable.Cancellable' or 'P.Nothing'.
    -> Maybe (Gio.Callbacks.AsyncReadyCallback)
    -- ^ /@callback@/: Callback function to invoke when the proxy is ready.
    -> m ()
dBusProxyNew :: a
-> [DBusProxyFlags]
-> Maybe DBusInterfaceInfo
-> Maybe Text
-> Text
-> Text
-> Maybe b
-> Maybe AsyncReadyCallback
-> m ()
dBusProxyNew connection :: a
connection flags :: [DBusProxyFlags]
flags info :: Maybe DBusInterfaceInfo
info name :: Maybe Text
name objectPath :: Text
objectPath interfaceName :: Text
interfaceName cancellable :: Maybe b
cancellable callback :: Maybe AsyncReadyCallback
callback = 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 DBusConnection
connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    let flags' :: CUInt
flags' = [DBusProxyFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [DBusProxyFlags]
flags
    Ptr DBusInterfaceInfo
maybeInfo <- case Maybe DBusInterfaceInfo
info of
        Nothing -> Ptr DBusInterfaceInfo -> IO (Ptr DBusInterfaceInfo)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr DBusInterfaceInfo
forall a. Ptr a
nullPtr
        Just jInfo :: DBusInterfaceInfo
jInfo -> do
            Ptr DBusInterfaceInfo
jInfo' <- DBusInterfaceInfo -> IO (Ptr DBusInterfaceInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr DBusInterfaceInfo
jInfo
            Ptr DBusInterfaceInfo -> IO (Ptr DBusInterfaceInfo)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr DBusInterfaceInfo
jInfo'
    CString
maybeName <- case Maybe Text
name of
        Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just jName :: Text
jName -> do
            CString
jName' <- Text -> IO CString
textToCString Text
jName
            CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jName'
    CString
objectPath' <- Text -> IO CString
textToCString Text
objectPath
    CString
interfaceName' <- Text -> IO CString
textToCString Text
interfaceName
    Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
        Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just jCancellable :: b
jCancellable -> do
            Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    FunPtr C_AsyncReadyCallback
maybeCallback <- case Maybe AsyncReadyCallback
callback of
        Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_AsyncReadyCallback
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
        Just jCallback :: AsyncReadyCallback
jCallback -> do
            Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
            FunPtr C_AsyncReadyCallback
jCallback' <- C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
Gio.Callbacks.mk_AsyncReadyCallback (Maybe (Ptr (FunPtr C_AsyncReadyCallback))
-> AsyncReadyCallback_WithClosures -> C_AsyncReadyCallback
Gio.Callbacks.wrap_AsyncReadyCallback (Ptr (FunPtr C_AsyncReadyCallback)
-> Maybe (Ptr (FunPtr C_AsyncReadyCallback))
forall a. a -> Maybe a
Just Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback) (AsyncReadyCallback -> AsyncReadyCallback_WithClosures
Gio.Callbacks.drop_closures_AsyncReadyCallback AsyncReadyCallback
jCallback))
            Ptr (FunPtr C_AsyncReadyCallback)
-> FunPtr C_AsyncReadyCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback FunPtr C_AsyncReadyCallback
jCallback'
            FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
jCallback'
    let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
    Ptr DBusConnection
-> CUInt
-> Ptr DBusInterfaceInfo
-> CString
-> CString
-> CString
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> IO ()
g_dbus_proxy_new Ptr DBusConnection
connection' CUInt
flags' Ptr DBusInterfaceInfo
maybeInfo CString
maybeName CString
objectPath' CString
interfaceName' Ptr Cancellable
maybeCancellable FunPtr C_AsyncReadyCallback
maybeCallback Ptr ()
forall a. Ptr a
userData
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
connection
    Maybe DBusInterfaceInfo -> (DBusInterfaceInfo -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe DBusInterfaceInfo
info DBusInterfaceInfo -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeName
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
objectPath'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
interfaceName'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif

-- method DBusProxy::new_for_bus
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "bus_type"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "BusType" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GBusType." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusProxyFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Flags used when constructing the proxy."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusInterfaceInfo" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A #GDBusInterfaceInfo specifying the minimal interface that @proxy conforms to or %NULL."
--                 , 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 bus name (well-known or unique)."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "object_path"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An object path." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "interface_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
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GCancellable or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "callback"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncReadyCallback" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "Callback function to invoke when the proxy is ready."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = 8
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "User data to pass to @callback."
--                 , 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_proxy_new_for_bus" g_dbus_proxy_new_for_bus :: 
    CInt ->                                 -- bus_type : TInterface (Name {namespace = "Gio", name = "BusType"})
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gio", name = "DBusProxyFlags"})
    Ptr Gio.DBusInterfaceInfo.DBusInterfaceInfo -> -- info : TInterface (Name {namespace = "Gio", name = "DBusInterfaceInfo"})
    CString ->                              -- name : TBasicType TUTF8
    CString ->                              -- object_path : TBasicType TUTF8
    CString ->                              -- interface_name : TBasicType TUTF8
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    FunPtr Gio.Callbacks.C_AsyncReadyCallback -> -- callback : TInterface (Name {namespace = "Gio", name = "AsyncReadyCallback"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    IO ()

-- | Like 'GI.Gio.Objects.DBusProxy.dBusProxyNew' but takes a t'GI.Gio.Enums.BusType' instead of a t'GI.Gio.Objects.DBusConnection.DBusConnection'.
-- 
-- t'GI.Gio.Objects.DBusProxy.DBusProxy' is used in this [example][gdbus-wellknown-proxy].
-- 
-- /Since: 2.26/
dBusProxyNewForBus ::
    (B.CallStack.HasCallStack, MonadIO m, Gio.Cancellable.IsCancellable a) =>
    Gio.Enums.BusType
    -- ^ /@busType@/: A t'GI.Gio.Enums.BusType'.
    -> [Gio.Flags.DBusProxyFlags]
    -- ^ /@flags@/: Flags used when constructing the proxy.
    -> Maybe (Gio.DBusInterfaceInfo.DBusInterfaceInfo)
    -- ^ /@info@/: A t'GI.Gio.Structs.DBusInterfaceInfo.DBusInterfaceInfo' specifying the minimal interface that /@proxy@/ conforms to or 'P.Nothing'.
    -> T.Text
    -- ^ /@name@/: A bus name (well-known or unique).
    -> T.Text
    -- ^ /@objectPath@/: An object path.
    -> T.Text
    -- ^ /@interfaceName@/: A D-Bus interface name.
    -> Maybe (a)
    -- ^ /@cancellable@/: A t'GI.Gio.Objects.Cancellable.Cancellable' or 'P.Nothing'.
    -> Maybe (Gio.Callbacks.AsyncReadyCallback)
    -- ^ /@callback@/: Callback function to invoke when the proxy is ready.
    -> m ()
dBusProxyNewForBus :: BusType
-> [DBusProxyFlags]
-> Maybe DBusInterfaceInfo
-> Text
-> Text
-> Text
-> Maybe a
-> Maybe AsyncReadyCallback
-> m ()
dBusProxyNewForBus busType :: BusType
busType flags :: [DBusProxyFlags]
flags info :: Maybe DBusInterfaceInfo
info name :: Text
name objectPath :: Text
objectPath interfaceName :: Text
interfaceName cancellable :: Maybe a
cancellable callback :: Maybe AsyncReadyCallback
callback = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    let busType' :: CInt
busType' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (BusType -> Int) -> BusType -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BusType -> Int
forall a. Enum a => a -> Int
fromEnum) BusType
busType
    let flags' :: CUInt
flags' = [DBusProxyFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [DBusProxyFlags]
flags
    Ptr DBusInterfaceInfo
maybeInfo <- case Maybe DBusInterfaceInfo
info of
        Nothing -> Ptr DBusInterfaceInfo -> IO (Ptr DBusInterfaceInfo)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr DBusInterfaceInfo
forall a. Ptr a
nullPtr
        Just jInfo :: DBusInterfaceInfo
jInfo -> do
            Ptr DBusInterfaceInfo
jInfo' <- DBusInterfaceInfo -> IO (Ptr DBusInterfaceInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr DBusInterfaceInfo
jInfo
            Ptr DBusInterfaceInfo -> IO (Ptr DBusInterfaceInfo)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr DBusInterfaceInfo
jInfo'
    CString
name' <- Text -> IO CString
textToCString Text
name
    CString
objectPath' <- Text -> IO CString
textToCString Text
objectPath
    CString
interfaceName' <- Text -> IO CString
textToCString Text
interfaceName
    Ptr Cancellable
maybeCancellable <- case Maybe a
cancellable of
        Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just jCancellable :: a
jCancellable -> do
            Ptr Cancellable
jCancellable' <- a -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    FunPtr C_AsyncReadyCallback
maybeCallback <- case Maybe AsyncReadyCallback
callback of
        Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_AsyncReadyCallback
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
        Just jCallback :: AsyncReadyCallback
jCallback -> do
            Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
            FunPtr C_AsyncReadyCallback
jCallback' <- C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
Gio.Callbacks.mk_AsyncReadyCallback (Maybe (Ptr (FunPtr C_AsyncReadyCallback))
-> AsyncReadyCallback_WithClosures -> C_AsyncReadyCallback
Gio.Callbacks.wrap_AsyncReadyCallback (Ptr (FunPtr C_AsyncReadyCallback)
-> Maybe (Ptr (FunPtr C_AsyncReadyCallback))
forall a. a -> Maybe a
Just Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback) (AsyncReadyCallback -> AsyncReadyCallback_WithClosures
Gio.Callbacks.drop_closures_AsyncReadyCallback AsyncReadyCallback
jCallback))
            Ptr (FunPtr C_AsyncReadyCallback)
-> FunPtr C_AsyncReadyCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback FunPtr C_AsyncReadyCallback
jCallback'
            FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
jCallback'
    let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
    CInt
-> CUInt
-> Ptr DBusInterfaceInfo
-> CString
-> CString
-> CString
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> IO ()
g_dbus_proxy_new_for_bus CInt
busType' CUInt
flags' Ptr DBusInterfaceInfo
maybeInfo CString
name' CString
objectPath' CString
interfaceName' Ptr Cancellable
maybeCancellable FunPtr C_AsyncReadyCallback
maybeCallback Ptr ()
forall a. Ptr a
userData
    Maybe DBusInterfaceInfo -> (DBusInterfaceInfo -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe DBusInterfaceInfo
info DBusInterfaceInfo -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Maybe a -> (a -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe a
cancellable a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
objectPath'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
interfaceName'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif