{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- The t'GI.Gio.Objects.DBusConnection.DBusConnection' type is used for D-Bus connections to remote
-- peers such as a message buses. It is a low-level API that offers a
-- lot of flexibility. For instance, it lets you establish a connection
-- over any transport that can by represented as an t'GI.Gio.Objects.IOStream.IOStream'.
-- 
-- This class is rarely used directly in D-Bus clients. If you are writing
-- a D-Bus client, it is often easier to use the @/g_bus_own_name()/@,
-- @/g_bus_watch_name()/@ or 'GI.Gio.Objects.DBusProxy.dBusProxyNewForBus' APIs.
-- 
-- As an exception to the usual GLib rule that a particular object must not
-- be used by two threads at the same time, t'GI.Gio.Objects.DBusConnection.DBusConnection'\'s methods may be
-- called from any thread. This is so that 'GI.Gio.Functions.busGet' and 'GI.Gio.Functions.busGetSync'
-- can safely return the same t'GI.Gio.Objects.DBusConnection.DBusConnection' when called from any thread.
-- 
-- Most of the ways to obtain a t'GI.Gio.Objects.DBusConnection.DBusConnection' automatically initialize it
-- (i.e. connect to D-Bus): for instance, 'GI.Gio.Objects.DBusConnection.dBusConnectionNew' and
-- 'GI.Gio.Functions.busGet', and the synchronous versions of those methods, give you an
-- initialized connection. Language bindings for GIO should use
-- @/g_initable_new()/@ or @/g_async_initable_new_async()/@, which also initialize the
-- connection.
-- 
-- If you construct an uninitialized t'GI.Gio.Objects.DBusConnection.DBusConnection', such as via
-- @/g_object_new()/@, you must initialize it via 'GI.Gio.Interfaces.Initable.initableInit' or
-- 'GI.Gio.Interfaces.AsyncInitable.asyncInitableInitAsync' before using its methods or properties.
-- Calling methods or accessing properties on a t'GI.Gio.Objects.DBusConnection.DBusConnection' that has not
-- completed initialization successfully is considered to be invalid, and leads
-- to undefined behaviour. In particular, if initialization fails with a
-- t'GError', the only valid thing you can do with that t'GI.Gio.Objects.DBusConnection.DBusConnection' is to
-- free it with 'GI.GObject.Objects.Object.objectUnref'.
-- 
-- ## An example D-Bus server # {@/gdbus/@-server}
-- 
-- Here is an example for a D-Bus server:
-- <https://git.gnome.org/browse/glib/tree/gio/tests/gdbus-example-server.c gdbus-example-server.c>
-- 
-- ## An example for exporting a subtree # {@/gdbus/@-subtree-server}
-- 
-- Here is an example for exporting a subtree:
-- <https://git.gnome.org/browse/glib/tree/gio/tests/gdbus-example-subtree.c gdbus-example-subtree.c>
-- 
-- ## An example for file descriptor passing # {@/gdbus/@-unix-fd-client}
-- 
-- Here is an example for passing UNIX file descriptors:
-- <https://git.gnome.org/browse/glib/tree/gio/tests/gdbus-example-unix-fd-client.c gdbus-unix-fd-client.c>
-- 
-- ## An example for exporting a GObject # {@/gdbus/@-export}
-- 
-- Here is an example for exporting a t'GI.GObject.Objects.Object.Object':
-- <https://git.gnome.org/browse/glib/tree/gio/tests/gdbus-example-export.c gdbus-example-export.c>
-- 
-- /Since: 2.26/

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

module GI.Gio.Objects.DBusConnection
    ( 

-- * Exported types
    DBusConnection(..)                      ,
    IsDBusConnection                        ,
    toDBusConnection                        ,
    noDBusConnection                        ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveDBusConnectionMethod             ,
#endif


-- ** addFilter #method:addFilter#

#if defined(ENABLE_OVERLOADING)
    DBusConnectionAddFilterMethodInfo       ,
#endif
    dBusConnectionAddFilter                 ,


-- ** call #method:call#

#if defined(ENABLE_OVERLOADING)
    DBusConnectionCallMethodInfo            ,
#endif
    dBusConnectionCall                      ,


-- ** callFinish #method:callFinish#

#if defined(ENABLE_OVERLOADING)
    DBusConnectionCallFinishMethodInfo      ,
#endif
    dBusConnectionCallFinish                ,


-- ** callSync #method:callSync#

#if defined(ENABLE_OVERLOADING)
    DBusConnectionCallSyncMethodInfo        ,
#endif
    dBusConnectionCallSync                  ,


-- ** callWithUnixFdList #method:callWithUnixFdList#

#if defined(ENABLE_OVERLOADING)
    DBusConnectionCallWithUnixFdListMethodInfo,
#endif
    dBusConnectionCallWithUnixFdList        ,


-- ** callWithUnixFdListFinish #method:callWithUnixFdListFinish#

#if defined(ENABLE_OVERLOADING)
    DBusConnectionCallWithUnixFdListFinishMethodInfo,
#endif
    dBusConnectionCallWithUnixFdListFinish  ,


-- ** callWithUnixFdListSync #method:callWithUnixFdListSync#

#if defined(ENABLE_OVERLOADING)
    DBusConnectionCallWithUnixFdListSyncMethodInfo,
#endif
    dBusConnectionCallWithUnixFdListSync    ,


-- ** close #method:close#

#if defined(ENABLE_OVERLOADING)
    DBusConnectionCloseMethodInfo           ,
#endif
    dBusConnectionClose                     ,


-- ** closeFinish #method:closeFinish#

#if defined(ENABLE_OVERLOADING)
    DBusConnectionCloseFinishMethodInfo     ,
#endif
    dBusConnectionCloseFinish               ,


-- ** closeSync #method:closeSync#

#if defined(ENABLE_OVERLOADING)
    DBusConnectionCloseSyncMethodInfo       ,
#endif
    dBusConnectionCloseSync                 ,


-- ** emitSignal #method:emitSignal#

#if defined(ENABLE_OVERLOADING)
    DBusConnectionEmitSignalMethodInfo      ,
#endif
    dBusConnectionEmitSignal                ,


-- ** exportActionGroup #method:exportActionGroup#

#if defined(ENABLE_OVERLOADING)
    DBusConnectionExportActionGroupMethodInfo,
#endif
    dBusConnectionExportActionGroup         ,


-- ** exportMenuModel #method:exportMenuModel#

#if defined(ENABLE_OVERLOADING)
    DBusConnectionExportMenuModelMethodInfo ,
#endif
    dBusConnectionExportMenuModel           ,


-- ** flush #method:flush#

#if defined(ENABLE_OVERLOADING)
    DBusConnectionFlushMethodInfo           ,
#endif
    dBusConnectionFlush                     ,


-- ** flushFinish #method:flushFinish#

#if defined(ENABLE_OVERLOADING)
    DBusConnectionFlushFinishMethodInfo     ,
#endif
    dBusConnectionFlushFinish               ,


-- ** flushSync #method:flushSync#

#if defined(ENABLE_OVERLOADING)
    DBusConnectionFlushSyncMethodInfo       ,
#endif
    dBusConnectionFlushSync                 ,


-- ** getCapabilities #method:getCapabilities#

#if defined(ENABLE_OVERLOADING)
    DBusConnectionGetCapabilitiesMethodInfo ,
#endif
    dBusConnectionGetCapabilities           ,


-- ** getExitOnClose #method:getExitOnClose#

#if defined(ENABLE_OVERLOADING)
    DBusConnectionGetExitOnCloseMethodInfo  ,
#endif
    dBusConnectionGetExitOnClose            ,


-- ** getFlags #method:getFlags#

#if defined(ENABLE_OVERLOADING)
    DBusConnectionGetFlagsMethodInfo        ,
#endif
    dBusConnectionGetFlags                  ,


-- ** getGuid #method:getGuid#

#if defined(ENABLE_OVERLOADING)
    DBusConnectionGetGuidMethodInfo         ,
#endif
    dBusConnectionGetGuid                   ,


-- ** getLastSerial #method:getLastSerial#

#if defined(ENABLE_OVERLOADING)
    DBusConnectionGetLastSerialMethodInfo   ,
#endif
    dBusConnectionGetLastSerial             ,


-- ** getPeerCredentials #method:getPeerCredentials#

#if defined(ENABLE_OVERLOADING)
    DBusConnectionGetPeerCredentialsMethodInfo,
#endif
    dBusConnectionGetPeerCredentials        ,


-- ** getStream #method:getStream#

#if defined(ENABLE_OVERLOADING)
    DBusConnectionGetStreamMethodInfo       ,
#endif
    dBusConnectionGetStream                 ,


-- ** getUniqueName #method:getUniqueName#

#if defined(ENABLE_OVERLOADING)
    DBusConnectionGetUniqueNameMethodInfo   ,
#endif
    dBusConnectionGetUniqueName             ,


-- ** isClosed #method:isClosed#

#if defined(ENABLE_OVERLOADING)
    DBusConnectionIsClosedMethodInfo        ,
#endif
    dBusConnectionIsClosed                  ,


-- ** new #method:new#

    dBusConnectionNew                       ,


-- ** newFinish #method:newFinish#

    dBusConnectionNewFinish                 ,


-- ** newForAddress #method:newForAddress#

    dBusConnectionNewForAddress             ,


-- ** newForAddressFinish #method:newForAddressFinish#

    dBusConnectionNewForAddressFinish       ,


-- ** newForAddressSync #method:newForAddressSync#

    dBusConnectionNewForAddressSync         ,


-- ** newSync #method:newSync#

    dBusConnectionNewSync                   ,


-- ** registerObject #method:registerObject#

#if defined(ENABLE_OVERLOADING)
    DBusConnectionRegisterObjectMethodInfo  ,
#endif
    dBusConnectionRegisterObject            ,


-- ** registerSubtree #method:registerSubtree#

#if defined(ENABLE_OVERLOADING)
    DBusConnectionRegisterSubtreeMethodInfo ,
#endif
    dBusConnectionRegisterSubtree           ,


-- ** removeFilter #method:removeFilter#

#if defined(ENABLE_OVERLOADING)
    DBusConnectionRemoveFilterMethodInfo    ,
#endif
    dBusConnectionRemoveFilter              ,


-- ** sendMessage #method:sendMessage#

#if defined(ENABLE_OVERLOADING)
    DBusConnectionSendMessageMethodInfo     ,
#endif
    dBusConnectionSendMessage               ,


-- ** sendMessageWithReply #method:sendMessageWithReply#

#if defined(ENABLE_OVERLOADING)
    DBusConnectionSendMessageWithReplyMethodInfo,
#endif
    dBusConnectionSendMessageWithReply      ,


-- ** sendMessageWithReplyFinish #method:sendMessageWithReplyFinish#

#if defined(ENABLE_OVERLOADING)
    DBusConnectionSendMessageWithReplyFinishMethodInfo,
#endif
    dBusConnectionSendMessageWithReplyFinish,


-- ** sendMessageWithReplySync #method:sendMessageWithReplySync#

#if defined(ENABLE_OVERLOADING)
    DBusConnectionSendMessageWithReplySyncMethodInfo,
#endif
    dBusConnectionSendMessageWithReplySync  ,


-- ** setExitOnClose #method:setExitOnClose#

#if defined(ENABLE_OVERLOADING)
    DBusConnectionSetExitOnCloseMethodInfo  ,
#endif
    dBusConnectionSetExitOnClose            ,


-- ** signalSubscribe #method:signalSubscribe#

#if defined(ENABLE_OVERLOADING)
    DBusConnectionSignalSubscribeMethodInfo ,
#endif
    dBusConnectionSignalSubscribe           ,


-- ** signalUnsubscribe #method:signalUnsubscribe#

#if defined(ENABLE_OVERLOADING)
    DBusConnectionSignalUnsubscribeMethodInfo,
#endif
    dBusConnectionSignalUnsubscribe         ,


-- ** startMessageProcessing #method:startMessageProcessing#

#if defined(ENABLE_OVERLOADING)
    DBusConnectionStartMessageProcessingMethodInfo,
#endif
    dBusConnectionStartMessageProcessing    ,


-- ** unexportActionGroup #method:unexportActionGroup#

#if defined(ENABLE_OVERLOADING)
    DBusConnectionUnexportActionGroupMethodInfo,
#endif
    dBusConnectionUnexportActionGroup       ,


-- ** unexportMenuModel #method:unexportMenuModel#

#if defined(ENABLE_OVERLOADING)
    DBusConnectionUnexportMenuModelMethodInfo,
#endif
    dBusConnectionUnexportMenuModel         ,


-- ** unregisterObject #method:unregisterObject#

#if defined(ENABLE_OVERLOADING)
    DBusConnectionUnregisterObjectMethodInfo,
#endif
    dBusConnectionUnregisterObject          ,


-- ** unregisterSubtree #method:unregisterSubtree#

#if defined(ENABLE_OVERLOADING)
    DBusConnectionUnregisterSubtreeMethodInfo,
#endif
    dBusConnectionUnregisterSubtree         ,




 -- * Properties
-- ** address #attr:address#
-- | A D-Bus address specifying potential endpoints that can be used
-- when establishing the connection.
-- 
-- /Since: 2.26/

#if defined(ENABLE_OVERLOADING)
    DBusConnectionAddressPropertyInfo       ,
#endif
    constructDBusConnectionAddress          ,
#if defined(ENABLE_OVERLOADING)
    dBusConnectionAddress                   ,
#endif


-- ** authenticationObserver #attr:authenticationObserver#
-- | A t'GI.Gio.Objects.DBusAuthObserver.DBusAuthObserver' object to assist in the authentication process or 'P.Nothing'.
-- 
-- /Since: 2.26/

#if defined(ENABLE_OVERLOADING)
    DBusConnectionAuthenticationObserverPropertyInfo,
#endif
    constructDBusConnectionAuthenticationObserver,
#if defined(ENABLE_OVERLOADING)
    dBusConnectionAuthenticationObserver    ,
#endif


-- ** capabilities #attr:capabilities#
-- | Flags from the t'GI.Gio.Flags.DBusCapabilityFlags' enumeration
-- representing connection features negotiated with the other peer.
-- 
-- /Since: 2.26/

#if defined(ENABLE_OVERLOADING)
    DBusConnectionCapabilitiesPropertyInfo  ,
#endif
#if defined(ENABLE_OVERLOADING)
    dBusConnectionCapabilities              ,
#endif
    getDBusConnectionCapabilities           ,


-- ** closed #attr:closed#
-- | A boolean specifying whether the connection has been closed.
-- 
-- /Since: 2.26/

#if defined(ENABLE_OVERLOADING)
    DBusConnectionClosedPropertyInfo        ,
#endif
#if defined(ENABLE_OVERLOADING)
    dBusConnectionClosed                    ,
#endif
    getDBusConnectionClosed                 ,


-- ** exitOnClose #attr:exitOnClose#
-- | A boolean specifying whether the process will be terminated (by
-- calling @raise(SIGTERM)@) if the connection is closed by the
-- remote peer.
-- 
-- Note that t'GI.Gio.Objects.DBusConnection.DBusConnection' objects returned by 'GI.Gio.Functions.busGetFinish'
-- and 'GI.Gio.Functions.busGetSync' will (usually) have this property set to 'P.True'.
-- 
-- /Since: 2.26/

#if defined(ENABLE_OVERLOADING)
    DBusConnectionExitOnClosePropertyInfo   ,
#endif
    constructDBusConnectionExitOnClose      ,
#if defined(ENABLE_OVERLOADING)
    dBusConnectionExitOnClose               ,
#endif
    getDBusConnectionExitOnClose            ,
    setDBusConnectionExitOnClose            ,


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

#if defined(ENABLE_OVERLOADING)
    DBusConnectionFlagsPropertyInfo         ,
#endif
    constructDBusConnectionFlags            ,
#if defined(ENABLE_OVERLOADING)
    dBusConnectionFlags                     ,
#endif
    getDBusConnectionFlags                  ,


-- ** guid #attr:guid#
-- | The GUID of the peer performing the role of server when
-- authenticating.
-- 
-- If you are constructing a t'GI.Gio.Objects.DBusConnection.DBusConnection' and pass
-- 'GI.Gio.Flags.DBusConnectionFlagsAuthenticationServer' in the
-- t'GI.Gio.Objects.DBusConnection.DBusConnection':@/flags/@ property then you MUST also set this
-- property to a valid guid.
-- 
-- If you are constructing a t'GI.Gio.Objects.DBusConnection.DBusConnection' and pass
-- 'GI.Gio.Flags.DBusConnectionFlagsAuthenticationClient' in the
-- t'GI.Gio.Objects.DBusConnection.DBusConnection':@/flags/@ property you will be able to read the GUID
-- of the other peer here after the connection has been successfully
-- initialized.
-- 
-- /Since: 2.26/

#if defined(ENABLE_OVERLOADING)
    DBusConnectionGuidPropertyInfo          ,
#endif
    constructDBusConnectionGuid             ,
#if defined(ENABLE_OVERLOADING)
    dBusConnectionGuid                      ,
#endif
    getDBusConnectionGuid                   ,


-- ** stream #attr:stream#
-- | The underlying t'GI.Gio.Objects.IOStream.IOStream' used for I\/O.
-- 
-- If this is passed on construction and is a t'GI.Gio.Objects.SocketConnection.SocketConnection',
-- then the corresponding t'GI.Gio.Objects.Socket.Socket' will be put into non-blocking mode.
-- 
-- While the t'GI.Gio.Objects.DBusConnection.DBusConnection' is active, it will interact with this
-- stream from a worker thread, so it is not safe to interact with
-- the stream directly.
-- 
-- /Since: 2.26/

#if defined(ENABLE_OVERLOADING)
    DBusConnectionStreamPropertyInfo        ,
#endif
    constructDBusConnectionStream           ,
#if defined(ENABLE_OVERLOADING)
    dBusConnectionStream                    ,
#endif
    getDBusConnectionStream                 ,


-- ** uniqueName #attr:uniqueName#
-- | The unique name as assigned by the message bus or 'P.Nothing' if the
-- connection is not open or not a message bus connection.
-- 
-- /Since: 2.26/

#if defined(ENABLE_OVERLOADING)
    DBusConnectionUniqueNamePropertyInfo    ,
#endif
#if defined(ENABLE_OVERLOADING)
    dBusConnectionUniqueName                ,
#endif
    getDBusConnectionUniqueName             ,




 -- * Signals
-- ** closed #signal:closed#

    C_DBusConnectionClosedCallback          ,
    DBusConnectionClosedCallback            ,
#if defined(ENABLE_OVERLOADING)
    DBusConnectionClosedSignalInfo          ,
#endif
    afterDBusConnectionClosed               ,
    genClosure_DBusConnectionClosed         ,
    mk_DBusConnectionClosedCallback         ,
    noDBusConnectionClosedCallback          ,
    onDBusConnectionClosed                  ,
    wrap_DBusConnectionClosedCallback       ,




    ) 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.GLib.Structs.VariantType as GLib.VariantType
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Callbacks as Gio.Callbacks
import {-# SOURCE #-} qualified GI.Gio.Flags as Gio.Flags
import {-# SOURCE #-} qualified GI.Gio.Interfaces.ActionGroup as Gio.ActionGroup
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.Initable as Gio.Initable
import {-# SOURCE #-} qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
import {-# SOURCE #-} qualified GI.Gio.Objects.Credentials as Gio.Credentials
import {-# SOURCE #-} qualified GI.Gio.Objects.DBusAuthObserver as Gio.DBusAuthObserver
import {-# SOURCE #-} qualified GI.Gio.Objects.DBusMessage as Gio.DBusMessage
import {-# SOURCE #-} qualified GI.Gio.Objects.IOStream as Gio.IOStream
import {-# SOURCE #-} qualified GI.Gio.Objects.MenuModel as Gio.MenuModel
import {-# SOURCE #-} qualified GI.Gio.Objects.UnixFDList as Gio.UnixFDList
import {-# SOURCE #-} qualified GI.Gio.Structs.DBusInterfaceInfo as Gio.DBusInterfaceInfo
import {-# SOURCE #-} qualified GI.Gio.Structs.DBusSubtreeVTable as Gio.DBusSubtreeVTable

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

instance GObject DBusConnection where
    gobjectType :: IO GType
gobjectType = IO GType
c_g_dbus_connection_get_type
    

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

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

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

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

-- | A convenience alias for `Nothing` :: `Maybe` `DBusConnection`.
noDBusConnection :: Maybe DBusConnection
noDBusConnection :: Maybe DBusConnection
noDBusConnection = Maybe DBusConnection
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolveDBusConnectionMethod (t :: Symbol) (o :: *) :: * where
    ResolveDBusConnectionMethod "addFilter" o = DBusConnectionAddFilterMethodInfo
    ResolveDBusConnectionMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveDBusConnectionMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveDBusConnectionMethod "call" o = DBusConnectionCallMethodInfo
    ResolveDBusConnectionMethod "callFinish" o = DBusConnectionCallFinishMethodInfo
    ResolveDBusConnectionMethod "callSync" o = DBusConnectionCallSyncMethodInfo
    ResolveDBusConnectionMethod "callWithUnixFdList" o = DBusConnectionCallWithUnixFdListMethodInfo
    ResolveDBusConnectionMethod "callWithUnixFdListFinish" o = DBusConnectionCallWithUnixFdListFinishMethodInfo
    ResolveDBusConnectionMethod "callWithUnixFdListSync" o = DBusConnectionCallWithUnixFdListSyncMethodInfo
    ResolveDBusConnectionMethod "close" o = DBusConnectionCloseMethodInfo
    ResolveDBusConnectionMethod "closeFinish" o = DBusConnectionCloseFinishMethodInfo
    ResolveDBusConnectionMethod "closeSync" o = DBusConnectionCloseSyncMethodInfo
    ResolveDBusConnectionMethod "emitSignal" o = DBusConnectionEmitSignalMethodInfo
    ResolveDBusConnectionMethod "exportActionGroup" o = DBusConnectionExportActionGroupMethodInfo
    ResolveDBusConnectionMethod "exportMenuModel" o = DBusConnectionExportMenuModelMethodInfo
    ResolveDBusConnectionMethod "flush" o = DBusConnectionFlushMethodInfo
    ResolveDBusConnectionMethod "flushFinish" o = DBusConnectionFlushFinishMethodInfo
    ResolveDBusConnectionMethod "flushSync" o = DBusConnectionFlushSyncMethodInfo
    ResolveDBusConnectionMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveDBusConnectionMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveDBusConnectionMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveDBusConnectionMethod "init" o = Gio.Initable.InitableInitMethodInfo
    ResolveDBusConnectionMethod "initAsync" o = Gio.AsyncInitable.AsyncInitableInitAsyncMethodInfo
    ResolveDBusConnectionMethod "initFinish" o = Gio.AsyncInitable.AsyncInitableInitFinishMethodInfo
    ResolveDBusConnectionMethod "isClosed" o = DBusConnectionIsClosedMethodInfo
    ResolveDBusConnectionMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveDBusConnectionMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveDBusConnectionMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveDBusConnectionMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveDBusConnectionMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveDBusConnectionMethod "registerObject" o = DBusConnectionRegisterObjectMethodInfo
    ResolveDBusConnectionMethod "registerSubtree" o = DBusConnectionRegisterSubtreeMethodInfo
    ResolveDBusConnectionMethod "removeFilter" o = DBusConnectionRemoveFilterMethodInfo
    ResolveDBusConnectionMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveDBusConnectionMethod "sendMessage" o = DBusConnectionSendMessageMethodInfo
    ResolveDBusConnectionMethod "sendMessageWithReply" o = DBusConnectionSendMessageWithReplyMethodInfo
    ResolveDBusConnectionMethod "sendMessageWithReplyFinish" o = DBusConnectionSendMessageWithReplyFinishMethodInfo
    ResolveDBusConnectionMethod "sendMessageWithReplySync" o = DBusConnectionSendMessageWithReplySyncMethodInfo
    ResolveDBusConnectionMethod "signalSubscribe" o = DBusConnectionSignalSubscribeMethodInfo
    ResolveDBusConnectionMethod "signalUnsubscribe" o = DBusConnectionSignalUnsubscribeMethodInfo
    ResolveDBusConnectionMethod "startMessageProcessing" o = DBusConnectionStartMessageProcessingMethodInfo
    ResolveDBusConnectionMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveDBusConnectionMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveDBusConnectionMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveDBusConnectionMethod "unexportActionGroup" o = DBusConnectionUnexportActionGroupMethodInfo
    ResolveDBusConnectionMethod "unexportMenuModel" o = DBusConnectionUnexportMenuModelMethodInfo
    ResolveDBusConnectionMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveDBusConnectionMethod "unregisterObject" o = DBusConnectionUnregisterObjectMethodInfo
    ResolveDBusConnectionMethod "unregisterSubtree" o = DBusConnectionUnregisterSubtreeMethodInfo
    ResolveDBusConnectionMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveDBusConnectionMethod "getCapabilities" o = DBusConnectionGetCapabilitiesMethodInfo
    ResolveDBusConnectionMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveDBusConnectionMethod "getExitOnClose" o = DBusConnectionGetExitOnCloseMethodInfo
    ResolveDBusConnectionMethod "getFlags" o = DBusConnectionGetFlagsMethodInfo
    ResolveDBusConnectionMethod "getGuid" o = DBusConnectionGetGuidMethodInfo
    ResolveDBusConnectionMethod "getLastSerial" o = DBusConnectionGetLastSerialMethodInfo
    ResolveDBusConnectionMethod "getPeerCredentials" o = DBusConnectionGetPeerCredentialsMethodInfo
    ResolveDBusConnectionMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveDBusConnectionMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveDBusConnectionMethod "getStream" o = DBusConnectionGetStreamMethodInfo
    ResolveDBusConnectionMethod "getUniqueName" o = DBusConnectionGetUniqueNameMethodInfo
    ResolveDBusConnectionMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveDBusConnectionMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveDBusConnectionMethod "setExitOnClose" o = DBusConnectionSetExitOnCloseMethodInfo
    ResolveDBusConnectionMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveDBusConnectionMethod l o = O.MethodResolutionFailed l o

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

#endif

-- signal DBusConnection::closed
-- | Emitted when the connection is closed.
-- 
-- The cause of this event can be
-- 
-- * If 'GI.Gio.Objects.DBusConnection.dBusConnectionClose' is called. In this case
-- /@remotePeerVanished@/ is set to 'P.False' and /@error@/ is 'P.Nothing'.
-- * If the remote peer closes the connection. In this case
-- /@remotePeerVanished@/ is set to 'P.True' and /@error@/ is set.
-- * If the remote peer sends invalid or malformed data. In this
-- case /@remotePeerVanished@/ is set to 'P.False' and /@error@/ is set.
-- 
-- 
-- Upon receiving this signal, you should give up your reference to
-- /@connection@/. You are guaranteed that this signal is emitted only
-- once.
-- 
-- /Since: 2.26/
type DBusConnectionClosedCallback =
    Bool
    -- ^ /@remotePeerVanished@/: 'P.True' if /@connection@/ is closed because the
    --     remote peer closed its end of the connection
    -> Maybe GError
    -- ^ /@error@/: a t'GError' with more details about the event or 'P.Nothing'
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `DBusConnectionClosedCallback`@.
noDBusConnectionClosedCallback :: Maybe DBusConnectionClosedCallback
noDBusConnectionClosedCallback :: Maybe DBusConnectionClosedCallback
noDBusConnectionClosedCallback = Maybe DBusConnectionClosedCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_DBusConnectionClosedCallback =
    Ptr () ->                               -- object
    CInt ->
    Ptr GError ->
    Ptr () ->                               -- user_data
    IO ()

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

-- | Wrap the callback into a `GClosure`.
genClosure_DBusConnectionClosed :: MonadIO m => DBusConnectionClosedCallback -> m (GClosure C_DBusConnectionClosedCallback)
genClosure_DBusConnectionClosed :: DBusConnectionClosedCallback
-> m (GClosure C_DBusConnectionClosedCallback)
genClosure_DBusConnectionClosed cb :: DBusConnectionClosedCallback
cb = IO (GClosure C_DBusConnectionClosedCallback)
-> m (GClosure C_DBusConnectionClosedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_DBusConnectionClosedCallback)
 -> m (GClosure C_DBusConnectionClosedCallback))
-> IO (GClosure C_DBusConnectionClosedCallback)
-> m (GClosure C_DBusConnectionClosedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DBusConnectionClosedCallback
cb' = DBusConnectionClosedCallback -> C_DBusConnectionClosedCallback
wrap_DBusConnectionClosedCallback DBusConnectionClosedCallback
cb
    C_DBusConnectionClosedCallback
-> IO (FunPtr C_DBusConnectionClosedCallback)
mk_DBusConnectionClosedCallback C_DBusConnectionClosedCallback
cb' IO (FunPtr C_DBusConnectionClosedCallback)
-> (FunPtr C_DBusConnectionClosedCallback
    -> IO (GClosure C_DBusConnectionClosedCallback))
-> IO (GClosure C_DBusConnectionClosedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_DBusConnectionClosedCallback
-> IO (GClosure C_DBusConnectionClosedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `DBusConnectionClosedCallback` into a `C_DBusConnectionClosedCallback`.
wrap_DBusConnectionClosedCallback ::
    DBusConnectionClosedCallback ->
    C_DBusConnectionClosedCallback
wrap_DBusConnectionClosedCallback :: DBusConnectionClosedCallback -> C_DBusConnectionClosedCallback
wrap_DBusConnectionClosedCallback _cb :: DBusConnectionClosedCallback
_cb _ remotePeerVanished :: CInt
remotePeerVanished error_ :: Ptr GError
error_ _ = do
    let remotePeerVanished' :: Bool
remotePeerVanished' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
remotePeerVanished
    Maybe GError
maybeError_ <-
        if Ptr GError
error_ Ptr GError -> Ptr GError -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr GError
forall a. Ptr a
nullPtr
        then Maybe GError -> IO (Maybe GError)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe GError
forall a. Maybe a
Nothing
        else do
            GError
error_' <- ((ManagedPtr GError -> GError) -> Ptr GError -> IO GError
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr GError -> GError
GError) Ptr GError
error_
            Maybe GError -> IO (Maybe GError)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe GError -> IO (Maybe GError))
-> Maybe GError -> IO (Maybe GError)
forall a b. (a -> b) -> a -> b
$ GError -> Maybe GError
forall a. a -> Maybe a
Just GError
error_'
    DBusConnectionClosedCallback
_cb  Bool
remotePeerVanished' Maybe GError
maybeError_


-- | Connect a signal handler for the [closed](#signal:closed) 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' dBusConnection #closed callback
-- @
-- 
-- 
onDBusConnectionClosed :: (IsDBusConnection a, MonadIO m) => a -> DBusConnectionClosedCallback -> m SignalHandlerId
onDBusConnectionClosed :: a -> DBusConnectionClosedCallback -> m SignalHandlerId
onDBusConnectionClosed obj :: a
obj cb :: DBusConnectionClosedCallback
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_DBusConnectionClosedCallback
cb' = DBusConnectionClosedCallback -> C_DBusConnectionClosedCallback
wrap_DBusConnectionClosedCallback DBusConnectionClosedCallback
cb
    FunPtr C_DBusConnectionClosedCallback
cb'' <- C_DBusConnectionClosedCallback
-> IO (FunPtr C_DBusConnectionClosedCallback)
mk_DBusConnectionClosedCallback C_DBusConnectionClosedCallback
cb'
    a
-> Text
-> FunPtr C_DBusConnectionClosedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "closed" FunPtr C_DBusConnectionClosedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [closed](#signal:closed) 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' dBusConnection #closed callback
-- @
-- 
-- 
afterDBusConnectionClosed :: (IsDBusConnection a, MonadIO m) => a -> DBusConnectionClosedCallback -> m SignalHandlerId
afterDBusConnectionClosed :: a -> DBusConnectionClosedCallback -> m SignalHandlerId
afterDBusConnectionClosed obj :: a
obj cb :: DBusConnectionClosedCallback
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_DBusConnectionClosedCallback
cb' = DBusConnectionClosedCallback -> C_DBusConnectionClosedCallback
wrap_DBusConnectionClosedCallback DBusConnectionClosedCallback
cb
    FunPtr C_DBusConnectionClosedCallback
cb'' <- C_DBusConnectionClosedCallback
-> IO (FunPtr C_DBusConnectionClosedCallback)
mk_DBusConnectionClosedCallback C_DBusConnectionClosedCallback
cb'
    a
-> Text
-> FunPtr C_DBusConnectionClosedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "closed" FunPtr C_DBusConnectionClosedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data DBusConnectionClosedSignalInfo
instance SignalInfo DBusConnectionClosedSignalInfo where
    type HaskellCallbackType DBusConnectionClosedSignalInfo = DBusConnectionClosedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_DBusConnectionClosedCallback cb
        cb'' <- mk_DBusConnectionClosedCallback cb'
        connectSignalFunPtr obj "closed" cb'' connectMode detail

#endif

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

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

#if defined(ENABLE_OVERLOADING)
data DBusConnectionAddressPropertyInfo
instance AttrInfo DBusConnectionAddressPropertyInfo where
    type AttrAllowedOps DBusConnectionAddressPropertyInfo = '[ 'AttrConstruct, 'AttrClear]
    type AttrBaseTypeConstraint DBusConnectionAddressPropertyInfo = IsDBusConnection
    type AttrSetTypeConstraint DBusConnectionAddressPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint DBusConnectionAddressPropertyInfo = (~) T.Text
    type AttrTransferType DBusConnectionAddressPropertyInfo = T.Text
    type AttrGetType DBusConnectionAddressPropertyInfo = ()
    type AttrLabel DBusConnectionAddressPropertyInfo = "address"
    type AttrOrigin DBusConnectionAddressPropertyInfo = DBusConnection
    attrGet = undefined
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructDBusConnectionAddress
    attrClear = undefined
#endif

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

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

#if defined(ENABLE_OVERLOADING)
data DBusConnectionAuthenticationObserverPropertyInfo
instance AttrInfo DBusConnectionAuthenticationObserverPropertyInfo where
    type AttrAllowedOps DBusConnectionAuthenticationObserverPropertyInfo = '[ 'AttrConstruct, 'AttrClear]
    type AttrBaseTypeConstraint DBusConnectionAuthenticationObserverPropertyInfo = IsDBusConnection
    type AttrSetTypeConstraint DBusConnectionAuthenticationObserverPropertyInfo = Gio.DBusAuthObserver.IsDBusAuthObserver
    type AttrTransferTypeConstraint DBusConnectionAuthenticationObserverPropertyInfo = Gio.DBusAuthObserver.IsDBusAuthObserver
    type AttrTransferType DBusConnectionAuthenticationObserverPropertyInfo = Gio.DBusAuthObserver.DBusAuthObserver
    type AttrGetType DBusConnectionAuthenticationObserverPropertyInfo = ()
    type AttrLabel DBusConnectionAuthenticationObserverPropertyInfo = "authentication-observer"
    type AttrOrigin DBusConnectionAuthenticationObserverPropertyInfo = DBusConnection
    attrGet = undefined
    attrSet = undefined
    attrTransfer _ v = do
        unsafeCastTo Gio.DBusAuthObserver.DBusAuthObserver v
    attrConstruct = constructDBusConnectionAuthenticationObserver
    attrClear = undefined
#endif

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

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

#if defined(ENABLE_OVERLOADING)
data DBusConnectionCapabilitiesPropertyInfo
instance AttrInfo DBusConnectionCapabilitiesPropertyInfo where
    type AttrAllowedOps DBusConnectionCapabilitiesPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint DBusConnectionCapabilitiesPropertyInfo = IsDBusConnection
    type AttrSetTypeConstraint DBusConnectionCapabilitiesPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DBusConnectionCapabilitiesPropertyInfo = (~) ()
    type AttrTransferType DBusConnectionCapabilitiesPropertyInfo = ()
    type AttrGetType DBusConnectionCapabilitiesPropertyInfo = [Gio.Flags.DBusCapabilityFlags]
    type AttrLabel DBusConnectionCapabilitiesPropertyInfo = "capabilities"
    type AttrOrigin DBusConnectionCapabilitiesPropertyInfo = DBusConnection
    attrGet = getDBusConnectionCapabilities
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

-- VVV Prop "closed"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@closed@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dBusConnection #closed
-- @
getDBusConnectionClosed :: (MonadIO m, IsDBusConnection o) => o -> m Bool
getDBusConnectionClosed :: o -> m Bool
getDBusConnectionClosed obj :: o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj "closed"

#if defined(ENABLE_OVERLOADING)
data DBusConnectionClosedPropertyInfo
instance AttrInfo DBusConnectionClosedPropertyInfo where
    type AttrAllowedOps DBusConnectionClosedPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint DBusConnectionClosedPropertyInfo = IsDBusConnection
    type AttrSetTypeConstraint DBusConnectionClosedPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DBusConnectionClosedPropertyInfo = (~) ()
    type AttrTransferType DBusConnectionClosedPropertyInfo = ()
    type AttrGetType DBusConnectionClosedPropertyInfo = Bool
    type AttrLabel DBusConnectionClosedPropertyInfo = "closed"
    type AttrOrigin DBusConnectionClosedPropertyInfo = DBusConnection
    attrGet = getDBusConnectionClosed
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

-- VVV Prop "exit-on-close"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@exit-on-close@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dBusConnection #exitOnClose
-- @
getDBusConnectionExitOnClose :: (MonadIO m, IsDBusConnection o) => o -> m Bool
getDBusConnectionExitOnClose :: o -> m Bool
getDBusConnectionExitOnClose obj :: o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj "exit-on-close"

-- | Set the value of the “@exit-on-close@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' dBusConnection [ #exitOnClose 'Data.GI.Base.Attributes.:=' value ]
-- @
setDBusConnectionExitOnClose :: (MonadIO m, IsDBusConnection o) => o -> Bool -> m ()
setDBusConnectionExitOnClose :: o -> Bool -> m ()
setDBusConnectionExitOnClose obj :: o
obj val :: Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj "exit-on-close" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@exit-on-close@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDBusConnectionExitOnClose :: (IsDBusConnection o) => Bool -> IO (GValueConstruct o)
constructDBusConnectionExitOnClose :: Bool -> IO (GValueConstruct o)
constructDBusConnectionExitOnClose val :: Bool
val = String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool "exit-on-close" Bool
val

#if defined(ENABLE_OVERLOADING)
data DBusConnectionExitOnClosePropertyInfo
instance AttrInfo DBusConnectionExitOnClosePropertyInfo where
    type AttrAllowedOps DBusConnectionExitOnClosePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint DBusConnectionExitOnClosePropertyInfo = IsDBusConnection
    type AttrSetTypeConstraint DBusConnectionExitOnClosePropertyInfo = (~) Bool
    type AttrTransferTypeConstraint DBusConnectionExitOnClosePropertyInfo = (~) Bool
    type AttrTransferType DBusConnectionExitOnClosePropertyInfo = Bool
    type AttrGetType DBusConnectionExitOnClosePropertyInfo = Bool
    type AttrLabel DBusConnectionExitOnClosePropertyInfo = "exit-on-close"
    type AttrOrigin DBusConnectionExitOnClosePropertyInfo = DBusConnection
    attrGet = getDBusConnectionExitOnClose
    attrSet = setDBusConnectionExitOnClose
    attrTransfer _ v = do
        return v
    attrConstruct = constructDBusConnectionExitOnClose
    attrClear = undefined
#endif

-- VVV Prop "flags"
   -- Type: TInterface (Name {namespace = "Gio", name = "DBusConnectionFlags"})
   -- 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' dBusConnection #flags
-- @
getDBusConnectionFlags :: (MonadIO m, IsDBusConnection o) => o -> m [Gio.Flags.DBusConnectionFlags]
getDBusConnectionFlags :: o -> m [DBusConnectionFlags]
getDBusConnectionFlags obj :: o
obj = IO [DBusConnectionFlags] -> m [DBusConnectionFlags]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [DBusConnectionFlags] -> m [DBusConnectionFlags])
-> IO [DBusConnectionFlags] -> m [DBusConnectionFlags]
forall a b. (a -> b) -> a -> b
$ o -> String -> IO [DBusConnectionFlags]
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`.
constructDBusConnectionFlags :: (IsDBusConnection o) => [Gio.Flags.DBusConnectionFlags] -> IO (GValueConstruct o)
constructDBusConnectionFlags :: [DBusConnectionFlags] -> IO (GValueConstruct o)
constructDBusConnectionFlags val :: [DBusConnectionFlags]
val = String -> [DBusConnectionFlags] -> IO (GValueConstruct o)
forall a o.
(IsGFlag a, BoxedFlags a) =>
String -> [a] -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyFlags "flags" [DBusConnectionFlags]
val

#if defined(ENABLE_OVERLOADING)
data DBusConnectionFlagsPropertyInfo
instance AttrInfo DBusConnectionFlagsPropertyInfo where
    type AttrAllowedOps DBusConnectionFlagsPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint DBusConnectionFlagsPropertyInfo = IsDBusConnection
    type AttrSetTypeConstraint DBusConnectionFlagsPropertyInfo = (~) [Gio.Flags.DBusConnectionFlags]
    type AttrTransferTypeConstraint DBusConnectionFlagsPropertyInfo = (~) [Gio.Flags.DBusConnectionFlags]
    type AttrTransferType DBusConnectionFlagsPropertyInfo = [Gio.Flags.DBusConnectionFlags]
    type AttrGetType DBusConnectionFlagsPropertyInfo = [Gio.Flags.DBusConnectionFlags]
    type AttrLabel DBusConnectionFlagsPropertyInfo = "flags"
    type AttrOrigin DBusConnectionFlagsPropertyInfo = DBusConnection
    attrGet = getDBusConnectionFlags
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructDBusConnectionFlags
    attrClear = undefined
#endif

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

-- | Get the value of the “@guid@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dBusConnection #guid
-- @
getDBusConnectionGuid :: (MonadIO m, IsDBusConnection o) => o -> m T.Text
getDBusConnectionGuid :: o -> m Text
getDBusConnectionGuid 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 "getDBusConnectionGuid" (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 "guid"

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

#if defined(ENABLE_OVERLOADING)
data DBusConnectionGuidPropertyInfo
instance AttrInfo DBusConnectionGuidPropertyInfo where
    type AttrAllowedOps DBusConnectionGuidPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DBusConnectionGuidPropertyInfo = IsDBusConnection
    type AttrSetTypeConstraint DBusConnectionGuidPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint DBusConnectionGuidPropertyInfo = (~) T.Text
    type AttrTransferType DBusConnectionGuidPropertyInfo = T.Text
    type AttrGetType DBusConnectionGuidPropertyInfo = T.Text
    type AttrLabel DBusConnectionGuidPropertyInfo = "guid"
    type AttrOrigin DBusConnectionGuidPropertyInfo = DBusConnection
    attrGet = getDBusConnectionGuid
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructDBusConnectionGuid
    attrClear = undefined
#endif

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

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

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

#if defined(ENABLE_OVERLOADING)
data DBusConnectionStreamPropertyInfo
instance AttrInfo DBusConnectionStreamPropertyInfo where
    type AttrAllowedOps DBusConnectionStreamPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DBusConnectionStreamPropertyInfo = IsDBusConnection
    type AttrSetTypeConstraint DBusConnectionStreamPropertyInfo = Gio.IOStream.IsIOStream
    type AttrTransferTypeConstraint DBusConnectionStreamPropertyInfo = Gio.IOStream.IsIOStream
    type AttrTransferType DBusConnectionStreamPropertyInfo = Gio.IOStream.IOStream
    type AttrGetType DBusConnectionStreamPropertyInfo = Gio.IOStream.IOStream
    type AttrLabel DBusConnectionStreamPropertyInfo = "stream"
    type AttrOrigin DBusConnectionStreamPropertyInfo = DBusConnection
    attrGet = getDBusConnectionStream
    attrSet = undefined
    attrTransfer _ v = do
        unsafeCastTo Gio.IOStream.IOStream v
    attrConstruct = constructDBusConnectionStream
    attrClear = undefined
#endif

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

-- | Get the value of the “@unique-name@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dBusConnection #uniqueName
-- @
getDBusConnectionUniqueName :: (MonadIO m, IsDBusConnection o) => o -> m (Maybe T.Text)
getDBusConnectionUniqueName :: o -> m (Maybe Text)
getDBusConnectionUniqueName 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 "unique-name"

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

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DBusConnection
type instance O.AttributeList DBusConnection = DBusConnectionAttributeList
type DBusConnectionAttributeList = ('[ '("address", DBusConnectionAddressPropertyInfo), '("authenticationObserver", DBusConnectionAuthenticationObserverPropertyInfo), '("capabilities", DBusConnectionCapabilitiesPropertyInfo), '("closed", DBusConnectionClosedPropertyInfo), '("exitOnClose", DBusConnectionExitOnClosePropertyInfo), '("flags", DBusConnectionFlagsPropertyInfo), '("guid", DBusConnectionGuidPropertyInfo), '("stream", DBusConnectionStreamPropertyInfo), '("uniqueName", DBusConnectionUniqueNamePropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
dBusConnectionAddress :: AttrLabelProxy "address"
dBusConnectionAddress = AttrLabelProxy

dBusConnectionAuthenticationObserver :: AttrLabelProxy "authenticationObserver"
dBusConnectionAuthenticationObserver = AttrLabelProxy

dBusConnectionCapabilities :: AttrLabelProxy "capabilities"
dBusConnectionCapabilities = AttrLabelProxy

dBusConnectionClosed :: AttrLabelProxy "closed"
dBusConnectionClosed = AttrLabelProxy

dBusConnectionExitOnClose :: AttrLabelProxy "exitOnClose"
dBusConnectionExitOnClose = AttrLabelProxy

dBusConnectionFlags :: AttrLabelProxy "flags"
dBusConnectionFlags = AttrLabelProxy

dBusConnectionGuid :: AttrLabelProxy "guid"
dBusConnectionGuid = AttrLabelProxy

dBusConnectionStream :: AttrLabelProxy "stream"
dBusConnectionStream = AttrLabelProxy

dBusConnectionUniqueName :: AttrLabelProxy "uniqueName"
dBusConnectionUniqueName = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList DBusConnection = DBusConnectionSignalList
type DBusConnectionSignalList = ('[ '("closed", DBusConnectionClosedSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

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

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

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

#if defined(ENABLE_OVERLOADING)
#endif

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

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

-- | Finishes an operation started with 'GI.Gio.Objects.DBusConnection.dBusConnectionNewForAddress'.
-- 
-- /Since: 2.26/
dBusConnectionNewForAddressFinish ::
    (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.DBusConnection.dBusConnectionNew'
    -> m DBusConnection
    -- ^ __Returns:__ a t'GI.Gio.Objects.DBusConnection.DBusConnection' or 'P.Nothing' if /@error@/ is set. Free with
    --     'GI.GObject.Objects.Object.objectUnref'. /(Can throw 'Data.GI.Base.GError.GError')/
dBusConnectionNewForAddressFinish :: a -> m DBusConnection
dBusConnectionNewForAddressFinish res :: a
res = 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 AsyncResult
res' <- a -> IO (Ptr AsyncResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
res
    IO DBusConnection -> IO () -> IO DBusConnection
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr DBusConnection
result <- (Ptr (Ptr GError) -> IO (Ptr DBusConnection))
-> IO (Ptr DBusConnection)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr DBusConnection))
 -> IO (Ptr DBusConnection))
-> (Ptr (Ptr GError) -> IO (Ptr DBusConnection))
-> IO (Ptr DBusConnection)
forall a b. (a -> b) -> a -> b
$ Ptr AsyncResult -> Ptr (Ptr GError) -> IO (Ptr DBusConnection)
g_dbus_connection_new_for_address_finish Ptr AsyncResult
res'
        Text -> Ptr DBusConnection -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusConnectionNewForAddressFinish" 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
wrapObject ManagedPtr DBusConnection -> DBusConnection
DBusConnection) Ptr DBusConnection
result
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
res
        DBusConnection -> IO DBusConnection
forall (m :: * -> *) a. Monad m => a -> m a
return DBusConnection
result'
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method DBusConnection::new_for_address_sync
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "address"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a D-Bus address" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "DBusConnectionFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "flags describing how to make the connection"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "observer"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusAuthObserver" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDBusAuthObserver or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GCancellable or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gio" , name = "DBusConnection" })
-- throws : True
-- Skip return : False

foreign import ccall "g_dbus_connection_new_for_address_sync" g_dbus_connection_new_for_address_sync :: 
    CString ->                              -- address : TBasicType TUTF8
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gio", name = "DBusConnectionFlags"})
    Ptr Gio.DBusAuthObserver.DBusAuthObserver -> -- observer : TInterface (Name {namespace = "Gio", name = "DBusAuthObserver"})
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr DBusConnection)

-- | Synchronously connects and sets up a D-Bus client connection for
-- exchanging D-Bus messages with an endpoint specified by /@address@/
-- which must be in the
-- <https://dbus.freedesktop.org/doc/dbus-specification.html#addresses D-Bus address format>.
-- 
-- This constructor can only be used to initiate client-side
-- connections - use 'GI.Gio.Objects.DBusConnection.dBusConnectionNewSync' if you need to act
-- as the server. In particular, /@flags@/ cannot contain the
-- 'GI.Gio.Flags.DBusConnectionFlagsAuthenticationServer' or
-- 'GI.Gio.Flags.DBusConnectionFlagsAuthenticationAllowAnonymous' flags.
-- 
-- This is a synchronous failable constructor. See
-- 'GI.Gio.Objects.DBusConnection.dBusConnectionNewForAddress' for the asynchronous version.
-- 
-- If /@observer@/ is not 'P.Nothing' it may be used to control the
-- authentication process.
-- 
-- /Since: 2.26/
dBusConnectionNewForAddressSync ::
    (B.CallStack.HasCallStack, MonadIO m, Gio.DBusAuthObserver.IsDBusAuthObserver a, Gio.Cancellable.IsCancellable b) =>
    T.Text
    -- ^ /@address@/: a D-Bus address
    -> [Gio.Flags.DBusConnectionFlags]
    -- ^ /@flags@/: flags describing how to make the connection
    -> Maybe (a)
    -- ^ /@observer@/: a t'GI.Gio.Objects.DBusAuthObserver.DBusAuthObserver' or 'P.Nothing'
    -> Maybe (b)
    -- ^ /@cancellable@/: a t'GI.Gio.Objects.Cancellable.Cancellable' or 'P.Nothing'
    -> m DBusConnection
    -- ^ __Returns:__ a t'GI.Gio.Objects.DBusConnection.DBusConnection' or 'P.Nothing' if /@error@/ is set. Free with
    --     'GI.GObject.Objects.Object.objectUnref'. /(Can throw 'Data.GI.Base.GError.GError')/
dBusConnectionNewForAddressSync :: Text
-> [DBusConnectionFlags] -> Maybe a -> Maybe b -> m DBusConnection
dBusConnectionNewForAddressSync address :: Text
address flags :: [DBusConnectionFlags]
flags observer :: Maybe a
observer cancellable :: Maybe b
cancellable = 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
    CString
address' <- Text -> IO CString
textToCString Text
address
    let flags' :: CUInt
flags' = [DBusConnectionFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [DBusConnectionFlags]
flags
    Ptr DBusAuthObserver
maybeObserver <- case Maybe a
observer of
        Nothing -> Ptr DBusAuthObserver -> IO (Ptr DBusAuthObserver)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr DBusAuthObserver
forall a. Ptr a
nullPtr
        Just jObserver :: a
jObserver -> do
            Ptr DBusAuthObserver
jObserver' <- a -> IO (Ptr DBusAuthObserver)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
jObserver
            Ptr DBusAuthObserver -> IO (Ptr DBusAuthObserver)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr DBusAuthObserver
jObserver'
    Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
        Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just jCancellable :: b
jCancellable -> do
            Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    IO DBusConnection -> IO () -> IO DBusConnection
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr DBusConnection
result <- (Ptr (Ptr GError) -> IO (Ptr DBusConnection))
-> IO (Ptr DBusConnection)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr DBusConnection))
 -> IO (Ptr DBusConnection))
-> (Ptr (Ptr GError) -> IO (Ptr DBusConnection))
-> IO (Ptr DBusConnection)
forall a b. (a -> b) -> a -> b
$ CString
-> CUInt
-> Ptr DBusAuthObserver
-> Ptr Cancellable
-> Ptr (Ptr GError)
-> IO (Ptr DBusConnection)
g_dbus_connection_new_for_address_sync CString
address' CUInt
flags' Ptr DBusAuthObserver
maybeObserver Ptr Cancellable
maybeCancellable
        Text -> Ptr DBusConnection -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusConnectionNewForAddressSync" 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
wrapObject ManagedPtr DBusConnection -> DBusConnection
DBusConnection) Ptr DBusConnection
result
        Maybe a -> (a -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe a
observer a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
address'
        DBusConnection -> IO DBusConnection
forall (m :: * -> *) a. Monad m => a -> m a
return DBusConnection
result'
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
address'
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method DBusConnection::new_sync
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "stream"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "IOStream" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GIOStream" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "guid"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the GUID to use if a authenticating as a server or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "DBusConnectionFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "flags describing how to make the connection"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "observer"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusAuthObserver" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDBusAuthObserver or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GCancellable or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gio" , name = "DBusConnection" })
-- throws : True
-- Skip return : False

foreign import ccall "g_dbus_connection_new_sync" g_dbus_connection_new_sync :: 
    Ptr Gio.IOStream.IOStream ->            -- stream : TInterface (Name {namespace = "Gio", name = "IOStream"})
    CString ->                              -- guid : TBasicType TUTF8
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gio", name = "DBusConnectionFlags"})
    Ptr Gio.DBusAuthObserver.DBusAuthObserver -> -- observer : TInterface (Name {namespace = "Gio", name = "DBusAuthObserver"})
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr DBusConnection)

-- | Synchronously sets up a D-Bus connection for exchanging D-Bus messages
-- with the end represented by /@stream@/.
-- 
-- If /@stream@/ is a t'GI.Gio.Objects.SocketConnection.SocketConnection', then the corresponding t'GI.Gio.Objects.Socket.Socket'
-- will be put into non-blocking mode.
-- 
-- The D-Bus connection will interact with /@stream@/ from a worker thread.
-- As a result, the caller should not interact with /@stream@/ after this
-- method has been called, except by calling 'GI.GObject.Objects.Object.objectUnref' on it.
-- 
-- If /@observer@/ is not 'P.Nothing' it may be used to control the
-- authentication process.
-- 
-- This is a synchronous failable constructor. See
-- 'GI.Gio.Objects.DBusConnection.dBusConnectionNew' for the asynchronous version.
-- 
-- /Since: 2.26/
dBusConnectionNewSync ::
    (B.CallStack.HasCallStack, MonadIO m, Gio.IOStream.IsIOStream a, Gio.DBusAuthObserver.IsDBusAuthObserver b, Gio.Cancellable.IsCancellable c) =>
    a
    -- ^ /@stream@/: a t'GI.Gio.Objects.IOStream.IOStream'
    -> Maybe (T.Text)
    -- ^ /@guid@/: the GUID to use if a authenticating as a server or 'P.Nothing'
    -> [Gio.Flags.DBusConnectionFlags]
    -- ^ /@flags@/: flags describing how to make the connection
    -> Maybe (b)
    -- ^ /@observer@/: a t'GI.Gio.Objects.DBusAuthObserver.DBusAuthObserver' or 'P.Nothing'
    -> Maybe (c)
    -- ^ /@cancellable@/: a t'GI.Gio.Objects.Cancellable.Cancellable' or 'P.Nothing'
    -> m DBusConnection
    -- ^ __Returns:__ a t'GI.Gio.Objects.DBusConnection.DBusConnection' or 'P.Nothing' if /@error@/ is set. Free with 'GI.GObject.Objects.Object.objectUnref'. /(Can throw 'Data.GI.Base.GError.GError')/
dBusConnectionNewSync :: a
-> Maybe Text
-> [DBusConnectionFlags]
-> Maybe b
-> Maybe c
-> m DBusConnection
dBusConnectionNewSync stream :: a
stream guid :: Maybe Text
guid flags :: [DBusConnectionFlags]
flags observer :: Maybe b
observer cancellable :: Maybe c
cancellable = 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 IOStream
stream' <- a -> IO (Ptr IOStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
stream
    CString
maybeGuid <- case Maybe Text
guid of
        Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just jGuid :: Text
jGuid -> do
            CString
jGuid' <- Text -> IO CString
textToCString Text
jGuid
            CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jGuid'
    let flags' :: CUInt
flags' = [DBusConnectionFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [DBusConnectionFlags]
flags
    Ptr DBusAuthObserver
maybeObserver <- case Maybe b
observer of
        Nothing -> Ptr DBusAuthObserver -> IO (Ptr DBusAuthObserver)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr DBusAuthObserver
forall a. Ptr a
nullPtr
        Just jObserver :: b
jObserver -> do
            Ptr DBusAuthObserver
jObserver' <- b -> IO (Ptr DBusAuthObserver)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jObserver
            Ptr DBusAuthObserver -> IO (Ptr DBusAuthObserver)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr DBusAuthObserver
jObserver'
    Ptr Cancellable
maybeCancellable <- case Maybe c
cancellable of
        Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just jCancellable :: c
jCancellable -> do
            Ptr Cancellable
jCancellable' <- c -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    IO DBusConnection -> IO () -> IO DBusConnection
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr DBusConnection
result <- (Ptr (Ptr GError) -> IO (Ptr DBusConnection))
-> IO (Ptr DBusConnection)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr DBusConnection))
 -> IO (Ptr DBusConnection))
-> (Ptr (Ptr GError) -> IO (Ptr DBusConnection))
-> IO (Ptr DBusConnection)
forall a b. (a -> b) -> a -> b
$ Ptr IOStream
-> CString
-> CUInt
-> Ptr DBusAuthObserver
-> Ptr Cancellable
-> Ptr (Ptr GError)
-> IO (Ptr DBusConnection)
g_dbus_connection_new_sync Ptr IOStream
stream' CString
maybeGuid CUInt
flags' Ptr DBusAuthObserver
maybeObserver Ptr Cancellable
maybeCancellable
        Text -> Ptr DBusConnection -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusConnectionNewSync" 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
wrapObject ManagedPtr DBusConnection -> DBusConnection
DBusConnection) Ptr DBusConnection
result
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
stream
        Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
observer b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        Maybe c -> (c -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe c
cancellable c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeGuid
        DBusConnection -> IO DBusConnection
forall (m :: * -> *) a. Monad m => a -> m a
return DBusConnection
result'
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeGuid
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method DBusConnection::add_filter
-- method type : OrdinaryMethod
-- 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 = "filter_function"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "DBusMessageFilterFunction" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a filter function" , sinceVersion = Nothing }
--           , argScope = ScopeTypeNotified
--           , argClosure = 2
--           , argDestroy = 3
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "user data to pass to @filter_function"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data_free_func"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "DestroyNotify" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "function to free @user_data with when filter\n    is removed or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt)
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_connection_add_filter" g_dbus_connection_add_filter :: 
    Ptr DBusConnection ->                   -- connection : TInterface (Name {namespace = "Gio", name = "DBusConnection"})
    FunPtr Gio.Callbacks.C_DBusMessageFilterFunction -> -- filter_function : TInterface (Name {namespace = "Gio", name = "DBusMessageFilterFunction"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    FunPtr GLib.Callbacks.C_DestroyNotify -> -- user_data_free_func : TInterface (Name {namespace = "GLib", name = "DestroyNotify"})
    IO Word32

-- | Adds a message filter. Filters are handlers that are run on all
-- incoming and outgoing messages, prior to standard dispatch. Filters
-- are run in the order that they were added.  The same handler can be
-- added as a filter more than once, in which case it will be run more
-- than once.  Filters added during a filter callback won\'t be run on
-- the message being processed. Filter functions are allowed to modify
-- and even drop messages.
-- 
-- Note that filters are run in a dedicated message handling thread so
-- they can\'t block and, generally, can\'t do anything but signal a
-- worker thread. Also note that filters are rarely needed - use API
-- such as 'GI.Gio.Objects.DBusConnection.dBusConnectionSendMessageWithReply',
-- 'GI.Gio.Objects.DBusConnection.dBusConnectionSignalSubscribe' or 'GI.Gio.Objects.DBusConnection.dBusConnectionCall' instead.
-- 
-- If a filter consumes an incoming message the message is not
-- dispatched anywhere else - not even the standard dispatch machinery
-- (that API such as 'GI.Gio.Objects.DBusConnection.dBusConnectionSignalSubscribe' and
-- 'GI.Gio.Objects.DBusConnection.dBusConnectionSendMessageWithReply' relies on) will see the
-- message. Similarly, if a filter consumes an outgoing message, the
-- message will not be sent to the other peer.
-- 
-- If /@userDataFreeFunc@/ is non-'P.Nothing', it will be called (in the
-- thread-default main context of the thread you are calling this
-- method from) at some point after /@userData@/ is no longer
-- needed. (It is not guaranteed to be called synchronously when the
-- filter is removed, and may be called after /@connection@/ has been
-- destroyed.)
-- 
-- /Since: 2.26/
dBusConnectionAddFilter ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusConnection a) =>
    a
    -- ^ /@connection@/: a t'GI.Gio.Objects.DBusConnection.DBusConnection'
    -> Gio.Callbacks.DBusMessageFilterFunction
    -- ^ /@filterFunction@/: a filter function
    -> m Word32
    -- ^ __Returns:__ a filter identifier that can be used with
    --     'GI.Gio.Objects.DBusConnection.dBusConnectionRemoveFilter'
dBusConnectionAddFilter :: a -> DBusMessageFilterFunction -> m Word32
dBusConnectionAddFilter connection :: a
connection filterFunction :: DBusMessageFilterFunction
filterFunction = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusConnection
connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    FunPtr C_DBusMessageFilterFunction
filterFunction' <- C_DBusMessageFilterFunction
-> IO (FunPtr C_DBusMessageFilterFunction)
Gio.Callbacks.mk_DBusMessageFilterFunction (Maybe (Ptr (FunPtr C_DBusMessageFilterFunction))
-> DBusMessageFilterFunction_WithClosures
-> C_DBusMessageFilterFunction
Gio.Callbacks.wrap_DBusMessageFilterFunction Maybe (Ptr (FunPtr C_DBusMessageFilterFunction))
forall a. Maybe a
Nothing (DBusMessageFilterFunction -> DBusMessageFilterFunction_WithClosures
Gio.Callbacks.drop_closures_DBusMessageFilterFunction DBusMessageFilterFunction
filterFunction))
    let userData :: Ptr ()
userData = FunPtr C_DBusMessageFilterFunction -> Ptr ()
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr C_DBusMessageFilterFunction
filterFunction'
    let userDataFreeFunc :: FunPtr (Ptr a -> IO ())
userDataFreeFunc = FunPtr (Ptr a -> IO ())
forall a. FunPtr (Ptr a -> IO ())
safeFreeFunPtrPtr
    Word32
result <- Ptr DBusConnection
-> FunPtr C_DBusMessageFilterFunction
-> Ptr ()
-> FunPtr C_DestroyNotify
-> IO Word32
g_dbus_connection_add_filter Ptr DBusConnection
connection' FunPtr C_DBusMessageFilterFunction
filterFunction' Ptr ()
userData FunPtr C_DestroyNotify
forall a. FunPtr (Ptr a -> IO ())
userDataFreeFunc
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
connection
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data DBusConnectionAddFilterMethodInfo
instance (signature ~ (Gio.Callbacks.DBusMessageFilterFunction -> m Word32), MonadIO m, IsDBusConnection a) => O.MethodInfo DBusConnectionAddFilterMethodInfo a signature where
    overloadedMethod = dBusConnectionAddFilter

#endif

-- method DBusConnection::call
-- method type : OrdinaryMethod
-- 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 = "bus_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a unique or well-known bus name or %NULL if\n    @connection is not a message bus connection"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "object_path"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "path of remote object"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "interface_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "D-Bus interface to invoke method on"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "method_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the name of the method to invoke"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "parameters"
--           , argType = TVariant
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a #GVariant tuple with parameters for the method\n    or %NULL if not passing parameters"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "reply_type"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "VariantType" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the expected type of the reply (which will be a\n    tuple), or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusCallFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "flags from the #GDBusCallFlags enumeration"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "timeout_msec"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the timeout in milliseconds, -1 to use the default\n    timeout or %G_MAXINT for no timeout"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GCancellable or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "callback"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncReadyCallback" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a #GAsyncReadyCallback to call when the request\n    is satisfied or %NULL if you don't care about the result of the\n    method invocation"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = 11
--           , 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_connection_call" g_dbus_connection_call :: 
    Ptr DBusConnection ->                   -- connection : TInterface (Name {namespace = "Gio", name = "DBusConnection"})
    CString ->                              -- bus_name : TBasicType TUTF8
    CString ->                              -- object_path : TBasicType TUTF8
    CString ->                              -- interface_name : TBasicType TUTF8
    CString ->                              -- method_name : TBasicType TUTF8
    Ptr GVariant ->                         -- parameters : TVariant
    Ptr GLib.VariantType.VariantType ->     -- reply_type : TInterface (Name {namespace = "GLib", name = "VariantType"})
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gio", name = "DBusCallFlags"})
    Int32 ->                                -- timeout_msec : TBasicType TInt
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    FunPtr Gio.Callbacks.C_AsyncReadyCallback -> -- callback : TInterface (Name {namespace = "Gio", name = "AsyncReadyCallback"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    IO ()

-- | Asynchronously invokes the /@methodName@/ method on the
-- /@interfaceName@/ D-Bus interface on the remote object at
-- /@objectPath@/ owned by /@busName@/.
-- 
-- If /@connection@/ is closed then the operation will fail with
-- 'GI.Gio.Enums.IOErrorEnumClosed'. If /@cancellable@/ is canceled, the operation will
-- fail with 'GI.Gio.Enums.IOErrorEnumCancelled'. If /@parameters@/ contains a value
-- not compatible with the D-Bus protocol, the operation fails with
-- 'GI.Gio.Enums.IOErrorEnumInvalidArgument'.
-- 
-- If /@replyType@/ is non-'P.Nothing' then the reply will be checked for having this type and an
-- error will be raised if it does not match.  Said another way, if you give a /@replyType@/
-- then any non-'P.Nothing' return value will be of this type. Unless it’s
-- @/G_VARIANT_TYPE_UNIT/@, the /@replyType@/ will be a tuple containing one or more
-- values.
-- 
-- If the /@parameters@/ t'GVariant' is floating, it is consumed. This allows
-- convenient \'inline\' use of @/g_variant_new()/@, e.g.:
-- 
-- === /C code/
-- >
-- > g_dbus_connection_call (connection,
-- >                         "org.freedesktop.StringThings",
-- >                         "/org/freedesktop/StringThings",
-- >                         "org.freedesktop.StringThings",
-- >                         "TwoStrings",
-- >                         g_variant_new ("(ss)",
-- >                                        "Thing One",
-- >                                        "Thing Two"),
-- >                         NULL,
-- >                         G_DBUS_CALL_FLAGS_NONE,
-- >                         -1,
-- >                         NULL,
-- >                         (GAsyncReadyCallback) two_strings_done,
-- >                         NULL);
-- 
-- 
-- This is an asynchronous method. When the operation is finished,
-- /@callback@/ will be invoked in the
-- [thread-default main context][g-main-context-push-thread-default]
-- of the thread you are calling this method from. You can then call
-- 'GI.Gio.Objects.DBusConnection.dBusConnectionCallFinish' to get the result of the operation.
-- See 'GI.Gio.Objects.DBusConnection.dBusConnectionCallSync' for the synchronous version of this
-- function.
-- 
-- If /@callback@/ is 'P.Nothing' then the D-Bus method call message will be sent with
-- the 'GI.Gio.Flags.DBusMessageFlagsNoReplyExpected' flag set.
-- 
-- /Since: 2.26/
dBusConnectionCall ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusConnection a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@connection@/: a t'GI.Gio.Objects.DBusConnection.DBusConnection'
    -> Maybe (T.Text)
    -- ^ /@busName@/: a unique or well-known bus name or 'P.Nothing' if
    --     /@connection@/ is not a message bus connection
    -> T.Text
    -- ^ /@objectPath@/: path of remote object
    -> T.Text
    -- ^ /@interfaceName@/: D-Bus interface to invoke method on
    -> T.Text
    -- ^ /@methodName@/: the name of the method to invoke
    -> Maybe (GVariant)
    -- ^ /@parameters@/: a t'GVariant' tuple with parameters for the method
    --     or 'P.Nothing' if not passing parameters
    -> Maybe (GLib.VariantType.VariantType)
    -- ^ /@replyType@/: the expected type of the reply (which will be a
    --     tuple), or 'P.Nothing'
    -> [Gio.Flags.DBusCallFlags]
    -- ^ /@flags@/: flags from the t'GI.Gio.Flags.DBusCallFlags' enumeration
    -> Int32
    -- ^ /@timeoutMsec@/: the timeout in milliseconds, -1 to use the default
    --     timeout or @/G_MAXINT/@ for no timeout
    -> Maybe (b)
    -- ^ /@cancellable@/: a t'GI.Gio.Objects.Cancellable.Cancellable' or 'P.Nothing'
    -> Maybe (Gio.Callbacks.AsyncReadyCallback)
    -- ^ /@callback@/: a t'GI.Gio.Callbacks.AsyncReadyCallback' to call when the request
    --     is satisfied or 'P.Nothing' if you don\'t care about the result of the
    --     method invocation
    -> m ()
dBusConnectionCall :: a
-> Maybe Text
-> Text
-> Text
-> Text
-> Maybe GVariant
-> Maybe VariantType
-> [DBusCallFlags]
-> Int32
-> Maybe b
-> Maybe AsyncReadyCallback
-> m ()
dBusConnectionCall connection :: a
connection busName :: Maybe Text
busName objectPath :: Text
objectPath interfaceName :: Text
interfaceName methodName :: Text
methodName parameters :: Maybe GVariant
parameters replyType :: Maybe VariantType
replyType flags :: [DBusCallFlags]
flags timeoutMsec :: Int32
timeoutMsec cancellable :: Maybe b
cancellable callback :: Maybe AsyncReadyCallback
callback = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusConnection
connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    CString
maybeBusName <- case Maybe Text
busName of
        Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just jBusName :: Text
jBusName -> do
            CString
jBusName' <- Text -> IO CString
textToCString Text
jBusName
            CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jBusName'
    CString
objectPath' <- Text -> IO CString
textToCString Text
objectPath
    CString
interfaceName' <- Text -> IO CString
textToCString Text
interfaceName
    CString
methodName' <- Text -> IO CString
textToCString Text
methodName
    Ptr GVariant
maybeParameters <- case Maybe GVariant
parameters of
        Nothing -> Ptr GVariant -> IO (Ptr GVariant)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GVariant
forall a. Ptr a
nullPtr
        Just jParameters :: GVariant
jParameters -> do
            Ptr GVariant
jParameters' <- GVariant -> IO (Ptr GVariant)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GVariant
jParameters
            Ptr GVariant -> IO (Ptr GVariant)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GVariant
jParameters'
    Ptr VariantType
maybeReplyType <- case Maybe VariantType
replyType of
        Nothing -> Ptr VariantType -> IO (Ptr VariantType)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr VariantType
forall a. Ptr a
nullPtr
        Just jReplyType :: VariantType
jReplyType -> do
            Ptr VariantType
jReplyType' <- VariantType -> IO (Ptr VariantType)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr VariantType
jReplyType
            Ptr VariantType -> IO (Ptr VariantType)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr VariantType
jReplyType'
    let flags' :: CUInt
flags' = [DBusCallFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [DBusCallFlags]
flags
    Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
        Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just jCancellable :: b
jCancellable -> do
            Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    FunPtr C_AsyncReadyCallback
maybeCallback <- case Maybe AsyncReadyCallback
callback of
        Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_AsyncReadyCallback
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
        Just jCallback :: AsyncReadyCallback
jCallback -> do
            Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
            FunPtr C_AsyncReadyCallback
jCallback' <- C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
Gio.Callbacks.mk_AsyncReadyCallback (Maybe (Ptr (FunPtr C_AsyncReadyCallback))
-> AsyncReadyCallback_WithClosures -> C_AsyncReadyCallback
Gio.Callbacks.wrap_AsyncReadyCallback (Ptr (FunPtr C_AsyncReadyCallback)
-> Maybe (Ptr (FunPtr C_AsyncReadyCallback))
forall a. a -> Maybe a
Just Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback) (AsyncReadyCallback -> AsyncReadyCallback_WithClosures
Gio.Callbacks.drop_closures_AsyncReadyCallback AsyncReadyCallback
jCallback))
            Ptr (FunPtr C_AsyncReadyCallback)
-> FunPtr C_AsyncReadyCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback FunPtr C_AsyncReadyCallback
jCallback'
            FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
jCallback'
    let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
    Ptr DBusConnection
-> CString
-> CString
-> CString
-> CString
-> Ptr GVariant
-> Ptr VariantType
-> CUInt
-> Int32
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> C_DestroyNotify
g_dbus_connection_call Ptr DBusConnection
connection' CString
maybeBusName CString
objectPath' CString
interfaceName' CString
methodName' Ptr GVariant
maybeParameters Ptr VariantType
maybeReplyType CUInt
flags' Int32
timeoutMsec Ptr Cancellable
maybeCancellable FunPtr C_AsyncReadyCallback
maybeCallback Ptr ()
forall a. Ptr a
userData
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
connection
    Maybe GVariant -> (GVariant -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe GVariant
parameters GVariant -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Maybe VariantType -> (VariantType -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe VariantType
replyType VariantType -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeBusName
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
objectPath'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
interfaceName'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
methodName'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

#endif

-- method DBusConnection::call_finish
-- method type : OrdinaryMethod
-- 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 = "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_connection_call()"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just TVariant
-- throws : True
-- Skip return : False

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

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

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

#endif

-- method DBusConnection::call_sync
-- method type : OrdinaryMethod
-- 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 = "bus_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a unique or well-known bus name or %NULL if\n    @connection is not a message bus connection"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "object_path"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "path of remote object"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "interface_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "D-Bus interface to invoke method on"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "method_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the name of the method to invoke"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "parameters"
--           , argType = TVariant
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a #GVariant tuple with parameters for the method\n    or %NULL if not passing parameters"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "reply_type"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "VariantType" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the expected type of the reply, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusCallFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "flags from the #GDBusCallFlags enumeration"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "timeout_msec"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the timeout in milliseconds, -1 to use the default\n    timeout or %G_MAXINT for no timeout"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GCancellable or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just TVariant
-- throws : True
-- Skip return : False

foreign import ccall "g_dbus_connection_call_sync" g_dbus_connection_call_sync :: 
    Ptr DBusConnection ->                   -- connection : TInterface (Name {namespace = "Gio", name = "DBusConnection"})
    CString ->                              -- bus_name : TBasicType TUTF8
    CString ->                              -- object_path : TBasicType TUTF8
    CString ->                              -- interface_name : TBasicType TUTF8
    CString ->                              -- method_name : TBasicType TUTF8
    Ptr GVariant ->                         -- parameters : TVariant
    Ptr GLib.VariantType.VariantType ->     -- reply_type : TInterface (Name {namespace = "GLib", name = "VariantType"})
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gio", name = "DBusCallFlags"})
    Int32 ->                                -- timeout_msec : TBasicType TInt
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr GVariant)

-- | Synchronously invokes the /@methodName@/ method on the
-- /@interfaceName@/ D-Bus interface on the remote object at
-- /@objectPath@/ owned by /@busName@/.
-- 
-- If /@connection@/ is closed then the operation will fail with
-- 'GI.Gio.Enums.IOErrorEnumClosed'. If /@cancellable@/ is canceled, the
-- operation will fail with 'GI.Gio.Enums.IOErrorEnumCancelled'. If /@parameters@/
-- contains a value not compatible with the D-Bus protocol, the operation
-- fails with 'GI.Gio.Enums.IOErrorEnumInvalidArgument'.
-- 
-- If /@replyType@/ is non-'P.Nothing' then the reply will be checked for having
-- this type and an error will be raised if it does not match.  Said
-- another way, if you give a /@replyType@/ then any non-'P.Nothing' return
-- value will be of this type.
-- 
-- If the /@parameters@/ t'GVariant' is floating, it is consumed.
-- This allows convenient \'inline\' use of @/g_variant_new()/@, e.g.:
-- 
-- === /C code/
-- >
-- > g_dbus_connection_call_sync (connection,
-- >                              "org.freedesktop.StringThings",
-- >                              "/org/freedesktop/StringThings",
-- >                              "org.freedesktop.StringThings",
-- >                              "TwoStrings",
-- >                              g_variant_new ("(ss)",
-- >                                             "Thing One",
-- >                                             "Thing Two"),
-- >                              NULL,
-- >                              G_DBUS_CALL_FLAGS_NONE,
-- >                              -1,
-- >                              NULL,
-- >                              &error);
-- 
-- 
-- The calling thread is blocked until a reply is received. See
-- 'GI.Gio.Objects.DBusConnection.dBusConnectionCall' for the asynchronous version of
-- this method.
-- 
-- /Since: 2.26/
dBusConnectionCallSync ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusConnection a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@connection@/: a t'GI.Gio.Objects.DBusConnection.DBusConnection'
    -> Maybe (T.Text)
    -- ^ /@busName@/: a unique or well-known bus name or 'P.Nothing' if
    --     /@connection@/ is not a message bus connection
    -> T.Text
    -- ^ /@objectPath@/: path of remote object
    -> T.Text
    -- ^ /@interfaceName@/: D-Bus interface to invoke method on
    -> T.Text
    -- ^ /@methodName@/: the name of the method to invoke
    -> Maybe (GVariant)
    -- ^ /@parameters@/: a t'GVariant' tuple with parameters for the method
    --     or 'P.Nothing' if not passing parameters
    -> Maybe (GLib.VariantType.VariantType)
    -- ^ /@replyType@/: the expected type of the reply, or 'P.Nothing'
    -> [Gio.Flags.DBusCallFlags]
    -- ^ /@flags@/: flags from the t'GI.Gio.Flags.DBusCallFlags' enumeration
    -> Int32
    -- ^ /@timeoutMsec@/: the timeout in milliseconds, -1 to use the default
    --     timeout or @/G_MAXINT/@ for no timeout
    -> Maybe (b)
    -- ^ /@cancellable@/: a t'GI.Gio.Objects.Cancellable.Cancellable' or 'P.Nothing'
    -> m GVariant
    -- ^ __Returns:__ 'P.Nothing' if /@error@/ is set. Otherwise a t'GVariant' tuple with
    --     return values. Free with 'GI.GLib.Structs.Variant.variantUnref'. /(Can throw 'Data.GI.Base.GError.GError')/
dBusConnectionCallSync :: a
-> Maybe Text
-> Text
-> Text
-> Text
-> Maybe GVariant
-> Maybe VariantType
-> [DBusCallFlags]
-> Int32
-> Maybe b
-> m GVariant
dBusConnectionCallSync connection :: a
connection busName :: Maybe Text
busName objectPath :: Text
objectPath interfaceName :: Text
interfaceName methodName :: Text
methodName parameters :: Maybe GVariant
parameters replyType :: Maybe VariantType
replyType flags :: [DBusCallFlags]
flags timeoutMsec :: Int32
timeoutMsec cancellable :: Maybe b
cancellable = IO GVariant -> m GVariant
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GVariant -> m GVariant) -> IO GVariant -> m GVariant
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusConnection
connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    CString
maybeBusName <- case Maybe Text
busName of
        Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just jBusName :: Text
jBusName -> do
            CString
jBusName' <- Text -> IO CString
textToCString Text
jBusName
            CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jBusName'
    CString
objectPath' <- Text -> IO CString
textToCString Text
objectPath
    CString
interfaceName' <- Text -> IO CString
textToCString Text
interfaceName
    CString
methodName' <- Text -> IO CString
textToCString Text
methodName
    Ptr GVariant
maybeParameters <- case Maybe GVariant
parameters of
        Nothing -> Ptr GVariant -> IO (Ptr GVariant)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GVariant
forall a. Ptr a
nullPtr
        Just jParameters :: GVariant
jParameters -> do
            Ptr GVariant
jParameters' <- GVariant -> IO (Ptr GVariant)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GVariant
jParameters
            Ptr GVariant -> IO (Ptr GVariant)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GVariant
jParameters'
    Ptr VariantType
maybeReplyType <- case Maybe VariantType
replyType of
        Nothing -> Ptr VariantType -> IO (Ptr VariantType)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr VariantType
forall a. Ptr a
nullPtr
        Just jReplyType :: VariantType
jReplyType -> do
            Ptr VariantType
jReplyType' <- VariantType -> IO (Ptr VariantType)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr VariantType
jReplyType
            Ptr VariantType -> IO (Ptr VariantType)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr VariantType
jReplyType'
    let flags' :: CUInt
flags' = [DBusCallFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [DBusCallFlags]
flags
    Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
        Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just jCancellable :: b
jCancellable -> do
            Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    IO GVariant -> IO () -> IO GVariant
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr GVariant
result <- (Ptr (Ptr GError) -> IO (Ptr GVariant)) -> IO (Ptr GVariant)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr GVariant)) -> IO (Ptr GVariant))
-> (Ptr (Ptr GError) -> IO (Ptr GVariant)) -> IO (Ptr GVariant)
forall a b. (a -> b) -> a -> b
$ Ptr DBusConnection
-> CString
-> CString
-> CString
-> CString
-> Ptr GVariant
-> Ptr VariantType
-> CUInt
-> Int32
-> Ptr Cancellable
-> Ptr (Ptr GError)
-> IO (Ptr GVariant)
g_dbus_connection_call_sync Ptr DBusConnection
connection' CString
maybeBusName CString
objectPath' CString
interfaceName' CString
methodName' Ptr GVariant
maybeParameters Ptr VariantType
maybeReplyType CUInt
flags' Int32
timeoutMsec Ptr Cancellable
maybeCancellable
        Text -> Ptr GVariant -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusConnectionCallSync" Ptr GVariant
result
        GVariant
result' <- Ptr GVariant -> IO GVariant
B.GVariant.wrapGVariantPtr Ptr GVariant
result
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
connection
        Maybe GVariant -> (GVariant -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe GVariant
parameters GVariant -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        Maybe VariantType -> (VariantType -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe VariantType
replyType VariantType -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeBusName
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
objectPath'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
interfaceName'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
methodName'
        GVariant -> IO GVariant
forall (m :: * -> *) a. Monad m => a -> m a
return GVariant
result'
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeBusName
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
objectPath'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
interfaceName'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
methodName'
     )

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

#endif

-- method DBusConnection::call_with_unix_fd_list
-- method type : OrdinaryMethod
-- 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 = "bus_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a unique or well-known bus name or %NULL if\n    @connection is not a message bus connection"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "object_path"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "path of remote object"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "interface_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "D-Bus interface to invoke method on"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "method_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the name of the method to invoke"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "parameters"
--           , argType = TVariant
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a #GVariant tuple with parameters for the method\n    or %NULL if not passing parameters"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "reply_type"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "VariantType" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the expected type of the reply, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusCallFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "flags from the #GDBusCallFlags enumeration"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "timeout_msec"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the timeout in milliseconds, -1 to use the default\n    timeout or %G_MAXINT for no timeout"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "fd_list"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "UnixFDList" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GUnixFDList or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GCancellable or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "callback"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncReadyCallback" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a #GAsyncReadyCallback to call when the request is\n    satisfied or %NULL if you don't * care about the result of the\n    method invocation"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = 12
--           , 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_connection_call_with_unix_fd_list" g_dbus_connection_call_with_unix_fd_list :: 
    Ptr DBusConnection ->                   -- connection : TInterface (Name {namespace = "Gio", name = "DBusConnection"})
    CString ->                              -- bus_name : TBasicType TUTF8
    CString ->                              -- object_path : TBasicType TUTF8
    CString ->                              -- interface_name : TBasicType TUTF8
    CString ->                              -- method_name : TBasicType TUTF8
    Ptr GVariant ->                         -- parameters : TVariant
    Ptr GLib.VariantType.VariantType ->     -- reply_type : TInterface (Name {namespace = "GLib", name = "VariantType"})
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gio", name = "DBusCallFlags"})
    Int32 ->                                -- timeout_msec : TBasicType TInt
    Ptr Gio.UnixFDList.UnixFDList ->        -- fd_list : TInterface (Name {namespace = "Gio", name = "UnixFDList"})
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    FunPtr Gio.Callbacks.C_AsyncReadyCallback -> -- callback : TInterface (Name {namespace = "Gio", name = "AsyncReadyCallback"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    IO ()

-- | Like 'GI.Gio.Objects.DBusConnection.dBusConnectionCall' but also takes a t'GI.Gio.Objects.UnixFDList.UnixFDList' object.
-- 
-- This method is only available on UNIX.
-- 
-- /Since: 2.30/
dBusConnectionCallWithUnixFdList ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusConnection a, Gio.UnixFDList.IsUnixFDList b, Gio.Cancellable.IsCancellable c) =>
    a
    -- ^ /@connection@/: a t'GI.Gio.Objects.DBusConnection.DBusConnection'
    -> Maybe (T.Text)
    -- ^ /@busName@/: a unique or well-known bus name or 'P.Nothing' if
    --     /@connection@/ is not a message bus connection
    -> T.Text
    -- ^ /@objectPath@/: path of remote object
    -> T.Text
    -- ^ /@interfaceName@/: D-Bus interface to invoke method on
    -> T.Text
    -- ^ /@methodName@/: the name of the method to invoke
    -> Maybe (GVariant)
    -- ^ /@parameters@/: a t'GVariant' tuple with parameters for the method
    --     or 'P.Nothing' if not passing parameters
    -> Maybe (GLib.VariantType.VariantType)
    -- ^ /@replyType@/: the expected type of the reply, or 'P.Nothing'
    -> [Gio.Flags.DBusCallFlags]
    -- ^ /@flags@/: flags from the t'GI.Gio.Flags.DBusCallFlags' enumeration
    -> Int32
    -- ^ /@timeoutMsec@/: the timeout in milliseconds, -1 to use the default
    --     timeout or @/G_MAXINT/@ for no timeout
    -> Maybe (b)
    -- ^ /@fdList@/: a t'GI.Gio.Objects.UnixFDList.UnixFDList' or 'P.Nothing'
    -> Maybe (c)
    -- ^ /@cancellable@/: a t'GI.Gio.Objects.Cancellable.Cancellable' or 'P.Nothing'
    -> Maybe (Gio.Callbacks.AsyncReadyCallback)
    -- ^ /@callback@/: a t'GI.Gio.Callbacks.AsyncReadyCallback' to call when the request is
    --     satisfied or 'P.Nothing' if you don\'t * care about the result of the
    --     method invocation
    -> m ()
dBusConnectionCallWithUnixFdList :: a
-> Maybe Text
-> Text
-> Text
-> Text
-> Maybe GVariant
-> Maybe VariantType
-> [DBusCallFlags]
-> Int32
-> Maybe b
-> Maybe c
-> Maybe AsyncReadyCallback
-> m ()
dBusConnectionCallWithUnixFdList connection :: a
connection busName :: Maybe Text
busName objectPath :: Text
objectPath interfaceName :: Text
interfaceName methodName :: Text
methodName parameters :: Maybe GVariant
parameters replyType :: Maybe VariantType
replyType flags :: [DBusCallFlags]
flags timeoutMsec :: Int32
timeoutMsec fdList :: Maybe b
fdList cancellable :: Maybe c
cancellable callback :: Maybe AsyncReadyCallback
callback = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusConnection
connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    CString
maybeBusName <- case Maybe Text
busName of
        Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just jBusName :: Text
jBusName -> do
            CString
jBusName' <- Text -> IO CString
textToCString Text
jBusName
            CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jBusName'
    CString
objectPath' <- Text -> IO CString
textToCString Text
objectPath
    CString
interfaceName' <- Text -> IO CString
textToCString Text
interfaceName
    CString
methodName' <- Text -> IO CString
textToCString Text
methodName
    Ptr GVariant
maybeParameters <- case Maybe GVariant
parameters of
        Nothing -> Ptr GVariant -> IO (Ptr GVariant)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GVariant
forall a. Ptr a
nullPtr
        Just jParameters :: GVariant
jParameters -> do
            Ptr GVariant
jParameters' <- GVariant -> IO (Ptr GVariant)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GVariant
jParameters
            Ptr GVariant -> IO (Ptr GVariant)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GVariant
jParameters'
    Ptr VariantType
maybeReplyType <- case Maybe VariantType
replyType of
        Nothing -> Ptr VariantType -> IO (Ptr VariantType)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr VariantType
forall a. Ptr a
nullPtr
        Just jReplyType :: VariantType
jReplyType -> do
            Ptr VariantType
jReplyType' <- VariantType -> IO (Ptr VariantType)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr VariantType
jReplyType
            Ptr VariantType -> IO (Ptr VariantType)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr VariantType
jReplyType'
    let flags' :: CUInt
flags' = [DBusCallFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [DBusCallFlags]
flags
    Ptr UnixFDList
maybeFdList <- case Maybe b
fdList of
        Nothing -> Ptr UnixFDList -> IO (Ptr UnixFDList)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr UnixFDList
forall a. Ptr a
nullPtr
        Just jFdList :: b
jFdList -> do
            Ptr UnixFDList
jFdList' <- b -> IO (Ptr UnixFDList)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jFdList
            Ptr UnixFDList -> IO (Ptr UnixFDList)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr UnixFDList
jFdList'
    Ptr Cancellable
maybeCancellable <- case Maybe c
cancellable of
        Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just jCancellable :: c
jCancellable -> do
            Ptr Cancellable
jCancellable' <- c -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    FunPtr C_AsyncReadyCallback
maybeCallback <- case Maybe AsyncReadyCallback
callback of
        Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_AsyncReadyCallback
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
        Just jCallback :: AsyncReadyCallback
jCallback -> do
            Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
            FunPtr C_AsyncReadyCallback
jCallback' <- C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
Gio.Callbacks.mk_AsyncReadyCallback (Maybe (Ptr (FunPtr C_AsyncReadyCallback))
-> AsyncReadyCallback_WithClosures -> C_AsyncReadyCallback
Gio.Callbacks.wrap_AsyncReadyCallback (Ptr (FunPtr C_AsyncReadyCallback)
-> Maybe (Ptr (FunPtr C_AsyncReadyCallback))
forall a. a -> Maybe a
Just Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback) (AsyncReadyCallback -> AsyncReadyCallback_WithClosures
Gio.Callbacks.drop_closures_AsyncReadyCallback AsyncReadyCallback
jCallback))
            Ptr (FunPtr C_AsyncReadyCallback)
-> FunPtr C_AsyncReadyCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback FunPtr C_AsyncReadyCallback
jCallback'
            FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
jCallback'
    let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
    Ptr DBusConnection
-> CString
-> CString
-> CString
-> CString
-> Ptr GVariant
-> Ptr VariantType
-> CUInt
-> Int32
-> Ptr UnixFDList
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> C_DestroyNotify
g_dbus_connection_call_with_unix_fd_list Ptr DBusConnection
connection' CString
maybeBusName CString
objectPath' CString
interfaceName' CString
methodName' Ptr GVariant
maybeParameters Ptr VariantType
maybeReplyType CUInt
flags' Int32
timeoutMsec Ptr UnixFDList
maybeFdList Ptr Cancellable
maybeCancellable FunPtr C_AsyncReadyCallback
maybeCallback Ptr ()
forall a. Ptr a
userData
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
connection
    Maybe GVariant -> (GVariant -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe GVariant
parameters GVariant -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Maybe VariantType -> (VariantType -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe VariantType
replyType VariantType -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
fdList b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Maybe c -> (c -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe c
cancellable c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeBusName
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
objectPath'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
interfaceName'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
methodName'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

#endif

-- method DBusConnection::call_with_unix_fd_list_finish
-- method type : OrdinaryMethod
-- 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 = "out_fd_list"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "UnixFDList" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for a #GUnixFDList or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "res"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncResult" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a #GAsyncResult obtained from the #GAsyncReadyCallback passed to\n    g_dbus_connection_call_with_unix_fd_list()"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just TVariant
-- throws : True
-- Skip return : False

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

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

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

#endif

-- method DBusConnection::call_with_unix_fd_list_sync
-- method type : OrdinaryMethod
-- 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 = "bus_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a unique or well-known bus name or %NULL\n    if @connection is not a message bus connection"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "object_path"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "path of remote object"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "interface_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "D-Bus interface to invoke method on"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "method_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the name of the method to invoke"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "parameters"
--           , argType = TVariant
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a #GVariant tuple with parameters for\n    the method or %NULL if not passing parameters"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "reply_type"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "VariantType" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the expected type of the reply, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusCallFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "flags from the #GDBusCallFlags enumeration"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "timeout_msec"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the timeout in milliseconds, -1 to use the default\n    timeout or %G_MAXINT for no timeout"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "fd_list"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "UnixFDList" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GUnixFDList or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "out_fd_list"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "UnixFDList" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for a #GUnixFDList or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GCancellable or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just TVariant
-- throws : True
-- Skip return : False

foreign import ccall "g_dbus_connection_call_with_unix_fd_list_sync" g_dbus_connection_call_with_unix_fd_list_sync :: 
    Ptr DBusConnection ->                   -- connection : TInterface (Name {namespace = "Gio", name = "DBusConnection"})
    CString ->                              -- bus_name : TBasicType TUTF8
    CString ->                              -- object_path : TBasicType TUTF8
    CString ->                              -- interface_name : TBasicType TUTF8
    CString ->                              -- method_name : TBasicType TUTF8
    Ptr GVariant ->                         -- parameters : TVariant
    Ptr GLib.VariantType.VariantType ->     -- reply_type : TInterface (Name {namespace = "GLib", name = "VariantType"})
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gio", name = "DBusCallFlags"})
    Int32 ->                                -- timeout_msec : TBasicType TInt
    Ptr Gio.UnixFDList.UnixFDList ->        -- fd_list : TInterface (Name {namespace = "Gio", name = "UnixFDList"})
    Ptr (Ptr Gio.UnixFDList.UnixFDList) ->  -- out_fd_list : TInterface (Name {namespace = "Gio", name = "UnixFDList"})
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr GVariant)

-- | Like 'GI.Gio.Objects.DBusConnection.dBusConnectionCallSync' but also takes and returns t'GI.Gio.Objects.UnixFDList.UnixFDList' objects.
-- 
-- This method is only available on UNIX.
-- 
-- /Since: 2.30/
dBusConnectionCallWithUnixFdListSync ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusConnection a, Gio.UnixFDList.IsUnixFDList b, Gio.Cancellable.IsCancellable c) =>
    a
    -- ^ /@connection@/: a t'GI.Gio.Objects.DBusConnection.DBusConnection'
    -> Maybe (T.Text)
    -- ^ /@busName@/: a unique or well-known bus name or 'P.Nothing'
    --     if /@connection@/ is not a message bus connection
    -> T.Text
    -- ^ /@objectPath@/: path of remote object
    -> T.Text
    -- ^ /@interfaceName@/: D-Bus interface to invoke method on
    -> T.Text
    -- ^ /@methodName@/: the name of the method to invoke
    -> Maybe (GVariant)
    -- ^ /@parameters@/: a t'GVariant' tuple with parameters for
    --     the method or 'P.Nothing' if not passing parameters
    -> Maybe (GLib.VariantType.VariantType)
    -- ^ /@replyType@/: the expected type of the reply, or 'P.Nothing'
    -> [Gio.Flags.DBusCallFlags]
    -- ^ /@flags@/: flags from the t'GI.Gio.Flags.DBusCallFlags' enumeration
    -> Int32
    -- ^ /@timeoutMsec@/: the timeout in milliseconds, -1 to use the default
    --     timeout or @/G_MAXINT/@ for no timeout
    -> Maybe (b)
    -- ^ /@fdList@/: a t'GI.Gio.Objects.UnixFDList.UnixFDList' or 'P.Nothing'
    -> Maybe (c)
    -- ^ /@cancellable@/: a t'GI.Gio.Objects.Cancellable.Cancellable' or 'P.Nothing'
    -> m ((GVariant, Gio.UnixFDList.UnixFDList))
    -- ^ __Returns:__ 'P.Nothing' if /@error@/ is set. Otherwise a t'GVariant' tuple with
    --     return values. Free with 'GI.GLib.Structs.Variant.variantUnref'. /(Can throw 'Data.GI.Base.GError.GError')/
dBusConnectionCallWithUnixFdListSync :: a
-> Maybe Text
-> Text
-> Text
-> Text
-> Maybe GVariant
-> Maybe VariantType
-> [DBusCallFlags]
-> Int32
-> Maybe b
-> Maybe c
-> m (GVariant, UnixFDList)
dBusConnectionCallWithUnixFdListSync connection :: a
connection busName :: Maybe Text
busName objectPath :: Text
objectPath interfaceName :: Text
interfaceName methodName :: Text
methodName parameters :: Maybe GVariant
parameters replyType :: Maybe VariantType
replyType flags :: [DBusCallFlags]
flags timeoutMsec :: Int32
timeoutMsec fdList :: Maybe b
fdList cancellable :: Maybe c
cancellable = IO (GVariant, UnixFDList) -> m (GVariant, UnixFDList)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GVariant, UnixFDList) -> m (GVariant, UnixFDList))
-> IO (GVariant, UnixFDList) -> m (GVariant, UnixFDList)
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusConnection
connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    CString
maybeBusName <- case Maybe Text
busName of
        Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just jBusName :: Text
jBusName -> do
            CString
jBusName' <- Text -> IO CString
textToCString Text
jBusName
            CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jBusName'
    CString
objectPath' <- Text -> IO CString
textToCString Text
objectPath
    CString
interfaceName' <- Text -> IO CString
textToCString Text
interfaceName
    CString
methodName' <- Text -> IO CString
textToCString Text
methodName
    Ptr GVariant
maybeParameters <- case Maybe GVariant
parameters of
        Nothing -> Ptr GVariant -> IO (Ptr GVariant)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GVariant
forall a. Ptr a
nullPtr
        Just jParameters :: GVariant
jParameters -> do
            Ptr GVariant
jParameters' <- GVariant -> IO (Ptr GVariant)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GVariant
jParameters
            Ptr GVariant -> IO (Ptr GVariant)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GVariant
jParameters'
    Ptr VariantType
maybeReplyType <- case Maybe VariantType
replyType of
        Nothing -> Ptr VariantType -> IO (Ptr VariantType)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr VariantType
forall a. Ptr a
nullPtr
        Just jReplyType :: VariantType
jReplyType -> do
            Ptr VariantType
jReplyType' <- VariantType -> IO (Ptr VariantType)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr VariantType
jReplyType
            Ptr VariantType -> IO (Ptr VariantType)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr VariantType
jReplyType'
    let flags' :: CUInt
flags' = [DBusCallFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [DBusCallFlags]
flags
    Ptr UnixFDList
maybeFdList <- case Maybe b
fdList of
        Nothing -> Ptr UnixFDList -> IO (Ptr UnixFDList)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr UnixFDList
forall a. Ptr a
nullPtr
        Just jFdList :: b
jFdList -> do
            Ptr UnixFDList
jFdList' <- b -> IO (Ptr UnixFDList)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jFdList
            Ptr UnixFDList -> IO (Ptr UnixFDList)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr UnixFDList
jFdList'
    Ptr (Ptr UnixFDList)
outFdList <- IO (Ptr (Ptr UnixFDList))
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr (Ptr Gio.UnixFDList.UnixFDList))
    Ptr Cancellable
maybeCancellable <- case Maybe c
cancellable of
        Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just jCancellable :: c
jCancellable -> do
            Ptr Cancellable
jCancellable' <- c -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    IO (GVariant, UnixFDList) -> IO () -> IO (GVariant, UnixFDList)
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr GVariant
result <- (Ptr (Ptr GError) -> IO (Ptr GVariant)) -> IO (Ptr GVariant)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr GVariant)) -> IO (Ptr GVariant))
-> (Ptr (Ptr GError) -> IO (Ptr GVariant)) -> IO (Ptr GVariant)
forall a b. (a -> b) -> a -> b
$ Ptr DBusConnection
-> CString
-> CString
-> CString
-> CString
-> Ptr GVariant
-> Ptr VariantType
-> CUInt
-> Int32
-> Ptr UnixFDList
-> Ptr (Ptr UnixFDList)
-> Ptr Cancellable
-> Ptr (Ptr GError)
-> IO (Ptr GVariant)
g_dbus_connection_call_with_unix_fd_list_sync Ptr DBusConnection
connection' CString
maybeBusName CString
objectPath' CString
interfaceName' CString
methodName' Ptr GVariant
maybeParameters Ptr VariantType
maybeReplyType CUInt
flags' Int32
timeoutMsec Ptr UnixFDList
maybeFdList Ptr (Ptr UnixFDList)
outFdList Ptr Cancellable
maybeCancellable
        Text -> Ptr GVariant -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusConnectionCallWithUnixFdListSync" Ptr GVariant
result
        GVariant
result' <- Ptr GVariant -> IO GVariant
B.GVariant.wrapGVariantPtr Ptr GVariant
result
        Ptr UnixFDList
outFdList' <- Ptr (Ptr UnixFDList) -> IO (Ptr UnixFDList)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr UnixFDList)
outFdList
        UnixFDList
outFdList'' <- ((ManagedPtr UnixFDList -> UnixFDList)
-> Ptr UnixFDList -> IO UnixFDList
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr UnixFDList -> UnixFDList
Gio.UnixFDList.UnixFDList) Ptr UnixFDList
outFdList'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
connection
        Maybe GVariant -> (GVariant -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe GVariant
parameters GVariant -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        Maybe VariantType -> (VariantType -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe VariantType
replyType VariantType -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
fdList b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        Maybe c -> (c -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe c
cancellable c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeBusName
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
objectPath'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
interfaceName'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
methodName'
        Ptr (Ptr UnixFDList) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr UnixFDList)
outFdList
        (GVariant, UnixFDList) -> IO (GVariant, UnixFDList)
forall (m :: * -> *) a. Monad m => a -> m a
return (GVariant
result', UnixFDList
outFdList'')
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeBusName
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
objectPath'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
interfaceName'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
methodName'
        Ptr (Ptr UnixFDList) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr UnixFDList)
outFdList
     )

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

#endif

-- method DBusConnection::close
-- method type : OrdinaryMethod
-- 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 = "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\n    satisfied or %NULL if you don't care about the result"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = 3
--           , 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_connection_close" g_dbus_connection_close :: 
    Ptr DBusConnection ->                   -- connection : TInterface (Name {namespace = "Gio", name = "DBusConnection"})
    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 ()

-- | Closes /@connection@/. Note that this never causes the process to
-- exit (this might only happen if the other end of a shared message
-- bus connection disconnects, see t'GI.Gio.Objects.DBusConnection.DBusConnection':@/exit-on-close/@).
-- 
-- Once the connection is closed, operations such as sending a message
-- will return with the error 'GI.Gio.Enums.IOErrorEnumClosed'. Closing a connection
-- will not automatically flush the connection so queued messages may
-- be lost. Use 'GI.Gio.Objects.DBusConnection.dBusConnectionFlush' if you need such guarantees.
-- 
-- If /@connection@/ is already closed, this method fails with
-- 'GI.Gio.Enums.IOErrorEnumClosed'.
-- 
-- When /@connection@/ has been closed, the [closed]("GI.Gio.Objects.DBusConnection#signal:closed")
-- signal is emitted in the
-- [thread-default main context][g-main-context-push-thread-default]
-- of the thread that /@connection@/ was constructed in.
-- 
-- This is an asynchronous method. When the operation is finished,
-- /@callback@/ will be invoked in the
-- [thread-default main context][g-main-context-push-thread-default]
-- of the thread you are calling this method from. You can
-- then call 'GI.Gio.Objects.DBusConnection.dBusConnectionCloseFinish' to get the result of the
-- operation. See 'GI.Gio.Objects.DBusConnection.dBusConnectionCloseSync' for the synchronous
-- version.
-- 
-- /Since: 2.26/
dBusConnectionClose ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusConnection a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@connection@/: a t'GI.Gio.Objects.DBusConnection.DBusConnection'
    -> Maybe (b)
    -- ^ /@cancellable@/: a t'GI.Gio.Objects.Cancellable.Cancellable' or 'P.Nothing'
    -> Maybe (Gio.Callbacks.AsyncReadyCallback)
    -- ^ /@callback@/: a t'GI.Gio.Callbacks.AsyncReadyCallback' to call when the request is
    --     satisfied or 'P.Nothing' if you don\'t care about the result
    -> m ()
dBusConnectionClose :: a -> Maybe b -> Maybe AsyncReadyCallback -> m ()
dBusConnectionClose connection :: a
connection 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
    Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
        Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just jCancellable :: b
jCancellable -> do
            Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    FunPtr C_AsyncReadyCallback
maybeCallback <- case Maybe AsyncReadyCallback
callback of
        Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_AsyncReadyCallback
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
        Just jCallback :: AsyncReadyCallback
jCallback -> do
            Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
            FunPtr C_AsyncReadyCallback
jCallback' <- C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
Gio.Callbacks.mk_AsyncReadyCallback (Maybe (Ptr (FunPtr C_AsyncReadyCallback))
-> AsyncReadyCallback_WithClosures -> C_AsyncReadyCallback
Gio.Callbacks.wrap_AsyncReadyCallback (Ptr (FunPtr C_AsyncReadyCallback)
-> Maybe (Ptr (FunPtr C_AsyncReadyCallback))
forall a. a -> Maybe a
Just Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback) (AsyncReadyCallback -> AsyncReadyCallback_WithClosures
Gio.Callbacks.drop_closures_AsyncReadyCallback AsyncReadyCallback
jCallback))
            Ptr (FunPtr C_AsyncReadyCallback)
-> FunPtr C_AsyncReadyCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback FunPtr C_AsyncReadyCallback
jCallback'
            FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
jCallback'
    let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
    Ptr DBusConnection
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> C_DestroyNotify
g_dbus_connection_close Ptr DBusConnection
connection' 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
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DBusConnectionCloseMethodInfo
instance (signature ~ (Maybe (b) -> Maybe (Gio.Callbacks.AsyncReadyCallback) -> m ()), MonadIO m, IsDBusConnection a, Gio.Cancellable.IsCancellable b) => O.MethodInfo DBusConnectionCloseMethodInfo a signature where
    overloadedMethod = dBusConnectionClose

#endif

-- method DBusConnection::close_finish
-- method type : OrdinaryMethod
-- 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 = "res"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncResult" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a #GAsyncResult obtained from the #GAsyncReadyCallback passed\n    to g_dbus_connection_close()"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

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

-- | Finishes an operation started with 'GI.Gio.Objects.DBusConnection.dBusConnectionClose'.
-- 
-- /Since: 2.26/
dBusConnectionCloseFinish ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusConnection a, Gio.AsyncResult.IsAsyncResult b) =>
    a
    -- ^ /@connection@/: a t'GI.Gio.Objects.DBusConnection.DBusConnection'
    -> b
    -- ^ /@res@/: a t'GI.Gio.Interfaces.AsyncResult.AsyncResult' obtained from the t'GI.Gio.Callbacks.AsyncReadyCallback' passed
    --     to 'GI.Gio.Objects.DBusConnection.dBusConnectionClose'
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
dBusConnectionCloseFinish :: a -> b -> m ()
dBusConnectionCloseFinish connection :: a
connection res :: b
res = 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
    Ptr AsyncResult
res' <- b -> IO (Ptr AsyncResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
res
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr DBusConnection
-> Ptr AsyncResult -> Ptr (Ptr GError) -> IO CInt
g_dbus_connection_close_finish Ptr DBusConnection
connection' Ptr AsyncResult
res'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
connection
        b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
res
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data DBusConnectionCloseFinishMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsDBusConnection a, Gio.AsyncResult.IsAsyncResult b) => O.MethodInfo DBusConnectionCloseFinishMethodInfo a signature where
    overloadedMethod = dBusConnectionCloseFinish

#endif

-- method DBusConnection::close_sync
-- method type : OrdinaryMethod
-- 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 = "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 (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_dbus_connection_close_sync" g_dbus_connection_close_sync :: 
    Ptr DBusConnection ->                   -- connection : TInterface (Name {namespace = "Gio", name = "DBusConnection"})
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Synchronously closes /@connection@/. The calling thread is blocked
-- until this is done. See 'GI.Gio.Objects.DBusConnection.dBusConnectionClose' for the
-- asynchronous version of this method and more details about what it
-- does.
-- 
-- /Since: 2.26/
dBusConnectionCloseSync ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusConnection a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@connection@/: a t'GI.Gio.Objects.DBusConnection.DBusConnection'
    -> Maybe (b)
    -- ^ /@cancellable@/: a t'GI.Gio.Objects.Cancellable.Cancellable' or 'P.Nothing'
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
dBusConnectionCloseSync :: a -> Maybe b -> m ()
dBusConnectionCloseSync connection :: a
connection cancellable :: Maybe b
cancellable = 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
    Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
        Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just jCancellable :: b
jCancellable -> do
            Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr DBusConnection
-> Ptr Cancellable -> Ptr (Ptr GError) -> IO CInt
g_dbus_connection_close_sync Ptr DBusConnection
connection' Ptr Cancellable
maybeCancellable
        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
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data DBusConnectionCloseSyncMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsDBusConnection a, Gio.Cancellable.IsCancellable b) => O.MethodInfo DBusConnectionCloseSyncMethodInfo a signature where
    overloadedMethod = dBusConnectionCloseSync

#endif

-- method DBusConnection::emit_signal
-- method type : OrdinaryMethod
-- 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 = "destination_bus_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the unique bus name for the destination\n    for the signal or %NULL to emit to all listeners"
--                 , 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 "path of remote object"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "interface_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "D-Bus interface to emit a signal on"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "signal_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the name of the signal to emit"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "parameters"
--           , argType = TVariant
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a #GVariant tuple with parameters for the signal\n             or %NULL if not passing parameters"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_dbus_connection_emit_signal" g_dbus_connection_emit_signal :: 
    Ptr DBusConnection ->                   -- connection : TInterface (Name {namespace = "Gio", name = "DBusConnection"})
    CString ->                              -- destination_bus_name : TBasicType TUTF8
    CString ->                              -- object_path : TBasicType TUTF8
    CString ->                              -- interface_name : TBasicType TUTF8
    CString ->                              -- signal_name : TBasicType TUTF8
    Ptr GVariant ->                         -- parameters : TVariant
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Emits a signal.
-- 
-- If the parameters GVariant is floating, it is consumed.
-- 
-- This can only fail if /@parameters@/ is not compatible with the D-Bus protocol
-- ('GI.Gio.Enums.IOErrorEnumInvalidArgument'), or if /@connection@/ has been closed
-- ('GI.Gio.Enums.IOErrorEnumClosed').
-- 
-- /Since: 2.26/
dBusConnectionEmitSignal ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusConnection a) =>
    a
    -- ^ /@connection@/: a t'GI.Gio.Objects.DBusConnection.DBusConnection'
    -> Maybe (T.Text)
    -- ^ /@destinationBusName@/: the unique bus name for the destination
    --     for the signal or 'P.Nothing' to emit to all listeners
    -> T.Text
    -- ^ /@objectPath@/: path of remote object
    -> T.Text
    -- ^ /@interfaceName@/: D-Bus interface to emit a signal on
    -> T.Text
    -- ^ /@signalName@/: the name of the signal to emit
    -> Maybe (GVariant)
    -- ^ /@parameters@/: a t'GVariant' tuple with parameters for the signal
    --              or 'P.Nothing' if not passing parameters
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
dBusConnectionEmitSignal :: a -> Maybe Text -> Text -> Text -> Text -> Maybe GVariant -> m ()
dBusConnectionEmitSignal connection :: a
connection destinationBusName :: Maybe Text
destinationBusName objectPath :: Text
objectPath interfaceName :: Text
interfaceName signalName :: Text
signalName parameters :: Maybe GVariant
parameters = 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
    CString
maybeDestinationBusName <- case Maybe Text
destinationBusName of
        Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just jDestinationBusName :: Text
jDestinationBusName -> do
            CString
jDestinationBusName' <- Text -> IO CString
textToCString Text
jDestinationBusName
            CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jDestinationBusName'
    CString
objectPath' <- Text -> IO CString
textToCString Text
objectPath
    CString
interfaceName' <- Text -> IO CString
textToCString Text
interfaceName
    CString
signalName' <- Text -> IO CString
textToCString Text
signalName
    Ptr GVariant
maybeParameters <- case Maybe GVariant
parameters of
        Nothing -> Ptr GVariant -> IO (Ptr GVariant)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GVariant
forall a. Ptr a
nullPtr
        Just jParameters :: GVariant
jParameters -> do
            Ptr GVariant
jParameters' <- GVariant -> IO (Ptr GVariant)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GVariant
jParameters
            Ptr GVariant -> IO (Ptr GVariant)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GVariant
jParameters'
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr DBusConnection
-> CString
-> CString
-> CString
-> CString
-> Ptr GVariant
-> Ptr (Ptr GError)
-> IO CInt
g_dbus_connection_emit_signal Ptr DBusConnection
connection' CString
maybeDestinationBusName CString
objectPath' CString
interfaceName' CString
signalName' Ptr GVariant
maybeParameters
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
connection
        Maybe GVariant -> (GVariant -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe GVariant
parameters GVariant -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeDestinationBusName
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
objectPath'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
interfaceName'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
signalName'
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeDestinationBusName
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
objectPath'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
interfaceName'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
signalName'
     )

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

#endif

-- method DBusConnection::export_action_group
-- method type : OrdinaryMethod
-- 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 = "object_path"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a D-Bus object path"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "action_group"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "ActionGroup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GActionGroup" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt)
-- throws : True
-- Skip return : False

foreign import ccall "g_dbus_connection_export_action_group" g_dbus_connection_export_action_group :: 
    Ptr DBusConnection ->                   -- connection : TInterface (Name {namespace = "Gio", name = "DBusConnection"})
    CString ->                              -- object_path : TBasicType TUTF8
    Ptr Gio.ActionGroup.ActionGroup ->      -- action_group : TInterface (Name {namespace = "Gio", name = "ActionGroup"})
    Ptr (Ptr GError) ->                     -- error
    IO Word32

-- | Exports /@actionGroup@/ on /@connection@/ at /@objectPath@/.
-- 
-- The implemented D-Bus API should be considered private.  It is
-- subject to change in the future.
-- 
-- A given object path can only have one action group exported on it.
-- If this constraint is violated, the export will fail and 0 will be
-- returned (with /@error@/ set accordingly).
-- 
-- You can unexport the action group using
-- 'GI.Gio.Objects.DBusConnection.dBusConnectionUnexportActionGroup' with the return value of
-- this function.
-- 
-- The thread default main context is taken at the time of this call.
-- All incoming action activations and state change requests are
-- reported from this context.  Any changes on the action group that
-- cause it to emit signals must also come from this same context.
-- Since incoming action activations and state change requests are
-- rather likely to cause changes on the action group, this effectively
-- limits a given action group to being exported from only one main
-- context.
-- 
-- /Since: 2.32/
dBusConnectionExportActionGroup ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusConnection a, Gio.ActionGroup.IsActionGroup b) =>
    a
    -- ^ /@connection@/: a t'GI.Gio.Objects.DBusConnection.DBusConnection'
    -> T.Text
    -- ^ /@objectPath@/: a D-Bus object path
    -> b
    -- ^ /@actionGroup@/: a t'GI.Gio.Interfaces.ActionGroup.ActionGroup'
    -> m Word32
    -- ^ __Returns:__ the ID of the export (never zero), or 0 in case of failure /(Can throw 'Data.GI.Base.GError.GError')/
dBusConnectionExportActionGroup :: a -> Text -> b -> m Word32
dBusConnectionExportActionGroup connection :: a
connection objectPath :: Text
objectPath actionGroup :: b
actionGroup = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusConnection
connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    CString
objectPath' <- Text -> IO CString
textToCString Text
objectPath
    Ptr ActionGroup
actionGroup' <- b -> IO (Ptr ActionGroup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
actionGroup
    IO Word32 -> IO () -> IO Word32
forall a b. IO a -> IO b -> IO a
onException (do
        Word32
result <- (Ptr (Ptr GError) -> IO Word32) -> IO Word32
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO Word32) -> IO Word32)
-> (Ptr (Ptr GError) -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ Ptr DBusConnection
-> CString -> Ptr ActionGroup -> Ptr (Ptr GError) -> IO Word32
g_dbus_connection_export_action_group Ptr DBusConnection
connection' CString
objectPath' Ptr ActionGroup
actionGroup'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
connection
        b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
actionGroup
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
objectPath'
        Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
objectPath'
     )

#if defined(ENABLE_OVERLOADING)
data DBusConnectionExportActionGroupMethodInfo
instance (signature ~ (T.Text -> b -> m Word32), MonadIO m, IsDBusConnection a, Gio.ActionGroup.IsActionGroup b) => O.MethodInfo DBusConnectionExportActionGroupMethodInfo a signature where
    overloadedMethod = dBusConnectionExportActionGroup

#endif

-- method DBusConnection::export_menu_model
-- method type : OrdinaryMethod
-- 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 = "object_path"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a D-Bus object path"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "menu"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "MenuModel" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMenuModel" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt)
-- throws : True
-- Skip return : False

foreign import ccall "g_dbus_connection_export_menu_model" g_dbus_connection_export_menu_model :: 
    Ptr DBusConnection ->                   -- connection : TInterface (Name {namespace = "Gio", name = "DBusConnection"})
    CString ->                              -- object_path : TBasicType TUTF8
    Ptr Gio.MenuModel.MenuModel ->          -- menu : TInterface (Name {namespace = "Gio", name = "MenuModel"})
    Ptr (Ptr GError) ->                     -- error
    IO Word32

-- | Exports /@menu@/ on /@connection@/ at /@objectPath@/.
-- 
-- The implemented D-Bus API should be considered private.
-- It is subject to change in the future.
-- 
-- An object path can only have one menu model exported on it. If this
-- constraint is violated, the export will fail and 0 will be
-- returned (with /@error@/ set accordingly).
-- 
-- You can unexport the menu model using
-- 'GI.Gio.Objects.DBusConnection.dBusConnectionUnexportMenuModel' with the return value of
-- this function.
-- 
-- /Since: 2.32/
dBusConnectionExportMenuModel ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusConnection a, Gio.MenuModel.IsMenuModel b) =>
    a
    -- ^ /@connection@/: a t'GI.Gio.Objects.DBusConnection.DBusConnection'
    -> T.Text
    -- ^ /@objectPath@/: a D-Bus object path
    -> b
    -- ^ /@menu@/: a t'GI.Gio.Objects.MenuModel.MenuModel'
    -> m Word32
    -- ^ __Returns:__ the ID of the export (never zero), or 0 in case of failure /(Can throw 'Data.GI.Base.GError.GError')/
dBusConnectionExportMenuModel :: a -> Text -> b -> m Word32
dBusConnectionExportMenuModel connection :: a
connection objectPath :: Text
objectPath menu :: b
menu = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusConnection
connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    CString
objectPath' <- Text -> IO CString
textToCString Text
objectPath
    Ptr MenuModel
menu' <- b -> IO (Ptr MenuModel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
menu
    IO Word32 -> IO () -> IO Word32
forall a b. IO a -> IO b -> IO a
onException (do
        Word32
result <- (Ptr (Ptr GError) -> IO Word32) -> IO Word32
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO Word32) -> IO Word32)
-> (Ptr (Ptr GError) -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ Ptr DBusConnection
-> CString -> Ptr MenuModel -> Ptr (Ptr GError) -> IO Word32
g_dbus_connection_export_menu_model Ptr DBusConnection
connection' CString
objectPath' Ptr MenuModel
menu'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
connection
        b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
menu
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
objectPath'
        Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
objectPath'
     )

#if defined(ENABLE_OVERLOADING)
data DBusConnectionExportMenuModelMethodInfo
instance (signature ~ (T.Text -> b -> m Word32), MonadIO m, IsDBusConnection a, Gio.MenuModel.IsMenuModel b) => O.MethodInfo DBusConnectionExportMenuModelMethodInfo a signature where
    overloadedMethod = dBusConnectionExportMenuModel

#endif

-- method DBusConnection::flush
-- method type : OrdinaryMethod
-- 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 = "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\n    request is satisfied or %NULL if you don't care about the result"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = 3
--           , 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_connection_flush" g_dbus_connection_flush :: 
    Ptr DBusConnection ->                   -- connection : TInterface (Name {namespace = "Gio", name = "DBusConnection"})
    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 flushes /@connection@/, that is, writes all queued
-- outgoing message to the transport and then flushes the transport
-- (using 'GI.Gio.Objects.OutputStream.outputStreamFlushAsync'). This is useful in programs
-- that wants to emit a D-Bus signal and then exit immediately. Without
-- flushing the connection, there is no guaranteed that the message has
-- been sent to the networking buffers in the OS kernel.
-- 
-- This is an asynchronous method. When the operation is finished,
-- /@callback@/ will be invoked in the
-- [thread-default main context][g-main-context-push-thread-default]
-- of the thread you are calling this method from. You can
-- then call 'GI.Gio.Objects.DBusConnection.dBusConnectionFlushFinish' to get the result of the
-- operation. See 'GI.Gio.Objects.DBusConnection.dBusConnectionFlushSync' for the synchronous
-- version.
-- 
-- /Since: 2.26/
dBusConnectionFlush ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusConnection a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@connection@/: a t'GI.Gio.Objects.DBusConnection.DBusConnection'
    -> Maybe (b)
    -- ^ /@cancellable@/: a t'GI.Gio.Objects.Cancellable.Cancellable' or 'P.Nothing'
    -> Maybe (Gio.Callbacks.AsyncReadyCallback)
    -- ^ /@callback@/: a t'GI.Gio.Callbacks.AsyncReadyCallback' to call when the
    --     request is satisfied or 'P.Nothing' if you don\'t care about the result
    -> m ()
dBusConnectionFlush :: a -> Maybe b -> Maybe AsyncReadyCallback -> m ()
dBusConnectionFlush connection :: a
connection 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
    Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
        Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just jCancellable :: b
jCancellable -> do
            Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    FunPtr C_AsyncReadyCallback
maybeCallback <- case Maybe AsyncReadyCallback
callback of
        Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_AsyncReadyCallback
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
        Just jCallback :: AsyncReadyCallback
jCallback -> do
            Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
            FunPtr C_AsyncReadyCallback
jCallback' <- C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
Gio.Callbacks.mk_AsyncReadyCallback (Maybe (Ptr (FunPtr C_AsyncReadyCallback))
-> AsyncReadyCallback_WithClosures -> C_AsyncReadyCallback
Gio.Callbacks.wrap_AsyncReadyCallback (Ptr (FunPtr C_AsyncReadyCallback)
-> Maybe (Ptr (FunPtr C_AsyncReadyCallback))
forall a. a -> Maybe a
Just Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback) (AsyncReadyCallback -> AsyncReadyCallback_WithClosures
Gio.Callbacks.drop_closures_AsyncReadyCallback AsyncReadyCallback
jCallback))
            Ptr (FunPtr C_AsyncReadyCallback)
-> FunPtr C_AsyncReadyCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback FunPtr C_AsyncReadyCallback
jCallback'
            FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
jCallback'
    let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
    Ptr DBusConnection
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> C_DestroyNotify
g_dbus_connection_flush Ptr DBusConnection
connection' 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
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DBusConnectionFlushMethodInfo
instance (signature ~ (Maybe (b) -> Maybe (Gio.Callbacks.AsyncReadyCallback) -> m ()), MonadIO m, IsDBusConnection a, Gio.Cancellable.IsCancellable b) => O.MethodInfo DBusConnectionFlushMethodInfo a signature where
    overloadedMethod = dBusConnectionFlush

#endif

-- method DBusConnection::flush_finish
-- method type : OrdinaryMethod
-- 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 = "res"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncResult" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a #GAsyncResult obtained from the #GAsyncReadyCallback passed\n    to g_dbus_connection_flush()"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

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

-- | Finishes an operation started with 'GI.Gio.Objects.DBusConnection.dBusConnectionFlush'.
-- 
-- /Since: 2.26/
dBusConnectionFlushFinish ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusConnection a, Gio.AsyncResult.IsAsyncResult b) =>
    a
    -- ^ /@connection@/: a t'GI.Gio.Objects.DBusConnection.DBusConnection'
    -> b
    -- ^ /@res@/: a t'GI.Gio.Interfaces.AsyncResult.AsyncResult' obtained from the t'GI.Gio.Callbacks.AsyncReadyCallback' passed
    --     to 'GI.Gio.Objects.DBusConnection.dBusConnectionFlush'
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
dBusConnectionFlushFinish :: a -> b -> m ()
dBusConnectionFlushFinish connection :: a
connection res :: b
res = 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
    Ptr AsyncResult
res' <- b -> IO (Ptr AsyncResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
res
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr DBusConnection
-> Ptr AsyncResult -> Ptr (Ptr GError) -> IO CInt
g_dbus_connection_flush_finish Ptr DBusConnection
connection' Ptr AsyncResult
res'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
connection
        b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
res
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data DBusConnectionFlushFinishMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsDBusConnection a, Gio.AsyncResult.IsAsyncResult b) => O.MethodInfo DBusConnectionFlushFinishMethodInfo a signature where
    overloadedMethod = dBusConnectionFlushFinish

#endif

-- method DBusConnection::flush_sync
-- method type : OrdinaryMethod
-- 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 = "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 (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_dbus_connection_flush_sync" g_dbus_connection_flush_sync :: 
    Ptr DBusConnection ->                   -- connection : TInterface (Name {namespace = "Gio", name = "DBusConnection"})
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Synchronously flushes /@connection@/. The calling thread is blocked
-- until this is done. See 'GI.Gio.Objects.DBusConnection.dBusConnectionFlush' for the
-- asynchronous version of this method and more details about what it
-- does.
-- 
-- /Since: 2.26/
dBusConnectionFlushSync ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusConnection a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@connection@/: a t'GI.Gio.Objects.DBusConnection.DBusConnection'
    -> Maybe (b)
    -- ^ /@cancellable@/: a t'GI.Gio.Objects.Cancellable.Cancellable' or 'P.Nothing'
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
dBusConnectionFlushSync :: a -> Maybe b -> m ()
dBusConnectionFlushSync connection :: a
connection cancellable :: Maybe b
cancellable = 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
    Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
        Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just jCancellable :: b
jCancellable -> do
            Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr DBusConnection
-> Ptr Cancellable -> Ptr (Ptr GError) -> IO CInt
g_dbus_connection_flush_sync Ptr DBusConnection
connection' Ptr Cancellable
maybeCancellable
        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
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data DBusConnectionFlushSyncMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsDBusConnection a, Gio.Cancellable.IsCancellable b) => O.MethodInfo DBusConnectionFlushSyncMethodInfo a signature where
    overloadedMethod = dBusConnectionFlushSync

#endif

-- method DBusConnection::get_capabilities
-- method type : OrdinaryMethod
-- 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
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Gio" , name = "DBusCapabilityFlags" })
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_connection_get_capabilities" g_dbus_connection_get_capabilities :: 
    Ptr DBusConnection ->                   -- connection : TInterface (Name {namespace = "Gio", name = "DBusConnection"})
    IO CUInt

-- | Gets the capabilities negotiated with the remote peer
-- 
-- /Since: 2.26/
dBusConnectionGetCapabilities ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusConnection a) =>
    a
    -- ^ /@connection@/: a t'GI.Gio.Objects.DBusConnection.DBusConnection'
    -> m [Gio.Flags.DBusCapabilityFlags]
    -- ^ __Returns:__ zero or more flags from the t'GI.Gio.Flags.DBusCapabilityFlags' enumeration
dBusConnectionGetCapabilities :: a -> m [DBusCapabilityFlags]
dBusConnectionGetCapabilities connection :: a
connection = IO [DBusCapabilityFlags] -> m [DBusCapabilityFlags]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [DBusCapabilityFlags] -> m [DBusCapabilityFlags])
-> IO [DBusCapabilityFlags] -> m [DBusCapabilityFlags]
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
    CUInt
result <- Ptr DBusConnection -> IO CUInt
g_dbus_connection_get_capabilities Ptr DBusConnection
connection'
    let result' :: [DBusCapabilityFlags]
result' = CUInt -> [DBusCapabilityFlags]
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
connection
    [DBusCapabilityFlags] -> IO [DBusCapabilityFlags]
forall (m :: * -> *) a. Monad m => a -> m a
return [DBusCapabilityFlags]
result'

#if defined(ENABLE_OVERLOADING)
data DBusConnectionGetCapabilitiesMethodInfo
instance (signature ~ (m [Gio.Flags.DBusCapabilityFlags]), MonadIO m, IsDBusConnection a) => O.MethodInfo DBusConnectionGetCapabilitiesMethodInfo a signature where
    overloadedMethod = dBusConnectionGetCapabilities

#endif

-- method DBusConnection::get_exit_on_close
-- method type : OrdinaryMethod
-- 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
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_connection_get_exit_on_close" g_dbus_connection_get_exit_on_close :: 
    Ptr DBusConnection ->                   -- connection : TInterface (Name {namespace = "Gio", name = "DBusConnection"})
    IO CInt

-- | Gets whether the process is terminated when /@connection@/ is
-- closed by the remote peer. See
-- t'GI.Gio.Objects.DBusConnection.DBusConnection':@/exit-on-close/@ for more details.
-- 
-- /Since: 2.26/
dBusConnectionGetExitOnClose ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusConnection a) =>
    a
    -- ^ /@connection@/: a t'GI.Gio.Objects.DBusConnection.DBusConnection'
    -> m Bool
    -- ^ __Returns:__ whether the process is terminated when /@connection@/ is
    --     closed by the remote peer
dBusConnectionGetExitOnClose :: a -> m Bool
dBusConnectionGetExitOnClose connection :: a
connection = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusConnection
connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    CInt
result <- Ptr DBusConnection -> IO CInt
g_dbus_connection_get_exit_on_close Ptr DBusConnection
connection'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
connection
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data DBusConnectionGetExitOnCloseMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDBusConnection a) => O.MethodInfo DBusConnectionGetExitOnCloseMethodInfo a signature where
    overloadedMethod = dBusConnectionGetExitOnClose

#endif

-- method DBusConnection::get_flags
-- method type : OrdinaryMethod
-- 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
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Gio" , name = "DBusConnectionFlags" })
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_connection_get_flags" g_dbus_connection_get_flags :: 
    Ptr DBusConnection ->                   -- connection : TInterface (Name {namespace = "Gio", name = "DBusConnection"})
    IO CUInt

-- | Gets the flags used to construct this connection
-- 
-- /Since: 2.60/
dBusConnectionGetFlags ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusConnection a) =>
    a
    -- ^ /@connection@/: a t'GI.Gio.Objects.DBusConnection.DBusConnection'
    -> m [Gio.Flags.DBusConnectionFlags]
    -- ^ __Returns:__ zero or more flags from the t'GI.Gio.Flags.DBusConnectionFlags' enumeration
dBusConnectionGetFlags :: a -> m [DBusConnectionFlags]
dBusConnectionGetFlags connection :: a
connection = IO [DBusConnectionFlags] -> m [DBusConnectionFlags]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [DBusConnectionFlags] -> m [DBusConnectionFlags])
-> IO [DBusConnectionFlags] -> m [DBusConnectionFlags]
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
    CUInt
result <- Ptr DBusConnection -> IO CUInt
g_dbus_connection_get_flags Ptr DBusConnection
connection'
    let result' :: [DBusConnectionFlags]
result' = CUInt -> [DBusConnectionFlags]
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
connection
    [DBusConnectionFlags] -> IO [DBusConnectionFlags]
forall (m :: * -> *) a. Monad m => a -> m a
return [DBusConnectionFlags]
result'

#if defined(ENABLE_OVERLOADING)
data DBusConnectionGetFlagsMethodInfo
instance (signature ~ (m [Gio.Flags.DBusConnectionFlags]), MonadIO m, IsDBusConnection a) => O.MethodInfo DBusConnectionGetFlagsMethodInfo a signature where
    overloadedMethod = dBusConnectionGetFlags

#endif

-- method DBusConnection::get_guid
-- method type : OrdinaryMethod
-- 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
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_connection_get_guid" g_dbus_connection_get_guid :: 
    Ptr DBusConnection ->                   -- connection : TInterface (Name {namespace = "Gio", name = "DBusConnection"})
    IO CString

-- | The GUID of the peer performing the role of server when
-- authenticating. See t'GI.Gio.Objects.DBusConnection.DBusConnection':@/guid/@ for more details.
-- 
-- /Since: 2.26/
dBusConnectionGetGuid ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusConnection a) =>
    a
    -- ^ /@connection@/: a t'GI.Gio.Objects.DBusConnection.DBusConnection'
    -> m T.Text
    -- ^ __Returns:__ The GUID. Do not free this string, it is owned by
    --     /@connection@/.
dBusConnectionGetGuid :: a -> m Text
dBusConnectionGetGuid connection :: a
connection = 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 DBusConnection
connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    CString
result <- Ptr DBusConnection -> IO CString
g_dbus_connection_get_guid Ptr DBusConnection
connection'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusConnectionGetGuid" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
connection
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data DBusConnectionGetGuidMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDBusConnection a) => O.MethodInfo DBusConnectionGetGuidMethodInfo a signature where
    overloadedMethod = dBusConnectionGetGuid

#endif

-- method DBusConnection::get_last_serial
-- method type : OrdinaryMethod
-- 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
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt32)
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_connection_get_last_serial" g_dbus_connection_get_last_serial :: 
    Ptr DBusConnection ->                   -- connection : TInterface (Name {namespace = "Gio", name = "DBusConnection"})
    IO Word32

-- | Retrieves the last serial number assigned to a t'GI.Gio.Objects.DBusMessage.DBusMessage' on
-- the current thread. This includes messages sent via both low-level
-- API such as 'GI.Gio.Objects.DBusConnection.dBusConnectionSendMessage' as well as
-- high-level API such as 'GI.Gio.Objects.DBusConnection.dBusConnectionEmitSignal',
-- 'GI.Gio.Objects.DBusConnection.dBusConnectionCall' or 'GI.Gio.Objects.DBusProxy.dBusProxyCall'.
-- 
-- /Since: 2.34/
dBusConnectionGetLastSerial ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusConnection a) =>
    a
    -- ^ /@connection@/: a t'GI.Gio.Objects.DBusConnection.DBusConnection'
    -> m Word32
    -- ^ __Returns:__ the last used serial or zero when no message has been sent
    --     within the current thread
dBusConnectionGetLastSerial :: a -> m Word32
dBusConnectionGetLastSerial connection :: a
connection = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusConnection
connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    Word32
result <- Ptr DBusConnection -> IO Word32
g_dbus_connection_get_last_serial Ptr DBusConnection
connection'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
connection
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data DBusConnectionGetLastSerialMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsDBusConnection a) => O.MethodInfo DBusConnectionGetLastSerialMethodInfo a signature where
    overloadedMethod = dBusConnectionGetLastSerial

#endif

-- method DBusConnection::get_peer_credentials
-- method type : OrdinaryMethod
-- 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
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "Credentials" })
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_connection_get_peer_credentials" g_dbus_connection_get_peer_credentials :: 
    Ptr DBusConnection