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


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- The t'GI.Gio.Interfaces.DBusObject.DBusObject' type is the base type for D-Bus objects on both
-- the service side (see t'GI.Gio.Objects.DBusObjectSkeleton.DBusObjectSkeleton') and the client side
-- (see t'GI.Gio.Objects.DBusObjectProxy.DBusObjectProxy'). It is essentially just a container of
-- interfaces.

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

module GI.Gio.Interfaces.DBusObject
    ( 

-- * Exported types
    DBusObject(..)                          ,
    IsDBusObject                            ,
    toDBusObject                            ,


 -- * 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"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [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"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getData]("GI.GObject.Objects.Object#g:method:getData"), [getInterface]("GI.Gio.Interfaces.DBusObject#g:method:getInterface"), [getInterfaces]("GI.Gio.Interfaces.DBusObject#g:method:getInterfaces"), [getObjectPath]("GI.Gio.Interfaces.DBusObject#g:method:getObjectPath"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata").
-- 
-- ==== Setters
-- [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)
    ResolveDBusObjectMethod                 ,
#endif

-- ** getInterface #method:getInterface#

#if defined(ENABLE_OVERLOADING)
    DBusObjectGetInterfaceMethodInfo        ,
#endif
    dBusObjectGetInterface                  ,


-- ** getInterfaces #method:getInterfaces#

#if defined(ENABLE_OVERLOADING)
    DBusObjectGetInterfacesMethodInfo       ,
#endif
    dBusObjectGetInterfaces                 ,


-- ** getObjectPath #method:getObjectPath#

#if defined(ENABLE_OVERLOADING)
    DBusObjectGetObjectPathMethodInfo       ,
#endif
    dBusObjectGetObjectPath                 ,




 -- * Signals


-- ** interfaceAdded #signal:interfaceAdded#

    DBusObjectInterfaceAddedCallback        ,
#if defined(ENABLE_OVERLOADING)
    DBusObjectInterfaceAddedSignalInfo      ,
#endif
    afterDBusObjectInterfaceAdded           ,
    onDBusObjectInterfaceAdded              ,


-- ** interfaceRemoved #signal:interfaceRemoved#

    DBusObjectInterfaceRemovedCallback      ,
#if defined(ENABLE_OVERLOADING)
    DBusObjectInterfaceRemovedSignalInfo    ,
#endif
    afterDBusObjectInterfaceRemoved         ,
    onDBusObjectInterfaceRemoved            ,




    ) 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.Coerce as Coerce
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.DBusInterface as Gio.DBusInterface

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

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

foreign import ccall "g_dbus_object_get_type"
    c_g_dbus_object_get_type :: IO B.Types.GType

instance B.Types.TypedObject DBusObject where
    glibType :: IO GType
glibType = IO GType
c_g_dbus_object_get_type

instance B.Types.GObject DBusObject

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

