{-# LANGUAGE ImplicitParams, RankNTypes, TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- The @GDBusConnection@ 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 a 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 'GI.Gio.Functions.busOwnName',
-- 'GI.Gio.Functions.busWatchName' or [func/@gio@/.DBusProxy.new_for_bus] APIs.
-- 
-- As an exception to the usual GLib rule that a particular object must not
-- be used by two threads at the same time, @GDBusConnection@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 @GDBusConnection@ when
-- called from any thread.
-- 
-- Most of the ways to obtain a @GDBusConnection@ automatically initialize it
-- (i.e. connect to D-Bus): for instance, [func/@gio@/.DBusConnection.new] and
-- 'GI.Gio.Functions.busGet', and the synchronous versions of those methods, give you
-- an initialized connection. Language bindings for GIO should use
-- [func/@gio@/.Initable.new] or [func/@gio@/.AsyncInitable.new_async], which also
-- initialize the connection.
-- 
-- If you construct an uninitialized @GDBusConnection@, such as via
-- t'GI.GObject.Objects.Object.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 @GDBusConnection@ that has not
-- completed initialization successfully is considered to be invalid, and leads
-- to undefined behaviour. In particular, if initialization fails with a
-- @GError@, the only valid thing you can do with that @GDBusConnection@ is to
-- free it with 'GI.GObject.Objects.Object.objectUnref'.
-- 
-- == An example D-Bus server
-- 
-- Here is an example for a D-Bus server:
-- <https://gitlab.gnome.org/GNOME/glib/-/blob/HEAD/gio/tests/gdbus-example-server.c gdbus-example-server.c>
-- 
-- == An example for exporting a subtree
-- 
-- Here is an example for exporting a subtree:
-- <https://gitlab.gnome.org/GNOME/glib/-/blob/HEAD/gio/tests/gdbus-example-subtree.c gdbus-example-subtree.c>
-- 
-- == An example for file descriptor passing
-- 
-- Here is an example for passing UNIX file descriptors:
-- <https://gitlab.gnome.org/GNOME/glib/-/blob/HEAD/gio/tests/gdbus-example-unix-fd-client.c gdbus-unix-fd-client.c>
-- 
-- == An example for exporting a GObject
-- 
-- Here is an example for exporting a t'GI.GObject.Objects.Object.Object':
-- <https://gitlab.gnome.org/GNOME/glib/-/blob/HEAD/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                        ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [addFilter]("GI.Gio.Objects.DBusConnection#g:method:addFilter"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [call]("GI.Gio.Objects.DBusConnection#g:method:call"), [callFinish]("GI.Gio.Objects.DBusConnection#g:method:callFinish"), [callSync]("GI.Gio.Objects.DBusConnection#g:method:callSync"), [callWithUnixFdList]("GI.Gio.Objects.DBusConnection#g:method:callWithUnixFdList"), [callWithUnixFdListFinish]("GI.Gio.Objects.DBusConnection#g:method:callWithUnixFdListFinish"), [callWithUnixFdListSync]("GI.Gio.Objects.DBusConnection#g:method:callWithUnixFdListSync"), [close]("GI.Gio.Objects.DBusConnection#g:method:close"), [closeFinish]("GI.Gio.Objects.DBusConnection#g:method:closeFinish"), [closeSync]("GI.Gio.Objects.DBusConnection#g:method:closeSync"), [emitSignal]("GI.Gio.Objects.DBusConnection#g:method:emitSignal"), [exportActionGroup]("GI.Gio.Objects.DBusConnection#g:method:exportActionGroup"), [exportMenuModel]("GI.Gio.Objects.DBusConnection#g:method:exportMenuModel"), [flush]("GI.Gio.Objects.DBusConnection#g:method:flush"), [flushFinish]("GI.Gio.Objects.DBusConnection#g:method:flushFinish"), [flushSync]("GI.Gio.Objects.DBusConnection#g:method:flushSync"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [init]("GI.Gio.Interfaces.Initable#g:method:init"), [initAsync]("GI.Gio.Interfaces.AsyncInitable#g:method:initAsync"), [initFinish]("GI.Gio.Interfaces.AsyncInitable#g:method:initFinish"), [isClosed]("GI.Gio.Objects.DBusConnection#g:method:isClosed"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [registerObject]("GI.Gio.Objects.DBusConnection#g:method:registerObject"), [registerSubtree]("GI.Gio.Objects.DBusConnection#g:method:registerSubtree"), [removeFilter]("GI.Gio.Objects.DBusConnection#g:method:removeFilter"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [sendMessage]("GI.Gio.Objects.DBusConnection#g:method:sendMessage"), [sendMessageWithReply]("GI.Gio.Objects.DBusConnection#g:method:sendMessageWithReply"), [sendMessageWithReplyFinish]("GI.Gio.Objects.DBusConnection#g:method:sendMessageWithReplyFinish"), [sendMessageWithReplySync]("GI.Gio.Objects.DBusConnection#g:method:sendMessageWithReplySync"), [signalSubscribe]("GI.Gio.Objects.DBusConnection#g:method:signalSubscribe"), [signalUnsubscribe]("GI.Gio.Objects.DBusConnection#g:method:signalUnsubscribe"), [startMessageProcessing]("GI.Gio.Objects.DBusConnection#g:method:startMessageProcessing"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unexportActionGroup]("GI.Gio.Objects.DBusConnection#g:method:unexportActionGroup"), [unexportMenuModel]("GI.Gio.Objects.DBusConnection#g:method:unexportMenuModel"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [unregisterObject]("GI.Gio.Objects.DBusConnection#g:method:unregisterObject"), [unregisterSubtree]("GI.Gio.Objects.DBusConnection#g:method:unregisterSubtree"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getCapabilities]("GI.Gio.Objects.DBusConnection#g:method:getCapabilities"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getExitOnClose]("GI.Gio.Objects.DBusConnection#g:method:getExitOnClose"), [getFlags]("GI.Gio.Objects.DBusConnection#g:method:getFlags"), [getGuid]("GI.Gio.Objects.DBusConnection#g:method:getGuid"), [getLastSerial]("GI.Gio.Objects.DBusConnection#g:method:getLastSerial"), [getPeerCredentials]("GI.Gio.Objects.DBusConnection#g:method:getPeerCredentials"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getStream]("GI.Gio.Objects.DBusConnection#g:method:getStream"), [getUniqueName]("GI.Gio.Objects.DBusConnection#g:method:getUniqueName").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setExitOnClose]("GI.Gio.Objects.DBusConnection#g:method:setExitOnClose"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#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
-- [DBusConnection:flags]("GI.Gio.Objects.DBusConnection#g:attr: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
-- [DBusConnection:flags]("GI.Gio.Objects.DBusConnection#g:attr:flags") property you will be able to read the GUID
-- of the other peer here after the connection has been successfully
-- initialized.
-- 
-- Note that the
-- <https://dbus.freedesktop.org/doc/dbus-specification.html#addresses D-Bus specification>
-- uses the term ‘UUID’ to refer to this, whereas GLib consistently uses the
-- term ‘GUID’ for historical reasons.
-- 
-- Despite its name, the format of [DBusConnection:guid]("GI.Gio.Objects.DBusConnection#g:attr:guid") does not follow
-- <https://datatracker.ietf.org/doc/html/rfc4122 RFC 4122> or the Microsoft
-- GUID format.
-- 
-- /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#

    DBusConnectionClosedCallback            ,
#if defined(ENABLE_OVERLOADING)
    DBusConnectionClosedSignalInfo          ,
#endif
    afterDBusConnectionClosed               ,
    onDBusConnectionClosed                  ,




    ) where

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

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R
import qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT

-- Workaround for https://gitlab.haskell.org/ghc/ghc/-/issues/23392
#if MIN_VERSION_base(4,18,0)
import qualified GI.GLib.Callbacks as GLib.Callbacks
import qualified GI.GLib.Structs.Bytes as GLib.Bytes
import qualified GI.GLib.Structs.PollFD as GLib.PollFD
import qualified GI.GLib.Structs.Source as GLib.Source
import qualified GI.GLib.Structs.String as GLib.String
import qualified GI.GLib.Structs.VariantType as GLib.VariantType
import qualified GI.GObject.Callbacks as GObject.Callbacks
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.GObject.Structs.Parameter as GObject.Parameter
import qualified GI.Gio.Callbacks as Gio.Callbacks
import {-# SOURCE #-} qualified GI.Gio.Enums as Gio.Enums
import {-# SOURCE #-} qualified GI.Gio.Flags as Gio.Flags
import {-# SOURCE #-} qualified GI.Gio.Interfaces.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.InputStream as Gio.InputStream
import {-# SOURCE #-} qualified GI.Gio.Objects.MenuAttributeIter as Gio.MenuAttributeIter
import {-# SOURCE #-} qualified GI.Gio.Objects.MenuLinkIter as Gio.MenuLinkIter
import {-# SOURCE #-} qualified GI.Gio.Objects.MenuModel as Gio.MenuModel
import {-# SOURCE #-} qualified GI.Gio.Objects.OutputStream as Gio.OutputStream
import {-# SOURCE #-} qualified GI.Gio.Objects.UnixFDList as Gio.UnixFDList
import {-# SOURCE #-} qualified GI.Gio.Structs.DBusAnnotationInfo as Gio.DBusAnnotationInfo
import {-# SOURCE #-} qualified GI.Gio.Structs.DBusArgInfo as Gio.DBusArgInfo
import {-# SOURCE #-} qualified GI.Gio.Structs.DBusInterfaceInfo as Gio.DBusInterfaceInfo
import {-# SOURCE #-} qualified GI.Gio.Structs.DBusMethodInfo as Gio.DBusMethodInfo
import {-# SOURCE #-} qualified GI.Gio.Structs.DBusPropertyInfo as Gio.DBusPropertyInfo
import {-# SOURCE #-} qualified GI.Gio.Structs.DBusSignalInfo as Gio.DBusSignalInfo
import {-# SOURCE #-} qualified GI.Gio.Structs.DBusSubtreeVTable as Gio.DBusSubtreeVTable
import {-# SOURCE #-} qualified GI.Gio.Structs.OutputVector as Gio.OutputVector

#else
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

#endif

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

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

foreign import ccall "g_dbus_connection_get_type"
    c_g_dbus_connection_get_type :: IO B.Types.GType

instance B.Types.TypedObject DBusConnection where
    glibType :: IO GType
glibType = IO GType
c_g_dbus_connection_get_type

instance B.Types.GObject DBusConnection

-- | Type class for types which can be safely cast to `DBusConnection`, for instance with `toDBusConnection`.
class (SP.GObject o, O.IsDescendantOf DBusConnection o) => IsDBusConnection o
instance (SP.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 :: (MIO.MonadIO m, IsDBusConnection o) => o -> m DBusConnection
toDBusConnection :: forall (m :: * -> *) o.
(MonadIO m, IsDBusConnection o) =>
o -> m DBusConnection
toDBusConnection = IO DBusConnection -> m DBusConnection
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr DBusConnection -> DBusConnection
DBusConnection

-- | Convert 'DBusConnection' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe DBusConnection) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_g_dbus_connection_get_type
    gvalueSet_ :: Ptr GValue -> Maybe DBusConnection -> IO ()
gvalueSet_ Ptr GValue
gv Maybe DBusConnection
P.Nothing = Ptr GValue -> Ptr DBusConnection -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr DBusConnection
forall a. Ptr a
FP.nullPtr :: FP.Ptr DBusConnection)
    gvalueSet_ Ptr GValue
gv (P.Just DBusConnection
obj) = DBusConnection -> (Ptr DBusConnection -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr DBusConnection
obj (Ptr GValue -> Ptr DBusConnection -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe DBusConnection)
gvalueGet_ Ptr GValue
gv = do
        ptr <- Ptr GValue -> IO (Ptr DBusConnection)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr DBusConnection)
        if ptr /= FP.nullPtr
        then P.Just <$> B.ManagedPtr.newObject DBusConnection ptr
        else return P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveDBusConnectionMethod (t :: Symbol) (o :: DK.Type) :: DK.Type 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.OverloadedMethod 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

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

#endif

instance (info ~ ResolveDBusConnectionMethod t DBusConnection, O.OverloadedMethodInfo info DBusConnection) => OL.IsLabel t (O.MethodProxy info DBusConnection) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#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 ()

type C_DBusConnectionClosedCallback =
    Ptr DBusConnection ->                   -- 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_DBusConnectionClosedCallback :: 
    GObject a => (a -> DBusConnectionClosedCallback) ->
    C_DBusConnectionClosedCallback
wrap_DBusConnectionClosedCallback :: forall a.
GObject a =>
(a -> DBusConnectionClosedCallback)
-> C_DBusConnectionClosedCallback
wrap_DBusConnectionClosedCallback a -> DBusConnectionClosedCallback
gi'cb Ptr DBusConnection
gi'selfPtr CInt
remotePeerVanished Ptr GError
error_ Ptr ()
_ = do
    let remotePeerVanished' :: Bool
remotePeerVanished' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
remotePeerVanished
    maybeError_ <-
        if Ptr GError
error_ Ptr GError -> Ptr GError -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr GError
forall a. Ptr a
FP.nullPtr
        then Maybe GError -> IO (Maybe GError)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe GError
forall a. Maybe a
Nothing
        else do
            error_' <- ((ManagedPtr GError -> GError) -> Ptr GError -> IO GError
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr GError -> GError
GError) Ptr GError
error_
            return $ Just error_'
    B.ManagedPtr.withNewObject gi'selfPtr $ \DBusConnection
gi'self -> a -> DBusConnectionClosedCallback
gi'cb (DBusConnection -> a
forall a b. Coercible a b => a -> b
Coerce.coerce DBusConnection
gi'self)  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 -> ((?self :: a) => DBusConnectionClosedCallback) -> m SignalHandlerId
onDBusConnectionClosed :: forall a (m :: * -> *).
(IsDBusConnection a, MonadIO m) =>
a
-> ((?self::a) => DBusConnectionClosedCallback)
-> m SignalHandlerId
onDBusConnectionClosed a
obj (?self::a) => DBusConnectionClosedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
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 wrapped :: a -> DBusConnectionClosedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => DBusConnectionClosedCallback
DBusConnectionClosedCallback
cb
    let wrapped' :: C_DBusConnectionClosedCallback
wrapped' = (a -> DBusConnectionClosedCallback)
-> C_DBusConnectionClosedCallback
forall a.
GObject a =>
(a -> DBusConnectionClosedCallback)
-> C_DBusConnectionClosedCallback
wrap_DBusConnectionClosedCallback a -> DBusConnectionClosedCallback
wrapped
    wrapped'' <- C_DBusConnectionClosedCallback
-> IO (FunPtr C_DBusConnectionClosedCallback)
mk_DBusConnectionClosedCallback C_DBusConnectionClosedCallback
wrapped'
    connectSignalFunPtr obj "closed" wrapped'' SignalConnectBefore 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
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterDBusConnectionClosed :: (IsDBusConnection a, MonadIO m) => a -> ((?self :: a) => DBusConnectionClosedCallback) -> m SignalHandlerId
afterDBusConnectionClosed :: forall a (m :: * -> *).
(IsDBusConnection a, MonadIO m) =>
a
-> ((?self::a) => DBusConnectionClosedCallback)
-> m SignalHandlerId
afterDBusConnectionClosed a
obj (?self::a) => DBusConnectionClosedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
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 wrapped :: a -> DBusConnectionClosedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => DBusConnectionClosedCallback
DBusConnectionClosedCallback
cb
    let wrapped' :: C_DBusConnectionClosedCallback
wrapped' = (a -> DBusConnectionClosedCallback)
-> C_DBusConnectionClosedCallback
forall a.
GObject a =>
(a -> DBusConnectionClosedCallback)
-> C_DBusConnectionClosedCallback
wrap_DBusConnectionClosedCallback a -> DBusConnectionClosedCallback
wrapped
    wrapped'' <- C_DBusConnectionClosedCallback
-> IO (FunPtr C_DBusConnectionClosedCallback)
mk_DBusConnectionClosedCallback C_DBusConnectionClosedCallback
wrapped'
    connectSignalFunPtr obj "closed" wrapped'' SignalConnectAfter 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
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusConnection::closed"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusConnection.html#g:signal:closed"})

#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, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructDBusConnectionAddress :: forall o (m :: * -> *).
(IsDBusConnection o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructDBusConnectionAddress Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"address" (Text -> Maybe Text
forall a. a -> Maybe a
P.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
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusConnection.address"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusConnection.html#g:attr:address"
        })
#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, MIO.MonadIO m, Gio.DBusAuthObserver.IsDBusAuthObserver a) => a -> m (GValueConstruct o)
constructDBusConnectionAuthenticationObserver :: forall o (m :: * -> *) a.
(IsDBusConnection o, MonadIO m, IsDBusAuthObserver a) =>
a -> m (GValueConstruct o)
constructDBusConnectionAuthenticationObserver a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"authentication-observer" (a -> Maybe a
forall a. a -> Maybe a
P.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
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusConnection.authenticationObserver"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusConnection.html#g:attr:authenticationObserver"
        })
#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 :: forall (m :: * -> *) o.
(MonadIO m, IsDBusConnection o) =>
o -> m [DBusCapabilityFlags]
getDBusConnectionCapabilities o
obj = IO [DBusCapabilityFlags] -> m [DBusCapabilityFlags]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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 String
"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
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusConnection.capabilities"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusConnection.html#g:attr:capabilities"
        })
#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 :: forall (m :: * -> *) o.
(MonadIO m, IsDBusConnection o) =>
o -> m Bool
getDBusConnectionClosed o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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 String
"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
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusConnection.closed"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusConnection.html#g:attr:closed"
        })
#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 :: forall (m :: * -> *) o.
(MonadIO m, IsDBusConnection o) =>
o -> m Bool
getDBusConnectionExitOnClose o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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 String
"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 :: forall (m :: * -> *) o.
(MonadIO m, IsDBusConnection o) =>
o -> Bool -> m ()
setDBusConnectionExitOnClose o
obj Bool
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"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, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructDBusConnectionExitOnClose :: forall o (m :: * -> *).
(IsDBusConnection o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructDBusConnectionExitOnClose Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"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
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusConnection.exitOnClose"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusConnection.html#g:attr:exitOnClose"
        })
#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 :: forall (m :: * -> *) o.
(MonadIO m, IsDBusConnection o) =>
o -> m [DBusConnectionFlags]
getDBusConnectionFlags o
obj = IO [DBusConnectionFlags] -> m [DBusConnectionFlags]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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 String
"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, MIO.MonadIO m) => [Gio.Flags.DBusConnectionFlags] -> m (GValueConstruct o)
constructDBusConnectionFlags :: forall o (m :: * -> *).
(IsDBusConnection o, MonadIO m) =>
[DBusConnectionFlags] -> m (GValueConstruct o)
constructDBusConnectionFlags [DBusConnectionFlags]
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> [DBusConnectionFlags] -> IO (GValueConstruct o)
forall a o.
(IsGFlag a, BoxedFlags a) =>
String -> [a] -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyFlags String
"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
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusConnection.flags"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusConnection.html#g:attr:flags"
        })
#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 :: forall (m :: * -> *) o.
(MonadIO m, IsDBusConnection o) =>
o -> m Text
getDBusConnectionGuid o
obj = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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 Text
"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 String
"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, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructDBusConnectionGuid :: forall o (m :: * -> *).
(IsDBusConnection o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructDBusConnectionGuid Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"guid" (Text -> Maybe Text
forall a. a -> Maybe a
P.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
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusConnection.guid"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusConnection.html#g:attr:guid"
        })
#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 :: forall (m :: * -> *) o.
(MonadIO m, IsDBusConnection o) =>
o -> m IOStream
getDBusConnectionStream o
obj = IO IOStream -> m IOStream
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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 Text
"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 String
"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, MIO.MonadIO m, Gio.IOStream.IsIOStream a) => a -> m (GValueConstruct o)
constructDBusConnectionStream :: forall o (m :: * -> *) a.
(IsDBusConnection o, MonadIO m, IsIOStream a) =>
a -> m (GValueConstruct o)
constructDBusConnectionStream a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"stream" (a -> Maybe a
forall a. a -> Maybe a
P.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
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusConnection.stream"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusConnection.html#g:attr:stream"
        })
#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 :: forall (m :: * -> *) o.
(MonadIO m, IsDBusConnection o) =>
o -> m (Maybe Text)
getDBusConnectionUniqueName o
obj = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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 String
"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
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusConnection.uniqueName"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusConnection.html#g:attr:uniqueName"
        })
#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, DK.Type)])
#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, DK.Type)])

#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
--           , argCallbackUserData = 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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsAsyncResult a) =>
a -> m DBusConnection
dBusConnectionNewFinish a
res = IO DBusConnection -> m DBusConnection
forall a. IO a -> m a
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
    res' <- a -> IO (Ptr AsyncResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
res
    onException (do
        result <- propagateGError $ g_dbus_connection_new_finish res'
        checkUnexpectedReturnNULL "dBusConnectionNewFinish" result
        result' <- (wrapObject DBusConnection) result
        touchManagedPtr res
        return result'
     ) (do
        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
--           , argCallbackUserData = 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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsAsyncResult a) =>
a -> m DBusConnection
dBusConnectionNewForAddressFinish a
res = IO DBusConnection -> m DBusConnection
forall a. IO a -> m a
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
    res' <- a -> IO (Ptr AsyncResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
res
    onException (do
        result <- propagateGError $ g_dbus_connection_new_for_address_finish res'
        checkUnexpectedReturnNULL "dBusConnectionNewForAddressFinish" result
        result' <- (wrapObject DBusConnection) result
        touchManagedPtr res
        return result'
     ) (do
        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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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',
-- 'GI.Gio.Flags.DBusConnectionFlagsAuthenticationAllowAnonymous' or
-- 'GI.Gio.Flags.DBusConnectionFlagsAuthenticationRequireSameUser' 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 :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDBusAuthObserver a, IsCancellable b) =>
Text
-> [DBusConnectionFlags] -> Maybe a -> Maybe b -> m DBusConnection
dBusConnectionNewForAddressSync Text
address [DBusConnectionFlags]
flags Maybe a
observer Maybe b
cancellable = IO DBusConnection -> m DBusConnection
forall a. IO a -> m a
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
    address' <- Text -> IO CString
textToCString Text
address
    let flags' = [DBusConnectionFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [DBusConnectionFlags]
flags
    maybeObserver <- case observer of
        Maybe a
Nothing -> Ptr DBusAuthObserver -> IO (Ptr DBusAuthObserver)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr DBusAuthObserver
forall a. Ptr a
FP.nullPtr
        Just a
jObserver -> do
            jObserver' <- a -> IO (Ptr DBusAuthObserver)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
jObserver
            return jObserver'
    maybeCancellable <- case cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
FP.nullPtr
        Just b
jCancellable -> do
            jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            return jCancellable'
    onException (do
        result <- propagateGError $ g_dbus_connection_new_for_address_sync address' flags' maybeObserver maybeCancellable
        checkUnexpectedReturnNULL "dBusConnectionNewForAddressSync" result
        result' <- (wrapObject DBusConnection) result
        whenJust observer touchManagedPtr
        whenJust cancellable touchManagedPtr
        freeMem address'
        return result'
     ) (do
        freeMem 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
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "guid"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the GUID to use if authenticating as a server or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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 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 :: forall (m :: * -> *) a b c.
(HasCallStack, MonadIO m, IsIOStream a, IsDBusAuthObserver b,
 IsCancellable c) =>
a
-> Maybe Text
-> [DBusConnectionFlags]
-> Maybe b
-> Maybe c
-> m DBusConnection
dBusConnectionNewSync a
stream Maybe Text
guid [DBusConnectionFlags]
flags Maybe b
observer Maybe c
cancellable = IO DBusConnection -> m DBusConnection
forall a. IO a -> m a
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
    stream' <- a -> IO (Ptr IOStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
stream
    maybeGuid <- case guid of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
FP.nullPtr
        Just Text
jGuid -> do
            jGuid' <- Text -> IO CString
textToCString Text
jGuid
            return jGuid'
    let flags' = [DBusConnectionFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [DBusConnectionFlags]
flags
    maybeObserver <- case observer of
        Maybe b
Nothing -> Ptr DBusAuthObserver -> IO (Ptr DBusAuthObserver)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr DBusAuthObserver
forall a. Ptr a
FP.nullPtr
        Just b
jObserver -> do
            jObserver' <- b -> IO (Ptr DBusAuthObserver)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jObserver
            return jObserver'
    maybeCancellable <- case cancellable of
        Maybe c
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
FP.nullPtr
        Just c
jCancellable -> do
            jCancellable' <- c -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jCancellable
            return jCancellable'
    onException (do
        result <- propagateGError $ g_dbus_connection_new_sync stream' maybeGuid flags' maybeObserver maybeCancellable
        checkUnexpectedReturnNULL "dBusConnectionNewSync" result
        result' <- (wrapObject DBusConnection) result
        touchManagedPtr stream
        whenJust observer touchManagedPtr
        whenJust cancellable touchManagedPtr
        freeMem maybeGuid
        return result'
     ) (do
        freeMem 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusConnection a) =>
a -> DBusMessageFilterFunction -> m Word32
dBusConnectionAddFilter a
connection DBusMessageFilterFunction
filterFunction = IO Word32 -> m Word32
forall a. IO a -> m a
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
    connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    filterFunction' <- Gio.Callbacks.mk_DBusMessageFilterFunction (Gio.Callbacks.wrap_DBusMessageFilterFunction Nothing (Gio.Callbacks.drop_closures_DBusMessageFilterFunction filterFunction))
    let userData = FunPtr C_DBusMessageFilterFunction -> Ptr ()
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr C_DBusMessageFilterFunction
filterFunction'
    let userDataFreeFunc = FunPtr (Ptr a -> IO ())
forall a. FunPtr (Ptr a -> IO ())
SP.safeFreeFunPtrPtr
    result <- g_dbus_connection_add_filter connection' filterFunction' userData userDataFreeFunc
    touchManagedPtr connection
    return result

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

instance O.OverloadedMethodInfo DBusConnectionAddFilterMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusConnection.dBusConnectionAddFilter",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusConnection.html#v: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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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 :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDBusConnection a, IsCancellable b) =>
a
-> Maybe Text
-> Text
-> Text
-> Text
-> Maybe GVariant
-> Maybe VariantType
-> [DBusCallFlags]
-> Int32
-> Maybe b
-> Maybe AsyncReadyCallback
-> m ()
dBusConnectionCall a
connection Maybe Text
busName Text
objectPath Text
interfaceName Text
methodName Maybe GVariant
parameters Maybe VariantType
replyType [DBusCallFlags]
flags Int32
timeoutMsec Maybe b
cancellable Maybe AsyncReadyCallback
callback = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    maybeBusName <- case busName of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
FP.nullPtr
        Just Text
jBusName -> do
            jBusName' <- Text -> IO CString
textToCString Text
jBusName
            return jBusName'
    objectPath' <- textToCString objectPath
    interfaceName' <- textToCString interfaceName
    methodName' <- textToCString methodName
    maybeParameters <- case parameters of
        Maybe GVariant
Nothing -> Ptr GVariant -> IO (Ptr GVariant)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GVariant
forall a. Ptr a
FP.nullPtr
        Just GVariant
jParameters -> do
            jParameters' <- GVariant -> IO (Ptr GVariant)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GVariant
jParameters
            return jParameters'
    maybeReplyType <- case replyType of
        Maybe VariantType
Nothing -> Ptr VariantType -> IO (Ptr VariantType)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr VariantType
forall a. Ptr a
FP.nullPtr
        Just VariantType
jReplyType -> do
            jReplyType' <- VariantType -> IO (Ptr VariantType)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr VariantType
jReplyType
            return jReplyType'
    let flags' = [DBusCallFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [DBusCallFlags]
flags
    maybeCancellable <- case cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
FP.nullPtr
        Just b
jCancellable -> do
            jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            return jCancellable'
    maybeCallback <- case callback of
        Maybe AsyncReadyCallback
Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
forall a. FunPtr a
FP.nullFunPtr
        Just AsyncReadyCallback
jCallback -> do
            ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
            jCallback' <- Gio.Callbacks.mk_AsyncReadyCallback (Gio.Callbacks.wrap_AsyncReadyCallback (Just ptrcallback) (Gio.Callbacks.drop_closures_AsyncReadyCallback jCallback))
            poke ptrcallback jCallback'
            return jCallback'
    let userData = Ptr a
forall a. Ptr a
nullPtr
    g_dbus_connection_call connection' maybeBusName objectPath' interfaceName' methodName' maybeParameters maybeReplyType flags' timeoutMsec maybeCancellable maybeCallback userData
    touchManagedPtr connection
    whenJust parameters touchManagedPtr
    whenJust replyType touchManagedPtr
    whenJust cancellable touchManagedPtr
    freeMem maybeBusName
    freeMem objectPath'
    freeMem interfaceName'
    freeMem methodName'
    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.OverloadedMethod DBusConnectionCallMethodInfo a signature where
    overloadedMethod = dBusConnectionCall

instance O.OverloadedMethodInfo DBusConnectionCallMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusConnection.dBusConnectionCall",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusConnection.html#v: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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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 non-floating
    --     t'GVariant' tuple with return values. Free with 'GI.GLib.Structs.Variant.variantUnref'. /(Can throw 'Data.GI.Base.GError.GError')/
dBusConnectionCallFinish :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDBusConnection a, IsAsyncResult b) =>
a -> b -> m GVariant
dBusConnectionCallFinish a
connection b
res = IO GVariant -> m GVariant
forall a. IO a -> m a
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
    connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    res' <- unsafeManagedPtrCastPtr res
    onException (do
        result <- propagateGError $ g_dbus_connection_call_finish connection' res'
        checkUnexpectedReturnNULL "dBusConnectionCallFinish" result
        result' <- B.GVariant.wrapGVariantPtr result
        touchManagedPtr connection
        touchManagedPtr res
        return result'
     ) (do
        return ()
     )

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

instance O.OverloadedMethodInfo DBusConnectionCallFinishMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusConnection.dBusConnectionCallFinish",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusConnection.html#v: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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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 non-floating
    --     t'GVariant' tuple with return values. Free with 'GI.GLib.Structs.Variant.variantUnref'. /(Can throw 'Data.GI.Base.GError.GError')/
dBusConnectionCallSync :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDBusConnection a, IsCancellable b) =>
a
-> Maybe Text
-> Text
-> Text
-> Text
-> Maybe GVariant
-> Maybe VariantType
-> [DBusCallFlags]
-> Int32
-> Maybe b
-> m GVariant
dBusConnectionCallSync a
connection Maybe Text
busName Text
objectPath Text
interfaceName Text
methodName Maybe GVariant
parameters Maybe VariantType
replyType [DBusCallFlags]
flags Int32
timeoutMsec Maybe b
cancellable = IO GVariant -> m GVariant
forall a. IO a -> m a
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
    connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    maybeBusName <- case busName of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
