{-# 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.DBusObjectManagerClient.DBusObjectManagerClient' is used to create, monitor and delete object
-- proxies for remote objects exported by a t'GI.Gio.Objects.DBusObjectManagerServer.DBusObjectManagerServer' (or any
-- code implementing the
-- <http://dbus.freedesktop.org/doc/dbus-specification.html#standard-interfaces-objectmanager org.freedesktop.DBus.ObjectManager>
-- interface).
-- 
-- Once an instance of this type has been created, you can connect to
-- the [objectAdded]("GI.Gio.Interfaces.DBusObjectManager#signal:objectAdded") and
-- [objectRemoved]("GI.Gio.Interfaces.DBusObjectManager#signal:objectRemoved") signals and inspect the
-- t'GI.Gio.Objects.DBusObjectProxy.DBusObjectProxy' objects returned by
-- 'GI.Gio.Interfaces.DBusObjectManager.dBusObjectManagerGetObjects'.
-- 
-- If the name for a t'GI.Gio.Objects.DBusObjectManagerClient.DBusObjectManagerClient' is not owned by anyone at
-- object construction time, the default behavior is to request the
-- message bus to launch an owner for the name. This behavior can be
-- disabled using the 'GI.Gio.Flags.DBusObjectManagerClientFlagsDoNotAutoStart'
-- flag. It\'s also worth noting that this only works if the name of
-- interest is activatable in the first place. E.g. in some cases it
-- is not possible to launch an owner for the requested name. In this
-- case, t'GI.Gio.Objects.DBusObjectManagerClient.DBusObjectManagerClient' object construction still succeeds but
-- there will be no object proxies
-- (e.g. 'GI.Gio.Interfaces.DBusObjectManager.dBusObjectManagerGetObjects' returns the empty list) and
-- the t'GI.Gio.Objects.DBusObjectManagerClient.DBusObjectManagerClient':@/name-owner/@ property is 'P.Nothing'.
-- 
-- The owner of the requested name can come and go (for example
-- consider a system service being restarted) – t'GI.Gio.Objects.DBusObjectManagerClient.DBusObjectManagerClient'
-- handles this case too; simply connect to the [notify]("GI.GObject.Objects.Object#signal:notify")
-- signal to watch for changes on the t'GI.Gio.Objects.DBusObjectManagerClient.DBusObjectManagerClient':@/name-owner/@
-- property. When the name owner vanishes, the behavior is that
-- t'GI.Gio.Objects.DBusObjectManagerClient.DBusObjectManagerClient':@/name-owner/@ is set to 'P.Nothing' (this includes
-- emission of the [notify]("GI.GObject.Objects.Object#signal:notify") signal) and then
-- [objectRemoved]("GI.Gio.Interfaces.DBusObjectManager#signal:objectRemoved") signals are synthesized
-- for all currently existing object proxies. Since
-- t'GI.Gio.Objects.DBusObjectManagerClient.DBusObjectManagerClient':@/name-owner/@ is 'P.Nothing' when this happens, you can
-- use this information to disambiguate a synthesized signal from a
-- genuine signal caused by object removal on the remote
-- t'GI.Gio.Interfaces.DBusObjectManager.DBusObjectManager'. Similarly, when a new name owner appears,
-- [objectAdded]("GI.Gio.Interfaces.DBusObjectManager#signal:objectAdded") signals are synthesized
-- while t'GI.Gio.Objects.DBusObjectManagerClient.DBusObjectManagerClient':@/name-owner/@ is still 'P.Nothing'. Only when all
-- object proxies have been added, the t'GI.Gio.Objects.DBusObjectManagerClient.DBusObjectManagerClient':@/name-owner/@
-- is set to the new name owner (this includes emission of the
-- [notify]("GI.GObject.Objects.Object#signal:notify") signal).  Furthermore, you are guaranteed that
-- t'GI.Gio.Objects.DBusObjectManagerClient.DBusObjectManagerClient':@/name-owner/@ will alternate between a name owner
-- (e.g. @:1.42@) and 'P.Nothing' even in the case where
-- the name of interest is atomically replaced
-- 
-- Ultimately, t'GI.Gio.Objects.DBusObjectManagerClient.DBusObjectManagerClient' is used to obtain t'GI.Gio.Objects.DBusProxy.DBusProxy'
-- instances. All signals (including the
-- org.freedesktop.DBus.Properties[PropertiesChanged](#signal:PropertiesChanged) signal)
-- delivered to t'GI.Gio.Objects.DBusProxy.DBusProxy' instances are guaranteed to originate
-- from the name owner. This guarantee along with the behavior
-- described above, means that certain race conditions including the
-- \"half the proxy is from the old owner and the other half is from
-- the new owner\" problem cannot happen.
-- 
-- To avoid having the application connect to signals on the returned
-- t'GI.Gio.Objects.DBusObjectProxy.DBusObjectProxy' and t'GI.Gio.Objects.DBusProxy.DBusProxy' objects, the
-- [interfaceAdded]("GI.Gio.Interfaces.DBusObject#signal:interfaceAdded"),
-- [interfaceRemoved]("GI.Gio.Interfaces.DBusObject#signal:interfaceRemoved"),
-- [gPropertiesChanged]("GI.Gio.Objects.DBusProxy#signal:gPropertiesChanged") and
-- [gSignal]("GI.Gio.Objects.DBusProxy#signal:gSignal") signals
-- are also emitted on the t'GI.Gio.Objects.DBusObjectManagerClient.DBusObjectManagerClient' instance managing these
-- objects. The signals emitted are
-- [interfaceAdded]("GI.Gio.Interfaces.DBusObjectManager#signal:interfaceAdded"),
-- [interfaceRemoved]("GI.Gio.Interfaces.DBusObjectManager#signal:interfaceRemoved"),
-- [interfaceProxyPropertiesChanged]("GI.Gio.Objects.DBusObjectManagerClient#signal:interfaceProxyPropertiesChanged") and
-- [interfaceProxySignal]("GI.Gio.Objects.DBusObjectManagerClient#signal:interfaceProxySignal").
-- 
-- Note that all callbacks and signals are emitted in the
-- [thread-default main context][g-main-context-push-thread-default]
-- that the t'GI.Gio.Objects.DBusObjectManagerClient.DBusObjectManagerClient' object was constructed
-- in. Additionally, the t'GI.Gio.Objects.DBusObjectProxy.DBusObjectProxy' and t'GI.Gio.Objects.DBusProxy.DBusProxy' objects
-- originating from the t'GI.Gio.Objects.DBusObjectManagerClient.DBusObjectManagerClient' object will be created in
-- the same context and, consequently, will deliver signals in the
-- same main loop.
-- 
-- /Since: 2.30/

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

module GI.Gio.Objects.DBusObjectManagerClient
    ( 

-- * Exported types
    DBusObjectManagerClient(..)             ,
    IsDBusObjectManagerClient               ,
    toDBusObjectManagerClient               ,
    noDBusObjectManagerClient               ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveDBusObjectManagerClientMethod    ,
#endif


-- ** getConnection #method:getConnection#

#if defined(ENABLE_OVERLOADING)
    DBusObjectManagerClientGetConnectionMethodInfo,
#endif
    dBusObjectManagerClientGetConnection    ,


-- ** getFlags #method:getFlags#

#if defined(ENABLE_OVERLOADING)
    DBusObjectManagerClientGetFlagsMethodInfo,
#endif
    dBusObjectManagerClientGetFlags         ,


-- ** getName #method:getName#

#if defined(ENABLE_OVERLOADING)
    DBusObjectManagerClientGetNameMethodInfo,
#endif
    dBusObjectManagerClientGetName          ,


-- ** getNameOwner #method:getNameOwner#

#if defined(ENABLE_OVERLOADING)
    DBusObjectManagerClientGetNameOwnerMethodInfo,
#endif
    dBusObjectManagerClientGetNameOwner     ,


-- ** new #method:new#

    dBusObjectManagerClientNew              ,


-- ** newFinish #method:newFinish#

    dBusObjectManagerClientNewFinish        ,


-- ** newForBus #method:newForBus#

    dBusObjectManagerClientNewForBus        ,


-- ** newForBusFinish #method:newForBusFinish#

    dBusObjectManagerClientNewForBusFinish  ,


-- ** newForBusSync #method:newForBusSync#

    dBusObjectManagerClientNewForBusSync    ,


-- ** newSync #method:newSync#

    dBusObjectManagerClientNewSync          ,




 -- * Properties
-- ** busType #attr:busType#
-- | If this property is not 'GI.Gio.Enums.BusTypeNone', then
-- t'GI.Gio.Objects.DBusObjectManagerClient.DBusObjectManagerClient':@/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.30/

#if defined(ENABLE_OVERLOADING)
    DBusObjectManagerClientBusTypePropertyInfo,
#endif
    constructDBusObjectManagerClientBusType ,
#if defined(ENABLE_OVERLOADING)
    dBusObjectManagerClientBusType          ,
#endif


-- ** connection #attr:connection#
-- | The t'GI.Gio.Objects.DBusConnection.DBusConnection' to use.
-- 
-- /Since: 2.30/

#if defined(ENABLE_OVERLOADING)
    DBusObjectManagerClientConnectionPropertyInfo,
#endif
    constructDBusObjectManagerClientConnection,
#if defined(ENABLE_OVERLOADING)
    dBusObjectManagerClientConnection       ,
#endif
    getDBusObjectManagerClientConnection    ,


-- ** flags #attr:flags#
-- | Flags from the t'GI.Gio.Flags.DBusObjectManagerClientFlags' enumeration.
-- 
-- /Since: 2.30/

#if defined(ENABLE_OVERLOADING)
    DBusObjectManagerClientFlagsPropertyInfo,
#endif
    constructDBusObjectManagerClientFlags   ,
#if defined(ENABLE_OVERLOADING)
    dBusObjectManagerClientFlags            ,
#endif
    getDBusObjectManagerClientFlags         ,


-- ** getProxyTypeDestroyNotify #attr:getProxyTypeDestroyNotify#
-- | A t'GI.GLib.Callbacks.DestroyNotify' for the @/gpointer/@ user_data in t'GI.Gio.Objects.DBusObjectManagerClient.DBusObjectManagerClient':@/get-proxy-type-user-data/@.
-- 
-- /Since: 2.30/

#if defined(ENABLE_OVERLOADING)
    DBusObjectManagerClientGetProxyTypeDestroyNotifyPropertyInfo,
#endif
    constructDBusObjectManagerClientGetProxyTypeDestroyNotify,
#if defined(ENABLE_OVERLOADING)
    dBusObjectManagerClientGetProxyTypeDestroyNotify,
#endif
    getDBusObjectManagerClientGetProxyTypeDestroyNotify,


-- ** getProxyTypeFunc #attr:getProxyTypeFunc#
-- | The t'GI.Gio.Callbacks.DBusProxyTypeFunc' to use when determining what t'GType' to
-- use for interface proxies or 'P.Nothing'.
-- 
-- /Since: 2.30/

#if defined(ENABLE_OVERLOADING)
    DBusObjectManagerClientGetProxyTypeFuncPropertyInfo,
#endif
    constructDBusObjectManagerClientGetProxyTypeFunc,
#if defined(ENABLE_OVERLOADING)
    dBusObjectManagerClientGetProxyTypeFunc ,
#endif
    getDBusObjectManagerClientGetProxyTypeFunc,


-- ** getProxyTypeUserData #attr:getProxyTypeUserData#
-- | The @/gpointer/@ user_data to pass to t'GI.Gio.Objects.DBusObjectManagerClient.DBusObjectManagerClient':@/get-proxy-type-func/@.
-- 
-- /Since: 2.30/

#if defined(ENABLE_OVERLOADING)
    DBusObjectManagerClientGetProxyTypeUserDataPropertyInfo,
#endif
    constructDBusObjectManagerClientGetProxyTypeUserData,
#if defined(ENABLE_OVERLOADING)
    dBusObjectManagerClientGetProxyTypeUserData,
#endif
    getDBusObjectManagerClientGetProxyTypeUserData,


-- ** name #attr:name#
-- | The well-known name or unique name that the manager is for.
-- 
-- /Since: 2.30/

#if defined(ENABLE_OVERLOADING)
    DBusObjectManagerClientNamePropertyInfo ,
#endif
    constructDBusObjectManagerClientName    ,
#if defined(ENABLE_OVERLOADING)
    dBusObjectManagerClientName             ,
#endif
    getDBusObjectManagerClientName          ,


-- ** nameOwner #attr:nameOwner#
-- | The unique name that owns t'GI.Gio.Objects.DBusObjectManagerClient.DBusObjectManagerClient':@/name/@ or 'P.Nothing' if
-- no-one is currently owning the name. Connect to the
-- [notify]("GI.GObject.Objects.Object#signal:notify") signal to track changes to this property.
-- 
-- /Since: 2.30/

#if defined(ENABLE_OVERLOADING)
    DBusObjectManagerClientNameOwnerPropertyInfo,
#endif
#if defined(ENABLE_OVERLOADING)
    dBusObjectManagerClientNameOwner        ,
#endif
    getDBusObjectManagerClientNameOwner     ,


-- ** objectPath #attr:objectPath#
-- | The object path the manager is for.
-- 
-- /Since: 2.30/

#if defined(ENABLE_OVERLOADING)
    DBusObjectManagerClientObjectPathPropertyInfo,
#endif
    constructDBusObjectManagerClientObjectPath,
#if defined(ENABLE_OVERLOADING)
    dBusObjectManagerClientObjectPath       ,
#endif
    getDBusObjectManagerClientObjectPath    ,




 -- * Signals
-- ** interfaceProxyPropertiesChanged #signal:interfaceProxyPropertiesChanged#

    C_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback,
    DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback,
#if defined(ENABLE_OVERLOADING)
    DBusObjectManagerClientInterfaceProxyPropertiesChangedSignalInfo,
#endif
    afterDBusObjectManagerClientInterfaceProxyPropertiesChanged,
    genClosure_DBusObjectManagerClientInterfaceProxyPropertiesChanged,
    mk_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback,
    noDBusObjectManagerClientInterfaceProxyPropertiesChangedCallback,
    onDBusObjectManagerClientInterfaceProxyPropertiesChanged,
    wrap_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback,


-- ** interfaceProxySignal #signal:interfaceProxySignal#

    C_DBusObjectManagerClientInterfaceProxySignalCallback,
    DBusObjectManagerClientInterfaceProxySignalCallback,
#if defined(ENABLE_OVERLOADING)
    DBusObjectManagerClientInterfaceProxySignalSignalInfo,
#endif
    afterDBusObjectManagerClientInterfaceProxySignal,
    genClosure_DBusObjectManagerClientInterfaceProxySignal,
    mk_DBusObjectManagerClientInterfaceProxySignalCallback,
    noDBusObjectManagerClientInterfaceProxySignalCallback,
    onDBusObjectManagerClientInterfaceProxySignal,
    wrap_DBusObjectManagerClientInterfaceProxySignalCallback,




    ) 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.GLib.Callbacks as GLib.Callbacks
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.DBusObjectManager as Gio.DBusObjectManager
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.DBusObjectProxy as Gio.DBusObjectProxy
import {-# SOURCE #-} qualified GI.Gio.Objects.DBusProxy as Gio.DBusProxy

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

instance GObject DBusObjectManagerClient where
    gobjectType :: IO GType
gobjectType = IO GType
c_g_dbus_object_manager_client_get_type
    

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

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

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

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

-- | A convenience alias for `Nothing` :: `Maybe` `DBusObjectManagerClient`.
noDBusObjectManagerClient :: Maybe DBusObjectManagerClient
noDBusObjectManagerClient :: Maybe DBusObjectManagerClient
noDBusObjectManagerClient = Maybe DBusObjectManagerClient
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolveDBusObjectManagerClientMethod (t :: Symbol) (o :: *) :: * where
    ResolveDBusObjectManagerClientMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveDBusObjectManagerClientMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveDBusObjectManagerClientMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveDBusObjectManagerClientMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveDBusObjectManagerClientMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveDBusObjectManagerClientMethod "init" o = Gio.Initable.InitableInitMethodInfo
    ResolveDBusObjectManagerClientMethod "initAsync" o = Gio.AsyncInitable.AsyncInitableInitAsyncMethodInfo
    ResolveDBusObjectManagerClientMethod "initFinish" o = Gio.AsyncInitable.AsyncInitableInitFinishMethodInfo
    ResolveDBusObjectManagerClientMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveDBusObjectManagerClientMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveDBusObjectManagerClientMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveDBusObjectManagerClientMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveDBusObjectManagerClientMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveDBusObjectManagerClientMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveDBusObjectManagerClientMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveDBusObjectManagerClientMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveDBusObjectManagerClientMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveDBusObjectManagerClientMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveDBusObjectManagerClientMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveDBusObjectManagerClientMethod "getConnection" o = DBusObjectManagerClientGetConnectionMethodInfo
    ResolveDBusObjectManagerClientMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveDBusObjectManagerClientMethod "getFlags" o = DBusObjectManagerClientGetFlagsMethodInfo
    ResolveDBusObjectManagerClientMethod "getInterface" o = Gio.DBusObjectManager.DBusObjectManagerGetInterfaceMethodInfo
    ResolveDBusObjectManagerClientMethod "getName" o = DBusObjectManagerClientGetNameMethodInfo
    ResolveDBusObjectManagerClientMethod "getNameOwner" o = DBusObjectManagerClientGetNameOwnerMethodInfo
    ResolveDBusObjectManagerClientMethod "getObject" o = Gio.DBusObjectManager.DBusObjectManagerGetObjectMethodInfo
    ResolveDBusObjectManagerClientMethod "getObjectPath" o = Gio.DBusObjectManager.DBusObjectManagerGetObjectPathMethodInfo
    ResolveDBusObjectManagerClientMethod "getObjects" o = Gio.DBusObjectManager.DBusObjectManagerGetObjectsMethodInfo
    ResolveDBusObjectManagerClientMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveDBusObjectManagerClientMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveDBusObjectManagerClientMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveDBusObjectManagerClientMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveDBusObjectManagerClientMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveDBusObjectManagerClientMethod l o = O.MethodResolutionFailed l o

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

#endif

-- signal DBusObjectManagerClient::interface-proxy-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).
-- 
-- This signal exists purely as a convenience to avoid having to
-- connect signals to all interface proxies managed by /@manager@/.
-- 
-- This signal is emitted in the
-- [thread-default main context][g-main-context-push-thread-default]
-- that /@manager@/ was constructed in.
-- 
-- /Since: 2.30/
type DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback =
    Gio.DBusObjectProxy.DBusObjectProxy
    -- ^ /@objectProxy@/: The t'GI.Gio.Objects.DBusObjectProxy.DBusObjectProxy' on which an interface has properties that are changing.
    -> Gio.DBusProxy.DBusProxy
    -- ^ /@interfaceProxy@/: The t'GI.Gio.Objects.DBusProxy.DBusProxy' that has properties that are changing.
    -> GVariant
    -- ^ /@changedProperties@/: A t'GVariant' containing the properties that changed (type: @a{sv}@).
    -> [T.Text]
    -- ^ /@invalidatedProperties@/: A 'P.Nothing' terminated
    --   array of properties that were invalidated.
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback`@.
noDBusObjectManagerClientInterfaceProxyPropertiesChangedCallback :: Maybe DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback
noDBusObjectManagerClientInterfaceProxyPropertiesChangedCallback :: Maybe
  DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback
noDBusObjectManagerClientInterfaceProxyPropertiesChangedCallback = Maybe
  DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback
forall a. Maybe a
Nothing

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

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

-- | Wrap the callback into a `GClosure`.
genClosure_DBusObjectManagerClientInterfaceProxyPropertiesChanged :: MonadIO m => DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback -> m (GClosure C_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback)
genClosure_DBusObjectManagerClientInterfaceProxyPropertiesChanged :: DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback
-> m (GClosure
        C_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback)
genClosure_DBusObjectManagerClientInterfaceProxyPropertiesChanged cb :: DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback
cb = IO
  (GClosure
     C_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback)
-> m (GClosure
        C_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO
   (GClosure
      C_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback)
 -> m (GClosure
         C_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback))
-> IO
     (GClosure
        C_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback)
-> m (GClosure
        C_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback
cb' = DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback
-> C_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback
wrap_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback
cb
    C_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback
-> IO
     (FunPtr
        C_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback)
mk_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback C_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback
cb' IO
  (FunPtr
     C_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback)
-> (FunPtr
      C_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback
    -> IO
         (GClosure
            C_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback))
-> IO
     (GClosure
        C_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr
  C_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback
-> IO
     (GClosure
        C_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback` into a `C_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback`.
wrap_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback ::
    DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback ->
    C_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback
wrap_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback :: DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback
-> C_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback
wrap_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback _cb :: DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback
_cb _ objectProxy :: Ptr DBusObjectProxy
objectProxy interfaceProxy :: Ptr DBusProxy
interfaceProxy changedProperties :: Ptr GVariant
changedProperties invalidatedProperties :: Ptr CString
invalidatedProperties _ = do
    DBusObjectProxy
objectProxy' <- ((ManagedPtr DBusObjectProxy -> DBusObjectProxy)
-> Ptr DBusObjectProxy -> IO DBusObjectProxy
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr DBusObjectProxy -> DBusObjectProxy
Gio.DBusObjectProxy.DBusObjectProxy) Ptr DBusObjectProxy
objectProxy
    DBusProxy
interfaceProxy' <- ((ManagedPtr DBusProxy -> DBusProxy)
-> Ptr DBusProxy -> IO DBusProxy
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr DBusProxy -> DBusProxy
Gio.DBusProxy.DBusProxy) Ptr DBusProxy
interfaceProxy
    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
    DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback
_cb  DBusObjectProxy
objectProxy' DBusProxy
interfaceProxy' GVariant
changedProperties' [Text]
invalidatedProperties'


-- | Connect a signal handler for the [interfaceProxyPropertiesChanged](#signal:interfaceProxyPropertiesChanged) 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' dBusObjectManagerClient #interfaceProxyPropertiesChanged callback
-- @
-- 
-- 
onDBusObjectManagerClientInterfaceProxyPropertiesChanged :: (IsDBusObjectManagerClient a, MonadIO m) => a -> DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback -> m SignalHandlerId
onDBusObjectManagerClientInterfaceProxyPropertiesChanged :: a
-> DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback
-> m SignalHandlerId
onDBusObjectManagerClientInterfaceProxyPropertiesChanged obj :: a
obj cb :: DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback
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_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback
cb' = DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback
-> C_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback
wrap_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback
cb
    FunPtr
  C_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback
cb'' <- C_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback
-> IO
     (FunPtr
        C_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback)
mk_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback C_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback
cb'
    a
-> Text
-> FunPtr
     C_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "interface-proxy-properties-changed" FunPtr
  C_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [interfaceProxyPropertiesChanged](#signal:interfaceProxyPropertiesChanged) 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' dBusObjectManagerClient #interfaceProxyPropertiesChanged callback
-- @
-- 
-- 
afterDBusObjectManagerClientInterfaceProxyPropertiesChanged :: (IsDBusObjectManagerClient a, MonadIO m) => a -> DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback -> m SignalHandlerId
afterDBusObjectManagerClientInterfaceProxyPropertiesChanged :: a
-> DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback
-> m SignalHandlerId
afterDBusObjectManagerClientInterfaceProxyPropertiesChanged obj :: a
obj cb :: DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback
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_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback
cb' = DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback
-> C_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback
wrap_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback
cb
    FunPtr
  C_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback
cb'' <- C_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback
-> IO
     (FunPtr
        C_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback)
mk_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback C_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback
cb'
    a
-> Text
-> FunPtr
     C_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "interface-proxy-properties-changed" FunPtr
  C_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data DBusObjectManagerClientInterfaceProxyPropertiesChangedSignalInfo
instance SignalInfo DBusObjectManagerClientInterfaceProxyPropertiesChangedSignalInfo where
    type HaskellCallbackType DBusObjectManagerClientInterfaceProxyPropertiesChangedSignalInfo = DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback cb
        cb'' <- mk_DBusObjectManagerClientInterfaceProxyPropertiesChangedCallback cb'
        connectSignalFunPtr obj "interface-proxy-properties-changed" cb'' connectMode detail

#endif

-- signal DBusObjectManagerClient::interface-proxy-signal
-- | Emitted when a D-Bus signal is received on /@interfaceProxy@/.
-- 
-- This signal exists purely as a convenience to avoid having to
-- connect signals to all interface proxies managed by /@manager@/.
-- 
-- This signal is emitted in the
-- [thread-default main context][g-main-context-push-thread-default]
-- that /@manager@/ was constructed in.
-- 
-- /Since: 2.30/
type DBusObjectManagerClientInterfaceProxySignalCallback =
    Gio.DBusObjectProxy.DBusObjectProxy
    -- ^ /@objectProxy@/: The t'GI.Gio.Objects.DBusObjectProxy.DBusObjectProxy' on which an interface is emitting a D-Bus signal.
    -> Gio.DBusProxy.DBusProxy
    -- ^ /@interfaceProxy@/: The t'GI.Gio.Objects.DBusProxy.DBusProxy' that is emitting a D-Bus signal.
    -> T.Text
    -- ^ /@senderName@/: The sender of the signal or NULL if the connection is not a bus connection.
    -> T.Text
    -- ^ /@signalName@/: The signal name.
    -> GVariant
    -- ^ /@parameters@/: A t'GVariant' tuple with parameters for the signal.
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `DBusObjectManagerClientInterfaceProxySignalCallback`@.
noDBusObjectManagerClientInterfaceProxySignalCallback :: Maybe DBusObjectManagerClientInterfaceProxySignalCallback
noDBusObjectManagerClientInterfaceProxySignalCallback :: Maybe DBusObjectManagerClientInterfaceProxySignalCallback
noDBusObjectManagerClientInterfaceProxySignalCallback = Maybe DBusObjectManagerClientInterfaceProxySignalCallback
forall a. Maybe a
Nothing

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

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

-- | Wrap the callback into a `GClosure`.
genClosure_DBusObjectManagerClientInterfaceProxySignal :: MonadIO m => DBusObjectManagerClientInterfaceProxySignalCallback -> m (GClosure C_DBusObjectManagerClientInterfaceProxySignalCallback)
genClosure_DBusObjectManagerClientInterfaceProxySignal :: DBusObjectManagerClientInterfaceProxySignalCallback
-> m (GClosure
        C_DBusObjectManagerClientInterfaceProxySignalCallback)
genClosure_DBusObjectManagerClientInterfaceProxySignal cb :: DBusObjectManagerClientInterfaceProxySignalCallback
cb = IO (GClosure C_DBusObjectManagerClientInterfaceProxySignalCallback)
-> m (GClosure
        C_DBusObjectManagerClientInterfaceProxySignalCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO
   (GClosure C_DBusObjectManagerClientInterfaceProxySignalCallback)
 -> m (GClosure
         C_DBusObjectManagerClientInterfaceProxySignalCallback))
-> IO
     (GClosure C_DBusObjectManagerClientInterfaceProxySignalCallback)
-> m (GClosure
        C_DBusObjectManagerClientInterfaceProxySignalCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DBusObjectManagerClientInterfaceProxySignalCallback
cb' = DBusObjectManagerClientInterfaceProxySignalCallback
-> C_DBusObjectManagerClientInterfaceProxySignalCallback
wrap_DBusObjectManagerClientInterfaceProxySignalCallback DBusObjectManagerClientInterfaceProxySignalCallback
cb
    C_DBusObjectManagerClientInterfaceProxySignalCallback
-> IO
     (FunPtr C_DBusObjectManagerClientInterfaceProxySignalCallback)
mk_DBusObjectManagerClientInterfaceProxySignalCallback C_DBusObjectManagerClientInterfaceProxySignalCallback
cb' IO (FunPtr C_DBusObjectManagerClientInterfaceProxySignalCallback)
-> (FunPtr C_DBusObjectManagerClientInterfaceProxySignalCallback
    -> IO
         (GClosure C_DBusObjectManagerClientInterfaceProxySignalCallback))
-> IO
     (GClosure C_DBusObjectManagerClientInterfaceProxySignalCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_DBusObjectManagerClientInterfaceProxySignalCallback
-> IO
     (GClosure C_DBusObjectManagerClientInterfaceProxySignalCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `DBusObjectManagerClientInterfaceProxySignalCallback` into a `C_DBusObjectManagerClientInterfaceProxySignalCallback`.
wrap_DBusObjectManagerClientInterfaceProxySignalCallback ::
    DBusObjectManagerClientInterfaceProxySignalCallback ->
    C_DBusObjectManagerClientInterfaceProxySignalCallback
wrap_DBusObjectManagerClientInterfaceProxySignalCallback :: DBusObjectManagerClientInterfaceProxySignalCallback
-> C_DBusObjectManagerClientInterfaceProxySignalCallback
wrap_DBusObjectManagerClientInterfaceProxySignalCallback _cb :: DBusObjectManagerClientInterfaceProxySignalCallback
_cb _ objectProxy :: Ptr DBusObjectProxy
objectProxy interfaceProxy :: Ptr DBusProxy
interfaceProxy senderName :: CString
senderName signalName :: CString
signalName parameters :: Ptr GVariant
parameters _ = do
    DBusObjectProxy
objectProxy' <- ((ManagedPtr DBusObjectProxy -> DBusObjectProxy)
-> Ptr DBusObjectProxy -> IO DBusObjectProxy
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr DBusObjectProxy -> DBusObjectProxy
Gio.DBusObjectProxy.DBusObjectProxy) Ptr DBusObjectProxy
objectProxy
    DBusProxy
interfaceProxy' <- ((ManagedPtr DBusProxy -> DBusProxy)
-> Ptr DBusProxy -> IO DBusProxy
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr DBusProxy -> DBusProxy
Gio.DBusProxy.DBusProxy) Ptr DBusProxy
interfaceProxy
    Text
senderName' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
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
    DBusObjectManagerClientInterfaceProxySignalCallback
_cb  DBusObjectProxy
objectProxy' DBusProxy
interfaceProxy' Text
senderName' Text
signalName' GVariant
parameters'


-- | Connect a signal handler for the [interfaceProxySignal](#signal:interfaceProxySignal) 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' dBusObjectManagerClient #interfaceProxySignal callback
-- @
-- 
-- 
onDBusObjectManagerClientInterfaceProxySignal :: (IsDBusObjectManagerClient a, MonadIO m) => a -> DBusObjectManagerClientInterfaceProxySignalCallback -> m SignalHandlerId
onDBusObjectManagerClientInterfaceProxySignal :: a
-> DBusObjectManagerClientInterfaceProxySignalCallback
-> m SignalHandlerId
onDBusObjectManagerClientInterfaceProxySignal obj :: a
obj cb :: DBusObjectManagerClientInterfaceProxySignalCallback
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_DBusObjectManagerClientInterfaceProxySignalCallback
cb' = DBusObjectManagerClientInterfaceProxySignalCallback
-> C_DBusObjectManagerClientInterfaceProxySignalCallback
wrap_DBusObjectManagerClientInterfaceProxySignalCallback DBusObjectManagerClientInterfaceProxySignalCallback
cb
    FunPtr C_DBusObjectManagerClientInterfaceProxySignalCallback
cb'' <- C_DBusObjectManagerClientInterfaceProxySignalCallback
-> IO
     (FunPtr C_DBusObjectManagerClientInterfaceProxySignalCallback)
mk_DBusObjectManagerClientInterfaceProxySignalCallback C_DBusObjectManagerClientInterfaceProxySignalCallback
cb'
    a
-> Text
-> FunPtr C_DBusObjectManagerClientInterfaceProxySignalCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "interface-proxy-signal" FunPtr C_DBusObjectManagerClientInterfaceProxySignalCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [interfaceProxySignal](#signal:interfaceProxySignal) 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' dBusObjectManagerClient #interfaceProxySignal callback
-- @
-- 
-- 
afterDBusObjectManagerClientInterfaceProxySignal :: (IsDBusObjectManagerClient a, MonadIO m) => a -> DBusObjectManagerClientInterfaceProxySignalCallback -> m SignalHandlerId
afterDBusObjectManagerClientInterfaceProxySignal :: a
-> DBusObjectManagerClientInterfaceProxySignalCallback
-> m SignalHandlerId
afterDBusObjectManagerClientInterfaceProxySignal obj :: a
obj cb :: DBusObjectManagerClientInterfaceProxySignalCallback
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_DBusObjectManagerClientInterfaceProxySignalCallback
cb' = DBusObjectManagerClientInterfaceProxySignalCallback
-> C_DBusObjectManagerClientInterfaceProxySignalCallback
wrap_DBusObjectManagerClientInterfaceProxySignalCallback DBusObjectManagerClientInterfaceProxySignalCallback
cb
    FunPtr C_DBusObjectManagerClientInterfaceProxySignalCallback
cb'' <- C_DBusObjectManagerClientInterfaceProxySignalCallback
-> IO
     (FunPtr C_DBusObjectManagerClientInterfaceProxySignalCallback)
mk_DBusObjectManagerClientInterfaceProxySignalCallback C_DBusObjectManagerClientInterfaceProxySignalCallback
cb'
    a
-> Text
-> FunPtr C_DBusObjectManagerClientInterfaceProxySignalCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "interface-proxy-signal" FunPtr C_DBusObjectManagerClientInterfaceProxySignalCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data DBusObjectManagerClientInterfaceProxySignalSignalInfo
instance SignalInfo DBusObjectManagerClientInterfaceProxySignalSignalInfo where
    type HaskellCallbackType DBusObjectManagerClientInterfaceProxySignalSignalInfo = DBusObjectManagerClientInterfaceProxySignalCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_DBusObjectManagerClientInterfaceProxySignalCallback cb
        cb'' <- mk_DBusObjectManagerClientInterfaceProxySignalCallback cb'
        connectSignalFunPtr obj "interface-proxy-signal" cb'' connectMode detail

#endif

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

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

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

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

-- | Get the value of the “@connection@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dBusObjectManagerClient #connection
-- @
getDBusObjectManagerClientConnection :: (MonadIO m, IsDBusObjectManagerClient o) => o -> m Gio.DBusConnection.DBusConnection
getDBusObjectManagerClientConnection :: o -> m DBusConnection
getDBusObjectManagerClientConnection obj :: o
obj = 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
$ Text -> IO (Maybe DBusConnection) -> IO DBusConnection
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing "getDBusObjectManagerClientConnection" (IO (Maybe DBusConnection) -> IO DBusConnection)
-> IO (Maybe DBusConnection) -> IO 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 "connection" ManagedPtr DBusConnection -> DBusConnection
Gio.DBusConnection.DBusConnection

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

#if defined(ENABLE_OVERLOADING)
data DBusObjectManagerClientConnectionPropertyInfo
instance AttrInfo DBusObjectManagerClientConnectionPropertyInfo where
    type AttrAllowedOps DBusObjectManagerClientConnectionPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DBusObjectManagerClientConnectionPropertyInfo = IsDBusObjectManagerClient
    type AttrSetTypeConstraint DBusObjectManagerClientConnectionPropertyInfo = Gio.DBusConnection.IsDBusConnection
    type AttrTransferTypeConstraint DBusObjectManagerClientConnectionPropertyInfo = Gio.DBusConnection.IsDBusConnection
    type AttrTransferType DBusObjectManagerClientConnectionPropertyInfo = Gio.DBusConnection.DBusConnection
    type AttrGetType DBusObjectManagerClientConnectionPropertyInfo = Gio.DBusConnection.DBusConnection
    type AttrLabel DBusObjectManagerClientConnectionPropertyInfo = "connection"
    type AttrOrigin DBusObjectManagerClientConnectionPropertyInfo = DBusObjectManagerClient
    attrGet = getDBusObjectManagerClientConnection
    attrSet = undefined
    attrTransfer _ v = do
        unsafeCastTo Gio.DBusConnection.DBusConnection v
    attrConstruct = constructDBusObjectManagerClientConnection
    attrClear = undefined
#endif

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

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

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

#if defined(ENABLE_OVERLOADING)
data DBusObjectManagerClientFlagsPropertyInfo
instance AttrInfo DBusObjectManagerClientFlagsPropertyInfo where
    type AttrAllowedOps DBusObjectManagerClientFlagsPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint DBusObjectManagerClientFlagsPropertyInfo = IsDBusObjectManagerClient
    type AttrSetTypeConstraint DBusObjectManagerClientFlagsPropertyInfo = (~) [Gio.Flags.DBusObjectManagerClientFlags]
    type AttrTransferTypeConstraint DBusObjectManagerClientFlagsPropertyInfo = (~) [Gio.Flags.DBusObjectManagerClientFlags]
    type AttrTransferType DBusObjectManagerClientFlagsPropertyInfo = [Gio.Flags.DBusObjectManagerClientFlags]
    type AttrGetType DBusObjectManagerClientFlagsPropertyInfo = [Gio.Flags.DBusObjectManagerClientFlags]
    type AttrLabel DBusObjectManagerClientFlagsPropertyInfo = "flags"
    type AttrOrigin DBusObjectManagerClientFlagsPropertyInfo = DBusObjectManagerClient
    attrGet = getDBusObjectManagerClientFlags
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructDBusObjectManagerClientFlags
    attrClear = undefined
#endif

-- VVV Prop "get-proxy-type-destroy-notify"
   -- Type: TBasicType TPtr
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@get-proxy-type-destroy-notify@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dBusObjectManagerClient #getProxyTypeDestroyNotify
-- @
getDBusObjectManagerClientGetProxyTypeDestroyNotify :: (MonadIO m, IsDBusObjectManagerClient o) => o -> m (Ptr ())
getDBusObjectManagerClientGetProxyTypeDestroyNotify :: o -> m (Ptr ())
getDBusObjectManagerClientGetProxyTypeDestroyNotify obj :: o
obj = IO (Ptr ()) -> m (Ptr ())
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Ptr ()) -> m (Ptr ())) -> IO (Ptr ()) -> m (Ptr ())
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Ptr ())
forall a b. GObject a => a -> String -> IO (Ptr b)
B.Properties.getObjectPropertyPtr o
obj "get-proxy-type-destroy-notify"

-- | Construct a `GValueConstruct` with valid value for the “@get-proxy-type-destroy-notify@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDBusObjectManagerClientGetProxyTypeDestroyNotify :: (IsDBusObjectManagerClient o) => Ptr () -> IO (GValueConstruct o)
constructDBusObjectManagerClientGetProxyTypeDestroyNotify :: Ptr () -> IO (GValueConstruct o)
constructDBusObjectManagerClientGetProxyTypeDestroyNotify val :: Ptr ()
val = String -> Ptr () -> IO (GValueConstruct o)
forall b o. String -> Ptr b -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyPtr "get-proxy-type-destroy-notify" Ptr ()
val

#if defined(ENABLE_OVERLOADING)
data DBusObjectManagerClientGetProxyTypeDestroyNotifyPropertyInfo
instance AttrInfo DBusObjectManagerClientGetProxyTypeDestroyNotifyPropertyInfo where
    type AttrAllowedOps DBusObjectManagerClientGetProxyTypeDestroyNotifyPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint DBusObjectManagerClientGetProxyTypeDestroyNotifyPropertyInfo = IsDBusObjectManagerClient
    type AttrSetTypeConstraint DBusObjectManagerClientGetProxyTypeDestroyNotifyPropertyInfo = (~) (Ptr ())
    type AttrTransferTypeConstraint DBusObjectManagerClientGetProxyTypeDestroyNotifyPropertyInfo = (~) (Ptr ())
    type AttrTransferType DBusObjectManagerClientGetProxyTypeDestroyNotifyPropertyInfo = Ptr ()
    type AttrGetType DBusObjectManagerClientGetProxyTypeDestroyNotifyPropertyInfo = (Ptr ())
    type AttrLabel DBusObjectManagerClientGetProxyTypeDestroyNotifyPropertyInfo = "get-proxy-type-destroy-notify"
    type AttrOrigin DBusObjectManagerClientGetProxyTypeDestroyNotifyPropertyInfo = DBusObjectManagerClient
    attrGet = getDBusObjectManagerClientGetProxyTypeDestroyNotify
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructDBusObjectManagerClientGetProxyTypeDestroyNotify
    attrClear = undefined
#endif

-- VVV Prop "get-proxy-type-func"
   -- Type: TBasicType TPtr
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@get-proxy-type-func@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dBusObjectManagerClient #getProxyTypeFunc
-- @
getDBusObjectManagerClientGetProxyTypeFunc :: (MonadIO m, IsDBusObjectManagerClient o) => o -> m (Ptr ())
getDBusObjectManagerClientGetProxyTypeFunc :: o -> m (Ptr ())
getDBusObjectManagerClientGetProxyTypeFunc obj :: o
obj = IO (Ptr ()) -> m (Ptr ())
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Ptr ()) -> m (Ptr ())) -> IO (Ptr ()) -> m (Ptr ())
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Ptr ())
forall a b. GObject a => a -> String -> IO (Ptr b)
B.Properties.getObjectPropertyPtr o
obj "get-proxy-type-func"

