{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gio.Interfaces.DBusObjectManager
(
DBusObjectManager(..) ,
noDBusObjectManager ,
IsDBusObjectManager ,
toDBusObjectManager ,
#if defined(ENABLE_OVERLOADING)
ResolveDBusObjectManagerMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
DBusObjectManagerGetInterfaceMethodInfo ,
#endif
dBusObjectManagerGetInterface ,
#if defined(ENABLE_OVERLOADING)
DBusObjectManagerGetObjectMethodInfo ,
#endif
dBusObjectManagerGetObject ,
#if defined(ENABLE_OVERLOADING)
DBusObjectManagerGetObjectPathMethodInfo,
#endif
dBusObjectManagerGetObjectPath ,
#if defined(ENABLE_OVERLOADING)
DBusObjectManagerGetObjectsMethodInfo ,
#endif
dBusObjectManagerGetObjects ,
C_DBusObjectManagerInterfaceAddedCallback,
DBusObjectManagerInterfaceAddedCallback ,
#if defined(ENABLE_OVERLOADING)
DBusObjectManagerInterfaceAddedSignalInfo,
#endif
afterDBusObjectManagerInterfaceAdded ,
genClosure_DBusObjectManagerInterfaceAdded,
mk_DBusObjectManagerInterfaceAddedCallback,
noDBusObjectManagerInterfaceAddedCallback,
onDBusObjectManagerInterfaceAdded ,
wrap_DBusObjectManagerInterfaceAddedCallback,
C_DBusObjectManagerInterfaceRemovedCallback,
DBusObjectManagerInterfaceRemovedCallback,
#if defined(ENABLE_OVERLOADING)
DBusObjectManagerInterfaceRemovedSignalInfo,
#endif
afterDBusObjectManagerInterfaceRemoved ,
genClosure_DBusObjectManagerInterfaceRemoved,
mk_DBusObjectManagerInterfaceRemovedCallback,
noDBusObjectManagerInterfaceRemovedCallback,
onDBusObjectManagerInterfaceRemoved ,
wrap_DBusObjectManagerInterfaceRemovedCallback,
C_DBusObjectManagerObjectAddedCallback ,
DBusObjectManagerObjectAddedCallback ,
#if defined(ENABLE_OVERLOADING)
DBusObjectManagerObjectAddedSignalInfo ,
#endif
afterDBusObjectManagerObjectAdded ,
genClosure_DBusObjectManagerObjectAdded ,
mk_DBusObjectManagerObjectAddedCallback ,
noDBusObjectManagerObjectAddedCallback ,
onDBusObjectManagerObjectAdded ,
wrap_DBusObjectManagerObjectAddedCallback,
C_DBusObjectManagerObjectRemovedCallback,
DBusObjectManagerObjectRemovedCallback ,
#if defined(ENABLE_OVERLOADING)
DBusObjectManagerObjectRemovedSignalInfo,
#endif
afterDBusObjectManagerObjectRemoved ,
genClosure_DBusObjectManagerObjectRemoved,
mk_DBusObjectManagerObjectRemovedCallback,
noDBusObjectManagerObjectRemovedCallback,
onDBusObjectManagerObjectRemoved ,
wrap_DBusObjectManagerObjectRemovedCallback,
) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gio.Interfaces.DBusInterface as Gio.DBusInterface
import {-# SOURCE #-} qualified GI.Gio.Interfaces.DBusObject as Gio.DBusObject
newtype DBusObjectManager = DBusObjectManager (ManagedPtr DBusObjectManager)
deriving (DBusObjectManager -> DBusObjectManager -> Bool
(DBusObjectManager -> DBusObjectManager -> Bool)
-> (DBusObjectManager -> DBusObjectManager -> Bool)
-> Eq DBusObjectManager
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DBusObjectManager -> DBusObjectManager -> Bool
$c/= :: DBusObjectManager -> DBusObjectManager -> Bool
== :: DBusObjectManager -> DBusObjectManager -> Bool
$c== :: DBusObjectManager -> DBusObjectManager -> Bool
Eq)
noDBusObjectManager :: Maybe DBusObjectManager
noDBusObjectManager :: Maybe DBusObjectManager
noDBusObjectManager = Maybe DBusObjectManager
forall a. Maybe a
Nothing
type DBusObjectManagerInterfaceAddedCallback =
Gio.DBusObject.DBusObject
-> Gio.DBusInterface.DBusInterface
-> IO ()
noDBusObjectManagerInterfaceAddedCallback :: Maybe DBusObjectManagerInterfaceAddedCallback
noDBusObjectManagerInterfaceAddedCallback :: Maybe DBusObjectManagerInterfaceAddedCallback
noDBusObjectManagerInterfaceAddedCallback = Maybe DBusObjectManagerInterfaceAddedCallback
forall a. Maybe a
Nothing
type C_DBusObjectManagerInterfaceAddedCallback =
Ptr () ->
Ptr Gio.DBusObject.DBusObject ->
Ptr Gio.DBusInterface.DBusInterface ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_DBusObjectManagerInterfaceAddedCallback :: C_DBusObjectManagerInterfaceAddedCallback -> IO (FunPtr C_DBusObjectManagerInterfaceAddedCallback)
genClosure_DBusObjectManagerInterfaceAdded :: MonadIO m => DBusObjectManagerInterfaceAddedCallback -> m (GClosure C_DBusObjectManagerInterfaceAddedCallback)
genClosure_DBusObjectManagerInterfaceAdded :: DBusObjectManagerInterfaceAddedCallback
-> m (GClosure C_DBusObjectManagerInterfaceAddedCallback)
genClosure_DBusObjectManagerInterfaceAdded cb :: DBusObjectManagerInterfaceAddedCallback
cb = IO (GClosure C_DBusObjectManagerInterfaceAddedCallback)
-> m (GClosure C_DBusObjectManagerInterfaceAddedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_DBusObjectManagerInterfaceAddedCallback)
-> m (GClosure C_DBusObjectManagerInterfaceAddedCallback))
-> IO (GClosure C_DBusObjectManagerInterfaceAddedCallback)
-> m (GClosure C_DBusObjectManagerInterfaceAddedCallback)
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_DBusObjectManagerInterfaceAddedCallback
cb' = DBusObjectManagerInterfaceAddedCallback
-> C_DBusObjectManagerInterfaceAddedCallback
wrap_DBusObjectManagerInterfaceAddedCallback DBusObjectManagerInterfaceAddedCallback
cb
C_DBusObjectManagerInterfaceAddedCallback
-> IO (FunPtr C_DBusObjectManagerInterfaceAddedCallback)
mk_DBusObjectManagerInterfaceAddedCallback C_DBusObjectManagerInterfaceAddedCallback
cb' IO (FunPtr C_DBusObjectManagerInterfaceAddedCallback)
-> (FunPtr C_DBusObjectManagerInterfaceAddedCallback
-> IO (GClosure C_DBusObjectManagerInterfaceAddedCallback))
-> IO (GClosure C_DBusObjectManagerInterfaceAddedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_DBusObjectManagerInterfaceAddedCallback
-> IO (GClosure C_DBusObjectManagerInterfaceAddedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_DBusObjectManagerInterfaceAddedCallback ::
DBusObjectManagerInterfaceAddedCallback ->
C_DBusObjectManagerInterfaceAddedCallback
wrap_DBusObjectManagerInterfaceAddedCallback :: DBusObjectManagerInterfaceAddedCallback
-> C_DBusObjectManagerInterfaceAddedCallback
wrap_DBusObjectManagerInterfaceAddedCallback _cb :: DBusObjectManagerInterfaceAddedCallback
_cb _ object :: Ptr DBusObject
object interface :: Ptr DBusInterface
interface _ = do
DBusObject
object' <- ((ManagedPtr DBusObject -> DBusObject)
-> Ptr DBusObject -> IO DBusObject
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr DBusObject -> DBusObject
Gio.DBusObject.DBusObject) Ptr DBusObject
object
DBusInterface
interface' <- ((ManagedPtr DBusInterface -> DBusInterface)
-> Ptr DBusInterface -> IO DBusInterface
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr DBusInterface -> DBusInterface
Gio.DBusInterface.DBusInterface) Ptr DBusInterface
interface
DBusObjectManagerInterfaceAddedCallback
_cb DBusObject
object' DBusInterface
interface'
onDBusObjectManagerInterfaceAdded :: (IsDBusObjectManager a, MonadIO m) => a -> DBusObjectManagerInterfaceAddedCallback -> m SignalHandlerId
onDBusObjectManagerInterfaceAdded :: a -> DBusObjectManagerInterfaceAddedCallback -> m SignalHandlerId
onDBusObjectManagerInterfaceAdded obj :: a
obj cb :: DBusObjectManagerInterfaceAddedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_DBusObjectManagerInterfaceAddedCallback
cb' = DBusObjectManagerInterfaceAddedCallback
-> C_DBusObjectManagerInterfaceAddedCallback
wrap_DBusObjectManagerInterfaceAddedCallback DBusObjectManagerInterfaceAddedCallback
cb
FunPtr C_DBusObjectManagerInterfaceAddedCallback
cb'' <- C_DBusObjectManagerInterfaceAddedCallback
-> IO (FunPtr C_DBusObjectManagerInterfaceAddedCallback)
mk_DBusObjectManagerInterfaceAddedCallback C_DBusObjectManagerInterfaceAddedCallback
cb'
a
-> Text
-> FunPtr C_DBusObjectManagerInterfaceAddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "interface-added" FunPtr C_DBusObjectManagerInterfaceAddedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterDBusObjectManagerInterfaceAdded :: (IsDBusObjectManager a, MonadIO m) => a -> DBusObjectManagerInterfaceAddedCallback -> m SignalHandlerId
afterDBusObjectManagerInterfaceAdded :: a -> DBusObjectManagerInterfaceAddedCallback -> m SignalHandlerId
afterDBusObjectManagerInterfaceAdded obj :: a
obj cb :: DBusObjectManagerInterfaceAddedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_DBusObjectManagerInterfaceAddedCallback
cb' = DBusObjectManagerInterfaceAddedCallback
-> C_DBusObjectManagerInterfaceAddedCallback
wrap_DBusObjectManagerInterfaceAddedCallback DBusObjectManagerInterfaceAddedCallback
cb
FunPtr C_DBusObjectManagerInterfaceAddedCallback
cb'' <- C_DBusObjectManagerInterfaceAddedCallback
-> IO (FunPtr C_DBusObjectManagerInterfaceAddedCallback)
mk_DBusObjectManagerInterfaceAddedCallback C_DBusObjectManagerInterfaceAddedCallback
cb'
a
-> Text
-> FunPtr C_DBusObjectManagerInterfaceAddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "interface-added" FunPtr C_DBusObjectManagerInterfaceAddedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data DBusObjectManagerInterfaceAddedSignalInfo
instance SignalInfo DBusObjectManagerInterfaceAddedSignalInfo where
type HaskellCallbackType DBusObjectManagerInterfaceAddedSignalInfo = DBusObjectManagerInterfaceAddedCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_DBusObjectManagerInterfaceAddedCallback cb
cb'' <- mk_DBusObjectManagerInterfaceAddedCallback cb'
connectSignalFunPtr obj "interface-added" cb'' connectMode detail
#endif
type DBusObjectManagerInterfaceRemovedCallback =
Gio.DBusObject.DBusObject
-> Gio.DBusInterface.DBusInterface
-> IO ()
noDBusObjectManagerInterfaceRemovedCallback :: Maybe DBusObjectManagerInterfaceRemovedCallback
noDBusObjectManagerInterfaceRemovedCallback :: Maybe DBusObjectManagerInterfaceAddedCallback
noDBusObjectManagerInterfaceRemovedCallback = Maybe DBusObjectManagerInterfaceAddedCallback
forall a. Maybe a
Nothing
type C_DBusObjectManagerInterfaceRemovedCallback =
Ptr () ->
Ptr Gio.DBusObject.DBusObject ->
Ptr Gio.DBusInterface.DBusInterface ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_DBusObjectManagerInterfaceRemovedCallback :: C_DBusObjectManagerInterfaceRemovedCallback -> IO (FunPtr C_DBusObjectManagerInterfaceRemovedCallback)
genClosure_DBusObjectManagerInterfaceRemoved :: MonadIO m => DBusObjectManagerInterfaceRemovedCallback -> m (GClosure C_DBusObjectManagerInterfaceRemovedCallback)
genClosure_DBusObjectManagerInterfaceRemoved :: DBusObjectManagerInterfaceAddedCallback
-> m (GClosure C_DBusObjectManagerInterfaceAddedCallback)
genClosure_DBusObjectManagerInterfaceRemoved cb :: DBusObjectManagerInterfaceAddedCallback
cb = IO (GClosure C_DBusObjectManagerInterfaceAddedCallback)
-> m (GClosure C_DBusObjectManagerInterfaceAddedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_DBusObjectManagerInterfaceAddedCallback)
-> m (GClosure C_DBusObjectManagerInterfaceAddedCallback))
-> IO (GClosure C_DBusObjectManagerInterfaceAddedCallback)
-> m (GClosure C_DBusObjectManagerInterfaceAddedCallback)
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_DBusObjectManagerInterfaceAddedCallback
cb' = DBusObjectManagerInterfaceAddedCallback
-> C_DBusObjectManagerInterfaceAddedCallback
wrap_DBusObjectManagerInterfaceRemovedCallback DBusObjectManagerInterfaceAddedCallback
cb
C_DBusObjectManagerInterfaceAddedCallback
-> IO (FunPtr C_DBusObjectManagerInterfaceAddedCallback)
mk_DBusObjectManagerInterfaceRemovedCallback C_DBusObjectManagerInterfaceAddedCallback
cb' IO (FunPtr C_DBusObjectManagerInterfaceAddedCallback)
-> (FunPtr C_DBusObjectManagerInterfaceAddedCallback
-> IO (GClosure C_DBusObjectManagerInterfaceAddedCallback))
-> IO (GClosure C_DBusObjectManagerInterfaceAddedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_DBusObjectManagerInterfaceAddedCallback
-> IO (GClosure C_DBusObjectManagerInterfaceAddedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_DBusObjectManagerInterfaceRemovedCallback ::
DBusObjectManagerInterfaceRemovedCallback ->
C_DBusObjectManagerInterfaceRemovedCallback
wrap_DBusObjectManagerInterfaceRemovedCallback :: DBusObjectManagerInterfaceAddedCallback
-> C_DBusObjectManagerInterfaceAddedCallback
wrap_DBusObjectManagerInterfaceRemovedCallback _cb :: DBusObjectManagerInterfaceAddedCallback
_cb _ object :: Ptr DBusObject
object interface :: Ptr DBusInterface
interface _ = do
DBusObject
object' <- ((ManagedPtr DBusObject -> DBusObject)
-> Ptr DBusObject -> IO DBusObject
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr DBusObject -> DBusObject
Gio.DBusObject.DBusObject) Ptr DBusObject
object
DBusInterface
interface' <- ((ManagedPtr DBusInterface -> DBusInterface)
-> Ptr DBusInterface -> IO DBusInterface
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr DBusInterface -> DBusInterface
Gio.DBusInterface.DBusInterface) Ptr DBusInterface
interface
DBusObjectManagerInterfaceAddedCallback
_cb DBusObject
object' DBusInterface
interface'
onDBusObjectManagerInterfaceRemoved :: (IsDBusObjectManager a, MonadIO m) => a -> DBusObjectManagerInterfaceRemovedCallback -> m SignalHandlerId
onDBusObjectManagerInterfaceRemoved :: a -> DBusObjectManagerInterfaceAddedCallback -> m SignalHandlerId
onDBusObjectManagerInterfaceRemoved obj :: a
obj cb :: DBusObjectManagerInterfaceAddedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_DBusObjectManagerInterfaceAddedCallback
cb' = DBusObjectManagerInterfaceAddedCallback
-> C_DBusObjectManagerInterfaceAddedCallback
wrap_DBusObjectManagerInterfaceRemovedCallback DBusObjectManagerInterfaceAddedCallback
cb
FunPtr C_DBusObjectManagerInterfaceAddedCallback
cb'' <- C_DBusObjectManagerInterfaceAddedCallback
-> IO (FunPtr C_DBusObjectManagerInterfaceAddedCallback)
mk_DBusObjectManagerInterfaceRemovedCallback C_DBusObjectManagerInterfaceAddedCallback
cb'
a
-> Text
-> FunPtr C_DBusObjectManagerInterfaceAddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "interface-removed" FunPtr C_DBusObjectManagerInterfaceAddedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterDBusObjectManagerInterfaceRemoved :: (IsDBusObjectManager a, MonadIO m) => a -> DBusObjectManagerInterfaceRemovedCallback -> m SignalHandlerId
afterDBusObjectManagerInterfaceRemoved :: a -> DBusObjectManagerInterfaceAddedCallback -> m SignalHandlerId
afterDBusObjectManagerInterfaceRemoved obj :: a
obj cb :: DBusObjectManagerInterfaceAddedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_DBusObjectManagerInterfaceAddedCallback
cb' = DBusObjectManagerInterfaceAddedCallback
-> C_DBusObjectManagerInterfaceAddedCallback
wrap_DBusObjectManagerInterfaceRemovedCallback DBusObjectManagerInterfaceAddedCallback
cb
FunPtr C_DBusObjectManagerInterfaceAddedCallback
cb'' <- C_DBusObjectManagerInterfaceAddedCallback
-> IO (FunPtr C_DBusObjectManagerInterfaceAddedCallback)
mk_DBusObjectManagerInterfaceRemovedCallback C_DBusObjectManagerInterfaceAddedCallback
cb'
a
-> Text
-> FunPtr C_DBusObjectManagerInterfaceAddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "interface-removed" FunPtr C_DBusObjectManagerInterfaceAddedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data DBusObjectManagerInterfaceRemovedSignalInfo
instance SignalInfo DBusObjectManagerInterfaceRemovedSignalInfo where
type HaskellCallbackType DBusObjectManagerInterfaceRemovedSignalInfo = DBusObjectManagerInterfaceRemovedCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_DBusObjectManagerInterfaceRemovedCallback cb
cb'' <- mk_DBusObjectManagerInterfaceRemovedCallback cb'
connectSignalFunPtr obj "interface-removed" cb'' connectMode detail
#endif
type DBusObjectManagerObjectAddedCallback =
Gio.DBusObject.DBusObject
-> IO ()
noDBusObjectManagerObjectAddedCallback :: Maybe DBusObjectManagerObjectAddedCallback
noDBusObjectManagerObjectAddedCallback :: Maybe DBusObjectManagerObjectAddedCallback
noDBusObjectManagerObjectAddedCallback = Maybe DBusObjectManagerObjectAddedCallback
forall a. Maybe a
Nothing
type C_DBusObjectManagerObjectAddedCallback =
Ptr () ->
Ptr Gio.DBusObject.DBusObject ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_DBusObjectManagerObjectAddedCallback :: C_DBusObjectManagerObjectAddedCallback -> IO (FunPtr C_DBusObjectManagerObjectAddedCallback)
genClosure_DBusObjectManagerObjectAdded :: MonadIO m => DBusObjectManagerObjectAddedCallback -> m (GClosure C_DBusObjectManagerObjectAddedCallback)
genClosure_DBusObjectManagerObjectAdded :: DBusObjectManagerObjectAddedCallback
-> m (GClosure C_DBusObjectManagerObjectAddedCallback)
genClosure_DBusObjectManagerObjectAdded cb :: DBusObjectManagerObjectAddedCallback
cb = IO (GClosure C_DBusObjectManagerObjectAddedCallback)
-> m (GClosure C_DBusObjectManagerObjectAddedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_DBusObjectManagerObjectAddedCallback)
-> m (GClosure C_DBusObjectManagerObjectAddedCallback))
-> IO (GClosure C_DBusObjectManagerObjectAddedCallback)
-> m (GClosure C_DBusObjectManagerObjectAddedCallback)
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_DBusObjectManagerObjectAddedCallback
cb' = DBusObjectManagerObjectAddedCallback
-> C_DBusObjectManagerObjectAddedCallback
wrap_DBusObjectManagerObjectAddedCallback DBusObjectManagerObjectAddedCallback
cb
C_DBusObjectManagerObjectAddedCallback
-> IO (FunPtr C_DBusObjectManagerObjectAddedCallback)
mk_DBusObjectManagerObjectAddedCallback C_DBusObjectManagerObjectAddedCallback
cb' IO (FunPtr C_DBusObjectManagerObjectAddedCallback)
-> (FunPtr C_DBusObjectManagerObjectAddedCallback
-> IO (GClosure C_DBusObjectManagerObjectAddedCallback))
-> IO (GClosure C_DBusObjectManagerObjectAddedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_DBusObjectManagerObjectAddedCallback
-> IO (GClosure C_DBusObjectManagerObjectAddedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_DBusObjectManagerObjectAddedCallback ::
DBusObjectManagerObjectAddedCallback ->
C_DBusObjectManagerObjectAddedCallback
wrap_DBusObjectManagerObjectAddedCallback :: DBusObjectManagerObjectAddedCallback
-> C_DBusObjectManagerObjectAddedCallback
wrap_DBusObjectManagerObjectAddedCallback _cb :: DBusObjectManagerObjectAddedCallback
_cb _ object :: Ptr DBusObject
object _ = do
DBusObject
object' <- ((ManagedPtr DBusObject -> DBusObject)
-> Ptr DBusObject -> IO DBusObject
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr DBusObject -> DBusObject
Gio.DBusObject.DBusObject) Ptr DBusObject
object
DBusObjectManagerObjectAddedCallback
_cb DBusObject
object'
onDBusObjectManagerObjectAdded :: (IsDBusObjectManager a, MonadIO m) => a -> DBusObjectManagerObjectAddedCallback -> m SignalHandlerId
onDBusObjectManagerObjectAdded :: a -> DBusObjectManagerObjectAddedCallback -> m SignalHandlerId
onDBusObjectManagerObjectAdded obj :: a
obj cb :: DBusObjectManagerObjectAddedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_DBusObjectManagerObjectAddedCallback
cb' = DBusObjectManagerObjectAddedCallback
-> C_DBusObjectManagerObjectAddedCallback
wrap_DBusObjectManagerObjectAddedCallback DBusObjectManagerObjectAddedCallback
cb
FunPtr C_DBusObjectManagerObjectAddedCallback
cb'' <- C_DBusObjectManagerObjectAddedCallback
-> IO (FunPtr C_DBusObjectManagerObjectAddedCallback)
mk_DBusObjectManagerObjectAddedCallback C_DBusObjectManagerObjectAddedCallback
cb'
a
-> Text
-> FunPtr C_DBusObjectManagerObjectAddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "object-added" FunPtr C_DBusObjectManagerObjectAddedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterDBusObjectManagerObjectAdded :: (IsDBusObjectManager a, MonadIO m) => a -> DBusObjectManagerObjectAddedCallback -> m SignalHandlerId
afterDBusObjectManagerObjectAdded :: a -> DBusObjectManagerObjectAddedCallback -> m SignalHandlerId
afterDBusObjectManagerObjectAdded obj :: a
obj cb :: DBusObjectManagerObjectAddedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_DBusObjectManagerObjectAddedCallback
cb' = DBusObjectManagerObjectAddedCallback
-> C_DBusObjectManagerObjectAddedCallback
wrap_DBusObjectManagerObjectAddedCallback DBusObjectManagerObjectAddedCallback
cb
FunPtr C_DBusObjectManagerObjectAddedCallback
cb'' <- C_DBusObjectManagerObjectAddedCallback
-> IO (FunPtr C_DBusObjectManagerObjectAddedCallback)
mk_DBusObjectManagerObjectAddedCallback C_DBusObjectManagerObjectAddedCallback
cb'
a
-> Text
-> FunPtr C_DBusObjectManagerObjectAddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "object-added" FunPtr C_DBusObjectManagerObjectAddedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data DBusObjectManagerObjectAddedSignalInfo
instance SignalInfo DBusObjectManagerObjectAddedSignalInfo where
type HaskellCallbackType DBusObjectManagerObjectAddedSignalInfo = DBusObjectManagerObjectAddedCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_DBusObjectManagerObjectAddedCallback cb
cb'' <- mk_DBusObjectManagerObjectAddedCallback cb'
connectSignalFunPtr obj "object-added" cb'' connectMode detail
#endif
type DBusObjectManagerObjectRemovedCallback =
Gio.DBusObject.DBusObject
-> IO ()
noDBusObjectManagerObjectRemovedCallback :: Maybe DBusObjectManagerObjectRemovedCallback
noDBusObjectManagerObjectRemovedCallback :: Maybe DBusObjectManagerObjectAddedCallback
noDBusObjectManagerObjectRemovedCallback = Maybe DBusObjectManagerObjectAddedCallback
forall a. Maybe a
Nothing
type C_DBusObjectManagerObjectRemovedCallback =
Ptr () ->
Ptr Gio.DBusObject.DBusObject ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_DBusObjectManagerObjectRemovedCallback :: C_DBusObjectManagerObjectRemovedCallback -> IO (FunPtr C_DBusObjectManagerObjectRemovedCallback)
genClosure_DBusObjectManagerObjectRemoved :: MonadIO m => DBusObjectManagerObjectRemovedCallback -> m (GClosure C_DBusObjectManagerObjectRemovedCallback)
genClosure_DBusObjectManagerObjectRemoved :: DBusObjectManagerObjectAddedCallback
-> m (GClosure C_DBusObjectManagerObjectAddedCallback)
genClosure_DBusObjectManagerObjectRemoved cb :: DBusObjectManagerObjectAddedCallback
cb = IO (GClosure C_DBusObjectManagerObjectAddedCallback)
-> m (GClosure C_DBusObjectManagerObjectAddedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_DBusObjectManagerObjectAddedCallback)
-> m (GClosure C_DBusObjectManagerObjectAddedCallback))
-> IO (GClosure C_DBusObjectManagerObjectAddedCallback)
-> m (GClosure C_DBusObjectManagerObjectAddedCallback)
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_DBusObjectManagerObjectAddedCallback
cb' = DBusObjectManagerObjectAddedCallback
-> C_DBusObjectManagerObjectAddedCallback
wrap_DBusObjectManagerObjectRemovedCallback DBusObjectManagerObjectAddedCallback
cb
C_DBusObjectManagerObjectAddedCallback
-> IO (FunPtr C_DBusObjectManagerObjectAddedCallback)
mk_DBusObjectManagerObjectRemovedCallback C_DBusObjectManagerObjectAddedCallback
cb' IO (FunPtr C_DBusObjectManagerObjectAddedCallback)
-> (FunPtr C_DBusObjectManagerObjectAddedCallback
-> IO (GClosure C_DBusObjectManagerObjectAddedCallback))
-> IO (GClosure C_DBusObjectManagerObjectAddedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_DBusObjectManagerObjectAddedCallback
-> IO (GClosure C_DBusObjectManagerObjectAddedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_DBusObjectManagerObjectRemovedCallback ::
DBusObjectManagerObjectRemovedCallback ->
C_DBusObjectManagerObjectRemovedCallback
wrap_DBusObjectManagerObjectRemovedCallback :: DBusObjectManagerObjectAddedCallback
-> C_DBusObjectManagerObjectAddedCallback
wrap_DBusObjectManagerObjectRemovedCallback _cb :: DBusObjectManagerObjectAddedCallback
_cb _ object :: Ptr DBusObject
object _ = do
DBusObject
object' <- ((ManagedPtr DBusObject -> DBusObject)
-> Ptr DBusObject -> IO DBusObject
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr DBusObject -> DBusObject
Gio.DBusObject.DBusObject) Ptr DBusObject
object
DBusObjectManagerObjectAddedCallback
_cb DBusObject
object'
onDBusObjectManagerObjectRemoved :: (IsDBusObjectManager a, MonadIO m) => a -> DBusObjectManagerObjectRemovedCallback -> m SignalHandlerId
onDBusObjectManagerObjectRemoved :: a -> DBusObjectManagerObjectAddedCallback -> m SignalHandlerId
onDBusObjectManagerObjectRemoved obj :: a
obj cb :: DBusObjectManagerObjectAddedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_DBusObjectManagerObjectAddedCallback
cb' = DBusObjectManagerObjectAddedCallback
-> C_DBusObjectManagerObjectAddedCallback
wrap_DBusObjectManagerObjectRemovedCallback DBusObjectManagerObjectAddedCallback
cb
FunPtr C_DBusObjectManagerObjectAddedCallback
cb'' <- C_DBusObjectManagerObjectAddedCallback
-> IO (FunPtr C_DBusObjectManagerObjectAddedCallback)
mk_DBusObjectManagerObjectRemovedCallback C_DBusObjectManagerObjectAddedCallback
cb'
a
-> Text
-> FunPtr C_DBusObjectManagerObjectAddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "object-removed" FunPtr C_DBusObjectManagerObjectAddedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterDBusObjectManagerObjectRemoved :: (IsDBusObjectManager a, MonadIO m) => a -> DBusObjectManagerObjectRemovedCallback -> m SignalHandlerId
afterDBusObjectManagerObjectRemoved :: a -> DBusObjectManagerObjectAddedCallback -> m SignalHandlerId
afterDBusObjectManagerObjectRemoved obj :: a
obj cb :: DBusObjectManagerObjectAddedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_DBusObjectManagerObjectAddedCallback
cb' = DBusObjectManagerObjectAddedCallback
-> C_DBusObjectManagerObjectAddedCallback
wrap_DBusObjectManagerObjectRemovedCallback DBusObjectManagerObjectAddedCallback
cb
FunPtr C_DBusObjectManagerObjectAddedCallback
cb'' <- C_DBusObjectManagerObjectAddedCallback
-> IO (FunPtr C_DBusObjectManagerObjectAddedCallback)
mk_DBusObjectManagerObjectRemovedCallback C_DBusObjectManagerObjectAddedCallback
cb'
a
-> Text
-> FunPtr C_DBusObjectManagerObjectAddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "object-removed" FunPtr C_DBusObjectManagerObjectAddedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data DBusObjectManagerObjectRemovedSignalInfo
instance SignalInfo DBusObjectManagerObjectRemovedSignalInfo where
type HaskellCallbackType DBusObjectManagerObjectRemovedSignalInfo = DBusObjectManagerObjectRemovedCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_DBusObjectManagerObjectRemovedCallback cb
cb'' <- mk_DBusObjectManagerObjectRemovedCallback cb'
connectSignalFunPtr obj "object-removed" cb'' connectMode detail
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList DBusObjectManager = DBusObjectManagerSignalList
type DBusObjectManagerSignalList = ('[ '("interfaceAdded", DBusObjectManagerInterfaceAddedSignalInfo), '("interfaceRemoved", DBusObjectManagerInterfaceRemovedSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("objectAdded", DBusObjectManagerObjectAddedSignalInfo), '("objectRemoved", DBusObjectManagerObjectRemovedSignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "g_dbus_object_manager_get_type"
c_g_dbus_object_manager_get_type :: IO GType
instance GObject DBusObjectManager where
gobjectType :: IO GType
gobjectType = IO GType
c_g_dbus_object_manager_get_type
instance B.GValue.IsGValue DBusObjectManager where
toGValue :: DBusObjectManager -> IO GValue
toGValue o :: DBusObjectManager
o = do
GType
gtype <- IO GType
c_g_dbus_object_manager_get_type
DBusObjectManager
-> (Ptr DBusObjectManager -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr DBusObjectManager
o (GType
-> (GValue -> Ptr DBusObjectManager -> IO ())
-> Ptr DBusObjectManager
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr DBusObjectManager -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO DBusObjectManager
fromGValue gv :: GValue
gv = do
Ptr DBusObjectManager
ptr <- GValue -> IO (Ptr DBusObjectManager)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr DBusObjectManager)
(ManagedPtr DBusObjectManager -> DBusObjectManager)
-> Ptr DBusObjectManager -> IO DBusObjectManager
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr DBusObjectManager -> DBusObjectManager
DBusObjectManager Ptr DBusObjectManager
ptr
class (GObject o, O.IsDescendantOf DBusObjectManager o) => IsDBusObjectManager o
instance (GObject o, O.IsDescendantOf DBusObjectManager o) => IsDBusObjectManager o
instance O.HasParentTypes DBusObjectManager
type instance O.ParentTypes DBusObjectManager = '[GObject.Object.Object]
toDBusObjectManager :: (MonadIO m, IsDBusObjectManager o) => o -> m DBusObjectManager
toDBusObjectManager :: o -> m DBusObjectManager
toDBusObjectManager = IO DBusObjectManager -> m DBusObjectManager
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DBusObjectManager -> m DBusObjectManager)
-> (o -> IO DBusObjectManager) -> o -> m DBusObjectManager
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr DBusObjectManager -> DBusObjectManager)
-> o -> IO DBusObjectManager
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr DBusObjectManager -> DBusObjectManager
DBusObjectManager
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DBusObjectManager
type instance O.AttributeList DBusObjectManager = DBusObjectManagerAttributeList
type DBusObjectManagerAttributeList = ('[ ] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveDBusObjectManagerMethod (t :: Symbol) (o :: *) :: * where
ResolveDBusObjectManagerMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveDBusObjectManagerMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveDBusObjectManagerMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveDBusObjectManagerMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveDBusObjectManagerMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveDBusObjectManagerMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveDBusObjectManagerMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveDBusObjectManagerMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveDBusObjectManagerMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveDBusObjectManagerMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveDBusObjectManagerMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveDBusObjectManagerMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveDBusObjectManagerMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveDBusObjectManagerMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveDBusObjectManagerMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveDBusObjectManagerMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveDBusObjectManagerMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveDBusObjectManagerMethod "getInterface" o = DBusObjectManagerGetInterfaceMethodInfo
ResolveDBusObjectManagerMethod "getObject" o = DBusObjectManagerGetObjectMethodInfo
ResolveDBusObjectManagerMethod "getObjectPath" o = DBusObjectManagerGetObjectPathMethodInfo
ResolveDBusObjectManagerMethod "getObjects" o = DBusObjectManagerGetObjectsMethodInfo
ResolveDBusObjectManagerMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveDBusObjectManagerMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveDBusObjectManagerMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveDBusObjectManagerMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveDBusObjectManagerMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveDBusObjectManagerMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveDBusObjectManagerMethod t DBusObjectManager, O.MethodInfo info DBusObjectManager p) => OL.IsLabel t (DBusObjectManager -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif
foreign import ccall "g_dbus_object_manager_get_interface" g_dbus_object_manager_get_interface ::
Ptr DBusObjectManager ->
CString ->
CString ->
IO (Ptr Gio.DBusInterface.DBusInterface)
dBusObjectManagerGetInterface ::
(B.CallStack.HasCallStack, MonadIO m, IsDBusObjectManager a) =>
a
-> T.Text
-> T.Text
-> m Gio.DBusInterface.DBusInterface
dBusObjectManagerGetInterface :: a -> Text -> Text -> m DBusInterface
dBusObjectManagerGetInterface manager :: a
manager objectPath :: Text
objectPath interfaceName :: Text
interfaceName = IO DBusInterface -> m DBusInterface
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DBusInterface -> m DBusInterface)
-> IO DBusInterface -> m DBusInterface
forall a b. (a -> b) -> a -> b
$ do
Ptr DBusObjectManager
manager' <- a -> IO (Ptr DBusObjectManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
CString
objectPath' <- Text -> IO CString
textToCString Text
objectPath
CString
interfaceName' <- Text -> IO CString
textToCString Text
interfaceName
Ptr DBusInterface
result <- Ptr DBusObjectManager
-> CString -> CString -> IO (Ptr DBusInterface)
g_dbus_object_manager_get_interface Ptr DBusObjectManager
manager' CString
objectPath' CString
interfaceName'
Text -> Ptr DBusInterface -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusObjectManagerGetInterface" Ptr DBusInterface
result
DBusInterface
result' <- ((ManagedPtr DBusInterface -> DBusInterface)
-> Ptr DBusInterface -> IO DBusInterface
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr DBusInterface -> DBusInterface
Gio.DBusInterface.DBusInterface) Ptr DBusInterface
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
manager
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
objectPath'
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
interfaceName'
DBusInterface -> IO DBusInterface
forall (m :: * -> *) a. Monad m => a -> m a
return DBusInterface
result'
#if defined(ENABLE_OVERLOADING)
data DBusObjectManagerGetInterfaceMethodInfo
instance (signature ~ (T.Text -> T.Text -> m Gio.DBusInterface.DBusInterface), MonadIO m, IsDBusObjectManager a) => O.MethodInfo DBusObjectManagerGetInterfaceMethodInfo a signature where
overloadedMethod = dBusObjectManagerGetInterface
#endif
foreign import ccall "g_dbus_object_manager_get_object" g_dbus_object_manager_get_object ::
Ptr DBusObjectManager ->
CString ->
IO (Ptr Gio.DBusObject.DBusObject)
dBusObjectManagerGetObject ::
(B.CallStack.HasCallStack, MonadIO m, IsDBusObjectManager a) =>
a
-> T.Text
-> m Gio.DBusObject.DBusObject
dBusObjectManagerGetObject :: a -> Text -> m DBusObject
dBusObjectManagerGetObject manager :: a
manager objectPath :: Text
objectPath = IO DBusObject -> m DBusObject
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DBusObject -> m DBusObject) -> IO DBusObject -> m DBusObject
forall a b. (a -> b) -> a -> b
$ do
Ptr DBusObjectManager
manager' <- a -> IO (Ptr DBusObjectManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
CString
objectPath' <- Text -> IO CString
textToCString Text
objectPath
Ptr DBusObject
result <- Ptr DBusObjectManager -> CString -> IO (Ptr DBusObject)
g_dbus_object_manager_get_object Ptr DBusObjectManager
manager' CString
objectPath'
Text -> Ptr DBusObject -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusObjectManagerGetObject" Ptr DBusObject
result
DBusObject
result' <- ((ManagedPtr DBusObject -> DBusObject)
-> Ptr DBusObject -> IO DBusObject
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr DBusObject -> DBusObject
Gio.DBusObject.DBusObject) Ptr DBusObject
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
manager
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
objectPath'
DBusObject -> IO DBusObject
forall (m :: * -> *) a. Monad m => a -> m a
return DBusObject
result'
#if defined(ENABLE_OVERLOADING)
data DBusObjectManagerGetObjectMethodInfo
instance (signature ~ (T.Text -> m Gio.DBusObject.DBusObject), MonadIO m, IsDBusObjectManager a) => O.MethodInfo DBusObjectManagerGetObjectMethodInfo a signature where
overloadedMethod = dBusObjectManagerGetObject
#endif
foreign import ccall "g_dbus_object_manager_get_object_path" g_dbus_object_manager_get_object_path ::
Ptr DBusObjectManager ->
IO CString
dBusObjectManagerGetObjectPath ::
(B.CallStack.HasCallStack, MonadIO m, IsDBusObjectManager a) =>
a
-> m T.Text
dBusObjectManagerGetObjectPath :: a -> m Text
dBusObjectManagerGetObjectPath manager :: a
manager = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
Ptr DBusObjectManager
manager' <- a -> IO (Ptr DBusObjectManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
CString
result <- Ptr DBusObjectManager -> IO CString
g_dbus_object_manager_get_object_path Ptr DBusObjectManager
manager'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusObjectManagerGetObjectPath" CString
result
Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
manager
Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data DBusObjectManagerGetObjectPathMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDBusObjectManager a) => O.MethodInfo DBusObjectManagerGetObjectPathMethodInfo a signature where
overloadedMethod = dBusObjectManagerGetObjectPath
#endif
foreign import ccall "g_dbus_object_manager_get_objects" g_dbus_object_manager_get_objects ::
Ptr DBusObjectManager ->
IO (Ptr (GList (Ptr Gio.DBusObject.DBusObject)))
dBusObjectManagerGetObjects ::
(B.CallStack.HasCallStack, MonadIO m, IsDBusObjectManager a) =>
a
-> m [Gio.DBusObject.DBusObject]
dBusObjectManagerGetObjects :: a -> m [DBusObject]
dBusObjectManagerGetObjects manager :: a
manager = IO [DBusObject] -> m [DBusObject]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [DBusObject] -> m [DBusObject])
-> IO [DBusObject] -> m [DBusObject]
forall a b. (a -> b) -> a -> b
$ do
Ptr DBusObjectManager
manager' <- a -> IO (Ptr DBusObjectManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
Ptr (GList (Ptr DBusObject))
result <- Ptr DBusObjectManager -> IO (Ptr (GList (Ptr DBusObject)))
g_dbus_object_manager_get_objects Ptr DBusObjectManager
manager'
[Ptr DBusObject]
result' <- Ptr (GList (Ptr DBusObject)) -> IO [Ptr DBusObject]
forall a. Ptr (GList (Ptr a)) -> IO [Ptr a]
unpackGList Ptr (GList (Ptr DBusObject))
result
[DBusObject]
result'' <- (Ptr DBusObject -> IO DBusObject)
-> [Ptr DBusObject] -> IO [DBusObject]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((ManagedPtr DBusObject -> DBusObject)
-> Ptr DBusObject -> IO DBusObject
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr DBusObject -> DBusObject
Gio.DBusObject.DBusObject) [Ptr DBusObject]
result'
Ptr (GList (Ptr DBusObject)) -> IO ()
forall a. Ptr (GList a) -> IO ()
g_list_free Ptr (GList (Ptr DBusObject))
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
manager
[DBusObject] -> IO [DBusObject]
forall (m :: * -> *) a. Monad m => a -> m a
return [DBusObject]
result''
#if defined(ENABLE_OVERLOADING)
data DBusObjectManagerGetObjectsMethodInfo
instance (signature ~ (m [Gio.DBusObject.DBusObject]), MonadIO m, IsDBusObjectManager a) => O.MethodInfo DBusObjectManagerGetObjectsMethodInfo a signature where
overloadedMethod = dBusObjectManagerGetObjects
#endif