{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- t'GI.Gio.Objects.DBusObjectManagerServer.DBusObjectManagerServer' is used to export t'GI.Gio.Interfaces.DBusObject.DBusObject' instances using
-- the standardized
-- <http://dbus.freedesktop.org/doc/dbus-specification.html#standard-interfaces-objectmanager org.freedesktop.DBus.ObjectManager>
-- interface. For example, remote D-Bus clients can get all objects
-- and properties in a single call. Additionally, any change in the
-- object hierarchy is broadcast using signals. This means that D-Bus
-- clients can keep caches up to date by only listening to D-Bus
-- signals.
-- 
-- The recommended path to export an object manager at is the path form of the
-- well-known name of a D-Bus service, or below. For example, if a D-Bus service
-- is available at the well-known name @net.example.ExampleService1@, the object
-- manager should typically be exported at @\/net\/example\/ExampleService1@, or
-- below (to allow for multiple object managers in a service).
-- 
-- It is supported, but not recommended, to export an object manager at the root
-- path, @\/@.
-- 
-- See t'GI.Gio.Objects.DBusObjectManagerClient.DBusObjectManagerClient' for the client-side code that is
-- intended to be used with t'GI.Gio.Objects.DBusObjectManagerServer.DBusObjectManagerServer' or any D-Bus
-- object implementing the org.freedesktop.DBus.ObjectManager
-- interface.
-- 
-- /Since: 2.30/

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

module GI.Gio.Objects.DBusObjectManagerServer
    ( 

-- * Exported types
    DBusObjectManagerServer(..)             ,
    IsDBusObjectManagerServer               ,
    toDBusObjectManagerServer               ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [export]("GI.Gio.Objects.DBusObjectManagerServer#g:method:export"), [exportUniquely]("GI.Gio.Objects.DBusObjectManagerServer#g:method:exportUniquely"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isExported]("GI.Gio.Objects.DBusObjectManagerServer#g:method:isExported"), [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"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unexport]("GI.Gio.Objects.DBusObjectManagerServer#g:method:unexport"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getConnection]("GI.Gio.Objects.DBusObjectManagerServer#g:method:getConnection"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getInterface]("GI.Gio.Interfaces.DBusObjectManager#g:method:getInterface"), [getObject]("GI.Gio.Interfaces.DBusObjectManager#g:method:getObject"), [getObjectPath]("GI.Gio.Interfaces.DBusObjectManager#g:method:getObjectPath"), [getObjects]("GI.Gio.Interfaces.DBusObjectManager#g:method:getObjects"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata").
-- 
-- ==== Setters
-- [setConnection]("GI.Gio.Objects.DBusObjectManagerServer#g:method:setConnection"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveDBusObjectManagerServerMethod    ,
#endif

-- ** export #method:export#

#if defined(ENABLE_OVERLOADING)
    DBusObjectManagerServerExportMethodInfo ,
#endif
    dBusObjectManagerServerExport           ,


-- ** exportUniquely #method:exportUniquely#

#if defined(ENABLE_OVERLOADING)
    DBusObjectManagerServerExportUniquelyMethodInfo,
#endif
    dBusObjectManagerServerExportUniquely   ,


-- ** getConnection #method:getConnection#

#if defined(ENABLE_OVERLOADING)
    DBusObjectManagerServerGetConnectionMethodInfo,
#endif
    dBusObjectManagerServerGetConnection    ,


-- ** isExported #method:isExported#

#if defined(ENABLE_OVERLOADING)
    DBusObjectManagerServerIsExportedMethodInfo,
#endif
    dBusObjectManagerServerIsExported       ,


-- ** new #method:new#

    dBusObjectManagerServerNew              ,


-- ** setConnection #method:setConnection#

#if defined(ENABLE_OVERLOADING)
    DBusObjectManagerServerSetConnectionMethodInfo,
#endif
    dBusObjectManagerServerSetConnection    ,


-- ** unexport #method:unexport#

#if defined(ENABLE_OVERLOADING)
    DBusObjectManagerServerUnexportMethodInfo,
#endif
    dBusObjectManagerServerUnexport         ,




 -- * Properties


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

#if defined(ENABLE_OVERLOADING)
    DBusObjectManagerServerConnectionPropertyInfo,
#endif
    clearDBusObjectManagerServerConnection  ,
    constructDBusObjectManagerServerConnection,
#if defined(ENABLE_OVERLOADING)
    dBusObjectManagerServerConnection       ,
#endif
    getDBusObjectManagerServerConnection    ,
    setDBusObjectManagerServerConnection    ,


-- ** objectPath #attr:objectPath#
-- | The object path to register the manager object at.
-- 
-- /Since: 2.30/

#if defined(ENABLE_OVERLOADING)
    DBusObjectManagerServerObjectPathPropertyInfo,
#endif
    constructDBusObjectManagerServerObjectPath,
#if defined(ENABLE_OVERLOADING)
    dBusObjectManagerServerObjectPath       ,
#endif
    getDBusObjectManagerServerObjectPath    ,




    ) 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.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.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R

import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gio.Interfaces.DBusObjectManager as Gio.DBusObjectManager
import {-# SOURCE #-} qualified GI.Gio.Objects.DBusConnection as Gio.DBusConnection
import {-# SOURCE #-} qualified GI.Gio.Objects.DBusObjectSkeleton as Gio.DBusObjectSkeleton

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

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

foreign import ccall "g_dbus_object_manager_server_get_type"
    c_g_dbus_object_manager_server_get_type :: IO B.Types.GType

instance B.Types.TypedObject DBusObjectManagerServer where
    glibType :: IO GType
glibType = IO GType
c_g_dbus_object_manager_server_get_type

instance B.Types.GObject DBusObjectManagerServer

-- | Type class for types which can be safely cast to `DBusObjectManagerServer`, for instance with `toDBusObjectManagerServer`.
class (SP.GObject o, O.IsDescendantOf DBusObjectManagerServer o) => IsDBusObjectManagerServer o
instance (SP.GObject o, O.IsDescendantOf DBusObjectManagerServer o) => IsDBusObjectManagerServer o

instance O.HasParentTypes DBusObjectManagerServer
type instance O.ParentTypes DBusObjectManagerServer = '[GObject.Object.Object, Gio.DBusObjectManager.DBusObjectManager]

-- | Cast to `DBusObjectManagerServer`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toDBusObjectManagerServer :: (MIO.MonadIO m, IsDBusObjectManagerServer o) => o -> m DBusObjectManagerServer
toDBusObjectManagerServer :: forall (m :: * -> *) o.
(MonadIO m, IsDBusObjectManagerServer o) =>
o -> m DBusObjectManagerServer
toDBusObjectManagerServer = IO DBusObjectManagerServer -> m DBusObjectManagerServer
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO DBusObjectManagerServer -> m DBusObjectManagerServer)
-> (o -> IO DBusObjectManagerServer)
-> o
-> m DBusObjectManagerServer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr DBusObjectManagerServer -> DBusObjectManagerServer)
-> o -> IO DBusObjectManagerServer
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr DBusObjectManagerServer -> DBusObjectManagerServer
DBusObjectManagerServer

-- | Convert 'DBusObjectManagerServer' 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 DBusObjectManagerServer) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_g_dbus_object_manager_server_get_type
    gvalueSet_ :: Ptr GValue -> Maybe DBusObjectManagerServer -> IO ()
gvalueSet_ Ptr GValue
gv Maybe DBusObjectManagerServer
P.Nothing = Ptr GValue -> Ptr DBusObjectManagerServer -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr DBusObjectManagerServer
forall a. Ptr a
FP.nullPtr :: FP.Ptr DBusObjectManagerServer)
    gvalueSet_ Ptr GValue
gv (P.Just DBusObjectManagerServer
obj) = DBusObjectManagerServer
-> (Ptr DBusObjectManagerServer -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr DBusObjectManagerServer
obj (Ptr GValue -> Ptr DBusObjectManagerServer -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe DBusObjectManagerServer)
gvalueGet_ Ptr GValue
gv = do
        Ptr DBusObjectManagerServer
ptr <- Ptr GValue -> IO (Ptr DBusObjectManagerServer)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr DBusObjectManagerServer)
        if Ptr DBusObjectManagerServer
ptr Ptr DBusObjectManagerServer -> Ptr DBusObjectManagerServer -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr DBusObjectManagerServer
forall a. Ptr a
FP.nullPtr
        then DBusObjectManagerServer -> Maybe DBusObjectManagerServer
forall a. a -> Maybe a
P.Just (DBusObjectManagerServer -> Maybe DBusObjectManagerServer)
-> IO DBusObjectManagerServer -> IO (Maybe DBusObjectManagerServer)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr DBusObjectManagerServer -> DBusObjectManagerServer)
-> Ptr DBusObjectManagerServer -> IO DBusObjectManagerServer
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr DBusObjectManagerServer -> DBusObjectManagerServer
DBusObjectManagerServer Ptr DBusObjectManagerServer
ptr
        else Maybe DBusObjectManagerServer -> IO (Maybe DBusObjectManagerServer)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe DBusObjectManagerServer
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveDBusObjectManagerServerMethod (t :: Symbol) (o :: *) :: * where
    ResolveDBusObjectManagerServerMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveDBusObjectManagerServerMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveDBusObjectManagerServerMethod "export" o = DBusObjectManagerServerExportMethodInfo
    ResolveDBusObjectManagerServerMethod "exportUniquely" o = DBusObjectManagerServerExportUniquelyMethodInfo
    ResolveDBusObjectManagerServerMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveDBusObjectManagerServerMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveDBusObjectManagerServerMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveDBusObjectManagerServerMethod "isExported" o = DBusObjectManagerServerIsExportedMethodInfo
    ResolveDBusObjectManagerServerMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveDBusObjectManagerServerMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveDBusObjectManagerServerMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveDBusObjectManagerServerMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveDBusObjectManagerServerMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveDBusObjectManagerServerMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveDBusObjectManagerServerMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveDBusObjectManagerServerMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveDBusObjectManagerServerMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveDBusObjectManagerServerMethod "unexport" o = DBusObjectManagerServerUnexportMethodInfo
    ResolveDBusObjectManagerServerMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveDBusObjectManagerServerMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveDBusObjectManagerServerMethod "getConnection" o = DBusObjectManagerServerGetConnectionMethodInfo
    ResolveDBusObjectManagerServerMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveDBusObjectManagerServerMethod "getInterface" o = Gio.DBusObjectManager.DBusObjectManagerGetInterfaceMethodInfo
    ResolveDBusObjectManagerServerMethod "getObject" o = Gio.DBusObjectManager.DBusObjectManagerGetObjectMethodInfo
    ResolveDBusObjectManagerServerMethod "getObjectPath" o = Gio.DBusObjectManager.DBusObjectManagerGetObjectPathMethodInfo
    ResolveDBusObjectManagerServerMethod "getObjects" o = Gio.DBusObjectManager.DBusObjectManagerGetObjectsMethodInfo
    ResolveDBusObjectManagerServerMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveDBusObjectManagerServerMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveDBusObjectManagerServerMethod "setConnection" o = DBusObjectManagerServerSetConnectionMethodInfo
    ResolveDBusObjectManagerServerMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveDBusObjectManagerServerMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveDBusObjectManagerServerMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveDBusObjectManagerServerMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveDBusObjectManagerServerMethod t DBusObjectManagerServer, O.OverloadedMethod info DBusObjectManagerServer p) => OL.IsLabel t (DBusObjectManagerServer -> 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 ~ ResolveDBusObjectManagerServerMethod t DBusObjectManagerServer, O.OverloadedMethod info DBusObjectManagerServer p, R.HasField t DBusObjectManagerServer p) => R.HasField t DBusObjectManagerServer p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveDBusObjectManagerServerMethod t DBusObjectManagerServer, O.OverloadedMethodInfo info DBusObjectManagerServer) => OL.IsLabel t (O.MethodProxy info DBusObjectManagerServer) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif

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

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

