{- |
Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
License    : LGPL-2.1
Maintainer : Iñaki García Etxebarria (garetxe@gmail.com)
-}

module GI.Gio.Objects.DBusServer
    ( 

-- * Exported types
    DBusServer(..)                          ,
    DBusServerK                             ,
    toDBusServer                            ,
    noDBusServer                            ,


 -- * Methods
-- ** dBusServerGetClientAddress
    dBusServerGetClientAddress              ,


-- ** dBusServerGetFlags
    dBusServerGetFlags                      ,


-- ** dBusServerGetGuid
    dBusServerGetGuid                       ,


-- ** dBusServerIsActive
    dBusServerIsActive                      ,


-- ** dBusServerNewSync
    dBusServerNewSync                       ,


-- ** dBusServerStart
    dBusServerStart                         ,


-- ** dBusServerStop
    dBusServerStop                          ,




 -- * Properties
-- ** Active
    DBusServerActivePropertyInfo            ,
    getDBusServerActive                     ,


-- ** Address
    DBusServerAddressPropertyInfo           ,
    constructDBusServerAddress              ,
    getDBusServerAddress                    ,


-- ** AuthenticationObserver
    DBusServerAuthenticationObserverPropertyInfo,
    constructDBusServerAuthenticationObserver,
    getDBusServerAuthenticationObserver     ,


-- ** ClientAddress
    DBusServerClientAddressPropertyInfo     ,
    getDBusServerClientAddress              ,


-- ** Flags
    DBusServerFlagsPropertyInfo             ,
    constructDBusServerFlags                ,
    getDBusServerFlags                      ,


-- ** Guid
    DBusServerGuidPropertyInfo              ,
    constructDBusServerGuid                 ,
    getDBusServerGuid                       ,




 -- * Signals
-- ** NewConnection
    DBusServerNewConnectionCallback         ,
    DBusServerNewConnectionCallbackC        ,
    DBusServerNewConnectionSignalInfo       ,
    afterDBusServerNewConnection            ,
    dBusServerNewConnectionCallbackWrapper  ,
    dBusServerNewConnectionClosure          ,
    mkDBusServerNewConnectionCallback       ,
    noDBusServerNewConnectionCallback       ,
    onDBusServerNewConnection               ,




    ) where

import Prelude ()
import Data.GI.Base.ShortPrelude

import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map

import GI.Gio.Types
import GI.Gio.Callbacks
import qualified GI.GObject as GObject

newtype DBusServer = DBusServer (ForeignPtr DBusServer)
foreign import ccall "g_dbus_server_get_type"
    c_g_dbus_server_get_type :: IO GType

type instance ParentTypes DBusServer = DBusServerParentTypes
type DBusServerParentTypes = '[GObject.Object, Initable]

instance GObject DBusServer where
    gobjectIsInitiallyUnowned _ = False
    gobjectType _ = c_g_dbus_server_get_type
    

class GObject o => DBusServerK o
instance (GObject o, IsDescendantOf DBusServer o) => DBusServerK o

toDBusServer :: DBusServerK o => o -> IO DBusServer
toDBusServer = unsafeCastTo DBusServer

noDBusServer :: Maybe DBusServer
noDBusServer = Nothing

-- signal DBusServer::new-connection
type DBusServerNewConnectionCallback =
    DBusConnection ->
    IO Bool

noDBusServerNewConnectionCallback :: Maybe DBusServerNewConnectionCallback
noDBusServerNewConnectionCallback = Nothing

type DBusServerNewConnectionCallbackC =
    Ptr () ->                               -- object
    Ptr DBusConnection ->
    Ptr () ->                               -- user_data
    IO CInt

foreign import ccall "wrapper"
    mkDBusServerNewConnectionCallback :: DBusServerNewConnectionCallbackC -> IO (FunPtr DBusServerNewConnectionCallbackC)

dBusServerNewConnectionClosure :: DBusServerNewConnectionCallback -> IO Closure
dBusServerNewConnectionClosure cb = newCClosure =<< mkDBusServerNewConnectionCallback wrapped
    where wrapped = dBusServerNewConnectionCallbackWrapper cb

dBusServerNewConnectionCallbackWrapper ::
    DBusServerNewConnectionCallback ->
    Ptr () ->
    Ptr DBusConnection ->
    Ptr () ->
    IO CInt
dBusServerNewConnectionCallbackWrapper _cb _ connection _ = do
    connection' <- (newObject DBusConnection) connection
    result <- _cb  connection'
    let result' = (fromIntegral . fromEnum) result
    return result'

onDBusServerNewConnection :: (GObject a, MonadIO m) => a -> DBusServerNewConnectionCallback -> m SignalHandlerId
onDBusServerNewConnection obj cb = liftIO $ connectDBusServerNewConnection obj cb SignalConnectBefore
afterDBusServerNewConnection :: (GObject a, MonadIO m) => a -> DBusServerNewConnectionCallback -> m SignalHandlerId
afterDBusServerNewConnection obj cb = connectDBusServerNewConnection obj cb SignalConnectAfter

connectDBusServerNewConnection :: (GObject a, MonadIO m) =>
                                  a -> DBusServerNewConnectionCallback -> SignalConnectMode -> m SignalHandlerId
connectDBusServerNewConnection obj cb after = liftIO $ do
    cb' <- mkDBusServerNewConnectionCallback (dBusServerNewConnectionCallbackWrapper cb)
    connectSignalFunPtr obj "new-connection" cb' after

-- VVV Prop "active"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable]

getDBusServerActive :: (MonadIO m, DBusServerK o) => o -> m Bool
getDBusServerActive obj = liftIO $ getObjectPropertyBool obj "active"

data DBusServerActivePropertyInfo
instance AttrInfo DBusServerActivePropertyInfo where
    type AttrAllowedOps DBusServerActivePropertyInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint DBusServerActivePropertyInfo = (~) ()
    type AttrBaseTypeConstraint DBusServerActivePropertyInfo = DBusServerK
    type AttrGetType DBusServerActivePropertyInfo = Bool
    type AttrLabel DBusServerActivePropertyInfo = "DBusServer::active"
    attrGet _ = getDBusServerActive
    attrSet _ = undefined
    attrConstruct _ = undefined

-- VVV Prop "address"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]

getDBusServerAddress :: (MonadIO m, DBusServerK o) => o -> m T.Text
getDBusServerAddress obj = liftIO $ getObjectPropertyString obj "address"

constructDBusServerAddress :: T.Text -> IO ([Char], GValue)
constructDBusServerAddress val = constructObjectPropertyString "address" val

data DBusServerAddressPropertyInfo
instance AttrInfo DBusServerAddressPropertyInfo where
    type AttrAllowedOps DBusServerAddressPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint DBusServerAddressPropertyInfo = (~) T.Text
    type AttrBaseTypeConstraint DBusServerAddressPropertyInfo = DBusServerK
    type AttrGetType DBusServerAddressPropertyInfo = T.Text
    type AttrLabel DBusServerAddressPropertyInfo = "DBusServer::address"
    attrGet _ = getDBusServerAddress
    attrSet _ = undefined
    attrConstruct _ = constructDBusServerAddress

-- VVV Prop "authentication-observer"
   -- Type: TInterface "Gio" "DBusAuthObserver"
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]

getDBusServerAuthenticationObserver :: (MonadIO m, DBusServerK o) => o -> m DBusAuthObserver
getDBusServerAuthenticationObserver obj = liftIO $ getObjectPropertyObject obj "authentication-observer" DBusAuthObserver

constructDBusServerAuthenticationObserver :: (DBusAuthObserverK a) => a -> IO ([Char], GValue)
constructDBusServerAuthenticationObserver val = constructObjectPropertyObject "authentication-observer" val

data DBusServerAuthenticationObserverPropertyInfo
instance AttrInfo DBusServerAuthenticationObserverPropertyInfo where
    type AttrAllowedOps DBusServerAuthenticationObserverPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint DBusServerAuthenticationObserverPropertyInfo = DBusAuthObserverK
    type AttrBaseTypeConstraint DBusServerAuthenticationObserverPropertyInfo = DBusServerK
    type AttrGetType DBusServerAuthenticationObserverPropertyInfo = DBusAuthObserver
    type AttrLabel DBusServerAuthenticationObserverPropertyInfo = "DBusServer::authentication-observer"
    attrGet _ = getDBusServerAuthenticationObserver
    attrSet _ = undefined
    attrConstruct _ = constructDBusServerAuthenticationObserver

-- VVV Prop "client-address"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable]

getDBusServerClientAddress :: (MonadIO m, DBusServerK o) => o -> m T.Text
getDBusServerClientAddress obj = liftIO $ getObjectPropertyString obj "client-address"

data DBusServerClientAddressPropertyInfo
instance AttrInfo DBusServerClientAddressPropertyInfo where
    type AttrAllowedOps DBusServerClientAddressPropertyInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint DBusServerClientAddressPropertyInfo = (~) ()
    type AttrBaseTypeConstraint DBusServerClientAddressPropertyInfo = DBusServerK
    type AttrGetType DBusServerClientAddressPropertyInfo = T.Text
    type AttrLabel DBusServerClientAddressPropertyInfo = "DBusServer::client-address"
    attrGet _ = getDBusServerClientAddress
    attrSet _ = undefined
    attrConstruct _ = undefined

-- VVV Prop "flags"
   -- Type: TInterface "Gio" "DBusServerFlags"
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]

getDBusServerFlags :: (MonadIO m, DBusServerK o) => o -> m [DBusServerFlags]
getDBusServerFlags obj = liftIO $ getObjectPropertyFlags obj "flags"

constructDBusServerFlags :: [DBusServerFlags] -> IO ([Char], GValue)
constructDBusServerFlags val = constructObjectPropertyFlags "flags" val

data DBusServerFlagsPropertyInfo
instance AttrInfo DBusServerFlagsPropertyInfo where
    type AttrAllowedOps DBusServerFlagsPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint DBusServerFlagsPropertyInfo = (~) [DBusServerFlags]
    type AttrBaseTypeConstraint DBusServerFlagsPropertyInfo = DBusServerK
    type AttrGetType DBusServerFlagsPropertyInfo = [DBusServerFlags]
    type AttrLabel DBusServerFlagsPropertyInfo = "DBusServer::flags"
    attrGet _ = getDBusServerFlags
    attrSet _ = undefined
    attrConstruct _ = constructDBusServerFlags

-- VVV Prop "guid"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]

getDBusServerGuid :: (MonadIO m, DBusServerK o) => o -> m T.Text
getDBusServerGuid obj = liftIO $ getObjectPropertyString obj "guid"

constructDBusServerGuid :: T.Text -> IO ([Char], GValue)
constructDBusServerGuid val = constructObjectPropertyString "guid" val

data DBusServerGuidPropertyInfo
instance AttrInfo DBusServerGuidPropertyInfo where
    type AttrAllowedOps DBusServerGuidPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint DBusServerGuidPropertyInfo = (~) T.Text
    type AttrBaseTypeConstraint DBusServerGuidPropertyInfo = DBusServerK
    type AttrGetType DBusServerGuidPropertyInfo = T.Text
    type AttrLabel DBusServerGuidPropertyInfo = "DBusServer::guid"
    attrGet _ = getDBusServerGuid
    attrSet _ = undefined
    attrConstruct _ = constructDBusServerGuid

type instance AttributeList DBusServer = DBusServerAttributeList
type DBusServerAttributeList = ('[ '("active", DBusServerActivePropertyInfo), '("address", DBusServerAddressPropertyInfo), '("authentication-observer", DBusServerAuthenticationObserverPropertyInfo), '("client-address", DBusServerClientAddressPropertyInfo), '("flags", DBusServerFlagsPropertyInfo), '("guid", DBusServerGuidPropertyInfo)] :: [(Symbol, *)])

data DBusServerNewConnectionSignalInfo
instance SignalInfo DBusServerNewConnectionSignalInfo where
    type HaskellCallbackType DBusServerNewConnectionSignalInfo = DBusServerNewConnectionCallback
    connectSignal _ = connectDBusServerNewConnection

type instance SignalList DBusServer = DBusServerSignalList
type DBusServerSignalList = ('[ '("new-connection", DBusServerNewConnectionSignalInfo), '("notify", GObject.ObjectNotifySignalInfo), '("notify::[property]", GObjectNotifySignalInfo)] :: [(Symbol, *)])

-- method DBusServer::new_sync
-- method type : Constructor
-- Args : [Arg {argName = "address", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "flags", argType = TInterface "Gio" "DBusServerFlags", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "guid", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "observer", argType = TInterface "Gio" "DBusAuthObserver", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "address", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "flags", argType = TInterface "Gio" "DBusServerFlags", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "guid", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "observer", argType = TInterface "Gio" "DBusAuthObserver", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gio" "DBusServer"
-- throws : True
-- Skip return : False

foreign import ccall "g_dbus_server_new_sync" g_dbus_server_new_sync :: 
    CString ->                              -- address : TBasicType TUTF8
    CUInt ->                                -- flags : TInterface "Gio" "DBusServerFlags"
    CString ->                              -- guid : TBasicType TUTF8
    Ptr DBusAuthObserver ->                 -- observer : TInterface "Gio" "DBusAuthObserver"
    Ptr Cancellable ->                      -- cancellable : TInterface "Gio" "Cancellable"
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr DBusServer)


dBusServerNewSync ::
    (MonadIO m, DBusAuthObserverK a, CancellableK b) =>
    T.Text ->                               -- address
    [DBusServerFlags] ->                    -- flags
    T.Text ->                               -- guid
    Maybe (a) ->                            -- observer
    Maybe (b) ->                            -- cancellable
    m DBusServer
dBusServerNewSync address flags guid observer cancellable = liftIO $ do
    address' <- textToCString address
    let flags' = gflagsToWord flags
    guid' <- textToCString guid
    maybeObserver <- case observer of
        Nothing -> return nullPtr
        Just jObserver -> do
            let jObserver' = unsafeManagedPtrCastPtr jObserver
            return jObserver'
    maybeCancellable <- case cancellable of
        Nothing -> return nullPtr
        Just jCancellable -> do
            let jCancellable' = unsafeManagedPtrCastPtr jCancellable
            return jCancellable'
    onException (do
        result <- propagateGError $ g_dbus_server_new_sync address' flags' guid' maybeObserver maybeCancellable
        checkUnexpectedReturnNULL "g_dbus_server_new_sync" result
        result' <- (wrapObject DBusServer) result
        whenJust observer touchManagedPtr
        whenJust cancellable touchManagedPtr
        freeMem address'
        freeMem guid'
        return result'
     ) (do
        freeMem address'
        freeMem guid'
     )

-- method DBusServer::get_client_address
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "DBusServer", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "DBusServer", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_server_get_client_address" g_dbus_server_get_client_address :: 
    Ptr DBusServer ->                       -- _obj : TInterface "Gio" "DBusServer"
    IO CString


dBusServerGetClientAddress ::
    (MonadIO m, DBusServerK a) =>
    a ->                                    -- _obj
    m T.Text
dBusServerGetClientAddress _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- g_dbus_server_get_client_address _obj'
    checkUnexpectedReturnNULL "g_dbus_server_get_client_address" result
    result' <- cstringToText result
    touchManagedPtr _obj
    return result'

-- method DBusServer::get_flags
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "DBusServer", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "DBusServer", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gio" "DBusServerFlags"
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_server_get_flags" g_dbus_server_get_flags :: 
    Ptr DBusServer ->                       -- _obj : TInterface "Gio" "DBusServer"
    IO CUInt


dBusServerGetFlags ::
    (MonadIO m, DBusServerK a) =>
    a ->                                    -- _obj
    m [DBusServerFlags]
dBusServerGetFlags _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- g_dbus_server_get_flags _obj'
    let result' = wordToGFlags result
    touchManagedPtr _obj
    return result'

-- method DBusServer::get_guid
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "DBusServer", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "DBusServer", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_server_get_guid" g_dbus_server_get_guid :: 
    Ptr DBusServer ->                       -- _obj : TInterface "Gio" "DBusServer"
    IO CString


dBusServerGetGuid ::
    (MonadIO m, DBusServerK a) =>
    a ->                                    -- _obj
    m T.Text
dBusServerGetGuid _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- g_dbus_server_get_guid _obj'
    checkUnexpectedReturnNULL "g_dbus_server_get_guid" result
    result' <- cstringToText result
    touchManagedPtr _obj
    return result'

-- method DBusServer::is_active
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "DBusServer", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "DBusServer", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_server_is_active" g_dbus_server_is_active :: 
    Ptr DBusServer ->                       -- _obj : TInterface "Gio" "DBusServer"
    IO CInt


dBusServerIsActive ::
    (MonadIO m, DBusServerK a) =>
    a ->                                    -- _obj
    m Bool
dBusServerIsActive _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- g_dbus_server_is_active _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

-- method DBusServer::start
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "DBusServer", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "DBusServer", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_server_start" g_dbus_server_start :: 
    Ptr DBusServer ->                       -- _obj : TInterface "Gio" "DBusServer"
    IO ()


dBusServerStart ::
    (MonadIO m, DBusServerK a) =>
    a ->                                    -- _obj
    m ()
dBusServerStart _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    g_dbus_server_start _obj'
    touchManagedPtr _obj
    return ()

-- method DBusServer::stop
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "DBusServer", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "DBusServer", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_server_stop" g_dbus_server_stop :: 
    Ptr DBusServer ->                       -- _obj : TInterface "Gio" "DBusServer"
    IO ()


dBusServerStop ::
    (MonadIO m, DBusServerK a) =>
    a ->                                    -- _obj
    m ()
dBusServerStop _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    g_dbus_server_stop _obj'
    touchManagedPtr _obj
    return ()