-- | Construct a `GValueConstruct` with valid value for the “@get-proxy-type-func@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDBusObjectManagerClientGetProxyTypeFunc :: (IsDBusObjectManagerClient o) => Ptr () -> IO (GValueConstruct o)
constructDBusObjectManagerClientGetProxyTypeFunc :: Ptr () -> IO (GValueConstruct o)
constructDBusObjectManagerClientGetProxyTypeFunc val :: Ptr ()
val = String -> Ptr () -> IO (GValueConstruct o)
forall b o. String -> Ptr b -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyPtr "get-proxy-type-func" Ptr ()
val

#if defined(ENABLE_OVERLOADING)
data DBusObjectManagerClientGetProxyTypeFuncPropertyInfo
instance AttrInfo DBusObjectManagerClientGetProxyTypeFuncPropertyInfo where
    type AttrAllowedOps DBusObjectManagerClientGetProxyTypeFuncPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint DBusObjectManagerClientGetProxyTypeFuncPropertyInfo = IsDBusObjectManagerClient
    type AttrSetTypeConstraint DBusObjectManagerClientGetProxyTypeFuncPropertyInfo = (~) (Ptr ())
    type AttrTransferTypeConstraint DBusObjectManagerClientGetProxyTypeFuncPropertyInfo = (~) (Ptr ())
    type AttrTransferType DBusObjectManagerClientGetProxyTypeFuncPropertyInfo = Ptr ()
    type AttrGetType DBusObjectManagerClientGetProxyTypeFuncPropertyInfo = (Ptr ())
    type AttrLabel DBusObjectManagerClientGetProxyTypeFuncPropertyInfo = "get-proxy-type-func"
    type AttrOrigin DBusObjectManagerClientGetProxyTypeFuncPropertyInfo = DBusObjectManagerClient
    attrGet = getDBusObjectManagerClientGetProxyTypeFunc
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructDBusObjectManagerClientGetProxyTypeFunc
    attrClear = undefined