-- | Set the value of the “@connection@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' dBusObjectManagerServer [ #connection 'Data.GI.Base.Attributes.:=' value ]
-- @
setDBusObjectManagerServerConnection :: (MonadIO m, IsDBusObjectManagerServer o, Gio.DBusConnection.IsDBusConnection a) => o -> a -> m ()
setDBusObjectManagerServerConnection :: forall (m :: * -> *) o a.
(MonadIO m, IsDBusObjectManagerServer o, IsDBusConnection a) =>
o -> a -> m ()
setDBusObjectManagerServerConnection o
obj a
val = IO () -> m ()
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 -> Maybe a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"connection" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)

-- | Construct a `GValueConstruct` with valid value for the “@connection@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDBusObjectManagerServerConnection :: (IsDBusObjectManagerServer o, MIO.MonadIO m, Gio.DBusConnection.IsDBusConnection a) => a -> m (GValueConstruct o)
constructDBusObjectManagerServerConnection :: forall o (m :: * -> *) a.
(IsDBusObjectManagerServer o, MonadIO m, IsDBusConnection a) =>
a -> m (GValueConstruct o)
constructDBusObjectManagerServerConnection a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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
"connection" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

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

#if defined(ENABLE_OVERLOADING)
data DBusObjectManagerServerConnectionPropertyInfo
instance AttrInfo DBusObjectManagerServerConnectionPropertyInfo where
    type AttrAllowedOps DBusObjectManagerServerConnectionPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DBusObjectManagerServerConnectionPropertyInfo = IsDBusObjectManagerServer
    type AttrSetTypeConstraint DBusObjectManagerServerConnectionPropertyInfo = Gio.DBusConnection.IsDBusConnection
    type AttrTransferTypeConstraint DBusObjectManagerServerConnectionPropertyInfo = Gio.DBusConnection.IsDBusConnection
    type AttrTransferType DBusObjectManagerServerConnectionPropertyInfo = Gio.DBusConnection.DBusConnection
    type AttrGetType DBusObjectManagerServerConnectionPropertyInfo = (Maybe Gio.DBusConnection.DBusConnection)
    type AttrLabel DBusObjectManagerServerConnectionPropertyInfo = "connection"
    type AttrOrigin DBusObjectManagerServerConnectionPropertyInfo = DBusObjectManagerServer
    attrGet = getDBusObjectManagerServerConnection
    attrSet = setDBusObjectManagerServerConnection
    attrTransfer _ v = do
        unsafeCastTo Gio.DBusConnection.DBusConnection v
    attrConstruct = constructDBusObjectManagerServerConnection
    attrClear = clearDBusObjectManagerServerConnection