FP.nullPtr
        Just Text
jBusName -> do
            jBusName' <- Text -> IO CString
textToCString Text
jBusName
            return jBusName'
    objectPath' <- textToCString objectPath
    interfaceName' <- textToCString interfaceName
    methodName' <- textToCString methodName
    maybeParameters <- case parameters of
        Maybe GVariant
Nothing -> Ptr GVariant -> IO (Ptr GVariant)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GVariant
forall a. Ptr a
FP.nullPtr
        Just GVariant
jParameters -> do
            jParameters' <- GVariant -> IO (Ptr GVariant)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GVariant
jParameters
            return jParameters'
    maybeReplyType <- case replyType of
        Maybe VariantType
Nothing -> Ptr VariantType -> IO (Ptr VariantType)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr VariantType
forall a. Ptr a
FP.nullPtr
        Just VariantType
jReplyType -> do
            jReplyType' <- VariantType -> IO (Ptr VariantType)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr VariantType
jReplyType
            return jReplyType'
    let flags' = [DBusCallFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [DBusCallFlags]
flags
    maybeCancellable <- case cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
FP.nullPtr
        Just b
jCancellable -> do
            jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            return jCancellable'
    onException (do
        result <- propagateGError $ g_dbus_connection_call_sync connection' maybeBusName objectPath' interfaceName' methodName' maybeParameters maybeReplyType flags' timeoutMsec maybeCancellable
        checkUnexpectedReturnNULL "dBusConnectionCallSync" result
        result' <- B.GVariant.wrapGVariantPtr result
        touchManagedPtr connection
        whenJust parameters touchManagedPtr
        whenJust replyType touchManagedPtr
        whenJust cancellable touchManagedPtr
        freeMem maybeBusName
        freeMem objectPath'
        freeMem interfaceName'
        freeMem methodName'
        return result'
     ) (do
        freeMem maybeBusName
        freeMem objectPath'
        freeMem interfaceName'
        freeMem 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.OverloadedMethod DBusConnectionCallSyncMethodInfo a signature where
    overloadedMethod = dBusConnectionCallSync

instance O.OverloadedMethodInfo DBusConnectionCallSyncMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusConnection.dBusConnectionCallSync",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusConnection.html#v: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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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.
-- 
-- The file descriptors normally correspond to @/G_VARIANT_TYPE_HANDLE/@
-- values in the body of the message. For example, if a message contains
-- two file descriptors, /@fdList@/ would have length 2, and
-- @g_variant_new_handle (0)@ and @g_variant_new_handle (1)@ would appear
-- somewhere in the body of the message (not necessarily in that order!)
-- to represent the file descriptors at indexes 0 and 1 respectively.
-- 
-- When designing D-Bus APIs that are intended to be interoperable,
-- please note that non-GDBus implementations of D-Bus can usually only
-- access file descriptors if they are referenced in this way by a
-- value of type @/G_VARIANT_TYPE_HANDLE/@ in the body of the message.
-- 
-- 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 :: forall (m :: * -> *) a b c.
(HasCallStack, MonadIO m, IsDBusConnection a, IsUnixFDList b,
 IsCancellable c) =>
a
-> Maybe Text
-> Text
-> Text
-> Text
-> Maybe GVariant
-> Maybe VariantType
-> [DBusCallFlags]
-> Int32
-> Maybe b
-> Maybe c
-> Maybe AsyncReadyCallback
-> m ()
dBusConnectionCallWithUnixFdList a
connection Maybe Text
busName Text
objectPath Text
interfaceName Text
methodName Maybe GVariant
parameters Maybe VariantType
replyType [DBusCallFlags]
flags Int32
timeoutMsec Maybe b
fdList Maybe c
cancellable Maybe AsyncReadyCallback
callback = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    maybeBusName <- case busName of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
FP.nullPtr
        Just Text
jBusName -> do
            jBusName' <- Text -> IO CString
textToCString Text
jBusName
            return jBusName'
    objectPath' <- textToCString objectPath
    interfaceName' <- textToCString interfaceName
    methodName' <- textToCString methodName
    maybeParameters <- case parameters of
        Maybe GVariant
Nothing -> Ptr GVariant -> IO (Ptr GVariant)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GVariant
forall a. Ptr a
FP.nullPtr
        Just GVariant
jParameters -> do
            jParameters' <- GVariant -> IO (Ptr GVariant)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GVariant
jParameters
            return jParameters'
    maybeReplyType <- case replyType of
        Maybe VariantType
Nothing -> Ptr VariantType -> IO (Ptr VariantType)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr VariantType
forall a. Ptr a
FP.nullPtr
        Just VariantType
jReplyType -> do
            jReplyType' <- VariantType -> IO (Ptr VariantType)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr VariantType
jReplyType
            return jReplyType'
    let flags' = [DBusCallFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [DBusCallFlags]
flags
    maybeFdList <- case fdList of
        Maybe b
Nothing -> Ptr UnixFDList -> IO (Ptr UnixFDList)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr UnixFDList
forall a. Ptr a
FP.nullPtr
        Just b
jFdList -> do
            jFdList' <- b -> IO (Ptr UnixFDList)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jFdList
            return jFdList'
    maybeCancellable <- case cancellable of
        Maybe c
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
FP.nullPtr
        Just c
jCancellable -> do
            jCancellable' <- c -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jCancellable
            return jCancellable'
    maybeCallback <- case callback of
        Maybe AsyncReadyCallback
Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
forall a. FunPtr a
FP.nullFunPtr
        Just AsyncReadyCallback
jCallback -> do
            ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
            jCallback' <- Gio.Callbacks.mk_AsyncReadyCallback (Gio.Callbacks.wrap_AsyncReadyCallback (Just ptrcallback) (Gio.Callbacks.drop_closures_AsyncReadyCallback jCallback))
            poke ptrcallback jCallback'
            return jCallback'
    let userData = Ptr a
forall a. Ptr a
nullPtr
    g_dbus_connection_call_with_unix_fd_list connection' maybeBusName objectPath' interfaceName' methodName' maybeParameters maybeReplyType flags' timeoutMsec maybeFdList maybeCancellable maybeCallback userData
    touchManagedPtr connection
    whenJust parameters touchManagedPtr
    whenJust replyType touchManagedPtr
    whenJust fdList touchManagedPtr
    whenJust cancellable touchManagedPtr
    freeMem maybeBusName
    freeMem objectPath'
    freeMem interfaceName'
    freeMem methodName'
    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.OverloadedMethod DBusConnectionCallWithUnixFdListMethodInfo a signature where
    overloadedMethod = dBusConnectionCallWithUnixFdList

instance O.OverloadedMethodInfo DBusConnectionCallWithUnixFdListMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusConnection.dBusConnectionCallWithUnixFdList",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusConnection.html#v: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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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'.
-- 
-- The file descriptors normally correspond to @/G_VARIANT_TYPE_HANDLE/@
-- values in the body of the message. For example,
-- if 'GI.GLib.Structs.Variant.variantGetHandle' returns 5, that is intended to be a reference
-- to the file descriptor that can be accessed by
-- @g_unix_fd_list_get (*out_fd_list, 5, ...)@.
-- 
-- When designing D-Bus APIs that are intended to be interoperable,
-- please note that non-GDBus implementations of D-Bus can usually only
-- access file descriptors if they are referenced in this way by a
-- value of type @/G_VARIANT_TYPE_HANDLE/@ in the body of the message.
-- 
-- /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 non-floating
    --     t'GVariant' tuple with return values. Free with 'GI.GLib.Structs.Variant.variantUnref'. /(Can throw 'Data.GI.Base.GError.GError')/
dBusConnectionCallWithUnixFdListFinish :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDBusConnection a, IsAsyncResult b) =>
a -> b -> m (GVariant, UnixFDList)
dBusConnectionCallWithUnixFdListFinish a
connection b
res = IO (GVariant, UnixFDList) -> m (GVariant, UnixFDList)
forall a. IO a -> m a
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
    connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    outFdList <- callocMem :: IO (Ptr (Ptr Gio.UnixFDList.UnixFDList))
    res' <- unsafeManagedPtrCastPtr res
    onException (do
        result <- propagateGError $ g_dbus_connection_call_with_unix_fd_list_finish connection' outFdList res'
        checkUnexpectedReturnNULL "dBusConnectionCallWithUnixFdListFinish" result
        result' <- B.GVariant.wrapGVariantPtr result
        outFdList' <- peek outFdList
        outFdList'' <- (wrapObject Gio.UnixFDList.UnixFDList) outFdList'
        touchManagedPtr connection
        touchManagedPtr res
        freeMem outFdList
        return (result', outFdList'')
     ) (do
        freeMem outFdList
     )

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

instance O.OverloadedMethodInfo DBusConnectionCallWithUnixFdListFinishMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusConnection.dBusConnectionCallWithUnixFdListFinish",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusConnection.html#v: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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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.
-- See 'GI.Gio.Objects.DBusConnection.dBusConnectionCallWithUnixFdList' and
-- 'GI.Gio.Objects.DBusConnection.dBusConnectionCallWithUnixFdListFinish' for more details.
-- 
-- 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 non-floating
    --     t'GVariant' tuple with return values. Free with 'GI.GLib.Structs.Variant.variantUnref'. /(Can throw 'Data.GI.Base.GError.GError')/
dBusConnectionCallWithUnixFdListSync :: forall (m :: * -> *) a b c.
(HasCallStack, MonadIO m, IsDBusConnection a, IsUnixFDList b,
 IsCancellable c) =>
a
-> Maybe Text
-> Text
-> Text
-> Text
-> Maybe GVariant
-> Maybe VariantType
-> [DBusCallFlags]
-> Int32
-> Maybe b
-> Maybe c
-> m (GVariant, UnixFDList)
dBusConnectionCallWithUnixFdListSync a
connection Maybe Text
busName Text
objectPath Text
interfaceName Text
methodName Maybe GVariant
parameters Maybe VariantType
replyType [DBusCallFlags]
flags Int32
timeoutMsec Maybe b
fdList Maybe c
cancellable = IO (GVariant, UnixFDList) -> m (GVariant, UnixFDList)
forall a. IO a -> m a
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
    connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    maybeBusName <- case busName of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
FP.nullPtr
        Just Text
jBusName -> do
            jBusName' <- Text -> IO CString
textToCString Text
jBusName
            return jBusName'
    objectPath' <- textToCString objectPath
    interfaceName' <- textToCString interfaceName
    methodName' <- textToCString methodName
    maybeParameters <- case parameters of
        Maybe GVariant
Nothing -> Ptr GVariant -> IO (Ptr GVariant)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GVariant
forall a. Ptr a
FP.nullPtr
        Just GVariant
jParameters -> do
            jParameters' <- GVariant -> IO (Ptr GVariant)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GVariant
jParameters
            return jParameters'
    maybeReplyType <- case replyType of
        Maybe VariantType
Nothing -> Ptr VariantType -> IO (Ptr VariantType)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr VariantType
forall a. Ptr a
FP.nullPtr
        Just VariantType
jReplyType -> do
            jReplyType' <- VariantType -> IO (Ptr VariantType)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr VariantType
jReplyType
            return jReplyType'
    let flags' = [DBusCallFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [DBusCallFlags]
flags
    maybeFdList <- case fdList of
        Maybe b
Nothing -> Ptr UnixFDList -> IO (Ptr UnixFDList)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr UnixFDList
forall a. Ptr a
FP.nullPtr
        Just b
jFdList -> do
            jFdList' <- b -> IO (Ptr UnixFDList)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jFdList
            return jFdList'
    outFdList <- callocMem :: IO (Ptr (Ptr Gio.UnixFDList.UnixFDList))
    maybeCancellable <- case cancellable of
        Maybe c
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
FP.nullPtr
        Just c
jCancellable -> do
            jCancellable' <- c -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jCancellable
            return jCancellable'
    onException (do
        result <- propagateGError $ g_dbus_connection_call_with_unix_fd_list_sync connection' maybeBusName objectPath' interfaceName' methodName' maybeParameters maybeReplyType flags' timeoutMsec maybeFdList outFdList maybeCancellable
        checkUnexpectedReturnNULL "dBusConnectionCallWithUnixFdListSync" result
        result' <- B.GVariant.wrapGVariantPtr result
        outFdList' <- peek outFdList
        outFdList'' <- (wrapObject Gio.UnixFDList.UnixFDList) outFdList'
        touchManagedPtr connection
        whenJust parameters touchManagedPtr
        whenJust replyType touchManagedPtr
        whenJust fdList touchManagedPtr
        whenJust cancellable touchManagedPtr
        freeMem maybeBusName
        freeMem objectPath'
        freeMem interfaceName'
        freeMem methodName'
        freeMem outFdList
        return (result', outFdList'')
     ) (do
        freeMem maybeBusName
        freeMem objectPath'
        freeMem interfaceName'
        freeMem methodName'
        freeMem 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.OverloadedMethod DBusConnectionCallWithUnixFdListSyncMethodInfo a signature where
    overloadedMethod = dBusConnectionCallWithUnixFdListSync

instance O.OverloadedMethodInfo DBusConnectionCallWithUnixFdListSyncMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusConnection.dBusConnectionCallWithUnixFdListSync",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusConnection.html#v: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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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 [DBusConnection:exitOnClose]("GI.Gio.Objects.DBusConnection#g:attr:exitOnClose")).
-- 
-- 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 [DBusConnection::closed]("GI.Gio.Objects.DBusConnection#g: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 :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDBusConnection a, IsCancellable b) =>
a -> Maybe b -> Maybe AsyncReadyCallback -> m ()
dBusConnectionClose a
connection Maybe b
cancellable Maybe AsyncReadyCallback
callback = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    maybeCancellable <- case cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
FP.nullPtr
        Just b
jCancellable -> do
            jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            return jCancellable'
    maybeCallback <- case callback of
        Maybe AsyncReadyCallback
Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
forall a. FunPtr a
FP.nullFunPtr
        Just AsyncReadyCallback
jCallback -> do
            ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
            jCallback' <- Gio.Callbacks.mk_AsyncReadyCallback (Gio.Callbacks.wrap_AsyncReadyCallback (Just ptrcallback) (Gio.Callbacks.drop_closures_AsyncReadyCallback jCallback))
            poke ptrcallback jCallback'
            return jCallback'
    let userData = Ptr a
forall a. Ptr a
nullPtr
    g_dbus_connection_close connection' maybeCancellable maybeCallback userData
    touchManagedPtr connection
    whenJust cancellable touchManagedPtr
    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.OverloadedMethod DBusConnectionCloseMethodInfo a signature where
    overloadedMethod = dBusConnectionClose

instance O.OverloadedMethodInfo DBusConnectionCloseMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusConnection.dBusConnectionClose",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusConnection.html#v: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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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 :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDBusConnection a, IsAsyncResult b) =>
a -> b -> m ()
dBusConnectionCloseFinish a
connection b
res = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    res' <- unsafeManagedPtrCastPtr res
    onException (do
        _ <- propagateGError $ g_dbus_connection_close_finish connection' res'
        touchManagedPtr connection
        touchManagedPtr res
        return ()
     ) (do
        return ()
     )

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

instance O.OverloadedMethodInfo DBusConnectionCloseFinishMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusConnection.dBusConnectionCloseFinish",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusConnection.html#v: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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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 :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDBusConnection a, IsCancellable b) =>
a -> Maybe b -> m ()
dBusConnectionCloseSync a
connection Maybe b
cancellable = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    maybeCancellable <- case cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
FP.nullPtr
        Just b
jCancellable -> do
            jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            return jCancellable'
    onException (do
        _ <- propagateGError $ g_dbus_connection_close_sync connection' maybeCancellable
        touchManagedPtr connection
        whenJust cancellable touchManagedPtr
        return ()
     ) (do
        return ()
     )

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

instance O.OverloadedMethodInfo DBusConnectionCloseSyncMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusConnection.dBusConnectionCloseSync",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusConnection.html#v: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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusConnection a) =>
a -> Maybe Text -> Text -> Text -> Text -> Maybe GVariant -> m ()
dBusConnectionEmitSignal a
connection Maybe Text
destinationBusName Text
objectPath Text
interfaceName Text
signalName Maybe GVariant
parameters = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    maybeDestinationBusName <- case destinationBusName of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
FP.nullPtr
        Just Text
jDestinationBusName -> do
            jDestinationBusName' <- Text -> IO CString
textToCString Text
jDestinationBusName
            return jDestinationBusName'
    objectPath' <- textToCString objectPath
    interfaceName' <- textToCString interfaceName
    signalName' <- textToCString signalName
    maybeParameters <- case parameters of
        Maybe GVariant
Nothing -> Ptr GVariant -> IO (Ptr GVariant)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GVariant
forall a. Ptr a
FP.nullPtr
        Just GVariant
jParameters -> do
            jParameters' <- GVariant -> IO (Ptr GVariant)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GVariant
jParameters
            return jParameters'
    onException (do
        _ <- propagateGError $ g_dbus_connection_emit_signal connection' maybeDestinationBusName objectPath' interfaceName' signalName' maybeParameters
        touchManagedPtr connection
        whenJust parameters touchManagedPtr
        freeMem maybeDestinationBusName
        freeMem objectPath'
        freeMem interfaceName'
        freeMem signalName'
        return ()
     ) (do
        freeMem maybeDestinationBusName
        freeMem objectPath'
        freeMem interfaceName'
        freeMem 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.OverloadedMethod DBusConnectionEmitSignalMethodInfo a signature where
    overloadedMethod = dBusConnectionEmitSignal

instance O.OverloadedMethodInfo DBusConnectionEmitSignalMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusConnection.dBusConnectionEmitSignal",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusConnection.html#v: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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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 :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDBusConnection a, IsActionGroup b) =>
a -> Text -> b -> m Word32
dBusConnectionExportActionGroup a
connection Text
objectPath b
actionGroup = IO Word32 -> m Word32
forall a. IO a -> m a
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
    connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    objectPath' <- textToCString objectPath
    actionGroup' <- unsafeManagedPtrCastPtr actionGroup
    onException (do
        result <- propagateGError $ g_dbus_connection_export_action_group connection' objectPath' actionGroup'
        touchManagedPtr connection
        touchManagedPtr actionGroup
        freeMem objectPath'
        return result
     ) (do
        freeMem objectPath'
     )

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

instance O.OverloadedMethodInfo DBusConnectionExportActionGroupMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusConnection.dBusConnectionExportActionGroup",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusConnection.html#v: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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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).
-- 
-- Exporting menus with sections containing more than
-- 'GI.Gio.Constants.MENU_EXPORTER_MAX_SECTION_SIZE' items is not supported and results in
-- undefined behavior.
-- 
-- 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 :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDBusConnection a, IsMenuModel b) =>
a -> Text -> b -> m Word32
dBusConnectionExportMenuModel a
connection Text
objectPath b
menu = IO Word32 -> m Word32
forall a. IO a -> m a
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
    connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    objectPath' <- textToCString objectPath
    menu' <- unsafeManagedPtrCastPtr menu
    onException (do
        result <- propagateGError $ g_dbus_connection_export_menu_model connection' objectPath' menu'
        touchManagedPtr connection
        touchManagedPtr menu
        freeMem objectPath'
        return result
     ) (do
        freeMem objectPath'
     )

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

instance O.OverloadedMethodInfo DBusConnectionExportMenuModelMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusConnection.dBusConnectionExportMenuModel",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusConnection.html#v: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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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 :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDBusConnection a, IsCancellable b) =>
a -> Maybe b -> Maybe AsyncReadyCallback -> m ()
dBusConnectionFlush a
connection Maybe b
cancellable Maybe AsyncReadyCallback
callback = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    maybeCancellable <- case cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
FP.nullPtr
        Just b
jCancellable -> do
            jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            return jCancellable'
    maybeCallback <- case callback of
        Maybe AsyncReadyCallback
Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
forall a. FunPtr a
FP.nullFunPtr
        Just AsyncReadyCallback
jCallback -> do
            ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
            jCallback' <- Gio.Callbacks.mk_AsyncReadyCallback (Gio.Callbacks.wrap_AsyncReadyCallback (Just ptrcallback) (Gio.Callbacks.drop_closures_AsyncReadyCallback jCallback))
            poke ptrcallback jCallback'
            return jCallback'
    let userData = Ptr a
forall a. Ptr a
nullPtr
    g_dbus_connection_flush connection' maybeCancellable maybeCallback userData
    touchManagedPtr connection
    whenJust cancellable touchManagedPtr
    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.OverloadedMethod DBusConnectionFlushMethodInfo a signature where
    overloadedMethod = dBusConnectionFlush

instance O.OverloadedMethodInfo DBusConnectionFlushMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusConnection.dBusConnectionFlush",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusConnection.html#v: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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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 :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDBusConnection a, IsAsyncResult b) =>
a -> b -> m ()
dBusConnectionFlushFinish a
connection b
res = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    res' <- unsafeManagedPtrCastPtr res
    onException (do
        _ <- propagateGError $ g_dbus_connection_flush_finish connection' res'
        touchManagedPtr connection
        touchManagedPtr res
        return ()
     ) (do
        return ()
     )

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

instance O.OverloadedMethodInfo DBusConnectionFlushFinishMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusConnection.dBusConnectionFlushFinish",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusConnection.html#v: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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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 :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDBusConnection a, IsCancellable b) =>
a -> Maybe b -> m ()
dBusConnectionFlushSync a
connection Maybe b
cancellable = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    maybeCancellable <- case cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
FP.nullPtr
        Just b
jCancellable -> do
            jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            return jCancellable'
    onException (do
        _ <- propagateGError $ g_dbus_connection_flush_sync connection' maybeCancellable
        touchManagedPtr connection
        whenJust cancellable touchManagedPtr
        return ()
     ) (do
        return ()
     )

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

instance O.OverloadedMethodInfo DBusConnectionFlushSyncMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusConnection.dBusConnectionFlushSync",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusConnection.html#v: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
--           , argCallbackUserData = 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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusConnection a) =>
a -> m [DBusCapabilityFlags]
dBusConnectionGetCapabilities a
connection = IO [DBusCapabilityFlags] -> m [DBusCapabilityFlags]
forall a. IO a -> m a
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
    connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    result <- g_dbus_connection_get_capabilities connection'
    let result' = CUInt -> [DBusCapabilityFlags]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
result
    touchManagedPtr connection
    return result'

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

instance O.OverloadedMethodInfo DBusConnectionGetCapabilitiesMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusConnection.dBusConnectionGetCapabilities",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusConnection.html#v: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
--           , argCallbackUserData = 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
-- [DBusConnection:exitOnClose]("GI.Gio.Objects.DBusConnection#g:attr:exitOnClose") 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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusConnection a) =>
a -> m Bool
dBusConnectionGetExitOnClose a
connection = IO Bool -> m Bool
forall a. IO a -> m a
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
    connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    result <- g_dbus_connection_get_exit_on_close connection'
    let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    touchManagedPtr connection
    return result'

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

instance O.OverloadedMethodInfo DBusConnectionGetExitOnCloseMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusConnection.dBusConnectionGetExitOnClose",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusConnection.html#v: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
--           , argCallbackUserData = 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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusConnection a) =>
a -> m [DBusConnectionFlags]
dBusConnectionGetFlags a
connection = IO [DBusConnectionFlags] -> m [DBusConnectionFlags]
forall a. IO a -> m a
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
    connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    result <- g_dbus_connection_get_flags connection'
    let result' = CUInt -> [DBusConnectionFlags]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
result
    touchManagedPtr connection
    return result'

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

instance O.OverloadedMethodInfo DBusConnectionGetFlagsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusConnection.dBusConnectionGetFlags",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusConnection.html#v: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
--           , argCallbackUserData = 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 [DBusConnection:guid]("GI.Gio.Objects.DBusConnection#g:attr: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusConnection a) =>
a -> m Text
dBusConnectionGetGuid a
connection = IO Text -> m Text
forall a. IO a -> m a
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
    connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    result <- g_dbus_connection_get_guid connection'
    checkUnexpectedReturnNULL "dBusConnectionGetGuid" result
    result' <- cstringToText result
    touchManagedPtr connection
    return result'

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

instance O.OverloadedMethodInfo DBusConnectionGetGuidMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusConnection.dBusConnectionGetGuid",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusConnection.html#v: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
--           , argCallbackUserData = 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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusConnection a) =>
a -> m Word32
dBusConnectionGetLastSerial a
connection = IO Word32 -> m Word32
forall a. IO a -> m a
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
    connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    result <- g_dbus_connection_get_last_serial connection'
    touchManagedPtr connection
    return result

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

instance O.OverloadedMethodInfo DBusConnectionGetLastSerialMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusConnection.dBusConnectionGetLastSerial",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusConnection.html#v: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
--           , argCallbackUserData = 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 ->                   -- connection : TInterface (Name {namespace = "Gio", name = "DBusConnection"})
    IO (Ptr Gio.Credentials.Credentials)

-- | Gets the credentials of the authenticated peer. This will always
-- return 'P.Nothing' unless /@connection@/ acted as a server
-- (e.g. 'GI.Gio.Flags.DBusConnectionFlagsAuthenticationServer' was passed)
-- when set up and the client passed credentials as part of the
-- authentication process.
-- 
-- In a message bus setup, the message bus is always the server and
-- each application is a client. So this method will always return
-- 'P.Nothing' for message bus clients.
-- 
-- /Since: 2.26/
dBusConnectionGetPeerCredentials ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusConnection a) =>
    a
    -- ^ /@connection@/: a t'GI.Gio.Objects.DBusConnection.DBusConnection'
    -> m (Maybe Gio.Credentials.Credentials)
    -- ^ __Returns:__ a t'GI.Gio.Objects.Credentials.Credentials' or 'P.Nothing' if not
    --     available. Do not free this object, it is owned by /@connection@/.