#endif

-- VVV Prop "get-proxy-type-user-data"
   -- Type: TBasicType TPtr
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@get-proxy-type-user-data@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dBusObjectManagerClient #getProxyTypeUserData
-- @
getDBusObjectManagerClientGetProxyTypeUserData :: (MonadIO m, IsDBusObjectManagerClient o) => o -> m (Ptr ())
getDBusObjectManagerClientGetProxyTypeUserData :: o -> m (Ptr ())
getDBusObjectManagerClientGetProxyTypeUserData obj :: o
obj = IO (Ptr ()) -> m (Ptr ())
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Ptr ()) -> m (Ptr ())) -> IO (Ptr ()) -> m (Ptr ())
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Ptr ())
forall a b. GObject a => a -> String -> IO (Ptr b)
B.Properties.getObjectPropertyPtr o
obj "get-proxy-type-user-data"

-- | Construct a `GValueConstruct` with valid value for the “@get-proxy-type-user-data@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDBusObjectManagerClientGetProxyTypeUserData :: (IsDBusObjectManagerClient o) => Ptr () -> IO (GValueConstruct o)
constructDBusObjectManagerClientGetProxyTypeUserData :: Ptr () -> IO (GValueConstruct o)
constructDBusObjectManagerClientGetProxyTypeUserData val :: Ptr ()
val = String -> Ptr () -> IO (GValueConstruct o)
forall b o. String -> Ptr b -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyPtr "get-proxy-type-user-data" Ptr ()
val