#endif

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

-- | Get the value of the “@object-path@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dBusObjectManagerServer #objectPath
-- @
getDBusObjectManagerServerObjectPath :: (MonadIO m, IsDBusObjectManagerServer o) => o -> m (Maybe T.Text)
getDBusObjectManagerServerObjectPath :: forall (m :: * -> *) o.
(MonadIO m, IsDBusObjectManagerServer o) =>
o -> m (Maybe Text)
getDBusObjectManagerServerObjectPath o
obj = IO (Maybe Text) -> m (Maybe Text)
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
"object-path"

-- | Construct a `GValueConstruct` with valid value for the “@object-path@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDBusObjectManagerServerObjectPath :: (IsDBusObjectManagerServer o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructDBusObjectManagerServerObjectPath :: forall o (m :: * -> *).
(IsDBusObjectManagerServer o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructDBusObjectManagerServerObjectPath Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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
"object-path" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

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

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DBusObjectManagerServer
type instance O.AttributeList DBusObjectManagerServer = DBusObjectManagerServerAttributeList
type DBusObjectManagerServerAttributeList = ('[ '("connection", DBusObjectManagerServerConnectionPropertyInfo), '("objectPath", DBusObjectManagerServerObjectPathPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
dBusObjectManagerServerConnection :: AttrLabelProxy "connection"
dBusObjectManagerServerConnection = AttrLabelProxy

dBusObjectManagerServerObjectPath :: AttrLabelProxy "objectPath"
dBusObjectManagerServerObjectPath = AttrLabelProxy

#endif

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

#endif

-- method DBusObjectManagerServer::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "object_path"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "The object path to export the manager object at."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Gio" , name = "DBusObjectManagerServer" })
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_object_manager_server_new" g_dbus_object_manager_server_new :: 
    CString ->                              -- object_path : TBasicType TUTF8
    IO (Ptr DBusObjectManagerServer)

-- | Creates a new t'GI.Gio.Objects.DBusObjectManagerServer.DBusObjectManagerServer' object.
-- 
-- The returned server isn\'t yet exported on any connection. To do so,
-- use 'GI.Gio.Objects.DBusObjectManagerServer.dBusObjectManagerServerSetConnection'. Normally you
-- want to export all of your objects before doing so to avoid
-- <http://dbus.freedesktop.org/doc/dbus-specification.html#standard-interfaces-objectmanager InterfacesAdded>
-- signals being emitted.
-- 
-- /Since: 2.30/
dBusObjectManagerServerNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@objectPath@/: The object path to export the manager object at.
    -> m DBusObjectManagerServer
    -- ^ __Returns:__ A t'GI.Gio.Objects.DBusObjectManagerServer.DBusObjectManagerServer' object. Free with 'GI.GObject.Objects.Object.objectUnref'.
dBusObjectManagerServerNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> m DBusObjectManagerServer
dBusObjectManagerServerNew Text
objectPath = IO DBusObjectManagerServer -> m DBusObjectManagerServer
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DBusObjectManagerServer -> m DBusObjectManagerServer)
-> IO DBusObjectManagerServer -> m DBusObjectManagerServer
forall a b. (a -> b) -> a -> b
$ do
    CString
objectPath' <- Text -> IO CString
textToCString Text
objectPath
    Ptr DBusObjectManagerServer
result <- CString -> IO (Ptr DBusObjectManagerServer)
g_dbus_object_manager_server_new CString
objectPath'
    Text -> Ptr DBusObjectManagerServer -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"dBusObjectManagerServerNew" Ptr DBusObjectManagerServer
result
    DBusObjectManagerServer
result' <- ((ManagedPtr DBusObjectManagerServer -> DBusObjectManagerServer)
-> Ptr DBusObjectManagerServer -> IO DBusObjectManagerServer
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr DBusObjectManagerServer -> DBusObjectManagerServer
DBusObjectManagerServer) Ptr DBusObjectManagerServer
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
objectPath'
    DBusObjectManagerServer -> IO DBusObjectManagerServer
forall (m :: * -> *) a. Monad m => a -> m a
return DBusObjectManagerServer
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method DBusObjectManagerServer::export
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "manager"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "DBusObjectManagerServer" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusObjectManagerServer."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "object"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusObjectSkeleton" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusObjectSkeleton."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_object_manager_server_export" g_dbus_object_manager_server_export :: 
    Ptr DBusObjectManagerServer ->          -- manager : TInterface (Name {namespace = "Gio", name = "DBusObjectManagerServer"})
    Ptr Gio.DBusObjectSkeleton.DBusObjectSkeleton -> -- object : TInterface (Name {namespace = "Gio", name = "DBusObjectSkeleton"})
    IO ()

-- | Exports /@object@/ on /@manager@/.
-- 
-- If there is already a t'GI.Gio.Interfaces.DBusObject.DBusObject' exported at the object path,
-- then the old object is removed.
-- 
-- The object path for /@object@/ must be in the hierarchy rooted by the
-- object path for /@manager@/.
-- 
-- Note that /@manager@/ will take a reference on /@object@/ for as long as
-- it is exported.
-- 
-- /Since: 2.30/
dBusObjectManagerServerExport ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusObjectManagerServer a, Gio.DBusObjectSkeleton.IsDBusObjectSkeleton b) =>
    a
    -- ^ /@manager@/: A t'GI.Gio.Objects.DBusObjectManagerServer.DBusObjectManagerServer'.
    -> b
    -- ^ /@object@/: A t'GI.Gio.Objects.DBusObjectSkeleton.DBusObjectSkeleton'.
    -> m ()