instance O.HasParentTypes DBusObject
type instance O.ParentTypes DBusObject = '[GObject.Object.Object]

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

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

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DBusObject
type instance O.AttributeList DBusObject = DBusObjectAttributeList
type DBusObjectAttributeList = ('[ ] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveDBusObjectMethod (t :: Symbol) (o :: *) :: * where
    ResolveDBusObjectMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveDBusObjectMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveDBusObjectMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveDBusObjectMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveDBusObjectMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveDBusObjectMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveDBusObjectMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveDBusObjectMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveDBusObjectMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveDBusObjectMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveDBusObjectMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveDBusObjectMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveDBusObjectMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveDBusObjectMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveDBusObjectMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveDBusObjectMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveDBusObjectMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveDBusObjectMethod "getInterface" o = DBusObjectGetInterfaceMethodInfo
    ResolveDBusObjectMethod "getInterfaces" o = DBusObjectGetInterfacesMethodInfo
    ResolveDBusObjectMethod "getObjectPath" o = DBusObjectGetObjectPathMethodInfo
    ResolveDBusObjectMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveDBusObjectMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveDBusObjectMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveDBusObjectMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveDBusObjectMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveDBusObjectMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

-- method DBusObject::get_interface
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "object"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusObject" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusObject." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "interface_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A D-Bus interface name."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gio" , name = "DBusInterface" })
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_object_get_interface" g_dbus_object_get_interface :: 
    Ptr DBusObject ->                       -- object : TInterface (Name {namespace = "Gio", name = "DBusObject"})
    CString ->                              -- interface_name : TBasicType TUTF8
    IO (Ptr Gio.DBusInterface.DBusInterface)

-- | Gets the D-Bus interface with name /@interfaceName@/ associated with
-- /@object@/, if any.
-- 
-- /Since: 2.30/
dBusObjectGetInterface ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusObject a) =>
    a
    -- ^ /@object@/: A t'GI.Gio.Interfaces.DBusObject.DBusObject'.
    -> T.Text
    -- ^ /@interfaceName@/: A D-Bus interface name.
    -> m (Maybe Gio.DBusInterface.DBusInterface)
    -- ^ __Returns:__ 'P.Nothing' if not found, otherwise a
    --   t'GI.Gio.Interfaces.DBusInterface.DBusInterface' that must be freed with 'GI.GObject.Objects.Object.objectUnref'.
dBusObjectGetInterface :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusObject a) =>
a -> Text -> m (Maybe DBusInterface)
dBusObjectGetInterface a
object Text
interfaceName = IO (Maybe DBusInterface) -> m (Maybe DBusInterface)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe DBusInterface) -> m (Maybe DBusInterface))
-> IO (Maybe DBusInterface) -> m (Maybe DBusInterface)
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusObject
object' <- a -> IO (Ptr DBusObject)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
object
    CString
interfaceName' <- Text -> IO CString
textToCString Text
interfaceName
    Ptr DBusInterface
result <- Ptr DBusObject -> CString -> IO (Ptr DBusInterface)
g_dbus_object_get_interface Ptr DBusObject
object' CString
interfaceName'
    Maybe DBusInterface
maybeResult <- Ptr DBusInterface
-> (Ptr DBusInterface -> IO DBusInterface)
-> IO (Maybe DBusInterface)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr DBusInterface
result ((Ptr DBusInterface -> IO DBusInterface)
 -> IO (Maybe DBusInterface))
-> (Ptr DBusInterface -> IO DBusInterface)
-> IO (Maybe DBusInterface)
forall a b. (a -> b) -> a -> b
$ \Ptr DBusInterface
result' -> do
        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'
        DBusInterface -> IO DBusInterface
forall (m :: * -> *) a. Monad m => a -> m a
return DBusInterface
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
object
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
interfaceName'
    Maybe DBusInterface -> IO (Maybe DBusInterface)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe DBusInterface
maybeResult

#if defined(ENABLE_OVERLOADING)
data DBusObjectGetInterfaceMethodInfo
instance (signature ~ (T.Text -> m (Maybe Gio.DBusInterface.DBusInterface)), MonadIO m, IsDBusObject a) => O.OverloadedMethod DBusObjectGetInterfaceMethodInfo a signature where
    overloadedMethod = dBusObjectGetInterface

instance O.OverloadedMethodInfo DBusObjectGetInterfaceMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.DBusObject.dBusObjectGetInterface",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Interfaces-DBusObject.html#v:dBusObjectGetInterface"
        })


#endif

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

foreign import ccall "g_dbus_object_get_interfaces" g_dbus_object_get_interfaces :: 
    Ptr DBusObject ->                       -- object : TInterface (Name {namespace = "Gio", name = "DBusObject"})
    IO (Ptr (GList (Ptr Gio.DBusInterface.DBusInterface)))