dBusConnectionGetPeerCredentials :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusConnection a) =>
a -> m (Maybe Credentials)
dBusConnectionGetPeerCredentials a
connection = IO (Maybe Credentials) -> m (Maybe Credentials)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Credentials) -> m (Maybe Credentials))
-> IO (Maybe Credentials) -> m (Maybe Credentials)
forall a b. (a -> b) -> a -> b
$ do
    connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    result <- g_dbus_connection_get_peer_credentials connection'
    maybeResult <- convertIfNonNull result $ \Ptr Credentials
result' -> do
        result'' <- ((ManagedPtr Credentials -> Credentials)
-> Ptr Credentials -> IO Credentials
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Credentials -> Credentials
Gio.Credentials.Credentials) Ptr Credentials
result'
        return result''
    touchManagedPtr connection
    return maybeResult

#if defined(ENABLE_OVERLOADING)
data DBusConnectionGetPeerCredentialsMethodInfo
instance (signature ~ (m (Maybe Gio.Credentials.Credentials)), MonadIO m, IsDBusConnection a) => O.OverloadedMethod DBusConnectionGetPeerCredentialsMethodInfo a signature where
    overloadedMethod = dBusConnectionGetPeerCredentials

instance O.OverloadedMethodInfo DBusConnectionGetPeerCredentialsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusConnection.dBusConnectionGetPeerCredentials",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusConnection.html#v:dBusConnectionGetPeerCredentials"
        })