dBusObjectManagerServerExport :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDBusObjectManagerServer a,
 IsDBusObjectSkeleton b) =>
a -> b -> m ()
dBusObjectManagerServerExport a
manager b
object = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusObjectManagerServer
manager' <- a -> IO (Ptr DBusObjectManagerServer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
    Ptr DBusObjectSkeleton
object' <- b -> IO (Ptr DBusObjectSkeleton)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
object
    Ptr DBusObjectManagerServer -> Ptr DBusObjectSkeleton -> IO ()
g_dbus_object_manager_server_export Ptr DBusObjectManagerServer
manager' Ptr DBusObjectSkeleton
object'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
manager
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
object
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DBusObjectManagerServerExportMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsDBusObjectManagerServer a, Gio.DBusObjectSkeleton.IsDBusObjectSkeleton b) => O.OverloadedMethod DBusObjectManagerServerExportMethodInfo a signature where
    overloadedMethod = dBusObjectManagerServerExport

instance O.OverloadedMethodInfo DBusObjectManagerServerExportMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Objects.DBusObjectManagerServer.dBusObjectManagerServerExport",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Objects-DBusObjectManagerServer.html#v:dBusObjectManagerServerExport"
        }


#endif

-- method DBusObjectManagerServer::export_uniquely
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "manager"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "DBusObjectManagerServer" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusObjectManagerServer."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "object"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusObjectSkeleton" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An object." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_object_manager_server_export_uniquely" g_dbus_object_manager_server_export_uniquely :: 
    Ptr DBusObjectManagerServer ->          -- manager : TInterface (Name {namespace = "Gio", name = "DBusObjectManagerServer"})
    Ptr Gio.DBusObjectSkeleton.DBusObjectSkeleton -> -- object : TInterface (Name {namespace = "Gio", name = "DBusObjectSkeleton"})
    IO ()