-- | Gets the D-Bus interfaces associated with /@object@/.
-- 
-- /Since: 2.30/
dBusObjectGetInterfaces ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusObject a) =>
    a
    -- ^ /@object@/: A t'GI.Gio.Interfaces.DBusObject.DBusObject'.
    -> m [Gio.DBusInterface.DBusInterface]
    -- ^ __Returns:__ A list of t'GI.Gio.Interfaces.DBusInterface.DBusInterface' instances.
    --   The returned list must be freed by @/g_list_free()/@ after each element has been freed
    --   with 'GI.GObject.Objects.Object.objectUnref'.
dBusObjectGetInterfaces :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusObject a) =>
a -> m [DBusInterface]
dBusObjectGetInterfaces a
object = 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 DBusObject
object' <- a -> IO (Ptr DBusObject)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
object
    Ptr (GList (Ptr DBusInterface))
result <- Ptr DBusObject -> IO (Ptr (GList (Ptr DBusInterface)))
g_dbus_object_get_interfaces Ptr DBusObject
object'
    [Ptr DBusInterface]
result' <- Ptr (GList (Ptr DBusInterface)) -> IO [Ptr DBusInterface]
forall a. Ptr (GList (Ptr a)) -> IO [Ptr a]
unpackGList Ptr (GList (Ptr DBusInterface))
result
    [DBusInterface]
result'' <- (Ptr DBusInterface -> IO DBusInterface)
-> [Ptr DBusInterface] -> IO [DBusInterface]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((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'
    Ptr (GList (Ptr DBusInterface)) -> IO ()
forall a. Ptr (GList a) -> IO ()
g_list_free Ptr (GList (Ptr DBusInterface))
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
object
    [DBusInterface] -> IO [DBusInterface]
forall (m :: * -> *) a. Monad m => a -> m a
return [DBusInterface]
result''

#if defined(ENABLE_OVERLOADING)
data DBusObjectGetInterfacesMethodInfo
instance (signature ~ (m [Gio.DBusInterface.DBusInterface]), MonadIO m, IsDBusObject a) => O.OverloadedMethod DBusObjectGetInterfacesMethodInfo a signature where
    overloadedMethod = dBusObjectGetInterfaces

instance O.OverloadedMethodInfo DBusObjectGetInterfacesMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.DBusObject.dBusObjectGetInterfaces",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Interfaces-DBusObject.html#v:dBusObjectGetInterfaces"
        })


#endif

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

foreign import ccall "g_dbus_object_get_object_path" g_dbus_object_get_object_path :: 
    Ptr DBusObject ->                       -- object : TInterface (Name {namespace = "Gio", name = "DBusObject"})
    IO CString

-- | Gets the object path for /@object@/.
-- 
-- /Since: 2.30/
dBusObjectGetObjectPath ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusObject a) =>
    a
    -- ^ /@object@/: A t'GI.Gio.Interfaces.DBusObject.DBusObject'.
    -> m T.Text
    -- ^ __Returns:__ A string owned by /@object@/. Do not free.
dBusObjectGetObjectPath :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusObject a) =>
a -> m Text
dBusObjectGetObjectPath a
object = 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 DBusObject
object' <- a -> IO (Ptr DBusObject)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
object
    CString
result <- Ptr DBusObject -> IO CString
g_dbus_object_get_object_path Ptr DBusObject
object'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"dBusObjectGetObjectPath" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
object
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data DBusObjectGetObjectPathMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDBusObject a) => O.OverloadedMethod DBusObjectGetObjectPathMethodInfo a signature where
    overloadedMethod = dBusObjectGetObjectPath

instance O.OverloadedMethodInfo DBusObjectGetObjectPathMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.DBusObject.dBusObjectGetObjectPath",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Interfaces-DBusObject.html#v:dBusObjectGetObjectPath"
        })


#endif