#endif

-- method DBusConnection::get_stream
-- 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
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "IOStream" })
-- throws : False
-- Skip return : False

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

-- | Gets the underlying stream used for IO.
-- 
-- 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/
dBusConnectionGetStream ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusConnection a) =>
    a
    -- ^ /@connection@/: a t'GI.Gio.Objects.DBusConnection.DBusConnection'
    -> m Gio.IOStream.IOStream
    -- ^ __Returns:__ the stream used for IO
dBusConnectionGetStream :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusConnection a) =>
a -> m IOStream
dBusConnectionGetStream a
connection = IO IOStream -> m IOStream
forall a. IO a -> m a
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
$ do
    connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    result <- g_dbus_connection_get_stream connection'
    checkUnexpectedReturnNULL "dBusConnectionGetStream" result
    result' <- (newObject Gio.IOStream.IOStream) result
    touchManagedPtr connection
    return result'

#if defined(ENABLE_OVERLOADING)
data DBusConnectionGetStreamMethodInfo
instance (signature ~ (m Gio.IOStream.IOStream), MonadIO m, IsDBusConnection a) => O.OverloadedMethod DBusConnectionGetStreamMethodInfo a signature where
    overloadedMethod = dBusConnectionGetStream

instance O.OverloadedMethodInfo DBusConnectionGetStreamMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusConnection.dBusConnectionGetStream",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusConnection.html#v:dBusConnectionGetStream"
        })


#endif

-- method DBusConnection::get_unique_name
-- 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
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

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

-- | Gets the unique name of /@connection@/ as assigned by the message
-- bus. This can also be used to figure out if /@connection@/ is a
-- message bus connection.
-- 
-- /Since: 2.26/
dBusConnectionGetUniqueName ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusConnection a) =>
    a
    -- ^ /@connection@/: a t'GI.Gio.Objects.DBusConnection.DBusConnection'
    -> m (Maybe T.Text)
    -- ^ __Returns:__ the unique name or 'P.Nothing' if /@connection@/ is not a message
    --     bus connection. Do not free this string, it is owned by
    --     /@connection@/.
dBusConnectionGetUniqueName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusConnection a) =>
a -> m (Maybe Text)
dBusConnectionGetUniqueName a
connection = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    result <- g_dbus_connection_get_unique_name connection'
    maybeResult <- convertIfNonNull result $ \CString
result' -> do
        result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        return result''
    touchManagedPtr connection
    return maybeResult

#if defined(ENABLE_OVERLOADING)
data DBusConnectionGetUniqueNameMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsDBusConnection a) => O.OverloadedMethod DBusConnectionGetUniqueNameMethodInfo a signature where
    overloadedMethod = dBusConnectionGetUniqueName

instance O.OverloadedMethodInfo DBusConnectionGetUniqueNameMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusConnection.dBusConnectionGetUniqueName",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusConnection.html#v:dBusConnectionGetUniqueName"
        })


#endif

-- method DBusConnection::is_closed
-- 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
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

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

-- | Gets whether /@connection@/ is closed.
-- 
-- /Since: 2.26/
dBusConnectionIsClosed ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusConnection a) =>
    a
    -- ^ /@connection@/: a t'GI.Gio.Objects.DBusConnection.DBusConnection'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the connection is closed, 'P.False' otherwise
dBusConnectionIsClosed :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusConnection a) =>
a -> m Bool
dBusConnectionIsClosed a
connection = IO Bool -> m Bool
forall a. IO a -> m a
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
    connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    result <- g_dbus_connection_is_closed connection'
    let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    touchManagedPtr connection
    return result'

#if defined(ENABLE_OVERLOADING)
data DBusConnectionIsClosedMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDBusConnection a) => O.OverloadedMethod DBusConnectionIsClosedMethodInfo a signature where
    overloadedMethod = dBusConnectionIsClosed

instance O.OverloadedMethodInfo DBusConnectionIsClosedMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusConnection.dBusConnectionIsClosed",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusConnection.html#v:dBusConnectionIsClosed"
        })


#endif

-- method DBusConnection::register_object
-- 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
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "object_path"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The object path to register at."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "interface_info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusInterfaceInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Introspection data for the interface."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "method_call_closure"
--           , argType = TGClosure Nothing
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "#GClosure for handling incoming method calls."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "get_property_closure"
--           , argType = TGClosure Nothing
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "#GClosure for getting a property."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "set_property_closure"
--           , argType = TGClosure Nothing
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "#GClosure for setting a property."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt)
-- throws : True
-- Skip return : False

foreign import ccall "g_dbus_connection_register_object_with_closures" g_dbus_connection_register_object_with_closures :: 
    Ptr DBusConnection ->                   -- connection : TInterface (Name {namespace = "Gio", name = "DBusConnection"})
    CString ->                              -- object_path : TBasicType TUTF8
    Ptr Gio.DBusInterfaceInfo.DBusInterfaceInfo -> -- interface_info : TInterface (Name {namespace = "Gio", name = "DBusInterfaceInfo"})
    Ptr (GClosure ()) ->                    -- method_call_closure : TGClosure Nothing
    Ptr (GClosure ()) ->                    -- get_property_closure : TGClosure Nothing
    Ptr (GClosure ()) ->                    -- set_property_closure : TGClosure Nothing
    Ptr (Ptr GError) ->                     -- error
    IO Word32

-- | Version of @/g_dbus_connection_register_object()/@ using closures instead of a
-- t'GI.Gio.Structs.DBusInterfaceVTable.DBusInterfaceVTable' for easier binding in other languages.
-- 
-- /Since: 2.46/
dBusConnectionRegisterObject ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusConnection a) =>
    a
    -- ^ /@connection@/: A t'GI.Gio.Objects.DBusConnection.DBusConnection'.
    -> T.Text
    -- ^ /@objectPath@/: The object path to register at.
    -> Gio.DBusInterfaceInfo.DBusInterfaceInfo
    -- ^ /@interfaceInfo@/: Introspection data for the interface.
    -> Maybe (GClosure b)
    -- ^ /@methodCallClosure@/: t'GI.GObject.Structs.Closure.Closure' for handling incoming method calls.
    -> Maybe (GClosure c)
    -- ^ /@getPropertyClosure@/: t'GI.GObject.Structs.Closure.Closure' for getting a property.
    -> Maybe (GClosure d)
    -- ^ /@setPropertyClosure@/: t'GI.GObject.Structs.Closure.Closure' for setting a property.
    -> m Word32
    -- ^ __Returns:__ 0 if /@error@/ is set, otherwise a registration ID (never 0)
    -- that can be used with 'GI.Gio.Objects.DBusConnection.dBusConnectionUnregisterObject' . /(Can throw 'Data.GI.Base.GError.GError')/
dBusConnectionRegisterObject :: forall (m :: * -> *) a b c d.
(HasCallStack, MonadIO m, IsDBusConnection a) =>
a
-> Text
-> DBusInterfaceInfo
-> Maybe (GClosure b)
-> Maybe (GClosure c)
-> Maybe (GClosure d)
-> m Word32
dBusConnectionRegisterObject a
connection Text
objectPath DBusInterfaceInfo
interfaceInfo Maybe (GClosure b)
methodCallClosure Maybe (GClosure c)
getPropertyClosure Maybe (GClosure d)
setPropertyClosure = IO Word32 -> m Word32
forall a. IO a -> m a
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
    connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    objectPath' <- textToCString objectPath
    interfaceInfo' <- unsafeManagedPtrGetPtr interfaceInfo
    maybeMethodCallClosure <- case methodCallClosure of
        Maybe (GClosure b)
Nothing -> Ptr (GClosure ()) -> IO (Ptr (GClosure ()))
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr (GClosure ())
forall a. Ptr a
FP.nullPtr
        Just GClosure b
jMethodCallClosure -> do
            jMethodCallClosure' <- GClosure b -> IO (Ptr (GClosure ()))
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr GClosure b
jMethodCallClosure
            return jMethodCallClosure'
    maybeGetPropertyClosure <- case getPropertyClosure of
        Maybe (GClosure c)
Nothing -> Ptr (GClosure ()) -> IO (Ptr (GClosure ()))
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr (GClosure ())
forall a. Ptr a
FP.nullPtr
        Just GClosure c
jGetPropertyClosure -> do
            jGetPropertyClosure' <- GClosure c -> IO (Ptr (GClosure ()))
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr GClosure c
jGetPropertyClosure
            return jGetPropertyClosure'
    maybeSetPropertyClosure <- case setPropertyClosure of
        Maybe (GClosure d)
Nothing -> Ptr (GClosure ()) -> IO (Ptr (GClosure ()))
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr (GClosure ())
forall a. Ptr a
FP.nullPtr
        Just GClosure d
jSetPropertyClosure -> do
            jSetPropertyClosure' <- GClosure d -> IO (Ptr (GClosure ()))
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr GClosure d
jSetPropertyClosure
            return jSetPropertyClosure'
    onException (do
        result <- propagateGError $ g_dbus_connection_register_object_with_closures connection' objectPath' interfaceInfo' maybeMethodCallClosure maybeGetPropertyClosure maybeSetPropertyClosure
        touchManagedPtr connection
        touchManagedPtr interfaceInfo
        whenJust methodCallClosure touchManagedPtr
        whenJust getPropertyClosure touchManagedPtr
        whenJust setPropertyClosure touchManagedPtr
        freeMem objectPath'
        return result
     ) (do
        freeMem objectPath'
     )

#if defined(ENABLE_OVERLOADING)
data DBusConnectionRegisterObjectMethodInfo
instance (signature ~ (T.Text -> Gio.DBusInterfaceInfo.DBusInterfaceInfo -> Maybe (GClosure b) -> Maybe (GClosure c) -> Maybe (GClosure d) -> m Word32), MonadIO m, IsDBusConnection a) => O.OverloadedMethod DBusConnectionRegisterObjectMethodInfo a signature where
    overloadedMethod = dBusConnectionRegisterObject

instance O.OverloadedMethodInfo DBusConnectionRegisterObjectMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusConnection.dBusConnectionRegisterObject",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusConnection.html#v:dBusConnectionRegisterObject"
        })


#endif

-- method DBusConnection::register_subtree
-- 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
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "object_path"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the object path to register the subtree at"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "vtable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusSubtreeVTable" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a #GDBusSubtreeVTable to enumerate, introspect and\n    dispatch nodes in the subtree"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusSubtreeFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "flags used to fine tune the behavior of the subtree"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "data to pass to functions in @vtable"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = 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 call when the subtree is unregistered"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt)
-- throws : True
-- Skip return : False

foreign import ccall "g_dbus_connection_register_subtree" g_dbus_connection_register_subtree :: 
    Ptr DBusConnection ->                   -- connection : TInterface (Name {namespace = "Gio", name = "DBusConnection"})
    CString ->                              -- object_path : TBasicType TUTF8
    Ptr Gio.DBusSubtreeVTable.DBusSubtreeVTable -> -- vtable : TInterface (Name {namespace = "Gio", name = "DBusSubtreeVTable"})
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gio", name = "DBusSubtreeFlags"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    FunPtr GLib.Callbacks.C_DestroyNotify -> -- user_data_free_func : TInterface (Name {namespace = "GLib", name = "DestroyNotify"})
    Ptr (Ptr GError) ->                     -- error
    IO Word32

-- | Registers a whole subtree of dynamic objects.
-- 
-- The /@enumerate@/ and /@introspection@/ functions in /@vtable@/ are used to
-- convey, to remote callers, what nodes exist in the subtree rooted
-- by /@objectPath@/.
-- 
-- When handling remote calls into any node in the subtree, first the
-- /@enumerate@/ function is used to check if the node exists. If the node exists
-- or the 'GI.Gio.Flags.DBusSubtreeFlagsDispatchToUnenumeratedNodes' flag is set
-- the /@introspection@/ function is used to check if the node supports the
-- requested method. If so, the /@dispatch@/ function is used to determine
-- where to dispatch the call. The collected t'GI.Gio.Structs.DBusInterfaceVTable.DBusInterfaceVTable' and
-- @/gpointer/@ will be used to call into the interface vtable for processing
-- the request.
-- 
-- All calls into user-provided code will be invoked in the
-- [thread-default main context][g-main-context-push-thread-default]
-- of the thread you are calling this method from.
-- 
-- If an existing subtree is already registered at /@objectPath@/ or
-- then /@error@/ is set to 'GI.Gio.Enums.IOErrorEnumExists'.
-- 
-- Note that it is valid to register regular objects (using
-- @/g_dbus_connection_register_object()/@) in a subtree registered with
-- 'GI.Gio.Objects.DBusConnection.dBusConnectionRegisterSubtree' - if so, the subtree handler
-- is tried as the last resort. One way to think about a subtree
-- handler is to consider it a fallback handler for object paths not
-- registered via @/g_dbus_connection_register_object()/@ or other bindings.
-- 
-- Note that /@vtable@/ will be copied so you cannot change it after
-- registration.
-- 
-- See this [server][gdbus-subtree-server] for an example of how to use
-- this method.
-- 
-- /Since: 2.26/
dBusConnectionRegisterSubtree ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusConnection a) =>
    a
    -- ^ /@connection@/: a t'GI.Gio.Objects.DBusConnection.DBusConnection'
    -> T.Text
    -- ^ /@objectPath@/: the object path to register the subtree at
    -> Gio.DBusSubtreeVTable.DBusSubtreeVTable
    -- ^ /@vtable@/: a t'GI.Gio.Structs.DBusSubtreeVTable.DBusSubtreeVTable' to enumerate, introspect and
    --     dispatch nodes in the subtree
    -> [Gio.Flags.DBusSubtreeFlags]
    -- ^ /@flags@/: flags used to fine tune the behavior of the subtree
    -> Ptr ()
    -- ^ /@userData@/: data to pass to functions in /@vtable@/
    -> GLib.Callbacks.DestroyNotify
    -- ^ /@userDataFreeFunc@/: function to call when the subtree is unregistered
    -> m Word32
    -- ^ __Returns:__ 0 if /@error@/ is set, otherwise a subtree registration ID (never 0)
    -- that can be used with 'GI.Gio.Objects.DBusConnection.dBusConnectionUnregisterSubtree' /(Can throw 'Data.GI.Base.GError.GError')/
dBusConnectionRegisterSubtree :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusConnection a) =>
a
-> Text
-> DBusSubtreeVTable
-> [DBusSubtreeFlags]
-> Ptr ()
-> C_DestroyNotify
-> m Word32
dBusConnectionRegisterSubtree a
connection Text
objectPath DBusSubtreeVTable
vtable [DBusSubtreeFlags]
flags Ptr ()
userData C_DestroyNotify
userDataFreeFunc = IO Word32 -> m Word32
forall a. IO a -> m a
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
    connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    objectPath' <- textToCString objectPath
    vtable' <- unsafeManagedPtrGetPtr vtable
    let flags' = [DBusSubtreeFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [DBusSubtreeFlags]
flags
    ptruserDataFreeFunc <- callocMem :: IO (Ptr (FunPtr GLib.Callbacks.C_DestroyNotify))
    userDataFreeFunc' <- GLib.Callbacks.mk_DestroyNotify (GLib.Callbacks.wrap_DestroyNotify (Just ptruserDataFreeFunc) userDataFreeFunc)
    poke ptruserDataFreeFunc userDataFreeFunc'
    onException (do
        result <- propagateGError $ g_dbus_connection_register_subtree connection' objectPath' vtable' flags' userData userDataFreeFunc'
        touchManagedPtr connection
        touchManagedPtr vtable
        freeMem objectPath'
        return result
     ) (do
        freeMem objectPath'
     )

#if defined(ENABLE_OVERLOADING)
data DBusConnectionRegisterSubtreeMethodInfo
instance (signature ~ (T.Text -> Gio.DBusSubtreeVTable.DBusSubtreeVTable -> [Gio.Flags.DBusSubtreeFlags] -> Ptr () -> GLib.Callbacks.DestroyNotify -> m Word32), MonadIO m, IsDBusConnection a) => O.OverloadedMethod DBusConnectionRegisterSubtreeMethodInfo a signature where
    overloadedMethod = dBusConnectionRegisterSubtree

instance O.OverloadedMethodInfo DBusConnectionRegisterSubtreeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusConnection.dBusConnectionRegisterSubtree",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusConnection.html#v:dBusConnectionRegisterSubtree"
        })


#endif

-- method DBusConnection::remove_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
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "filter_id"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "an identifier obtained from g_dbus_connection_add_filter()"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

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

-- | Removes a filter.
-- 
-- Note that since filters run in a different thread, there is a race
-- condition where it is possible that the filter will be running even
-- after calling 'GI.Gio.Objects.DBusConnection.dBusConnectionRemoveFilter', so you cannot just
-- free data that the filter might be using. Instead, you should pass
-- a t'GI.GLib.Callbacks.DestroyNotify' to 'GI.Gio.Objects.DBusConnection.dBusConnectionAddFilter', which will be
-- called when it is guaranteed that the data is no longer needed.
-- 
-- /Since: 2.26/
dBusConnectionRemoveFilter ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusConnection a) =>
    a
    -- ^ /@connection@/: a t'GI.Gio.Objects.DBusConnection.DBusConnection'
    -> Word32
    -- ^ /@filterId@/: an identifier obtained from 'GI.Gio.Objects.DBusConnection.dBusConnectionAddFilter'
    -> m ()
dBusConnectionRemoveFilter :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusConnection a) =>
a -> Word32 -> m ()
dBusConnectionRemoveFilter a
connection Word32
filterId = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    g_dbus_connection_remove_filter connection' filterId
    touchManagedPtr connection
    return ()

#if defined(ENABLE_OVERLOADING)
data DBusConnectionRemoveFilterMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsDBusConnection a) => O.OverloadedMethod DBusConnectionRemoveFilterMethodInfo a signature where
    overloadedMethod = dBusConnectionRemoveFilter

instance O.OverloadedMethodInfo DBusConnectionRemoveFilterMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusConnection.dBusConnectionRemoveFilter",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusConnection.html#v:dBusConnectionRemoveFilter"
        })


#endif

-- method DBusConnection::send_message
-- 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
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "message"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusMessage" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDBusMessage" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "DBusSendMessageFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "flags affecting how the message is sent"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "out_serial"
--           , argType = TBasicType TUInt32
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "return location for serial number assigned\n    to @message when sending it or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_dbus_connection_send_message" g_dbus_connection_send_message :: 
    Ptr DBusConnection ->                   -- connection : TInterface (Name {namespace = "Gio", name = "DBusConnection"})
    Ptr Gio.DBusMessage.DBusMessage ->      -- message : TInterface (Name {namespace = "Gio", name = "DBusMessage"})
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gio", name = "DBusSendMessageFlags"})
    Ptr Word32 ->                           -- out_serial : TBasicType TUInt32
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Asynchronously sends /@message@/ to the peer represented by /@connection@/.
-- 
-- Unless /@flags@/ contain the
-- 'GI.Gio.Flags.DBusSendMessageFlagsPreserveSerial' flag, the serial number
-- will be assigned by /@connection@/ and set on /@message@/ via
-- 'GI.Gio.Objects.DBusMessage.dBusMessageSetSerial'. If /@outSerial@/ is not 'P.Nothing', then the
-- serial number used will be written to this location prior to
-- submitting the message to the underlying transport. While it has a @volatile@
-- qualifier, this is a historical artifact and the argument passed to it should
-- not be @volatile@.
-- 
-- If /@connection@/ is closed then the operation will fail with
-- 'GI.Gio.Enums.IOErrorEnumClosed'. If /@message@/ is not well-formed,
-- the operation fails with 'GI.Gio.Enums.IOErrorEnumInvalidArgument'.
-- 
-- See this [server][gdbus-server] and [client][gdbus-unix-fd-client]
-- for an example of how to use this low-level API to send and receive
-- UNIX file descriptors.
-- 
-- Note that /@message@/ must be unlocked, unless /@flags@/ contain the
-- 'GI.Gio.Flags.DBusSendMessageFlagsPreserveSerial' flag.
-- 
-- /Since: 2.26/
dBusConnectionSendMessage ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusConnection a, Gio.DBusMessage.IsDBusMessage b) =>
    a
    -- ^ /@connection@/: a t'GI.Gio.Objects.DBusConnection.DBusConnection'
    -> b
    -- ^ /@message@/: a t'GI.Gio.Objects.DBusMessage.DBusMessage'
    -> [Gio.Flags.DBusSendMessageFlags]
    -- ^ /@flags@/: flags affecting how the message is sent
    -> m (Word32)
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
dBusConnectionSendMessage :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDBusConnection a, IsDBusMessage b) =>
a -> b -> [DBusSendMessageFlags] -> m Word32
dBusConnectionSendMessage a
connection b
message [DBusSendMessageFlags]
flags = IO Word32 -> m Word32
forall a. IO a -> m a
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
    connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    message' <- unsafeManagedPtrCastPtr message
    let flags' = [DBusSendMessageFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [DBusSendMessageFlags]
flags
    outSerial <- allocMem :: IO (Ptr Word32)
    onException (do
        _ <- propagateGError $ g_dbus_connection_send_message connection' message' flags' outSerial
        outSerial' <- peek outSerial
        touchManagedPtr connection
        touchManagedPtr message
        freeMem outSerial
        return outSerial'
     ) (do
        freeMem outSerial
     )

#if defined(ENABLE_OVERLOADING)
data DBusConnectionSendMessageMethodInfo
instance (signature ~ (b -> [Gio.Flags.DBusSendMessageFlags] -> m (Word32)), MonadIO m, IsDBusConnection a, Gio.DBusMessage.IsDBusMessage b) => O.OverloadedMethod DBusConnectionSendMessageMethodInfo a signature where
    overloadedMethod = dBusConnectionSendMessage

instance O.OverloadedMethodInfo DBusConnectionSendMessageMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusConnection.dBusConnectionSendMessage",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusConnection.html#v:dBusConnectionSendMessage"
        })


#endif

-- method DBusConnection::send_message_with_reply
-- 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
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "message"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusMessage" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDBusMessage" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "DBusSendMessageFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "flags affecting how the message is sent"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = 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
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "out_serial"
--           , argType = TBasicType TUInt32
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "return location for serial number assigned\n    to @message when sending it or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = 7
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = 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
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_connection_send_message_with_reply" g_dbus_connection_send_message_with_reply :: 
    Ptr DBusConnection ->                   -- connection : TInterface (Name {namespace = "Gio", name = "DBusConnection"})
    Ptr Gio.DBusMessage.DBusMessage ->      -- message : TInterface (Name {namespace = "Gio", name = "DBusMessage"})
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gio", name = "DBusSendMessageFlags"})
    Int32 ->                                -- timeout_msec : TBasicType TInt
    Ptr Word32 ->                           -- out_serial : TBasicType TUInt32
    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 sends /@message@/ to the peer represented by /@connection@/.
-- 
-- Unless /@flags@/ contain the
-- 'GI.Gio.Flags.DBusSendMessageFlagsPreserveSerial' flag, the serial number
-- will be assigned by /@connection@/ and set on /@message@/ via
-- 'GI.Gio.Objects.DBusMessage.dBusMessageSetSerial'. If /@outSerial@/ is not 'P.Nothing', then the
-- serial number used will be written to this location prior to
-- submitting the message to the underlying transport. While it has a @volatile@
-- qualifier, this is a historical artifact and the argument passed to it should
-- not be @volatile@.
-- 
-- 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 /@message@/ is not well-formed,
-- the operation fails with 'GI.Gio.Enums.IOErrorEnumInvalidArgument'.
-- 
-- 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.dBusConnectionSendMessageWithReplyFinish' to get the result of the operation.
-- See 'GI.Gio.Objects.DBusConnection.dBusConnectionSendMessageWithReplySync' for the synchronous version.
-- 
-- Note that /@message@/ must be unlocked, unless /@flags@/ contain the
-- 'GI.Gio.Flags.DBusSendMessageFlagsPreserveSerial' flag.
-- 
-- See this [server][gdbus-server] and [client][gdbus-unix-fd-client]
-- for an example of how to use this low-level API to send and receive
-- UNIX file descriptors.
-- 
-- /Since: 2.26/
dBusConnectionSendMessageWithReply ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusConnection a, Gio.DBusMessage.IsDBusMessage b, Gio.Cancellable.IsCancellable c) =>
    a
    -- ^ /@connection@/: a t'GI.Gio.Objects.DBusConnection.DBusConnection'
    -> b
    -- ^ /@message@/: a t'GI.Gio.Objects.DBusMessage.DBusMessage'
    -> [Gio.Flags.DBusSendMessageFlags]
    -- ^ /@flags@/: flags affecting how the message is sent
    -> Int32
    -- ^ /@timeoutMsec@/: the timeout in milliseconds, -1 to use the default
    --     timeout or @/G_MAXINT/@ for no timeout
    -> 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
    -> m (Word32)
dBusConnectionSendMessageWithReply :: forall (m :: * -> *) a b c.
(HasCallStack, MonadIO m, IsDBusConnection a, IsDBusMessage b,
 IsCancellable c) =>
a
-> b
-> [DBusSendMessageFlags]
-> Int32
-> Maybe c
-> Maybe AsyncReadyCallback
-> m Word32
dBusConnectionSendMessageWithReply a
connection b
message [DBusSendMessageFlags]
flags Int32
timeoutMsec Maybe c
cancellable Maybe AsyncReadyCallback
callback = IO Word32 -> m Word32
forall a. IO a -> m a
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
    connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    message' <- unsafeManagedPtrCastPtr message
    let flags' = [DBusSendMessageFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [DBusSendMessageFlags]
flags
    outSerial <- allocMem :: IO (Ptr Word32)
    maybeCancellable <- case cancellable of
        Maybe c
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
FP.nullPtr
        Just c
jCancellable -> do
            jCancellable' <- c -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jCancellable
            return jCancellable'
    maybeCallback <- case callback of
        Maybe AsyncReadyCallback
Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
forall a. FunPtr a
FP.nullFunPtr
        Just AsyncReadyCallback
jCallback -> do
            ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
            jCallback' <- Gio.Callbacks.mk_AsyncReadyCallback (Gio.Callbacks.wrap_AsyncReadyCallback (Just ptrcallback) (Gio.Callbacks.drop_closures_AsyncReadyCallback jCallback))
            poke ptrcallback jCallback'
            return jCallback'
    let userData = Ptr a
forall a. Ptr a
nullPtr
    g_dbus_connection_send_message_with_reply connection' message' flags' timeoutMsec outSerial maybeCancellable maybeCallback userData
    outSerial' <- peek outSerial
    touchManagedPtr connection
    touchManagedPtr message
    whenJust cancellable touchManagedPtr
    freeMem outSerial
    return outSerial'

#if defined(ENABLE_OVERLOADING)
data DBusConnectionSendMessageWithReplyMethodInfo
instance (signature ~ (b -> [Gio.Flags.DBusSendMessageFlags] -> Int32 -> Maybe (c) -> Maybe (Gio.Callbacks.AsyncReadyCallback) -> m (Word32)), MonadIO m, IsDBusConnection a, Gio.DBusMessage.IsDBusMessage b, Gio.Cancellable.IsCancellable c) => O.OverloadedMethod DBusConnectionSendMessageWithReplyMethodInfo a signature where
    overloadedMethod = dBusConnectionSendMessageWithReply

instance O.OverloadedMethodInfo DBusConnectionSendMessageWithReplyMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusConnection.dBusConnectionSendMessageWithReply",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusConnection.html#v:dBusConnectionSendMessageWithReply"
        })


#endif

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

foreign import ccall "g_dbus_connection_send_message_with_reply_finish" g_dbus_connection_send_message_with_reply_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 Gio.DBusMessage.DBusMessage)

-- | Finishes an operation started with 'GI.Gio.Objects.DBusConnection.dBusConnectionSendMessageWithReply'.
-- 
-- Note that /@error@/ is only set if a local in-process error
-- occurred. That is to say that the returned t'GI.Gio.Objects.DBusMessage.DBusMessage' object may
-- be of type 'GI.Gio.Enums.DBusMessageTypeError'. Use
-- 'GI.Gio.Objects.DBusMessage.dBusMessageToGerror' to transcode this to a t'GError'.
-- 
-- See this [server][gdbus-server] and [client][gdbus-unix-fd-client]
-- for an example of how to use this low-level API to send and receive
-- UNIX file descriptors.
-- 
-- /Since: 2.26/
dBusConnectionSendMessageWithReplyFinish ::
    (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.dBusConnectionSendMessageWithReply'
    -> m Gio.DBusMessage.DBusMessage
    -- ^ __Returns:__ a locked t'GI.Gio.Objects.DBusMessage.DBusMessage' or 'P.Nothing' if /@error@/ is set /(Can throw 'Data.GI.Base.GError.GError')/
dBusConnectionSendMessageWithReplyFinish :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDBusConnection a, IsAsyncResult b) =>
a -> b -> m DBusMessage
dBusConnectionSendMessageWithReplyFinish a
connection b
res = IO DBusMessage -> m DBusMessage
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DBusMessage -> m DBusMessage)
-> IO DBusMessage -> m DBusMessage
forall a b. (a -> b) -> a -> b
$ do
    connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    res' <- unsafeManagedPtrCastPtr res
    onException (do
        result <- propagateGError $ g_dbus_connection_send_message_with_reply_finish connection' res'
        checkUnexpectedReturnNULL "dBusConnectionSendMessageWithReplyFinish" result
        result' <- (wrapObject Gio.DBusMessage.DBusMessage) result
        touchManagedPtr connection
        touchManagedPtr res
        return result'
     ) (do
        return ()
     )

#if defined(ENABLE_OVERLOADING)
data DBusConnectionSendMessageWithReplyFinishMethodInfo
instance (signature ~ (b -> m Gio.DBusMessage.DBusMessage), MonadIO m, IsDBusConnection a, Gio.AsyncResult.IsAsyncResult b) => O.OverloadedMethod DBusConnectionSendMessageWithReplyFinishMethodInfo a signature where
    overloadedMethod = dBusConnectionSendMessageWithReplyFinish

instance O.OverloadedMethodInfo DBusConnectionSendMessageWithReplyFinishMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusConnection.dBusConnectionSendMessageWithReplyFinish",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusConnection.html#v:dBusConnectionSendMessageWithReplyFinish"
        })


#endif

-- method DBusConnection::send_message_with_reply_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
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "message"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusMessage" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDBusMessage" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "DBusSendMessageFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "flags affecting how the message is sent."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = 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
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "out_serial"
--           , argType = TBasicType TUInt32
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "return location for serial number\n    assigned to @message when sending it or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = 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
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "DBusMessage" })
-- throws : True
-- Skip return : False

foreign import ccall "g_dbus_connection_send_message_with_reply_sync" g_dbus_connection_send_message_with_reply_sync :: 
    Ptr DBusConnection ->                   -- connection : TInterface (Name {namespace = "Gio", name = "DBusConnection"})
    Ptr Gio.DBusMessage.DBusMessage ->      -- message : TInterface (Name {namespace = "Gio", name = "DBusMessage"})
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gio", name = "DBusSendMessageFlags"})
    Int32 ->                                -- timeout_msec : TBasicType TInt
    Ptr Word32 ->                           -- out_serial : TBasicType TUInt32
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Gio.DBusMessage.DBusMessage)

-- | Synchronously sends /@message@/ to the peer represented by /@connection@/
-- and blocks the calling thread until a reply is received or the
-- timeout is reached. See 'GI.Gio.Objects.DBusConnection.dBusConnectionSendMessageWithReply'
-- for the asynchronous version of this method.
-- 
-- Unless /@flags@/ contain the
-- 'GI.Gio.Flags.DBusSendMessageFlagsPreserveSerial' flag, the serial number
-- will be assigned by /@connection@/ and set on /@message@/ via
-- 'GI.Gio.Objects.DBusMessage.dBusMessageSetSerial'. If /@outSerial@/ is not 'P.Nothing', then the
-- serial number used will be written to this location prior to
-- submitting the message to the underlying transport. While it has a @volatile@
-- qualifier, this is a historical artifact and the argument passed to it should
-- not be @volatile@.
-- 
-- 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 /@message@/ is not well-formed,
-- the operation fails with 'GI.Gio.Enums.IOErrorEnumInvalidArgument'.
-- 
-- Note that /@error@/ is only set if a local in-process error
-- occurred. That is to say that the returned t'GI.Gio.Objects.DBusMessage.DBusMessage' object may
-- be of type 'GI.Gio.Enums.DBusMessageTypeError'. Use
-- 'GI.Gio.Objects.DBusMessage.dBusMessageToGerror' to transcode this to a t'GError'.
-- 
-- See this [server][gdbus-server] and [client][gdbus-unix-fd-client]
-- for an example of how to use this low-level API to send and receive
-- UNIX file descriptors.
-- 
-- Note that /@message@/ must be unlocked, unless /@flags@/ contain the
-- 'GI.Gio.Flags.DBusSendMessageFlagsPreserveSerial' flag.
-- 
-- /Since: 2.26/
dBusConnectionSendMessageWithReplySync ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusConnection a, Gio.DBusMessage.IsDBusMessage b, Gio.Cancellable.IsCancellable c) =>
    a
    -- ^ /@connection@/: a t'GI.Gio.Objects.DBusConnection.DBusConnection'
    -> b
    -- ^ /@message@/: a t'GI.Gio.Objects.DBusMessage.DBusMessage'
    -> [Gio.Flags.DBusSendMessageFlags]
    -- ^ /@flags@/: flags affecting how the message is sent.
    -> Int32
    -- ^ /@timeoutMsec@/: the timeout in milliseconds, -1 to use the default
    --     timeout or @/G_MAXINT/@ for no timeout
    -> Maybe (c)
    -- ^ /@cancellable@/: a t'GI.Gio.Objects.Cancellable.Cancellable' or 'P.Nothing'
    -> m ((Gio.DBusMessage.DBusMessage, Word32))
    -- ^ __Returns:__ a locked t'GI.Gio.Objects.DBusMessage.DBusMessage' that is the reply
    --     to /@message@/ or 'P.Nothing' if /@error@/ is set /(Can throw 'Data.GI.Base.GError.GError')/