-- | Like 'GI.Gio.Objects.DBusObjectManagerServer.dBusObjectManagerServerExport' but appends a string of
-- the form _N (with N being a natural number) to /@object@/\'s object path
-- if an object with the given path already exists. As such, the
-- t'GI.Gio.Objects.DBusObjectProxy.DBusObjectProxy':@/g-object-path/@ property of /@object@/ may be modified.
-- 
-- /Since: 2.30/
dBusObjectManagerServerExportUniquely ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusObjectManagerServer a, Gio.DBusObjectSkeleton.IsDBusObjectSkeleton b) =>
    a
    -- ^ /@manager@/: A t'GI.Gio.Objects.DBusObjectManagerServer.DBusObjectManagerServer'.
    -> b
    -- ^ /@object@/: An object.
    -> m ()
dBusObjectManagerServerExportUniquely :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDBusObjectManagerServer a,
 IsDBusObjectSkeleton b) =>
a -> b -> m ()
dBusObjectManagerServerExportUniquely a
manager b
object = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusObjectManagerServer
manager' <- a -> IO (Ptr DBusObjectManagerServer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
    Ptr DBusObjectSkeleton
object' <- b -> IO (Ptr DBusObjectSkeleton)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
object
    Ptr DBusObjectManagerServer -> Ptr DBusObjectSkeleton -> IO ()