-- signal DBusObject::interface-added
-- | Emitted when /@interface@/ is added to /@object@/.
-- 
-- /Since: 2.30/
type DBusObjectInterfaceAddedCallback =
    Gio.DBusInterface.DBusInterface
    -- ^ /@interface@/: The t'GI.Gio.Interfaces.DBusInterface.DBusInterface' that was added.
    -> IO ()

type C_DBusObjectInterfaceAddedCallback =
    Ptr DBusObject ->                       -- object
    Ptr Gio.DBusInterface.DBusInterface ->
    Ptr () ->                               -- user_data
    IO ()

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

wrap_DBusObjectInterfaceAddedCallback :: 
    GObject a => (a -> DBusObjectInterfaceAddedCallback) ->
    C_DBusObjectInterfaceAddedCallback
wrap_DBusObjectInterfaceAddedCallback :: forall a.
GObject a =>
(a -> DBusObjectInterfaceAddedCallback)
-> C_DBusObjectInterfaceAddedCallback
wrap_DBusObjectInterfaceAddedCallback a -> DBusObjectInterfaceAddedCallback
gi'cb Ptr DBusObject
gi'selfPtr Ptr DBusInterface
interface Ptr ()
_ = do
    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
    Ptr DBusObject -> (DBusObject -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr DBusObject
gi'selfPtr ((DBusObject -> IO ()) -> IO ()) -> (DBusObject -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \DBusObject
gi'self -> a -> DBusObjectInterfaceAddedCallback
gi'cb (DBusObject -> a
Coerce.coerce DBusObject
gi'self)  DBusInterface
interface'


-- | Connect a signal handler for the [interfaceAdded](#signal:interfaceAdded) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' dBusObject #interfaceAdded callback
-- @
-- 
-- 
onDBusObjectInterfaceAdded :: (IsDBusObject a, MonadIO m) => a -> ((?self :: a) => DBusObjectInterfaceAddedCallback) -> m SignalHandlerId
onDBusObjectInterfaceAdded :: forall a (m :: * -> *).
(IsDBusObject a, MonadIO m) =>
a
-> ((?self::a) => DBusObjectInterfaceAddedCallback)
-> m SignalHandlerId
onDBusObjectInterfaceAdded a
obj (?self::a) => DBusObjectInterfaceAddedCallback
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 wrapped :: a -> DBusObjectInterfaceAddedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => DBusObjectInterfaceAddedCallback
DBusObjectInterfaceAddedCallback
cb
    let wrapped' :: C_DBusObjectInterfaceAddedCallback
wrapped' = (a -> DBusObjectInterfaceAddedCallback)
-> C_DBusObjectInterfaceAddedCallback
forall a.
GObject a =>
(a -> DBusObjectInterfaceAddedCallback)
-> C_DBusObjectInterfaceAddedCallback
wrap_DBusObjectInterfaceAddedCallback a -> DBusObjectInterfaceAddedCallback
wrapped
    FunPtr C_DBusObjectInterfaceAddedCallback
wrapped'' <- C_DBusObjectInterfaceAddedCallback
-> IO (FunPtr C_DBusObjectInterfaceAddedCallback)
mk_DBusObjectInterfaceAddedCallback C_DBusObjectInterfaceAddedCallback
wrapped'
    a
-> Text
-> FunPtr C_DBusObjectInterfaceAddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"interface-added" FunPtr C_DBusObjectInterfaceAddedCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [interfaceAdded](#signal:interfaceAdded) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' dBusObject #interfaceAdded callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterDBusObjectInterfaceAdded :: (IsDBusObject a, MonadIO m) => a -> ((?self :: a) => DBusObjectInterfaceAddedCallback) -> m SignalHandlerId
afterDBusObjectInterfaceAdded :: forall a (m :: * -> *).
(IsDBusObject a, MonadIO m) =>
a
-> ((?self::a) => DBusObjectInterfaceAddedCallback)
-> m SignalHandlerId
afterDBusObjectInterfaceAdded a
obj (?self::a) => DBusObjectInterfaceAddedCallback
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 wrapped :: a -> DBusObjectInterfaceAddedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => DBusObjectInterfaceAddedCallback
DBusObjectInterfaceAddedCallback
cb
    let wrapped' :: C_DBusObjectInterfaceAddedCallback
wrapped' = (a -> DBusObjectInterfaceAddedCallback)
-> C_DBusObjectInterfaceAddedCallback
forall a.
GObject a =>
(a -> DBusObjectInterfaceAddedCallback)
-> C_DBusObjectInterfaceAddedCallback
wrap_DBusObjectInterfaceAddedCallback a -> DBusObjectInterfaceAddedCallback
wrapped
    FunPtr C_DBusObjectInterfaceAddedCallback
wrapped'' <- C_DBusObjectInterfaceAddedCallback
-> IO (FunPtr C_DBusObjectInterfaceAddedCallback)
mk_DBusObjectInterfaceAddedCallback C_DBusObjectInterfaceAddedCallback
wrapped'
    a
-> Text
-> FunPtr C_DBusObjectInterfaceAddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"interface-added" FunPtr C_DBusObjectInterfaceAddedCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data DBusObjectInterfaceAddedSignalInfo
instance SignalInfo DBusObjectInterfaceAddedSignalInfo where
    type HaskellCallbackType DBusObjectInterfaceAddedSignalInfo = DBusObjectInterfaceAddedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_DBusObjectInterfaceAddedCallback cb
        cb'' <- mk_DBusObjectInterfaceAddedCallback cb'
        connectSignalFunPtr obj "interface-added" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.DBusObject::interface-added"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Interfaces-DBusObject.html#g:signal:interfaceAdded"})

#endif

-- signal DBusObject::interface-removed
-- | Emitted when /@interface@/ is removed from /@object@/.
-- 
-- /Since: 2.30/
type DBusObjectInterfaceRemovedCallback =
    Gio.DBusInterface.DBusInterface
    -- ^ /@interface@/: The t'GI.Gio.Interfaces.DBusInterface.DBusInterface' that was removed.
    -> IO ()

type C_DBusObjectInterfaceRemovedCallback =
    Ptr DBusObject ->                       -- object
    Ptr Gio.DBusInterface.DBusInterface ->
    Ptr () ->                               -- user_data
    IO ()

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

wrap_DBusObjectInterfaceRemovedCallback :: 
    GObject a => (a -> DBusObjectInterfaceRemovedCallback) ->
    C_DBusObjectInterfaceRemovedCallback
wrap_DBusObjectInterfaceRemovedCallback :: forall a.
GObject a =>
(a -> DBusObjectInterfaceAddedCallback)
-> C_DBusObjectInterfaceAddedCallback
wrap_DBusObjectInterfaceRemovedCallback a -> DBusObjectInterfaceAddedCallback
gi'cb Ptr DBusObject
gi'selfPtr Ptr DBusInterface
interface Ptr ()
_ = do
    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
    Ptr DBusObject -> (DBusObject -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr DBusObject
gi'selfPtr ((DBusObject -> IO ()) -> IO ()) -> (DBusObject -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \DBusObject
gi'self -> a -> DBusObjectInterfaceAddedCallback
gi'cb (DBusObject -> a
Coerce.coerce DBusObject
gi'self)  DBusInterface
interface'


-- | Connect a signal handler for the [interfaceRemoved](#signal:interfaceRemoved) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' dBusObject #interfaceRemoved callback
-- @
-- 
-- 
onDBusObjectInterfaceRemoved :: (IsDBusObject a, MonadIO m) => a -> ((?self :: a) => DBusObjectInterfaceRemovedCallback) -> m SignalHandlerId
onDBusObjectInterfaceRemoved :: forall a (m :: * -> *).
(IsDBusObject a, MonadIO m) =>
a
-> ((?self::a) => DBusObjectInterfaceAddedCallback)
-> m SignalHandlerId
onDBusObjectInterfaceRemoved a
obj (?self::a) => DBusObjectInterfaceAddedCallback
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 wrapped :: a -> DBusObjectInterfaceAddedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => DBusObjectInterfaceAddedCallback
DBusObjectInterfaceAddedCallback
cb
    let wrapped' :: C_DBusObjectInterfaceAddedCallback
wrapped' = (a -> DBusObjectInterfaceAddedCallback)
-> C_DBusObjectInterfaceAddedCallback
forall a.
GObject a =>
(a -> DBusObjectInterfaceAddedCallback)
-> C_DBusObjectInterfaceAddedCallback
wrap_DBusObjectInterfaceRemovedCallback a -> DBusObjectInterfaceAddedCallback
wrapped
    FunPtr C_DBusObjectInterfaceAddedCallback
wrapped'' <- C_DBusObjectInterfaceAddedCallback
-> IO (FunPtr C_DBusObjectInterfaceAddedCallback)
mk_DBusObjectInterfaceRemovedCallback C_DBusObjectInterfaceAddedCallback
wrapped'
    a
-> Text
-> FunPtr C_DBusObjectInterfaceAddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"interface-removed" FunPtr C_DBusObjectInterfaceAddedCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [interfaceRemoved](#signal:interfaceRemoved) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' dBusObject #interfaceRemoved callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterDBusObjectInterfaceRemoved :: (IsDBusObject a, MonadIO m) => a -> ((?self :: a) => DBusObjectInterfaceRemovedCallback) -> m SignalHandlerId
afterDBusObjectInterfaceRemoved :: forall a (m :: * -> *).
(IsDBusObject a, MonadIO m) =>
a
-> ((?self::a) => DBusObjectInterfaceAddedCallback)
-> m SignalHandlerId
afterDBusObjectInterfaceRemoved a
obj (?self::a) => DBusObjectInterfaceAddedCallback
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 wrapped :: a -> DBusObjectInterfaceAddedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => DBusObjectInterfaceAddedCallback
DBusObjectInterfaceAddedCallback
cb
    let wrapped' :: C_DBusObjectInterfaceAddedCallback
wrapped' = (a -> DBusObjectInterfaceAddedCallback)
-> C_DBusObjectInterfaceAddedCallback
forall a.
GObject a =>
(a -> DBusObjectInterfaceAddedCallback)
-> C_DBusObjectInterfaceAddedCallback
wrap_DBusObjectInterfaceRemovedCallback a -> DBusObjectInterfaceAddedCallback
wrapped
    FunPtr C_DBusObjectInterfaceAddedCallback
wrapped'' <- C_DBusObjectInterfaceAddedCallback
-> IO (FunPtr C_DBusObjectInterfaceAddedCallback)
mk_DBusObjectInterfaceRemovedCallback C_DBusObjectInterfaceAddedCallback
wrapped'
    a
-> Text
-> FunPtr C_DBusObjectInterfaceAddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"interface-removed" FunPtr C_DBusObjectInterfaceAddedCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data DBusObjectInterfaceRemovedSignalInfo
instance SignalInfo DBusObjectInterfaceRemovedSignalInfo where
    type HaskellCallbackType DBusObjectInterfaceRemovedSignalInfo = DBusObjectInterfaceRemovedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_DBusObjectInterfaceRemovedCallback cb
        cb'' <- mk_DBusObjectInterfaceRemovedCallback cb'
        connectSignalFunPtr obj "interface-removed" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.DBusObject::interface-removed"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Interfaces-DBusObject.html#g:signal:interfaceRemoved"})

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList DBusObject = DBusObjectSignalList
type DBusObjectSignalList = ('[ '("interfaceAdded", DBusObjectInterfaceAddedSignalInfo), '("interfaceRemoved", DBusObjectInterfaceRemovedSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif