{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- /No description available in the introspection data./

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

module GI.NM.Objects.Object
    ( 

-- * Exported types
    Object(..)                              ,
    IsObject                                ,
    toObject                                ,


 -- * 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
-- [getClient]("GI.NM.Objects.Object#g:method:getClient"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getPath]("GI.NM.Objects.Object#g:method:getPath"), [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)
    ResolveObjectMethod                     ,
#endif

-- ** getClient #method:getClient#

#if defined(ENABLE_OVERLOADING)
    ObjectGetClientMethodInfo               ,
#endif
    objectGetClient                         ,


-- ** getPath #method:getPath#

#if defined(ENABLE_OVERLOADING)
    ObjectGetPathMethodInfo                 ,
#endif
    objectGetPath                           ,




 -- * Properties


-- ** client #attr:client#
-- | The NMClient instance as returned by 'GI.NM.Objects.Object.objectGetClient'.
-- 
-- When an NMObject gets removed from the NMClient cache,
-- the NMObject:path property stays unchanged, but this client
-- instance gets reset to 'P.Nothing'. You can use this property to
-- track removal of the object from the cache.
-- 
-- /Since: 1.34/

#if defined(ENABLE_OVERLOADING)
    ObjectClientPropertyInfo                ,
#endif
    getObjectClient                         ,
#if defined(ENABLE_OVERLOADING)
    objectClient                            ,
#endif


-- ** path #attr:path#
-- | The D-Bus object path.
-- 
-- The D-Bus path of an object instance never changes, even if the object
-- gets removed from the cache. To see whether the object is still in the
-- cache, check NMObject:client.

#if defined(ENABLE_OVERLOADING)
    ObjectPathPropertyInfo                  ,
#endif
    getObjectPath                           ,
#if defined(ENABLE_OVERLOADING)
    objectPath                              ,
#endif




    ) where

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

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

-- Workaround for https://gitlab.haskell.org/ghc/ghc/-/issues/23392
#if MIN_VERSION_base(4,18,0)
import qualified GI.GLib.Structs.Bytes as GLib.Bytes
import qualified GI.GLib.Structs.MainContext as GLib.MainContext
import qualified GI.GLib.Structs.VariantType as GLib.VariantType
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Callbacks as Gio.Callbacks
import qualified GI.Gio.Interfaces.AsyncInitable as Gio.AsyncInitable
import qualified GI.Gio.Interfaces.AsyncResult as Gio.AsyncResult
import qualified GI.Gio.Interfaces.Initable as Gio.Initable
import qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
import qualified GI.Gio.Objects.DBusConnection as Gio.DBusConnection
import qualified GI.NM.Callbacks as NM.Callbacks
import {-# SOURCE #-} qualified GI.NM.Enums as NM.Enums
import {-# SOURCE #-} qualified GI.NM.Flags as NM.Flags
import {-# SOURCE #-} qualified GI.NM.Interfaces.Connection as NM.Connection
import {-# SOURCE #-} qualified GI.NM.Objects.ActiveConnection as NM.ActiveConnection
import {-# SOURCE #-} qualified GI.NM.Objects.Checkpoint as NM.Checkpoint
import {-# SOURCE #-} qualified GI.NM.Objects.Client as NM.Client
import {-# SOURCE #-} qualified GI.NM.Objects.Device as NM.Device
import {-# SOURCE #-} qualified GI.NM.Objects.DhcpConfig as NM.DhcpConfig
import {-# SOURCE #-} qualified GI.NM.Objects.IPConfig as NM.IPConfig
import {-# SOURCE #-} qualified GI.NM.Objects.RemoteConnection as NM.RemoteConnection
import {-# SOURCE #-} qualified GI.NM.Objects.Setting as NM.Setting
import {-# SOURCE #-} qualified GI.NM.Objects.Setting8021x as NM.Setting8021x
import {-# SOURCE #-} qualified GI.NM.Objects.SettingAdsl as NM.SettingAdsl
import {-# SOURCE #-} qualified GI.NM.Objects.SettingBluetooth as NM.SettingBluetooth
import {-# SOURCE #-} qualified GI.NM.Objects.SettingBond as NM.SettingBond
import {-# SOURCE #-} qualified GI.NM.Objects.SettingBridge as NM.SettingBridge
import {-# SOURCE #-} qualified GI.NM.Objects.SettingBridgePort as NM.SettingBridgePort
import {-# SOURCE #-} qualified GI.NM.Objects.SettingCdma as NM.SettingCdma
import {-# SOURCE #-} qualified GI.NM.Objects.SettingConnection as NM.SettingConnection
import {-# SOURCE #-} qualified GI.NM.Objects.SettingDcb as NM.SettingDcb
import {-# SOURCE #-} qualified GI.NM.Objects.SettingDummy as NM.SettingDummy
import {-# SOURCE #-} qualified GI.NM.Objects.SettingGeneric as NM.SettingGeneric
import {-# SOURCE #-} qualified GI.NM.Objects.SettingGsm as NM.SettingGsm
import {-# SOURCE #-} qualified GI.NM.Objects.SettingIP4Config as NM.SettingIP4Config
import {-# SOURCE #-} qualified GI.NM.Objects.SettingIP6Config as NM.SettingIP6Config
import {-# SOURCE #-} qualified GI.NM.Objects.SettingIPConfig as NM.SettingIPConfig
import {-# SOURCE #-} qualified GI.NM.Objects.SettingIPTunnel as NM.SettingIPTunnel
import {-# SOURCE #-} qualified GI.NM.Objects.SettingInfiniband as NM.SettingInfiniband
import {-# SOURCE #-} qualified GI.NM.Objects.SettingMacsec as NM.SettingMacsec
import {-# SOURCE #-} qualified GI.NM.Objects.SettingMacvlan as NM.SettingMacvlan
import {-# SOURCE #-} qualified GI.NM.Objects.SettingOlpcMesh as NM.SettingOlpcMesh
import {-# SOURCE #-} qualified GI.NM.Objects.SettingOvsBridge as NM.SettingOvsBridge
import {-# SOURCE #-} qualified GI.NM.Objects.SettingOvsInterface as NM.SettingOvsInterface
import {-# SOURCE #-} qualified GI.NM.Objects.SettingOvsPatch as NM.SettingOvsPatch
import {-# SOURCE #-} qualified GI.NM.Objects.SettingOvsPort as NM.SettingOvsPort
import {-# SOURCE #-} qualified GI.NM.Objects.SettingPpp as NM.SettingPpp
import {-# SOURCE #-} qualified GI.NM.Objects.SettingPppoe as NM.SettingPppoe
import {-# SOURCE #-} qualified GI.NM.Objects.SettingProxy as NM.SettingProxy
import {-# SOURCE #-} qualified GI.NM.Objects.SettingSerial as NM.SettingSerial
import {-# SOURCE #-} qualified GI.NM.Objects.SettingTCConfig as NM.SettingTCConfig
import {-# SOURCE #-} qualified GI.NM.Objects.SettingTeam as NM.SettingTeam
import {-# SOURCE #-} qualified GI.NM.Objects.SettingTeamPort as NM.SettingTeamPort
import {-# SOURCE #-} qualified GI.NM.Objects.SettingTun as NM.SettingTun
import {-# SOURCE #-} qualified GI.NM.Objects.SettingVlan as NM.SettingVlan
import {-# SOURCE #-} qualified GI.NM.Objects.SettingVpn as NM.SettingVpn
import {-# SOURCE #-} qualified GI.NM.Objects.SettingVxlan as NM.SettingVxlan
import {-# SOURCE #-} qualified GI.NM.Objects.SettingWimax as NM.SettingWimax
import {-# SOURCE #-} qualified GI.NM.Objects.SettingWired as NM.SettingWired
import {-# SOURCE #-} qualified GI.NM.Objects.SettingWireless as NM.SettingWireless
import {-# SOURCE #-} qualified GI.NM.Objects.SettingWirelessSecurity as NM.SettingWirelessSecurity
import {-# SOURCE #-} qualified GI.NM.Structs.BridgeVlan as NM.BridgeVlan
import {-# SOURCE #-} qualified GI.NM.Structs.DnsEntry as NM.DnsEntry
import {-# SOURCE #-} qualified GI.NM.Structs.IPAddress as NM.IPAddress
import {-# SOURCE #-} qualified GI.NM.Structs.IPRoute as NM.IPRoute
import {-# SOURCE #-} qualified GI.NM.Structs.IPRoutingRule as NM.IPRoutingRule
import {-# SOURCE #-} qualified GI.NM.Structs.LldpNeighbor as NM.LldpNeighbor
import {-# SOURCE #-} qualified GI.NM.Structs.Range as NM.Range
import {-# SOURCE #-} qualified GI.NM.Structs.TCAction as NM.TCAction
import {-# SOURCE #-} qualified GI.NM.Structs.TCQdisc as NM.TCQdisc
import {-# SOURCE #-} qualified GI.NM.Structs.TCTfilter as NM.TCTfilter
import {-# SOURCE #-} qualified GI.NM.Structs.TeamLinkWatcher as NM.TeamLinkWatcher
import {-# SOURCE #-} qualified GI.NM.Structs.VariantAttributeSpec as NM.VariantAttributeSpec

#else
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.NM.Objects.Client as NM.Client

#endif

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

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

foreign import ccall "nm_object_get_type"
    c_nm_object_get_type :: IO B.Types.GType

instance B.Types.TypedObject Object where
    glibType :: IO GType
glibType = IO GType
c_nm_object_get_type

instance B.Types.GObject Object

-- | Type class for types which can be safely cast to t'Object', for instance with `toObject`.
class (SP.GObject o, O.IsDescendantOf Object o) => IsObject o
instance (SP.GObject o, O.IsDescendantOf Object o) => IsObject o

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

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

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

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

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

#endif

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

#endif

-- VVV Prop "client"
   -- Type: TInterface (Name {namespace = "NM", name = "Client"})
   -- Flags: [PropertyReadable]
   -- Nullable: (Nothing,Nothing)

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

#if defined(ENABLE_OVERLOADING)
data ObjectClientPropertyInfo
instance AttrInfo ObjectClientPropertyInfo where
    type AttrAllowedOps ObjectClientPropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ObjectClientPropertyInfo = IsObject
    type AttrSetTypeConstraint ObjectClientPropertyInfo = (~) ()
    type AttrTransferTypeConstraint ObjectClientPropertyInfo = (~) ()
    type AttrTransferType ObjectClientPropertyInfo = ()
    type AttrGetType ObjectClientPropertyInfo = (Maybe NM.Client.Client)
    type AttrLabel ObjectClientPropertyInfo = "client"
    type AttrOrigin ObjectClientPropertyInfo = Object
    attrGet = getObjectClient
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.Object.client"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-Object.html#g:attr:client"
        })
#endif

-- VVV Prop "path"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@path@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' object #path
-- @
getObjectPath :: (MonadIO m, IsObject o) => o -> m T.Text
getObjectPath :: forall (m :: * -> *) o. (MonadIO m, IsObject o) => o -> m Text
getObjectPath o
obj = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getObjectPath" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"path"

#if defined(ENABLE_OVERLOADING)
data ObjectPathPropertyInfo
instance AttrInfo ObjectPathPropertyInfo where
    type AttrAllowedOps ObjectPathPropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ObjectPathPropertyInfo = IsObject
    type AttrSetTypeConstraint ObjectPathPropertyInfo = (~) ()
    type AttrTransferTypeConstraint ObjectPathPropertyInfo = (~) ()
    type AttrTransferType ObjectPathPropertyInfo = ()
    type AttrGetType ObjectPathPropertyInfo = T.Text
    type AttrLabel ObjectPathPropertyInfo = "path"
    type AttrOrigin ObjectPathPropertyInfo = Object
    attrGet = getObjectPath
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.Object.path"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-Object.html#g:attr:path"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Object
type instance O.AttributeList Object = ObjectAttributeList
type ObjectAttributeList = ('[ '("client", ObjectClientPropertyInfo), '("path", ObjectPathPropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
objectClient :: AttrLabelProxy "client"
objectClient = AttrLabelProxy

objectPath :: AttrLabelProxy "path"
objectPath = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Object = ObjectSignalList
type ObjectSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])

#endif

-- method Object::get_client
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "object"
--           , argType = TInterface Name { namespace = "NM" , name = "Object" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #NMObject" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TPtr)
-- throws : False
-- Skip return : False

foreign import ccall "nm_object_get_client" nm_object_get_client :: 
    Ptr Object ->                           -- object : TInterface (Name {namespace = "NM", name = "Object"})
    IO (Ptr ())

-- | Returns the t'GI.NM.Objects.Client.Client' instance in which object is cached.
-- Also, if the object got removed from the client cached,
-- this returns 'P.Nothing'. So it can be used to check whether the
-- object is still alive.
-- 
-- /Since: 1.24/
objectGetClient ::
    (B.CallStack.HasCallStack, MonadIO m, IsObject a) =>
    a
    -- ^ /@object@/: a t'GI.NM.Objects.Object.Object'
    -> m (Ptr ())
    -- ^ __Returns:__ the t'GI.NM.Objects.Client.Client' cache in which the
    -- object can be found, or 'P.Nothing' if the object is no longer
    -- cached.
objectGetClient :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsObject a) =>
a -> m (Ptr ())
objectGetClient a
object = IO (Ptr ()) -> m (Ptr ())
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Ptr ()) -> m (Ptr ())) -> IO (Ptr ()) -> m (Ptr ())
forall a b. (a -> b) -> a -> b
$ do
    Ptr Object
object' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
object
    Ptr ()
result <- Ptr Object -> IO (Ptr ())
nm_object_get_client Ptr Object
object'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
object
    Ptr () -> IO (Ptr ())
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ()
result

#if defined(ENABLE_OVERLOADING)
data ObjectGetClientMethodInfo
instance (signature ~ (m (Ptr ())), MonadIO m, IsObject a) => O.OverloadedMethod ObjectGetClientMethodInfo a signature where
    overloadedMethod = objectGetClient

instance O.OverloadedMethodInfo ObjectGetClientMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.Object.objectGetClient",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-Object.html#v:objectGetClient"
        })


#endif

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

foreign import ccall "nm_object_get_path" nm_object_get_path :: 
    Ptr Object ->                           -- object : TInterface (Name {namespace = "NM", name = "Object"})
    IO CString

-- | Gets the DBus path of the t'GI.NM.Objects.Object.Object'.
objectGetPath ::
    (B.CallStack.HasCallStack, MonadIO m, IsObject a) =>
    a
    -- ^ /@object@/: a t'GI.NM.Objects.Object.Object'
    -> m T.Text
    -- ^ __Returns:__ the object\'s path. This is the internal string used by the
    -- object, and must not be modified.
    -- 
    -- Note that the D-Bus path of an NMObject never changes, even
    -- if the instance gets removed from the cache. To find out
    -- whether the object is still alive\/cached, check 'GI.NM.Objects.Object.objectGetClient'.
objectGetPath :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsObject a) =>
a -> m Text
objectGetPath a
object = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr Object
object' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
object
    CString
result <- Ptr Object -> IO CString
nm_object_get_path Ptr Object
object'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"objectGetPath" 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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data ObjectGetPathMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsObject a) => O.OverloadedMethod ObjectGetPathMethodInfo a signature where
    overloadedMethod = objectGetPath

instance O.OverloadedMethodInfo ObjectGetPathMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.Object.objectGetPath",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-Object.html#v:objectGetPath"
        })


#endif