g_dbus_object_manager_server_export_uniquely Ptr DBusObjectManagerServer
manager' Ptr DBusObjectSkeleton
object'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
manager
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
object
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DBusObjectManagerServerExportUniquelyMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsDBusObjectManagerServer a, Gio.DBusObjectSkeleton.IsDBusObjectSkeleton b) => O.OverloadedMethod DBusObjectManagerServerExportUniquelyMethodInfo a signature where
    overloadedMethod = dBusObjectManagerServerExportUniquely

instance O.OverloadedMethodInfo DBusObjectManagerServerExportUniquelyMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Objects.DBusObjectManagerServer.dBusObjectManagerServerExportUniquely",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Objects-DBusObjectManagerServer.html#v:dBusObjectManagerServerExportUniquely"
        }


#endif

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

foreign import ccall "g_dbus_object_manager_server_get_connection" g_dbus_object_manager_server_get_connection :: 
    Ptr DBusObjectManagerServer ->          -- manager : TInterface (Name {namespace = "Gio", name = "DBusObjectManagerServer"})
    IO (Ptr Gio.DBusConnection.DBusConnection)

-- | Gets the t'GI.Gio.Objects.DBusConnection.DBusConnection' used by /@manager@/.
-- 
-- /Since: 2.30/
dBusObjectManagerServerGetConnection ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusObjectManagerServer a) =>
    a
    -- ^ /@manager@/: A t'GI.Gio.Objects.DBusObjectManagerServer.DBusObjectManagerServer'
    -> m Gio.DBusConnection.DBusConnection
    -- ^ __Returns:__ A t'GI.Gio.Objects.DBusConnection.DBusConnection' object or 'P.Nothing' if
    --   /@manager@/ isn\'t exported on a connection. The returned object should
    --   be freed with 'GI.GObject.Objects.Object.objectUnref'.
dBusObjectManagerServerGetConnection :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusObjectManagerServer a) =>
a -> m DBusConnection
dBusObjectManagerServerGetConnection a
manager = IO DBusConnection -> m DBusConnection
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DBusConnection -> m DBusConnection)
-> IO DBusConnection -> m DBusConnection
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusObjectManagerServer
manager' <- a -> IO (Ptr DBusObjectManagerServer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
    Ptr DBusConnection
result <- Ptr DBusObjectManagerServer -> IO (Ptr DBusConnection)
g_dbus_object_manager_server_get_connection Ptr DBusObjectManagerServer
manager'
    Text -> Ptr DBusConnection -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"dBusObjectManagerServerGetConnection" Ptr DBusConnection
result
    DBusConnection
result' <- ((ManagedPtr DBusConnection -> DBusConnection)
-> Ptr DBusConnection -> IO DBusConnection
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr DBusConnection -> DBusConnection
Gio.DBusConnection.DBusConnection) Ptr DBusConnection
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
manager
    DBusConnection -> IO DBusConnection
forall (m :: * -> *) a. Monad m => a -> m a
return DBusConnection
result'

#if defined(ENABLE_OVERLOADING)
data DBusObjectManagerServerGetConnectionMethodInfo
instance (signature ~ (m Gio.DBusConnection.DBusConnection), MonadIO m, IsDBusObjectManagerServer a) => O.OverloadedMethod DBusObjectManagerServerGetConnectionMethodInfo a signature where
    overloadedMethod = dBusObjectManagerServerGetConnection

instance O.OverloadedMethodInfo DBusObjectManagerServerGetConnectionMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Objects.DBusObjectManagerServer.dBusObjectManagerServerGetConnection",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Objects-DBusObjectManagerServer.html#v:dBusObjectManagerServerGetConnection"
        }


#endif

-- method DBusObjectManagerServer::is_exported
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "manager"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "DBusObjectManagerServer" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusObjectManagerServer."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "object"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusObjectSkeleton" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An object." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_object_manager_server_is_exported" g_dbus_object_manager_server_is_exported :: 
    Ptr DBusObjectManagerServer ->          -- manager : TInterface (Name {namespace = "Gio", name = "DBusObjectManagerServer"})
    Ptr Gio.DBusObjectSkeleton.DBusObjectSkeleton -> -- object : TInterface (Name {namespace = "Gio", name = "DBusObjectSkeleton"})
    IO CInt

-- | Returns whether /@object@/ is currently exported on /@manager@/.
-- 
-- /Since: 2.34/
dBusObjectManagerServerIsExported ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusObjectManagerServer a, Gio.DBusObjectSkeleton.IsDBusObjectSkeleton b) =>
    a
    -- ^ /@manager@/: A t'GI.Gio.Objects.DBusObjectManagerServer.DBusObjectManagerServer'.
    -> b
    -- ^ /@object@/: An object.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@object@/ is exported
dBusObjectManagerServerIsExported :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDBusObjectManagerServer a,
 IsDBusObjectSkeleton b) =>
a -> b -> m Bool
dBusObjectManagerServerIsExported a
manager b
object = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusObjectManagerServer
manager' <- a -> IO (Ptr DBusObjectManagerServer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
    Ptr DBusObjectSkeleton
object' <- b -> IO (Ptr DBusObjectSkeleton)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
object
    CInt
result <- Ptr DBusObjectManagerServer -> Ptr DBusObjectSkeleton -> IO CInt
g_dbus_object_manager_server_is_exported Ptr DBusObjectManagerServer
manager' Ptr DBusObjectSkeleton
object'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
manager
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
object
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data DBusObjectManagerServerIsExportedMethodInfo
instance (signature ~ (b -> m Bool), MonadIO m, IsDBusObjectManagerServer a, Gio.DBusObjectSkeleton.IsDBusObjectSkeleton b) => O.OverloadedMethod DBusObjectManagerServerIsExportedMethodInfo a signature where
    overloadedMethod = dBusObjectManagerServerIsExported

instance O.OverloadedMethodInfo DBusObjectManagerServerIsExportedMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Objects.DBusObjectManagerServer.dBusObjectManagerServerIsExported",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Objects-DBusObjectManagerServer.html#v:dBusObjectManagerServerIsExported"
        }


#endif

-- method DBusObjectManagerServer::set_connection
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "manager"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "DBusObjectManagerServer" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusObjectManagerServer."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "connection"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusConnection" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusConnection or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

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