dBusConnectionSendMessageWithReplySync :: forall (m :: * -> *) a b c.
(HasCallStack, MonadIO m, IsDBusConnection a, IsDBusMessage b,
 IsCancellable c) =>
a
-> b
-> [DBusSendMessageFlags]
-> Int32
-> Maybe c
-> m (DBusMessage, Word32)
dBusConnectionSendMessageWithReplySync a
connection b
message [DBusSendMessageFlags]
flags Int32
timeoutMsec Maybe c
cancellable = IO (DBusMessage, Word32) -> m (DBusMessage, Word32)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (DBusMessage, Word32) -> m (DBusMessage, Word32))
-> IO (DBusMessage, Word32) -> m (DBusMessage, Word32)
forall a b. (a -> b) -> a -> b
$ do
    connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    message' <- unsafeManagedPtrCastPtr message
    let flags' = [DBusSendMessageFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [DBusSendMessageFlags]
flags
    outSerial <- allocMem :: IO (Ptr Word32)
    maybeCancellable <- case cancellable of
        Maybe c
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
FP.nullPtr
        Just c
jCancellable -> do
            jCancellable' <- c -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jCancellable
            return jCancellable'
    onException (do
        result <- propagateGError $ g_dbus_connection_send_message_with_reply_sync connection' message' flags' timeoutMsec outSerial maybeCancellable
        checkUnexpectedReturnNULL "dBusConnectionSendMessageWithReplySync" result
        result' <- (wrapObject Gio.DBusMessage.DBusMessage) result
        outSerial' <- peek outSerial
        touchManagedPtr connection
        touchManagedPtr message
        whenJust cancellable touchManagedPtr
        freeMem outSerial
        return (result', outSerial')
     ) (do
        freeMem outSerial
     )

#if defined(ENABLE_OVERLOADING)
data DBusConnectionSendMessageWithReplySyncMethodInfo
instance (signature ~ (b -> [Gio.Flags.DBusSendMessageFlags] -> Int32 -> Maybe (c) -> m ((Gio.DBusMessage.DBusMessage, Word32))), MonadIO m, IsDBusConnection a, Gio.DBusMessage.IsDBusMessage b, Gio.Cancellable.IsCancellable c) => O.OverloadedMethod DBusConnectionSendMessageWithReplySyncMethodInfo a signature where
    overloadedMethod = dBusConnectionSendMessageWithReplySync

instance O.OverloadedMethodInfo DBusConnectionSendMessageWithReplySyncMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusConnection.dBusConnectionSendMessageWithReplySync",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusConnection.html#v:dBusConnectionSendMessageWithReplySync"
        })


#endif

-- method DBusConnection::set_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
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "exit_on_close"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "whether the process should be terminated\n    when @connection is closed by the remote peer"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

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

-- | Sets whether the process should be terminated when /@connection@/ is
-- closed by the remote peer. See [DBusConnection:exitOnClose]("GI.Gio.Objects.DBusConnection#g:attr:exitOnClose") for
-- more details.
-- 
-- Note that this function should be used with care. Most modern UNIX
-- desktops tie the notion of a user session with the session bus, and expect
-- all of a user\'s applications to quit when their bus connection goes away.
-- If you are setting /@exitOnClose@/ to 'P.False' for the shared session
-- bus connection, you should make sure that your application exits
-- when the user session ends.
-- 
-- /Since: 2.26/
dBusConnectionSetExitOnClose ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusConnection a) =>
    a
    -- ^ /@connection@/: a t'GI.Gio.Objects.DBusConnection.DBusConnection'
    -> Bool
    -- ^ /@exitOnClose@/: whether the process should be terminated
    --     when /@connection@/ is closed by the remote peer
    -> m ()
dBusConnectionSetExitOnClose :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusConnection a) =>
a -> Bool -> m ()
dBusConnectionSetExitOnClose a
connection Bool
exitOnClose = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    let exitOnClose' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
exitOnClose
    g_dbus_connection_set_exit_on_close connection' exitOnClose'
    touchManagedPtr connection
    return ()

#if defined(ENABLE_OVERLOADING)
data DBusConnectionSetExitOnCloseMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsDBusConnection a) => O.OverloadedMethod DBusConnectionSetExitOnCloseMethodInfo a signature where
    overloadedMethod = dBusConnectionSetExitOnClose

instance O.OverloadedMethodInfo DBusConnectionSetExitOnCloseMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusConnection.dBusConnectionSetExitOnClose",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusConnection.html#v:dBusConnectionSetExitOnClose"
        })


#endif

-- method DBusConnection::signal_subscribe
-- 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
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "sender"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "sender name to match on (unique or well-known name)\n    or %NULL to listen from all senders"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "interface_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "D-Bus interface name to match on or %NULL to\n    match on all interfaces"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "member"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "D-Bus signal name to match on or %NULL to match on\n    all signals"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "object_path"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "object path to match on or %NULL to match on\n    all object paths"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "arg0"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "contents of first string argument to match on or %NULL\n    to match on all kinds of arguments"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusSignalFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "#GDBusSignalFlags describing how arg0 is used in subscribing to the\n    signal"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "callback"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusSignalCallback" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "callback to invoke when there is a signal matching the requested data"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeNotified
--           , argClosure = 8
--           , argDestroy = 9
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "user data to pass to @callback"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data_free_func"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "DestroyNotify" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "function to free @user_data with when\n    subscription is removed or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt)
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_connection_signal_subscribe" g_dbus_connection_signal_subscribe :: 
    Ptr DBusConnection ->                   -- connection : TInterface (Name {namespace = "Gio", name = "DBusConnection"})
    CString ->                              -- sender : TBasicType TUTF8
    CString ->                              -- interface_name : TBasicType TUTF8
    CString ->                              -- member : TBasicType TUTF8
    CString ->                              -- object_path : TBasicType TUTF8
    CString ->                              -- arg0 : TBasicType TUTF8
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gio", name = "DBusSignalFlags"})
    FunPtr Gio.Callbacks.C_DBusSignalCallback -> -- callback : TInterface (Name {namespace = "Gio", name = "DBusSignalCallback"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    FunPtr GLib.Callbacks.C_DestroyNotify -> -- user_data_free_func : TInterface (Name {namespace = "GLib", name = "DestroyNotify"})
    IO Word32

-- | Subscribes to signals on /@connection@/ and invokes /@callback@/ whenever
-- the signal is received. Note that /@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.
-- 
-- If /@connection@/ is not a message bus connection, /@sender@/ must be
-- 'P.Nothing'.
-- 
-- If /@sender@/ is a well-known name note that /@callback@/ is invoked with
-- the unique name for the owner of /@sender@/, not the well-known name
-- as one would expect. This is because the message bus rewrites the
-- name. As such, to avoid certain race conditions, users should be
-- tracking the name owner of the well-known name and use that when
-- processing the received signal.
-- 
-- If one of 'GI.Gio.Flags.DBusSignalFlagsMatchArg0Namespace' or
-- 'GI.Gio.Flags.DBusSignalFlagsMatchArg0Path' are given, /@arg0@/ is
-- interpreted as part of a namespace or path.  The first argument
-- of a signal is matched against that part as specified by D-Bus.
-- 
-- 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
-- signal is unsubscribed from, and may be called after /@connection@/
-- has been destroyed.)
-- 
-- As /@callback@/ is potentially invoked in a different thread from where it’s
-- emitted, it’s possible for this to happen after
-- 'GI.Gio.Objects.DBusConnection.dBusConnectionSignalUnsubscribe' has been called in another thread.
-- Due to this, /@userData@/ should have a strong reference which is freed with
-- /@userDataFreeFunc@/, rather than pointing to data whose lifecycle is tied
-- to the signal subscription. For example, if a t'GI.GObject.Objects.Object.Object' is used to store the
-- subscription ID from 'GI.Gio.Objects.DBusConnection.dBusConnectionSignalSubscribe', a strong reference
-- to that t'GI.GObject.Objects.Object.Object' must be passed to /@userData@/, and 'GI.GObject.Objects.Object.objectUnref' passed to
-- /@userDataFreeFunc@/. You are responsible for breaking the resulting
-- reference count cycle by explicitly unsubscribing from the signal when
-- dropping the last external reference to the t'GI.GObject.Objects.Object.Object'. Alternatively, a weak
-- reference may be used.
-- 
-- It is guaranteed that if you unsubscribe from a signal using
-- 'GI.Gio.Objects.DBusConnection.dBusConnectionSignalUnsubscribe' from the same thread which made the
-- corresponding 'GI.Gio.Objects.DBusConnection.dBusConnectionSignalSubscribe' call, /@callback@/ will not
-- be invoked after 'GI.Gio.Objects.DBusConnection.dBusConnectionSignalUnsubscribe' returns.
-- 
-- The returned subscription identifier is an opaque value which is guaranteed
-- to never be zero.
-- 
-- This function can never fail.
-- 
-- /Since: 2.26/
dBusConnectionSignalSubscribe ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusConnection a) =>
    a
    -- ^ /@connection@/: a t'GI.Gio.Objects.DBusConnection.DBusConnection'
    -> Maybe (T.Text)
    -- ^ /@sender@/: sender name to match on (unique or well-known name)
    --     or 'P.Nothing' to listen from all senders
    -> Maybe (T.Text)
    -- ^ /@interfaceName@/: D-Bus interface name to match on or 'P.Nothing' to
    --     match on all interfaces
    -> Maybe (T.Text)
    -- ^ /@member@/: D-Bus signal name to match on or 'P.Nothing' to match on
    --     all signals
    -> Maybe (T.Text)
    -- ^ /@objectPath@/: object path to match on or 'P.Nothing' to match on
    --     all object paths
    -> Maybe (T.Text)
    -- ^ /@arg0@/: contents of first string argument to match on or 'P.Nothing'
    --     to match on all kinds of arguments
    -> [Gio.Flags.DBusSignalFlags]
    -- ^ /@flags@/: t'GI.Gio.Flags.DBusSignalFlags' describing how arg0 is used in subscribing to the
    --     signal
    -> Gio.Callbacks.DBusSignalCallback
    -- ^ /@callback@/: callback to invoke when there is a signal matching the requested data
    -> m Word32
    -- ^ __Returns:__ a subscription identifier that can be used with 'GI.Gio.Objects.DBusConnection.dBusConnectionSignalUnsubscribe'
dBusConnectionSignalSubscribe :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusConnection a) =>
a
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> [DBusSignalFlags]
-> DBusSignalCallback
-> m Word32
dBusConnectionSignalSubscribe a
connection Maybe Text
sender Maybe Text
interfaceName Maybe Text
member Maybe Text
objectPath Maybe Text
arg0 [DBusSignalFlags]
flags DBusSignalCallback
callback = IO Word32 -> m Word32
forall a. IO a -> m a
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
    connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    maybeSender <- case sender of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
FP.nullPtr
        Just Text
jSender -> do
            jSender' <- Text -> IO CString
textToCString Text
jSender
            return jSender'
    maybeInterfaceName <- case interfaceName of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
FP.nullPtr
        Just Text
jInterfaceName -> do
            jInterfaceName' <- Text -> IO CString
textToCString Text
jInterfaceName
            return jInterfaceName'
    maybeMember <- case member of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
FP.nullPtr
        Just Text
jMember -> do
            jMember' <- Text -> IO CString
textToCString Text
jMember
            return jMember'
    maybeObjectPath <- case objectPath of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
FP.nullPtr
        Just Text
jObjectPath -> do
            jObjectPath' <- Text -> IO CString
textToCString Text
jObjectPath
            return jObjectPath'
    maybeArg0 <- case arg0 of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
FP.nullPtr
        Just Text
jArg0 -> do
            jArg0' <- Text -> IO CString
textToCString Text
jArg0
            return jArg0'
    let flags' = [DBusSignalFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [DBusSignalFlags]
flags
    callback' <- Gio.Callbacks.mk_DBusSignalCallback (Gio.Callbacks.wrap_DBusSignalCallback Nothing (Gio.Callbacks.drop_closures_DBusSignalCallback callback))
    let userData = FunPtr C_DBusSignalCallback -> Ptr ()
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr C_DBusSignalCallback
callback'
    let userDataFreeFunc = FunPtr (Ptr a -> IO ())
forall a. FunPtr (Ptr a -> IO ())
SP.safeFreeFunPtrPtr
    result <- g_dbus_connection_signal_subscribe connection' maybeSender maybeInterfaceName maybeMember maybeObjectPath maybeArg0 flags' callback' userData userDataFreeFunc
    touchManagedPtr connection
    freeMem maybeSender
    freeMem maybeInterfaceName
    freeMem maybeMember
    freeMem maybeObjectPath
    freeMem maybeArg0
    return result

#if defined(ENABLE_OVERLOADING)
data DBusConnectionSignalSubscribeMethodInfo
instance (signature ~ (Maybe (T.Text) -> Maybe (T.Text) -> Maybe (T.Text) -> Maybe (T.Text) -> Maybe (T.Text) -> [Gio.Flags.DBusSignalFlags] -> Gio.Callbacks.DBusSignalCallback -> m Word32), MonadIO m, IsDBusConnection a) => O.OverloadedMethod DBusConnectionSignalSubscribeMethodInfo a signature where
    overloadedMethod = dBusConnectionSignalSubscribe

instance O.OverloadedMethodInfo DBusConnectionSignalSubscribeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusConnection.dBusConnectionSignalSubscribe",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusConnection.html#v:dBusConnectionSignalSubscribe"
        })


#endif

-- method DBusConnection::signal_unsubscribe
-- 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
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "subscription_id"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a subscription id obtained from\n    g_dbus_connection_signal_subscribe()"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

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

-- | Unsubscribes from signals.
-- 
-- Note that there may still be D-Bus traffic to process (relating to this
-- signal subscription) in the current thread-default t'GI.GLib.Structs.MainContext.MainContext' after this
-- function has returned. You should continue to iterate the t'GI.GLib.Structs.MainContext.MainContext'
-- until the t'GI.GLib.Callbacks.DestroyNotify' function passed to
-- 'GI.Gio.Objects.DBusConnection.dBusConnectionSignalSubscribe' is called, in order to avoid memory
-- leaks through callbacks queued on the t'GI.GLib.Structs.MainContext.MainContext' after it’s stopped being
-- iterated.
-- Alternatively, any idle source with a priority lower than 'GI.GLib.Constants.PRIORITY_DEFAULT'
-- that was scheduled after unsubscription, also indicates that all resources
-- of this subscription are released.
-- 
-- /Since: 2.26/
dBusConnectionSignalUnsubscribe ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusConnection a) =>
    a
    -- ^ /@connection@/: a t'GI.Gio.Objects.DBusConnection.DBusConnection'
    -> Word32
    -- ^ /@subscriptionId@/: a subscription id obtained from
    --     'GI.Gio.Objects.DBusConnection.dBusConnectionSignalSubscribe'
    -> m ()
dBusConnectionSignalUnsubscribe :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusConnection a) =>
a -> Word32 -> m ()
dBusConnectionSignalUnsubscribe a
connection Word32
subscriptionId = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    g_dbus_connection_signal_unsubscribe connection' subscriptionId
    touchManagedPtr connection
    return ()

#if defined(ENABLE_OVERLOADING)
data DBusConnectionSignalUnsubscribeMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsDBusConnection a) => O.OverloadedMethod DBusConnectionSignalUnsubscribeMethodInfo a signature where
    overloadedMethod = dBusConnectionSignalUnsubscribe