#if defined(ENABLE_OVERLOADING)
data DBusObjectManagerClientGetProxyTypeUserDataPropertyInfo
instance AttrInfo DBusObjectManagerClientGetProxyTypeUserDataPropertyInfo where
    type AttrAllowedOps DBusObjectManagerClientGetProxyTypeUserDataPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint DBusObjectManagerClientGetProxyTypeUserDataPropertyInfo = IsDBusObjectManagerClient
    type AttrSetTypeConstraint DBusObjectManagerClientGetProxyTypeUserDataPropertyInfo = (~) (Ptr ())
    type AttrTransferTypeConstraint DBusObjectManagerClientGetProxyTypeUserDataPropertyInfo = (~) (Ptr ())
    type AttrTransferType DBusObjectManagerClientGetProxyTypeUserDataPropertyInfo = Ptr ()
    type AttrGetType DBusObjectManagerClientGetProxyTypeUserDataPropertyInfo = (Ptr ())
    type AttrLabel DBusObjectManagerClientGetProxyTypeUserDataPropertyInfo = "get-proxy-type-user-data"
    type AttrOrigin DBusObjectManagerClientGetProxyTypeUserDataPropertyInfo = DBusObjectManagerClient
    attrGet = getDBusObjectManagerClientGetProxyTypeUserData
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructDBusObjectManagerClientGetProxyTypeUserData
    attrClear = undefined
#endif

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

-- | Get the value of the “@name@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dBusObjectManagerClient #name
-- @
getDBusObjectManagerClientName :: (MonadIO m, IsDBusObjectManagerClient o) => o -> m T.Text
getDBusObjectManagerClientName :: o -> m Text
getDBusObjectManagerClientName obj :: o
obj = 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
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing "getDBusObjectManagerClientName" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO 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 "name"

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

#if defined(ENABLE_OVERLOADING)
data DBusObjectManagerClientNamePropertyInfo
instance AttrInfo DBusObjectManagerClientNamePropertyInfo where
    type AttrAllowedOps DBusObjectManagerClientNamePropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DBusObjectManagerClientNamePropertyInfo = IsDBusObjectManagerClient
    type AttrSetTypeConstraint DBusObjectManagerClientNamePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint DBusObjectManagerClientNamePropertyInfo = (~) T.Text
    type AttrTransferType DBusObjectManagerClientNamePropertyInfo = T.Text
    type AttrGetType DBusObjectManagerClientNamePropertyInfo = T.Text
    type AttrLabel DBusObjectManagerClientNamePropertyInfo = "name"
    type AttrOrigin DBusObjectManagerClientNamePropertyInfo = DBusObjectManagerClient
    attrGet = getDBusObjectManagerClientName
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructDBusObjectManagerClientName
    attrClear = undefined
#endif

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

-- | Get the value of the “@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' dBusObjectManagerClient #nameOwner
-- @
getDBusObjectManagerClientNameOwner :: (MonadIO m, IsDBusObjectManagerClient o) => o -> m (Maybe T.Text)
getDBusObjectManagerClientNameOwner :: o -> m (Maybe Text)
getDBusObjectManagerClientNameOwner 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 "name-owner"

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

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

-- | Get the value of the “@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' dBusObjectManagerClient #objectPath
-- @
getDBusObjectManagerClientObjectPath :: (MonadIO m, IsDBusObjectManagerClient o) => o -> m (Maybe T.Text)
getDBusObjectManagerClientObjectPath :: o -> m (Maybe Text)
getDBusObjectManagerClientObjectPath 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 "object-path"

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

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

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DBusObjectManagerClient
type instance O.AttributeList DBusObjectManagerClient = DBusObjectManagerClientAttributeList
type DBusObjectManagerClientAttributeList = ('[ '("busType", DBusObjectManagerClientBusTypePropertyInfo), '("connection", DBusObjectManagerClientConnectionPropertyInfo), '("flags", DBusObjectManagerClientFlagsPropertyInfo), '("getProxyTypeDestroyNotify", DBusObjectManagerClientGetProxyTypeDestroyNotifyPropertyInfo), '("getProxyTypeFunc", DBusObjectManagerClientGetProxyTypeFuncPropertyInfo), '("getProxyTypeUserData", DBusObjectManagerClientGetProxyTypeUserDataPropertyInfo), '("name", DBusObjectManagerClientNamePropertyInfo), '("nameOwner", DBusObjectManagerClientNameOwnerPropertyInfo), '("objectPath", DBusObjectManagerClientObjectPathPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
dBusObjectManagerClientBusType :: AttrLabelProxy "busType"
dBusObjectManagerClientBusType = AttrLabelProxy

dBusObjectManagerClientConnection :: AttrLabelProxy "connection"
dBusObjectManagerClientConnection = AttrLabelProxy

dBusObjectManagerClientFlags :: AttrLabelProxy "flags"
dBusObjectManagerClientFlags = AttrLabelProxy

dBusObjectManagerClientGetProxyTypeDestroyNotify :: AttrLabelProxy "getProxyTypeDestroyNotify"
dBusObjectManagerClientGetProxyTypeDestroyNotify = AttrLabelProxy

dBusObjectManagerClientGetProxyTypeFunc :: AttrLabelProxy "getProxyTypeFunc"
dBusObjectManagerClientGetProxyTypeFunc = AttrLabelProxy

dBusObjectManagerClientGetProxyTypeUserData :: AttrLabelProxy "getProxyTypeUserData"
dBusObjectManagerClientGetProxyTypeUserData = AttrLabelProxy

dBusObjectManagerClientName :: AttrLabelProxy "name"
dBusObjectManagerClientName = AttrLabelProxy

dBusObjectManagerClientNameOwner :: AttrLabelProxy "nameOwner"
dBusObjectManagerClientNameOwner = AttrLabelProxy

dBusObjectManagerClientObjectPath :: AttrLabelProxy "objectPath"
dBusObjectManagerClientObjectPath = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList DBusObjectManagerClient = DBusObjectManagerClientSignalList
type DBusObjectManagerClientSignalList = ('[ '("interfaceAdded", Gio.DBusObjectManager.DBusObjectManagerInterfaceAddedSignalInfo), '("interfaceProxyPropertiesChanged", DBusObjectManagerClientInterfaceProxyPropertiesChangedSignalInfo), '("interfaceProxySignal", DBusObjectManagerClientInterfaceProxySignalSignalInfo), '("interfaceRemoved", Gio.DBusObjectManager.DBusObjectManagerInterfaceRemovedSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("objectAdded", Gio.DBusObjectManager.DBusObjectManagerObjectAddedSignalInfo), '("objectRemoved", Gio.DBusObjectManager.DBusObjectManagerObjectRemovedSignalInfo)] :: [(Symbol, *)])

#endif

-- method DBusObjectManagerClient::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 passed to g_dbus_object_manager_client_new()."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Gio" , name = "DBusObjectManagerClient" })
-- throws : True
-- Skip return : False

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

-- | Finishes an operation started with 'GI.Gio.Objects.DBusObjectManagerClient.dBusObjectManagerClientNew'.
-- 
-- /Since: 2.30/
dBusObjectManagerClientNewFinish ::
    (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' passed to 'GI.Gio.Objects.DBusObjectManagerClient.dBusObjectManagerClientNew'.
    -> m DBusObjectManagerClient
    -- ^ __Returns:__ A
    --   t'GI.Gio.Objects.DBusObjectManagerClient.DBusObjectManagerClient' object or 'P.Nothing' if /@error@/ is set. Free
    --   with 'GI.GObject.Objects.Object.objectUnref'. /(Can throw 'Data.GI.Base.GError.GError')/
dBusObjectManagerClientNewFinish :: a -> m DBusObjectManagerClient
dBusObjectManagerClientNewFinish res :: a
res = IO DBusObjectManagerClient -> m DBusObjectManagerClient
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DBusObjectManagerClient -> m DBusObjectManagerClient)
-> IO DBusObjectManagerClient -> m DBusObjectManagerClient
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 DBusObjectManagerClient -> IO () -> IO DBusObjectManagerClient
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr DBusObjectManagerClient
result <- (Ptr (Ptr GError) -> IO (Ptr DBusObjectManagerClient))
-> IO (Ptr DBusObjectManagerClient)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr DBusObjectManagerClient))
 -> IO (Ptr DBusObjectManagerClient))
-> (Ptr (Ptr GError) -> IO (Ptr DBusObjectManagerClient))
-> IO (Ptr DBusObjectManagerClient)
forall a b. (a -> b) -> a -> b
$ Ptr AsyncResult
-> Ptr (Ptr GError) -> IO (Ptr DBusObjectManagerClient)
g_dbus_object_manager_client_new_finish Ptr AsyncResult
res'
        Text -> Ptr DBusObjectManagerClient -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusObjectManagerClientNewFinish" Ptr DBusObjectManagerClient
result
        DBusObjectManagerClient
result' <- ((ManagedPtr DBusObjectManagerClient -> DBusObjectManagerClient)
-> Ptr DBusObjectManagerClient -> IO DBusObjectManagerClient
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr DBusObjectManagerClient -> DBusObjectManagerClient
DBusObjectManagerClient) Ptr DBusObjectManagerClient
result
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
res
        DBusObjectManagerClient -> IO DBusObjectManagerClient
forall (m :: * -> *) a. Monad m => a -> m a
return DBusObjectManagerClient
result'
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method DBusObjectManagerClient::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 passed to g_dbus_object_manager_client_new_for_bus()."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Gio" , name = "DBusObjectManagerClient" })
-- throws : True
-- Skip return : False

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

-- | Finishes an operation started with 'GI.Gio.Objects.DBusObjectManagerClient.dBusObjectManagerClientNewForBus'.
-- 
-- /Since: 2.30/
dBusObjectManagerClientNewForBusFinish ::
    (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' passed to 'GI.Gio.Objects.DBusObjectManagerClient.dBusObjectManagerClientNewForBus'.
    -> m DBusObjectManagerClient
    -- ^ __Returns:__ A
    --   t'GI.Gio.Objects.DBusObjectManagerClient.DBusObjectManagerClient' object or 'P.Nothing' if /@error@/ is set. Free
    --   with 'GI.GObject.Objects.Object.objectUnref'. /(Can throw 'Data.GI.Base.GError.GError')/
dBusObjectManagerClientNewForBusFinish :: a -> m DBusObjectManagerClient
dBusObjectManagerClientNewForBusFinish res :: a
res = IO DBusObjectManagerClient -> m DBusObjectManagerClient
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DBusObjectManagerClient -> m DBusObjectManagerClient)
-> IO DBusObjectManagerClient -> m DBusObjectManagerClient
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 DBusObjectManagerClient -> IO () -> IO DBusObjectManagerClient
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr DBusObjectManagerClient
result <- (Ptr (Ptr GError) -> IO (Ptr DBusObjectManagerClient))
-> IO (Ptr DBusObjectManagerClient)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr DBusObjectManagerClient))
 -> IO (Ptr DBusObjectManagerClient))
-> (Ptr (Ptr GError) -> IO (Ptr DBusObjectManagerClient))
-> IO (Ptr DBusObjectManagerClient)
forall a b. (a -> b) -> a -> b
$ Ptr AsyncResult
-> Ptr (Ptr GError) -> IO (Ptr DBusObjectManagerClient)
g_dbus_object_manager_client_new_for_bus_finish Ptr AsyncResult
res'
        Text -> Ptr DBusObjectManagerClient -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusObjectManagerClientNewForBusFinish" Ptr DBusObjectManagerClient
result
        DBusObjectManagerClient
result' <- ((ManagedPtr DBusObjectManagerClient -> DBusObjectManagerClient)
-> Ptr DBusObjectManagerClient -> IO DBusObjectManagerClient
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr DBusObjectManagerClient -> DBusObjectManagerClient
DBusObjectManagerClient) Ptr DBusObjectManagerClient
result
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
res
        DBusObjectManagerClient -> IO DBusObjectManagerClient
forall (m :: * -> *) a. Monad m => a -> m a
return DBusObjectManagerClient
result'
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method DBusObjectManagerClient::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 = "DBusObjectManagerClientFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "Zero or more flags from the #GDBusObjectManagerClientFlags enumeration."
--                 , 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 "The owner of the control object (unique or well-known name)."
--                 , 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 "The object path of the control object."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "get_proxy_type_func"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusProxyTypeFunc" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A #GDBusProxyTypeFunc function or %NULL to always construct #GDBusProxy proxies."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeNotified
--           , argClosure = 5
--           , argDestroy = 6
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "get_proxy_type_user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "User data to pass to @get_proxy_type_func."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "get_proxy_type_destroy_notify"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "DestroyNotify" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "Free function for @get_proxy_type_user_data or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , 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 = "DBusObjectManagerClient" })
-- throws : True
-- Skip return : False

foreign import ccall "g_dbus_object_manager_client_new_for_bus_sync" g_dbus_object_manager_client_new_for_bus_sync :: 
    CInt ->                                 -- bus_type : TInterface (Name {namespace = "Gio", name = "BusType"})
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gio", name = "DBusObjectManagerClientFlags"})
    CString ->                              -- name : TBasicType TUTF8
    CString ->                              -- object_path : TBasicType TUTF8
    FunPtr Gio.Callbacks.C_DBusProxyTypeFunc -> -- get_proxy_type_func : TInterface (Name {namespace = "Gio", name = "DBusProxyTypeFunc"})
    Ptr () ->                               -- get_proxy_type_user_data : TBasicType TPtr
    FunPtr GLib.Callbacks.C_DestroyNotify -> -- get_proxy_type_destroy_notify : TInterface (Name {namespace = "GLib", name = "DestroyNotify"})
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr DBusObjectManagerClient)