-- | Exports all objects managed by /@manager@/ on /@connection@/. If
-- /@connection@/ is 'P.Nothing', stops exporting objects.
dBusObjectManagerServerSetConnection ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusObjectManagerServer a, Gio.DBusConnection.IsDBusConnection b) =>
    a
    -- ^ /@manager@/: A t'GI.Gio.Objects.DBusObjectManagerServer.DBusObjectManagerServer'.
    -> Maybe (b)
    -- ^ /@connection@/: A t'GI.Gio.Objects.DBusConnection.DBusConnection' or 'P.Nothing'.
    -> m ()
dBusObjectManagerServerSetConnection :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDBusObjectManagerServer a,
 IsDBusConnection b) =>
a -> Maybe b -> m ()
dBusObjectManagerServerSetConnection a
manager Maybe b
connection = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusObjectManagerServer
manager' <- a -> IO (Ptr DBusObjectManagerServer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
    Ptr DBusConnection
maybeConnection <- case Maybe b
connection of
        Maybe b
Nothing -> Ptr DBusConnection -> IO (Ptr DBusConnection)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr DBusConnection
forall a. Ptr a
nullPtr
        Just b
jConnection -> do
            Ptr DBusConnection
jConnection' <- b -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jConnection
            Ptr DBusConnection -> IO (Ptr DBusConnection)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr DBusConnection
jConnection'
    Ptr DBusObjectManagerServer -> Ptr DBusConnection -> IO ()
g_dbus_object_manager_server_set_connection Ptr DBusObjectManagerServer
manager' Ptr DBusConnection
maybeConnection
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
manager
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
connection b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DBusObjectManagerServerSetConnectionMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsDBusObjectManagerServer a, Gio.DBusConnection.IsDBusConnection b) => O.OverloadedMethod DBusObjectManagerServerSetConnectionMethodInfo a signature where
    overloadedMethod = dBusObjectManagerServerSetConnection

instance O.OverloadedMethodInfo DBusObjectManagerServerSetConnectionMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Objects.DBusObjectManagerServer.dBusObjectManagerServerSetConnection",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Objects-DBusObjectManagerServer.html#v:dBusObjectManagerServerSetConnection"
        }


#endif

-- method DBusObjectManagerServer::unexport
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "manager"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "DBusObjectManagerServer" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusObjectManagerServer."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "object_path"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An object path." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_object_manager_server_unexport" g_dbus_object_manager_server_unexport :: 
    Ptr DBusObjectManagerServer ->          -- manager : TInterface (Name {namespace = "Gio", name = "DBusObjectManagerServer"})
    CString ->                              -- object_path : TBasicType TUTF8
    IO CInt

-- | If /@manager@/ has an object at /@path@/, removes the object. Otherwise
-- does nothing.
-- 
-- Note that /@objectPath@/ must be in the hierarchy rooted by the
-- object path for /@manager@/.
-- 
-- /Since: 2.30/
dBusObjectManagerServerUnexport ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusObjectManagerServer a) =>
    a
    -- ^ /@manager@/: A t'GI.Gio.Objects.DBusObjectManagerServer.DBusObjectManagerServer'.
    -> T.Text
    -- ^ /@objectPath@/: An object path.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if object at /@objectPath@/ was removed, 'P.False' otherwise.
dBusObjectManagerServerUnexport :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusObjectManagerServer a) =>
a -> Text -> m Bool
dBusObjectManagerServerUnexport a
manager Text
objectPath = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusObjectManagerServer
manager' <- a -> IO (Ptr DBusObjectManagerServer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
    CString
objectPath' <- Text -> IO CString
textToCString Text
objectPath
    CInt
result <- Ptr DBusObjectManagerServer -> CString -> IO CInt
g_dbus_object_manager_server_unexport Ptr DBusObjectManagerServer
manager' CString
objectPath'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
manager
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
objectPath'
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data DBusObjectManagerServerUnexportMethodInfo
instance (signature ~ (T.Text -> m Bool), MonadIO m, IsDBusObjectManagerServer a) => O.OverloadedMethod DBusObjectManagerServerUnexportMethodInfo a signature where
    overloadedMethod = dBusObjectManagerServerUnexport

instance O.OverloadedMethodInfo DBusObjectManagerServerUnexportMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Objects.DBusObjectManagerServer.dBusObjectManagerServerUnexport",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Objects-DBusObjectManagerServer.html#v:dBusObjectManagerServerUnexport"
        }


#endif