instance O.OverloadedMethodInfo DBusConnectionSignalUnsubscribeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusConnection.dBusConnectionSignalUnsubscribe",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusConnection.html#v:dBusConnectionSignalUnsubscribe"
        })


#endif

-- method DBusConnection::start_message_processing
-- 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
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

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

-- | If /@connection@/ was created with
-- 'GI.Gio.Flags.DBusConnectionFlagsDelayMessageProcessing', this method
-- starts processing messages. Does nothing on if /@connection@/ wasn\'t
-- created with this flag or if the method has already been called.
-- 
-- /Since: 2.26/
dBusConnectionStartMessageProcessing ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusConnection a) =>
    a
    -- ^ /@connection@/: a t'GI.Gio.Objects.DBusConnection.DBusConnection'
    -> m ()
dBusConnectionStartMessageProcessing :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusConnection a) =>
a -> m ()
dBusConnectionStartMessageProcessing a
connection = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    g_dbus_connection_start_message_processing connection'
    touchManagedPtr connection
    return ()

#if defined(ENABLE_OVERLOADING)
data DBusConnectionStartMessageProcessingMethodInfo
instance (signature ~ (m ()), MonadIO m, IsDBusConnection a) => O.OverloadedMethod DBusConnectionStartMessageProcessingMethodInfo a signature where
    overloadedMethod = dBusConnectionStartMessageProcessing

instance O.OverloadedMethodInfo DBusConnectionStartMessageProcessingMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusConnection.dBusConnectionStartMessageProcessing",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusConnection.html#v:dBusConnectionStartMessageProcessing"
        })


#endif

-- method DBusConnection::unexport_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
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "export_id"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the ID from g_dbus_connection_export_action_group()"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

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

-- | Reverses the effect of a previous call to
-- 'GI.Gio.Objects.DBusConnection.dBusConnectionExportActionGroup'.
-- 
-- It is an error to call this function with an ID that wasn\'t returned
-- from 'GI.Gio.Objects.DBusConnection.dBusConnectionExportActionGroup' or to call it with the
-- same ID more than once.
-- 
-- /Since: 2.32/
dBusConnectionUnexportActionGroup ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusConnection a) =>
    a
    -- ^ /@connection@/: a t'GI.Gio.Objects.DBusConnection.DBusConnection'
    -> Word32
    -- ^ /@exportId@/: the ID from 'GI.Gio.Objects.DBusConnection.dBusConnectionExportActionGroup'
    -> m ()
dBusConnectionUnexportActionGroup :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusConnection a) =>
a -> Word32 -> m ()
dBusConnectionUnexportActionGroup a
connection Word32
exportId = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    g_dbus_connection_unexport_action_group connection' exportId
    touchManagedPtr connection
    return ()

#if defined(ENABLE_OVERLOADING)
data DBusConnectionUnexportActionGroupMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsDBusConnection a) => O.OverloadedMethod DBusConnectionUnexportActionGroupMethodInfo a signature where
    overloadedMethod = dBusConnectionUnexportActionGroup

instance O.OverloadedMethodInfo DBusConnectionUnexportActionGroupMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusConnection.dBusConnectionUnexportActionGroup",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusConnection.html#v:dBusConnectionUnexportActionGroup"
        })


#endif

-- method DBusConnection::unexport_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
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "export_id"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the ID from g_dbus_connection_export_menu_model()"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

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

-- | Reverses the effect of a previous call to
-- 'GI.Gio.Objects.DBusConnection.dBusConnectionExportMenuModel'.
-- 
-- It is an error to call this function with an ID that wasn\'t returned
-- from 'GI.Gio.Objects.DBusConnection.dBusConnectionExportMenuModel' or to call it with the
-- same ID more than once.
-- 
-- /Since: 2.32/
dBusConnectionUnexportMenuModel ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusConnection a) =>
    a
    -- ^ /@connection@/: a t'GI.Gio.Objects.DBusConnection.DBusConnection'
    -> Word32
    -- ^ /@exportId@/: the ID from 'GI.Gio.Objects.DBusConnection.dBusConnectionExportMenuModel'
    -> m ()
dBusConnectionUnexportMenuModel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusConnection a) =>
a -> Word32 -> m ()
dBusConnectionUnexportMenuModel a
connection Word32
exportId = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    g_dbus_connection_unexport_menu_model connection' exportId
    touchManagedPtr connection
    return ()

#if defined(ENABLE_OVERLOADING)
data DBusConnectionUnexportMenuModelMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsDBusConnection a) => O.OverloadedMethod DBusConnectionUnexportMenuModelMethodInfo a signature where
    overloadedMethod = dBusConnectionUnexportMenuModel

instance O.OverloadedMethodInfo DBusConnectionUnexportMenuModelMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusConnection.dBusConnectionUnexportMenuModel",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusConnection.html#v:dBusConnectionUnexportMenuModel"
        })


#endif

-- method DBusConnection::unregister_object
-- 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
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "registration_id"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a registration id obtained from\n    g_dbus_connection_register_object()"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_connection_unregister_object" g_dbus_connection_unregister_object :: 
    Ptr DBusConnection ->                   -- connection : TInterface (Name {namespace = "Gio", name = "DBusConnection"})
    Word32 ->                               -- registration_id : TBasicType TUInt
    IO CInt

-- | Unregisters an object.
-- 
-- /Since: 2.26/
dBusConnectionUnregisterObject ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusConnection a) =>
    a
    -- ^ /@connection@/: a t'GI.Gio.Objects.DBusConnection.DBusConnection'
    -> Word32
    -- ^ /@registrationId@/: a registration id obtained from
    --     @/g_dbus_connection_register_object()/@
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the object was unregistered, 'P.False' otherwise
dBusConnectionUnregisterObject :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusConnection a) =>
a -> Word32 -> m Bool
dBusConnectionUnregisterObject a
connection Word32
registrationId = IO Bool -> m Bool
forall a. IO a -> m a
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
    connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    result <- g_dbus_connection_unregister_object connection' registrationId
    let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    touchManagedPtr connection
    return result'

#if defined(ENABLE_OVERLOADING)
data DBusConnectionUnregisterObjectMethodInfo
instance (signature ~ (Word32 -> m Bool), MonadIO m, IsDBusConnection a) => O.OverloadedMethod DBusConnectionUnregisterObjectMethodInfo a signature where
    overloadedMethod = dBusConnectionUnregisterObject

instance O.OverloadedMethodInfo DBusConnectionUnregisterObjectMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusConnection.dBusConnectionUnregisterObject",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusConnection.html#v:dBusConnectionUnregisterObject"
        })


#endif

-- method DBusConnection::unregister_subtree
-- 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
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "registration_id"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a subtree registration id obtained from\n    g_dbus_connection_register_subtree()"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_connection_unregister_subtree" g_dbus_connection_unregister_subtree :: 
    Ptr DBusConnection ->                   -- connection : TInterface (Name {namespace = "Gio", name = "DBusConnection"})
    Word32 ->                               -- registration_id : TBasicType TUInt
    IO CInt

-- | Unregisters a subtree.
-- 
-- /Since: 2.26/
dBusConnectionUnregisterSubtree ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusConnection a) =>
    a
    -- ^ /@connection@/: a t'GI.Gio.Objects.DBusConnection.DBusConnection'
    -> Word32
    -- ^ /@registrationId@/: a subtree registration id obtained from
    --     'GI.Gio.Objects.DBusConnection.dBusConnectionRegisterSubtree'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the subtree was unregistered, 'P.False' otherwise
dBusConnectionUnregisterSubtree :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusConnection a) =>
a -> Word32 -> m Bool
dBusConnectionUnregisterSubtree a
connection Word32
registrationId = IO Bool -> m Bool
forall a. IO a -> m a
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
    connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    result <- g_dbus_connection_unregister_subtree connection' registrationId
    let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    touchManagedPtr connection
    return result'

#if defined(ENABLE_OVERLOADING)
data DBusConnectionUnregisterSubtreeMethodInfo
instance (signature ~ (Word32 -> m Bool), MonadIO m, IsDBusConnection a) => O.OverloadedMethod DBusConnectionUnregisterSubtreeMethodInfo a signature where
    overloadedMethod = dBusConnectionUnregisterSubtree

instance O.OverloadedMethodInfo DBusConnectionUnregisterSubtreeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusConnection.dBusConnectionUnregisterSubtree",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusConnection.html#v:dBusConnectionUnregisterSubtree"
        })


#endif

-- method DBusConnection::new
-- method type : MemberFunction
-- 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
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "guid"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the GUID to use if authenticating as a server or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "callback"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncReadyCallback" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #GAsyncReadyCallback to call when the request is satisfied"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = 6
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = 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
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_connection_new" g_dbus_connection_new :: 
    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"})
    FunPtr Gio.Callbacks.C_AsyncReadyCallback -> -- callback : TInterface (Name {namespace = "Gio", name = "AsyncReadyCallback"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    IO ()

-- | Asynchronously 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.
-- 
-- When the operation is finished, /@callback@/ will be invoked. You can
-- then call 'GI.Gio.Objects.DBusConnection.dBusConnectionNewFinish' to get the result of the
-- operation.
-- 
-- This is an asynchronous failable constructor. See
-- 'GI.Gio.Objects.DBusConnection.dBusConnectionNewSync' for the synchronous
-- version.
-- 
-- /Since: 2.26/
dBusConnectionNew ::
    (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 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'
    -> Maybe (Gio.Callbacks.AsyncReadyCallback)
    -- ^ /@callback@/: a t'GI.Gio.Callbacks.AsyncReadyCallback' to call when the request is satisfied
    -> m ()
dBusConnectionNew :: forall (m :: * -> *) a b c.
(HasCallStack, MonadIO m, IsIOStream a, IsDBusAuthObserver b,
 IsCancellable c) =>
a
-> Maybe Text
-> [DBusConnectionFlags]
-> Maybe b
-> Maybe c
-> Maybe AsyncReadyCallback
-> m ()
dBusConnectionNew a
stream Maybe Text
guid [DBusConnectionFlags]
flags Maybe b
observer Maybe c
cancellable Maybe AsyncReadyCallback
callback = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    stream' <- a -> IO (Ptr IOStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
stream
    maybeGuid <- case guid of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
FP.nullPtr
        Just Text
jGuid -> do
            jGuid' <- Text -> IO CString
textToCString Text
jGuid
            return jGuid'
    let flags' = [DBusConnectionFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [DBusConnectionFlags]
flags
    maybeObserver <- case observer of
        Maybe b
Nothing -> Ptr DBusAuthObserver -> IO (Ptr DBusAuthObserver)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr DBusAuthObserver
forall a. Ptr a
FP.nullPtr
        Just b
jObserver -> do
            jObserver' <- b -> IO (Ptr DBusAuthObserver)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jObserver
            return jObserver'
    maybeCancellable <- case cancellable of
        Maybe c
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
FP.nullPtr
        Just c
jCancellable -> do
            jCancellable' <- c -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jCancellable
            return jCancellable'
    maybeCallback <- case callback of
        Maybe AsyncReadyCallback
Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
forall a. FunPtr a
FP.nullFunPtr
        Just AsyncReadyCallback
jCallback -> do
            ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
            jCallback' <- Gio.Callbacks.mk_AsyncReadyCallback (Gio.Callbacks.wrap_AsyncReadyCallback (Just ptrcallback) (Gio.Callbacks.drop_closures_AsyncReadyCallback jCallback))
            poke ptrcallback jCallback'
            return jCallback'
    let userData = Ptr a
forall a. Ptr a
nullPtr
    g_dbus_connection_new stream' maybeGuid flags' maybeObserver maybeCancellable maybeCallback userData
    touchManagedPtr stream
    whenJust observer touchManagedPtr
    whenJust cancellable touchManagedPtr
    freeMem maybeGuid
    return ()

#if defined(ENABLE_OVERLOADING)
#endif

-- method DBusConnection::new_for_address
-- method type : MemberFunction
-- 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "callback"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncReadyCallback" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #GAsyncReadyCallback to call when the request is satisfied"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = 5
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = 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
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_connection_new_for_address" g_dbus_connection_new_for_address :: 
    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"})
    FunPtr Gio.Callbacks.C_AsyncReadyCallback -> -- callback : TInterface (Name {namespace = "Gio", name = "AsyncReadyCallback"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    IO ()

-- | Asynchronously 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.dBusConnectionNew' if you need to act as the
-- server. In particular, /@flags@/ cannot contain the
-- 'GI.Gio.Flags.DBusConnectionFlagsAuthenticationServer',
-- 'GI.Gio.Flags.DBusConnectionFlagsAuthenticationAllowAnonymous' or
-- 'GI.Gio.Flags.DBusConnectionFlagsAuthenticationRequireSameUser' flags.
-- 
-- When the operation is finished, /@callback@/ will be invoked. You can
-- then call 'GI.Gio.Objects.DBusConnection.dBusConnectionNewForAddressFinish' to get the result of
-- the operation.
-- 
-- If /@observer@/ is not 'P.Nothing' it may be used to control the
-- authentication process.
-- 
-- This is an asynchronous failable constructor. See
-- 'GI.Gio.Objects.DBusConnection.dBusConnectionNewForAddressSync' for the synchronous
-- version.
-- 
-- /Since: 2.26/
dBusConnectionNewForAddress ::
    (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'
    -> Maybe (Gio.Callbacks.AsyncReadyCallback)
    -- ^ /@callback@/: a t'GI.Gio.Callbacks.AsyncReadyCallback' to call when the request is satisfied
    -> m ()
dBusConnectionNewForAddress :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDBusAuthObserver a, IsCancellable b) =>
Text
-> [DBusConnectionFlags]
-> Maybe a
-> Maybe b
-> Maybe AsyncReadyCallback
-> m ()
dBusConnectionNewForAddress Text
address [DBusConnectionFlags]
flags Maybe a
observer Maybe b
cancellable Maybe AsyncReadyCallback
callback = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    address' <- Text -> IO CString
textToCString Text
address
    let flags' = [DBusConnectionFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [DBusConnectionFlags]
flags
    maybeObserver <- case observer of
        Maybe a
Nothing -> Ptr DBusAuthObserver -> IO (Ptr DBusAuthObserver)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr DBusAuthObserver
forall a. Ptr a
FP.nullPtr
        Just a
jObserver -> do
            jObserver' <- a -> IO (Ptr DBusAuthObserver)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
jObserver
            return jObserver'
    maybeCancellable <- case cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
FP.nullPtr
        Just b
jCancellable -> do
            jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            return jCancellable'
    maybeCallback <- case callback of
        Maybe AsyncReadyCallback
Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
forall a. FunPtr a
FP.nullFunPtr
        Just AsyncReadyCallback
jCallback -> do
            ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
            jCallback' <- Gio.Callbacks.mk_AsyncReadyCallback (Gio.Callbacks.wrap_AsyncReadyCallback (Just ptrcallback) (Gio.Callbacks.drop_closures_AsyncReadyCallback jCallback))
            poke ptrcallback jCallback'
            return jCallback'
    let userData = Ptr a
forall a. Ptr a
nullPtr
    g_dbus_connection_new_for_address address' flags' maybeObserver maybeCancellable maybeCallback userData
    whenJust observer touchManagedPtr
    whenJust cancellable touchManagedPtr
    freeMem address'
    return ()

#if defined(ENABLE_OVERLOADING)
#endif