-- | Like 'GI.Gio.Objects.DBusObjectManagerClient.dBusObjectManagerClientNewSync' but takes a t'GI.Gio.Enums.BusType' instead
-- of a t'GI.Gio.Objects.DBusConnection.DBusConnection'.
-- 
-- This is a synchronous failable constructor - the calling thread is
-- blocked until a reply is received. See 'GI.Gio.Objects.DBusObjectManagerClient.dBusObjectManagerClientNewForBus'
-- for the asynchronous version.
-- 
-- /Since: 2.30/
dBusObjectManagerClientNewForBusSync ::
    (B.CallStack.HasCallStack, MonadIO m, Gio.Cancellable.IsCancellable a) =>
    Gio.Enums.BusType
    -- ^ /@busType@/: A t'GI.Gio.Enums.BusType'.
    -> [Gio.Flags.DBusObjectManagerClientFlags]
    -- ^ /@flags@/: Zero or more flags from the t'GI.Gio.Flags.DBusObjectManagerClientFlags' enumeration.
    -> T.Text
    -- ^ /@name@/: The owner of the control object (unique or well-known name).
    -> T.Text
    -- ^ /@objectPath@/: The object path of the control object.
    -> Maybe (Gio.Callbacks.DBusProxyTypeFunc)
    -- ^ /@getProxyTypeFunc@/: A t'GI.Gio.Callbacks.DBusProxyTypeFunc' function or 'P.Nothing' to always construct t'GI.Gio.Objects.DBusProxy.DBusProxy' proxies.
    -> Maybe (a)
    -- ^ /@cancellable@/: A t'GI.Gio.Objects.Cancellable.Cancellable' or 'P.Nothing'
    -> m DBusObjectManagerClient
    -- ^ __Returns:__ A
    --   t'GI.Gio.Objects.DBusObjectManagerClient.DBusObjectManagerClient' object or 'P.Nothing' if /@error@/ is set. Free
    --   with 'GI.GObject.Objects.Object.objectUnref'. /(Can throw 'Data.GI.Base.GError.GError')/
dBusObjectManagerClientNewForBusSync :: BusType
-> [DBusObjectManagerClientFlags]
-> Text
-> Text
-> Maybe DBusProxyTypeFunc
-> Maybe a
-> m DBusObjectManagerClient
dBusObjectManagerClientNewForBusSync busType :: BusType
busType flags :: [DBusObjectManagerClientFlags]
flags name :: Text
name objectPath :: Text
objectPath getProxyTypeFunc :: Maybe DBusProxyTypeFunc
getProxyTypeFunc cancellable :: Maybe a
cancellable = IO DBusObjectManagerClient -> m DBusObjectManagerClient
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DBusObjectManagerClient -> m DBusObjectManagerClient)
-> IO DBusObjectManagerClient -> m DBusObjectManagerClient
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' = [DBusObjectManagerClientFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [DBusObjectManagerClientFlags]
flags
    CString
name' <- Text -> IO CString
textToCString Text
name
    CString
objectPath' <- Text -> IO CString
textToCString Text
objectPath
    FunPtr C_DBusProxyTypeFunc
maybeGetProxyTypeFunc <- case Maybe DBusProxyTypeFunc
getProxyTypeFunc of
        Nothing -> FunPtr C_DBusProxyTypeFunc -> IO (FunPtr C_DBusProxyTypeFunc)
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_DBusProxyTypeFunc
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
        Just jGetProxyTypeFunc :: DBusProxyTypeFunc
jGetProxyTypeFunc -> do
            FunPtr C_DBusProxyTypeFunc
jGetProxyTypeFunc' <- C_DBusProxyTypeFunc -> IO (FunPtr C_DBusProxyTypeFunc)
Gio.Callbacks.mk_DBusProxyTypeFunc (Maybe (Ptr (FunPtr C_DBusProxyTypeFunc))
-> DBusProxyTypeFunc_WithClosures -> C_DBusProxyTypeFunc
Gio.Callbacks.wrap_DBusProxyTypeFunc Maybe (Ptr (FunPtr C_DBusProxyTypeFunc))
forall a. Maybe a
Nothing (DBusProxyTypeFunc -> DBusProxyTypeFunc_WithClosures
Gio.Callbacks.drop_closures_DBusProxyTypeFunc DBusProxyTypeFunc
jGetProxyTypeFunc))
            FunPtr C_DBusProxyTypeFunc -> IO (FunPtr C_DBusProxyTypeFunc)
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_DBusProxyTypeFunc
jGetProxyTypeFunc'
    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'
    let getProxyTypeUserData :: Ptr ()
getProxyTypeUserData = FunPtr C_DBusProxyTypeFunc -> Ptr ()
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr C_DBusProxyTypeFunc
maybeGetProxyTypeFunc
    let getProxyTypeDestroyNotify :: FunPtr (Ptr a -> IO ())
getProxyTypeDestroyNotify = FunPtr (Ptr a -> IO ())
forall a. FunPtr (Ptr a -> IO ())
safeFreeFunPtrPtr
    IO DBusObjectManagerClient -> IO () -> IO DBusObjectManagerClient
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr DBusObjectManagerClient
result <- (Ptr (Ptr GError) -> IO (Ptr DBusObjectManagerClient))
-> IO (Ptr DBusObjectManagerClient)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr DBusObjectManagerClient))
 -> IO (Ptr DBusObjectManagerClient))
-> (Ptr (Ptr GError) -> IO (Ptr DBusObjectManagerClient))
-> IO (Ptr DBusObjectManagerClient)
forall a b. (a -> b) -> a -> b
$ CInt
-> CUInt
-> CString
-> CString
-> FunPtr C_DBusProxyTypeFunc
-> Ptr ()
-> FunPtr C_DestroyNotify
-> Ptr Cancellable
-> Ptr (Ptr GError)
-> IO (Ptr DBusObjectManagerClient)
g_dbus_object_manager_client_new_for_bus_sync CInt
busType' CUInt
flags' CString
name' CString
objectPath' FunPtr C_DBusProxyTypeFunc
maybeGetProxyTypeFunc Ptr ()
getProxyTypeUserData FunPtr C_DestroyNotify
forall a. FunPtr (Ptr a -> IO ())
getProxyTypeDestroyNotify Ptr Cancellable
maybeCancellable
        Text -> Ptr DBusObjectManagerClient -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusObjectManagerClientNewForBusSync" Ptr DBusObjectManagerClient
result
        DBusObjectManagerClient
result' <- ((ManagedPtr DBusObjectManagerClient -> DBusObjectManagerClient)
-> Ptr DBusObjectManagerClient -> IO DBusObjectManagerClient
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr DBusObjectManagerClient -> DBusObjectManagerClient
DBusObjectManagerClient) Ptr DBusObjectManagerClient
result
        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'
        DBusObjectManagerClient -> IO DBusObjectManagerClient
forall (m :: * -> *) a. Monad m => a -> m a
return DBusObjectManagerClient
result'
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
objectPath'
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method DBusObjectManagerClient::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 = "DBusObjectManagerClientFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "Zero or more flags from the #GDBusObjectManagerClientFlags enumeration."
--                 , 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
--                       "The owner of the control object (unique or well-known name), or %NULL when not using 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 "The object path of the control object."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "get_proxy_type_func"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusProxyTypeFunc" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A #GDBusProxyTypeFunc function or %NULL to always construct #GDBusProxy proxies."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeNotified
--           , argClosure = 5
--           , argDestroy = 6
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "get_proxy_type_user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "User data to pass to @get_proxy_type_func."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "get_proxy_type_destroy_notify"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "DestroyNotify" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "Free function for @get_proxy_type_user_data or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , 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 = "DBusObjectManagerClient" })
-- throws : True
-- Skip return : False

foreign import ccall "g_dbus_object_manager_client_new_sync" g_dbus_object_manager_client_new_sync :: 
    Ptr Gio.DBusConnection.DBusConnection -> -- connection : TInterface (Name {namespace = "Gio", name = "DBusConnection"})
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gio", name = "DBusObjectManagerClientFlags"})
    CString ->                              -- name : TBasicType TUTF8
    CString ->                              -- object_path : TBasicType TUTF8
    FunPtr Gio.Callbacks.C_DBusProxyTypeFunc -> -- get_proxy_type_func : TInterface (Name {namespace = "Gio", name = "DBusProxyTypeFunc"})
    Ptr () ->                               -- get_proxy_type_user_data : TBasicType TPtr
    FunPtr GLib.Callbacks.C_DestroyNotify -> -- get_proxy_type_destroy_notify : TInterface (Name {namespace = "GLib", name = "DestroyNotify"})
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr DBusObjectManagerClient)

-- | Creates a new t'GI.Gio.Objects.DBusObjectManagerClient.DBusObjectManagerClient' object.
-- 
-- This is a synchronous failable constructor - the calling thread is
-- blocked until a reply is received. See 'GI.Gio.Objects.DBusObjectManagerClient.dBusObjectManagerClientNew'
-- for the asynchronous version.
-- 
-- /Since: 2.30/
dBusObjectManagerClientNewSync ::
    (B.CallStack.HasCallStack, MonadIO m, Gio.DBusConnection.IsDBusConnection a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@connection@/: A t'GI.Gio.Objects.DBusConnection.DBusConnection'.
    -> [Gio.Flags.DBusObjectManagerClientFlags]
    -- ^ /@flags@/: Zero or more flags from the t'GI.Gio.Flags.DBusObjectManagerClientFlags' enumeration.
    -> Maybe (T.Text)
    -- ^ /@name@/: The owner of the control object (unique or well-known name), or 'P.Nothing' when not using a message bus connection.
    -> T.Text
    -- ^ /@objectPath@/: The object path of the control object.
    -> Maybe (Gio.Callbacks.DBusProxyTypeFunc)
    -- ^ /@getProxyTypeFunc@/: A t'GI.Gio.Callbacks.DBusProxyTypeFunc' function or 'P.Nothing' to always construct t'GI.Gio.Objects.DBusProxy.DBusProxy' proxies.
    -> Maybe (b)
    -- ^ /@cancellable@/: A t'GI.Gio.Objects.Cancellable.Cancellable' or 'P.Nothing'
    -> m DBusObjectManagerClient
    -- ^ __Returns:__ A
    --   t'GI.Gio.Objects.DBusObjectManagerClient.DBusObjectManagerClient' object or 'P.Nothing' if /@error@/ is set. Free
    --   with 'GI.GObject.Objects.Object.objectUnref'. /(Can throw 'Data.GI.Base.GError.GError')/
dBusObjectManagerClientNewSync :: a
-> [DBusObjectManagerClientFlags]
-> Maybe Text
-> Text
-> Maybe DBusProxyTypeFunc
-> Maybe b
-> m DBusObjectManagerClient
dBusObjectManagerClientNewSync connection :: a
connection flags :: [DBusObjectManagerClientFlags]
flags name :: Maybe Text
name objectPath :: Text
objectPath getProxyTypeFunc :: Maybe DBusProxyTypeFunc
getProxyTypeFunc cancellable :: Maybe b
cancellable = IO DBusObjectManagerClient -> m DBusObjectManagerClient
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DBusObjectManagerClient -> m DBusObjectManagerClient)
-> IO DBusObjectManagerClient -> m DBusObjectManagerClient
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' = [DBusObjectManagerClientFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [DBusObjectManagerClientFlags]
flags
    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
    FunPtr C_DBusProxyTypeFunc
maybeGetProxyTypeFunc <- case Maybe DBusProxyTypeFunc
getProxyTypeFunc of
        Nothing -> FunPtr C_DBusProxyTypeFunc -> IO (FunPtr C_DBusProxyTypeFunc)
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_DBusProxyTypeFunc
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
        Just jGetProxyTypeFunc :: DBusProxyTypeFunc
jGetProxyTypeFunc -> do
            FunPtr C_DBusProxyTypeFunc
jGetProxyTypeFunc' <- C_DBusProxyTypeFunc -> IO (FunPtr C_DBusProxyTypeFunc)
Gio.Callbacks.mk_DBusProxyTypeFunc (Maybe (Ptr (FunPtr C_DBusProxyTypeFunc))
-> DBusProxyTypeFunc_WithClosures -> C_DBusProxyTypeFunc
Gio.Callbacks.wrap_DBusProxyTypeFunc Maybe (Ptr (FunPtr C_DBusProxyTypeFunc))
forall a. Maybe a
Nothing (DBusProxyTypeFunc -> DBusProxyTypeFunc_WithClosures
Gio.Callbacks.drop_closures_DBusProxyTypeFunc DBusProxyTypeFunc
jGetProxyTypeFunc))
            FunPtr C_DBusProxyTypeFunc -> IO (FunPtr C_DBusProxyTypeFunc)
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_DBusProxyTypeFunc
jGetProxyTypeFunc'
    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'
    let getProxyTypeUserData :: Ptr ()
getProxyTypeUserData = FunPtr C_DBusProxyTypeFunc -> Ptr ()
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr C_DBusProxyTypeFunc
maybeGetProxyTypeFunc
    let getProxyTypeDestroyNotify :: FunPtr (Ptr a -> IO ())
getProxyTypeDestroyNotify = FunPtr (Ptr a -> IO ())
forall a. FunPtr (Ptr a -> IO ())
safeFreeFunPtrPtr
    IO DBusObjectManagerClient -> IO () -> IO DBusObjectManagerClient
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr DBusObjectManagerClient
result <- (Ptr (Ptr GError) -> IO (Ptr DBusObjectManagerClient))
-> IO (Ptr DBusObjectManagerClient)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr DBusObjectManagerClient))
 -> IO (Ptr DBusObjectManagerClient))
-> (Ptr (Ptr GError) -> IO (Ptr DBusObjectManagerClient))
-> IO (Ptr DBusObjectManagerClient)
forall a b. (a -> b) -> a -> b
$ Ptr DBusConnection
-> CUInt
-> CString
-> CString
-> FunPtr C_DBusProxyTypeFunc
-> Ptr ()
-> FunPtr C_DestroyNotify
-> Ptr Cancellable
-> Ptr (Ptr GError)
-> IO (Ptr DBusObjectManagerClient)
g_dbus_object_manager_client_new_sync Ptr DBusConnection
connection' CUInt
flags' CString
maybeName CString
objectPath' FunPtr C_DBusProxyTypeFunc
maybeGetProxyTypeFunc Ptr ()
getProxyTypeUserData FunPtr C_DestroyNotify
forall a. FunPtr (Ptr a -> IO ())
getProxyTypeDestroyNotify Ptr Cancellable
maybeCancellable
        Text -> Ptr DBusObjectManagerClient -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusObjectManagerClientNewSync" Ptr DBusObjectManagerClient
result
        DBusObjectManagerClient
result' <- ((ManagedPtr DBusObjectManagerClient -> DBusObjectManagerClient)
-> Ptr DBusObjectManagerClient -> IO DBusObjectManagerClient
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr DBusObjectManagerClient -> DBusObjectManagerClient
DBusObjectManagerClient) Ptr DBusObjectManagerClient
result
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
connection
        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'
        DBusObjectManagerClient -> IO DBusObjectManagerClient
forall (m :: * -> *) a. Monad m => a -> m a
return DBusObjectManagerClient
result'
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeName
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
objectPath'
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method DBusObjectManagerClient::get_connection
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "manager"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "DBusObjectManagerClient" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusObjectManagerClient"
--                 , 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_object_manager_client_get_connection" g_dbus_object_manager_client_get_connection :: 
    Ptr DBusObjectManagerClient ->          -- manager : TInterface (Name {namespace = "Gio", name = "DBusObjectManagerClient"})
    IO (Ptr Gio.DBusConnection.DBusConnection)

-- | Gets the t'GI.Gio.Objects.DBusConnection.DBusConnection' used by /@manager@/.
-- 
-- /Since: 2.30/
dBusObjectManagerClientGetConnection ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusObjectManagerClient a) =>
    a
    -- ^ /@manager@/: A t'GI.Gio.Objects.DBusObjectManagerClient.DBusObjectManagerClient'
    -> m Gio.DBusConnection.DBusConnection
    -- ^ __Returns:__ A t'GI.Gio.Objects.DBusConnection.DBusConnection' object. Do not free,
    --   the object belongs to /@manager@/.
dBusObjectManagerClientGetConnection :: a -> m DBusConnection
dBusObjectManagerClientGetConnection manager :: a
manager = 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 DBusObjectManagerClient
manager' <- a -> IO (Ptr DBusObjectManagerClient)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
    Ptr DBusConnection
result <- Ptr DBusObjectManagerClient -> IO (Ptr DBusConnection)
g_dbus_object_manager_client_get_connection Ptr DBusObjectManagerClient
manager'
    Text -> Ptr DBusConnection -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusObjectManagerClientGetConnection" 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
manager
    DBusConnection -> IO DBusConnection
forall (m :: * -> *) a. Monad m => a -> m a
return DBusConnection
result'

#if defined(ENABLE_OVERLOADING)
data DBusObjectManagerClientGetConnectionMethodInfo
instance (signature ~ (m Gio.DBusConnection.DBusConnection), MonadIO m, IsDBusObjectManagerClient a) => O.MethodInfo DBusObjectManagerClientGetConnectionMethodInfo a signature where
    overloadedMethod = dBusObjectManagerClientGetConnection

#endif

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

foreign import ccall "g_dbus_object_manager_client_get_flags" g_dbus_object_manager_client_get_flags :: 
    Ptr DBusObjectManagerClient ->          -- manager : TInterface (Name {namespace = "Gio", name = "DBusObjectManagerClient"})
    IO CUInt

-- | Gets the flags that /@manager@/ was constructed with.
-- 
-- /Since: 2.30/
dBusObjectManagerClientGetFlags ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusObjectManagerClient a) =>
    a
    -- ^ /@manager@/: A t'GI.Gio.Objects.DBusObjectManagerClient.DBusObjectManagerClient'
    -> m [Gio.Flags.DBusObjectManagerClientFlags]
    -- ^ __Returns:__ Zero of more flags from the t'GI.Gio.Flags.DBusObjectManagerClientFlags'
    -- enumeration.
dBusObjectManagerClientGetFlags :: a -> m [DBusObjectManagerClientFlags]
dBusObjectManagerClientGetFlags manager :: a
manager = IO [DBusObjectManagerClientFlags]
-> m [DBusObjectManagerClientFlags]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [DBusObjectManagerClientFlags]
 -> m [DBusObjectManagerClientFlags])
-> IO [DBusObjectManagerClientFlags]
-> m [DBusObjectManagerClientFlags]
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusObjectManagerClient
manager' <- a -> IO (Ptr DBusObjectManagerClient)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
    CUInt
result <- Ptr DBusObjectManagerClient -> IO CUInt
g_dbus_object_manager_client_get_flags Ptr DBusObjectManagerClient
manager'
    let result' :: [DBusObjectManagerClientFlags]
result' = CUInt -> [DBusObjectManagerClientFlags]
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
manager
    [DBusObjectManagerClientFlags] -> IO [DBusObjectManagerClientFlags]
forall (m :: * -> *) a. Monad m => a -> m a
return [DBusObjectManagerClientFlags]
result'

#if defined(ENABLE_OVERLOADING)
data DBusObjectManagerClientGetFlagsMethodInfo
instance (signature ~ (m [Gio.Flags.DBusObjectManagerClientFlags]), MonadIO m, IsDBusObjectManagerClient a) => O.MethodInfo DBusObjectManagerClientGetFlagsMethodInfo a signature where
    overloadedMethod = dBusObjectManagerClientGetFlags

#endif

-- method DBusObjectManagerClient::get_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "manager"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "DBusObjectManagerClient" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusObjectManagerClient"
--                 , 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_object_manager_client_get_name" g_dbus_object_manager_client_get_name :: 
    Ptr DBusObjectManagerClient ->          -- manager : TInterface (Name {namespace = "Gio", name = "DBusObjectManagerClient"})
    IO CString

-- | Gets the name that /@manager@/ is for, or 'P.Nothing' if not a message bus
-- connection.
-- 
-- /Since: 2.30/
dBusObjectManagerClientGetName ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusObjectManagerClient a) =>
    a
    -- ^ /@manager@/: A t'GI.Gio.Objects.DBusObjectManagerClient.DBusObjectManagerClient'
    -> m T.Text
    -- ^ __Returns:__ A unique or well-known name. Do not free, the string
    -- belongs to /@manager@/.
dBusObjectManagerClientGetName :: a -> m Text
dBusObjectManagerClientGetName manager :: a
manager = 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 DBusObjectManagerClient
manager' <- a -> IO (Ptr DBusObjectManagerClient)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
    CString
result <- Ptr DBusObjectManagerClient -> IO CString
g_dbus_object_manager_client_get_name Ptr DBusObjectManagerClient
manager'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusObjectManagerClientGetName" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
manager
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data DBusObjectManagerClientGetNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDBusObjectManagerClient a) => O.MethodInfo DBusObjectManagerClientGetNameMethodInfo a signature where
    overloadedMethod = dBusObjectManagerClientGetName

#endif

-- method DBusObjectManagerClient::get_name_owner
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "manager"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "DBusObjectManagerClient" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusObjectManagerClient."
--                 , 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_object_manager_client_get_name_owner" g_dbus_object_manager_client_get_name_owner :: 
    Ptr DBusObjectManagerClient ->          -- manager : TInterface (Name {namespace = "Gio", name = "DBusObjectManagerClient"})
    IO CString

-- | The unique name that owns the name that /@manager@/ is for or 'P.Nothing' if
-- no-one currently owns that name. You can connect to the
-- [notify]("GI.GObject.Objects.Object#signal:notify") signal to track changes to the
-- t'GI.Gio.Objects.DBusObjectManagerClient.DBusObjectManagerClient':@/name-owner/@ property.
-- 
-- /Since: 2.30/
dBusObjectManagerClientGetNameOwner ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusObjectManagerClient a) =>
    a
    -- ^ /@manager@/: A t'GI.Gio.Objects.DBusObjectManagerClient.DBusObjectManagerClient'.
    -> m (Maybe T.Text)
    -- ^ __Returns:__ The name owner or 'P.Nothing' if no name owner
    -- exists. Free with 'GI.GLib.Functions.free'.
dBusObjectManagerClientGetNameOwner :: a -> m (Maybe Text)
dBusObjectManagerClientGetNameOwner manager :: a
manager = 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 DBusObjectManagerClient
manager' <- a -> IO (Ptr DBusObjectManagerClient)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
    CString
result <- Ptr DBusObjectManagerClient -> IO CString
g_dbus_object_manager_client_get_name_owner Ptr DBusObjectManagerClient
manager'
    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
manager
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

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

#endif

-- method DBusObjectManagerClient::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 = "DBusObjectManagerClientFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "Zero or more flags from the #GDBusObjectManagerClientFlags enumeration."
--                 , 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 "The owner of the control object (unique or well-known name)."
--                 , 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 "The object path of the control object."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "get_proxy_type_func"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusProxyTypeFunc" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A #GDBusProxyTypeFunc function or %NULL to always construct #GDBusProxy proxies."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeNotified
--           , argClosure = 5
--           , argDestroy = 6
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "get_proxy_type_user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "User data to pass to @get_proxy_type_func."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "get_proxy_type_destroy_notify"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "DestroyNotify" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "Free function for @get_proxy_type_user_data or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , 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."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = 9
--           , 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_object_manager_client_new" g_dbus_object_manager_client_new :: 
    Ptr Gio.DBusConnection.DBusConnection -> -- connection : TInterface (Name {namespace = "Gio", name = "DBusConnection"})
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gio", name = "DBusObjectManagerClientFlags"})
    CString ->                              -- name : TBasicType TUTF8
    CString ->                              -- object_path : TBasicType TUTF8
    FunPtr Gio.Callbacks.C_DBusProxyTypeFunc -> -- get_proxy_type_func : TInterface (Name {namespace = "Gio", name = "DBusProxyTypeFunc"})
    Ptr () ->                               -- get_proxy_type_user_data : TBasicType TPtr
    FunPtr GLib.Callbacks.C_DestroyNotify -> -- get_proxy_type_destroy_notify : TInterface (Name {namespace = "GLib", name = "DestroyNotify"})
    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 creates a new t'GI.Gio.Objects.DBusObjectManagerClient.DBusObjectManagerClient' object.
-- 
-- This is an asynchronous failable constructor. When the result is
-- ready, /@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.DBusObjectManagerClient.dBusObjectManagerClientNewFinish' to get the result. See
-- 'GI.Gio.Objects.DBusObjectManagerClient.dBusObjectManagerClientNewSync' for the synchronous version.
-- 
-- /Since: 2.30/
dBusObjectManagerClientNew ::
    (B.CallStack.HasCallStack, MonadIO m, Gio.DBusConnection.IsDBusConnection a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@connection@/: A t'GI.Gio.Objects.DBusConnection.DBusConnection'.
    -> [Gio.Flags.DBusObjectManagerClientFlags]
    -- ^ /@flags@/: Zero or more flags from the t'GI.Gio.Flags.DBusObjectManagerClientFlags' enumeration.
    -> T.Text
    -- ^ /@name@/: The owner of the control object (unique or well-known name).
    -> T.Text
    -- ^ /@objectPath@/: The object path of the control object.
    -> Maybe (Gio.Callbacks.DBusProxyTypeFunc)
    -- ^ /@getProxyTypeFunc@/: A t'GI.Gio.Callbacks.DBusProxyTypeFunc' function or 'P.Nothing' to always construct t'GI.Gio.Objects.DBusProxy.DBusProxy' proxies.
    -> 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.
    -> m ()
dBusObjectManagerClientNew :: a
-> [DBusObjectManagerClientFlags]
-> Text
-> Text
-> Maybe DBusProxyTypeFunc
-> Maybe b
-> Maybe AsyncReadyCallback
-> m ()
dBusObjectManagerClientNew connection :: a
connection flags :: [DBusObjectManagerClientFlags]
flags name :: Text
name objectPath :: Text
objectPath getProxyTypeFunc :: Maybe DBusProxyTypeFunc
getProxyTypeFunc 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' = [DBusObjectManagerClientFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [DBusObjectManagerClientFlags]
flags
    CString
name' <- Text -> IO CString
textToCString Text
name
    CString
objectPath' <- Text -> IO CString
textToCString Text
objectPath
    FunPtr C_DBusProxyTypeFunc
maybeGetProxyTypeFunc <- case Maybe DBusProxyTypeFunc
getProxyTypeFunc of
        Nothing -> FunPtr C_DBusProxyTypeFunc -> IO (FunPtr C_DBusProxyTypeFunc)
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_DBusProxyTypeFunc
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
        Just jGetProxyTypeFunc :: DBusProxyTypeFunc
jGetProxyTypeFunc -> do
            FunPtr C_DBusProxyTypeFunc
jGetProxyTypeFunc' <- C_DBusProxyTypeFunc -> IO (FunPtr C_DBusProxyTypeFunc)
Gio.Callbacks.mk_DBusProxyTypeFunc (Maybe (Ptr (FunPtr C_DBusProxyTypeFunc))
-> DBusProxyTypeFunc_WithClosures -> C_DBusProxyTypeFunc
Gio.Callbacks.wrap_DBusProxyTypeFunc Maybe (Ptr (FunPtr C_DBusProxyTypeFunc))
forall a. Maybe a
Nothing (DBusProxyTypeFunc -> DBusProxyTypeFunc_WithClosures
Gio.Callbacks.drop_closures_DBusProxyTypeFunc DBusProxyTypeFunc
jGetProxyTypeFunc))
            FunPtr C_DBusProxyTypeFunc -> IO (FunPtr C_DBusProxyTypeFunc)
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_DBusProxyTypeFunc
jGetProxyTypeFunc'
    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 getProxyTypeUserData :: Ptr ()
getProxyTypeUserData = FunPtr C_DBusProxyTypeFunc -> Ptr ()
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr C_DBusProxyTypeFunc
maybeGetProxyTypeFunc
    let getProxyTypeDestroyNotify :: FunPtr (Ptr a -> IO ())
getProxyTypeDestroyNotify = FunPtr (Ptr a -> IO ())
forall a. FunPtr (Ptr a -> IO ())
safeFreeFunPtrPtr
    let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
    Ptr DBusConnection
-> CUInt
-> CString
-> CString
-> FunPtr C_DBusProxyTypeFunc
-> Ptr ()
-> FunPtr C_DestroyNotify
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> C_DestroyNotify
g_dbus_object_manager_client_new Ptr DBusConnection
connection' CUInt
flags' CString
name' CString
objectPath' FunPtr C_DBusProxyTypeFunc
maybeGetProxyTypeFunc Ptr ()
getProxyTypeUserData FunPtr C_DestroyNotify
forall a. FunPtr (Ptr a -> IO ())
getProxyTypeDestroyNotify 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 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
name'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
objectPath'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif

-- method DBusObjectManagerClient::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 = "DBusObjectManagerClientFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "Zero or more flags from the #GDBusObjectManagerClientFlags enumeration."
--                 , 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 "The owner of the control object (unique or well-known name)."
--                 , 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 "The object path of the control object."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "get_proxy_type_func"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusProxyTypeFunc" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A #GDBusProxyTypeFunc function or %NULL to always construct #GDBusProxy proxies."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeNotified
--           , argClosure = 5
--           , argDestroy = 6
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "get_proxy_type_user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "User data to pass to @get_proxy_type_func."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "get_proxy_type_destroy_notify"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "DestroyNotify" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "Free function for @get_proxy_type_user_data or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , 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."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = 9
--           , 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_object_manager_client_new_for_bus" g_dbus_object_manager_client_new_for_bus :: 
    CInt ->                                 -- bus_type : TInterface (Name {namespace = "Gio", name = "BusType"})
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gio", name = "DBusObjectManagerClientFlags"})
    CString ->                              -- name : TBasicType TUTF8
    CString ->                              -- object_path : TBasicType TUTF8
    FunPtr Gio.Callbacks.C_DBusProxyTypeFunc -> -- get_proxy_type_func : TInterface (Name {namespace = "Gio", name = "DBusProxyTypeFunc"})
    Ptr () ->                               -- get_proxy_type_user_data : TBasicType TPtr
    FunPtr GLib.Callbacks.C_DestroyNotify -> -- get_proxy_type_destroy_notify : TInterface (Name {namespace = "GLib", name = "DestroyNotify"})
    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.DBusObjectManagerClient.dBusObjectManagerClientNew' but takes a t'GI.Gio.Enums.BusType' instead of a
-- t'GI.Gio.Objects.DBusConnection.DBusConnection'.
-- 
-- This is an asynchronous failable constructor. When the result is
-- ready, /@callback@/ will be invoked in the
-- [thread-default main loop][g-main-context-push-thread-default]
-- of the thread you are calling this method from. You can
-- then call 'GI.Gio.Objects.DBusObjectManagerClient.dBusObjectManagerClientNewForBusFinish' to get the result. See
-- 'GI.Gio.Objects.DBusObjectManagerClient.dBusObjectManagerClientNewForBusSync' for the synchronous version.
-- 
-- /Since: 2.30/
dBusObjectManagerClientNewForBus ::
    (B.CallStack.HasCallStack, MonadIO m, Gio.Cancellable.IsCancellable a) =>
    Gio.Enums.BusType
    -- ^ /@busType@/: A t'GI.Gio.Enums.BusType'.
    -> [Gio.Flags.DBusObjectManagerClientFlags]
    -- ^ /@flags@/: Zero or more flags from the t'GI.Gio.Flags.DBusObjectManagerClientFlags' enumeration.
    -> T.Text
    -- ^ /@name@/: The owner of the control object (unique or well-known name).
    -> T.Text
    -- ^ /@objectPath@/: The object path of the control object.
    -> Maybe (Gio.Callbacks.DBusProxyTypeFunc)
    -- ^ /@getProxyTypeFunc@/: A t'GI.Gio.Callbacks.DBusProxyTypeFunc' function or 'P.Nothing' to always construct t'GI.Gio.Objects.DBusProxy.DBusProxy' proxies.
    -> Maybe (a)
    -- ^ /@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.
    -> m ()
dBusObjectManagerClientNewForBus :: BusType
-> [DBusObjectManagerClientFlags]
-> Text
-> Text
-> Maybe DBusProxyTypeFunc
-> Maybe a
-> Maybe AsyncReadyCallback
-> m ()
dBusObjectManagerClientNewForBus busType :: BusType
busType flags :: [DBusObjectManagerClientFlags]
flags name :: Text
name objectPath :: Text
objectPath getProxyTypeFunc :: Maybe DBusProxyTypeFunc
getProxyTypeFunc 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' = [DBusObjectManagerClientFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [DBusObjectManagerClientFlags]
flags
    CString
name' <- Text -> IO CString
textToCString Text
name
    CString
objectPath' <- Text -> IO CString
textToCString Text
objectPath
    FunPtr C_DBusProxyTypeFunc
maybeGetProxyTypeFunc <- case Maybe DBusProxyTypeFunc
getProxyTypeFunc of
        Nothing -> FunPtr C_DBusProxyTypeFunc -> IO (FunPtr C_DBusProxyTypeFunc)
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_DBusProxyTypeFunc
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
        Just jGetProxyTypeFunc :: DBusProxyTypeFunc
jGetProxyTypeFunc -> do
            FunPtr C_DBusProxyTypeFunc
jGetProxyTypeFunc' <- C_DBusProxyTypeFunc -> IO (FunPtr C_DBusProxyTypeFunc)
Gio.Callbacks.mk_DBusProxyTypeFunc (Maybe (Ptr (FunPtr C_DBusProxyTypeFunc))
-> DBusProxyTypeFunc_WithClosures -> C_DBusProxyTypeFunc
Gio.Callbacks.wrap_DBusProxyTypeFunc Maybe (Ptr (FunPtr C_DBusProxyTypeFunc))
forall a. Maybe a
Nothing (DBusProxyTypeFunc -> DBusProxyTypeFunc_WithClosures
Gio.Callbacks.drop_closures_DBusProxyTypeFunc DBusProxyTypeFunc
jGetProxyTypeFunc))
            FunPtr C_DBusProxyTypeFunc -> IO (FunPtr C_DBusProxyTypeFunc)
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_DBusProxyTypeFunc
jGetProxyTypeFunc'
    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 getProxyTypeUserData :: Ptr ()
getProxyTypeUserData = FunPtr C_DBusProxyTypeFunc -> Ptr ()
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr C_DBusProxyTypeFunc
maybeGetProxyTypeFunc
    let getProxyTypeDestroyNotify :: FunPtr (Ptr a -> IO ())
getProxyTypeDestroyNotify = FunPtr (Ptr a -> IO ())
forall a. FunPtr (Ptr a -> IO ())
safeFreeFunPtrPtr
    let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
    CInt
-> CUInt
-> CString
-> CString
-> FunPtr C_DBusProxyTypeFunc
-> Ptr ()
-> FunPtr C_DestroyNotify
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> C_DestroyNotify
g_dbus_object_manager_client_new_for_bus CInt
busType' CUInt
flags' CString
name' CString
objectPath' FunPtr C_DBusProxyTypeFunc
maybeGetProxyTypeFunc Ptr ()
getProxyTypeUserData FunPtr C_DestroyNotify
forall a. FunPtr (Ptr a -> IO ())
getProxyTypeDestroyNotify Ptr Cancellable
maybeCancellable FunPtr C_AsyncReadyCallback
maybeCallback Ptr ()
forall a. Ptr a
userData
    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'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif