{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gio.Objects.DBusServer
(
DBusServer(..) ,
IsDBusServer ,
toDBusServer ,
#if defined(ENABLE_OVERLOADING)
ResolveDBusServerMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
DBusServerGetClientAddressMethodInfo ,
#endif
dBusServerGetClientAddress ,
#if defined(ENABLE_OVERLOADING)
DBusServerGetFlagsMethodInfo ,
#endif
dBusServerGetFlags ,
#if defined(ENABLE_OVERLOADING)
DBusServerGetGuidMethodInfo ,
#endif
dBusServerGetGuid ,
#if defined(ENABLE_OVERLOADING)
DBusServerIsActiveMethodInfo ,
#endif
dBusServerIsActive ,
dBusServerNewSync ,
#if defined(ENABLE_OVERLOADING)
DBusServerStartMethodInfo ,
#endif
dBusServerStart ,
#if defined(ENABLE_OVERLOADING)
DBusServerStopMethodInfo ,
#endif
dBusServerStop ,
#if defined(ENABLE_OVERLOADING)
DBusServerActivePropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
dBusServerActive ,
#endif
getDBusServerActive ,
#if defined(ENABLE_OVERLOADING)
DBusServerAddressPropertyInfo ,
#endif
constructDBusServerAddress ,
#if defined(ENABLE_OVERLOADING)
dBusServerAddress ,
#endif
getDBusServerAddress ,
#if defined(ENABLE_OVERLOADING)
DBusServerAuthenticationObserverPropertyInfo,
#endif
constructDBusServerAuthenticationObserver,
#if defined(ENABLE_OVERLOADING)
dBusServerAuthenticationObserver ,
#endif
getDBusServerAuthenticationObserver ,
#if defined(ENABLE_OVERLOADING)
DBusServerClientAddressPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
dBusServerClientAddress ,
#endif
getDBusServerClientAddress ,
#if defined(ENABLE_OVERLOADING)
DBusServerFlagsPropertyInfo ,
#endif
constructDBusServerFlags ,
#if defined(ENABLE_OVERLOADING)
dBusServerFlags ,
#endif
getDBusServerFlags ,
#if defined(ENABLE_OVERLOADING)
DBusServerGuidPropertyInfo ,
#endif
constructDBusServerGuid ,
#if defined(ENABLE_OVERLOADING)
dBusServerGuid ,
#endif
getDBusServerGuid ,
C_DBusServerNewConnectionCallback ,
DBusServerNewConnectionCallback ,
#if defined(ENABLE_OVERLOADING)
DBusServerNewConnectionSignalInfo ,
#endif
afterDBusServerNewConnection ,
genClosure_DBusServerNewConnection ,
mk_DBusServerNewConnectionCallback ,
noDBusServerNewConnectionCallback ,
onDBusServerNewConnection ,
wrap_DBusServerNewConnectionCallback ,
) 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.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gio.Flags as Gio.Flags
import {-# SOURCE #-} qualified GI.Gio.Interfaces.Initable as Gio.Initable
import {-# SOURCE #-} qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
import {-# SOURCE #-} qualified GI.Gio.Objects.DBusAuthObserver as Gio.DBusAuthObserver
import {-# SOURCE #-} qualified GI.Gio.Objects.DBusConnection as Gio.DBusConnection
newtype DBusServer = DBusServer (SP.ManagedPtr DBusServer)
deriving (DBusServer -> DBusServer -> Bool
(DBusServer -> DBusServer -> Bool)
-> (DBusServer -> DBusServer -> Bool) -> Eq DBusServer
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DBusServer -> DBusServer -> Bool
$c/= :: DBusServer -> DBusServer -> Bool
== :: DBusServer -> DBusServer -> Bool
$c== :: DBusServer -> DBusServer -> Bool
Eq)
instance SP.ManagedPtrNewtype DBusServer where
toManagedPtr :: DBusServer -> ManagedPtr DBusServer
toManagedPtr (DBusServer ManagedPtr DBusServer
p) = ManagedPtr DBusServer
p
foreign import ccall "g_dbus_server_get_type"
c_g_dbus_server_get_type :: IO B.Types.GType
instance B.Types.TypedObject DBusServer where
glibType :: IO GType
glibType = IO GType
c_g_dbus_server_get_type
instance B.Types.GObject DBusServer
instance B.GValue.IsGValue DBusServer where
toGValue :: DBusServer -> IO GValue
toGValue DBusServer
o = do
GType
gtype <- IO GType
c_g_dbus_server_get_type
DBusServer -> (Ptr DBusServer -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr DBusServer
o (GType
-> (GValue -> Ptr DBusServer -> IO ())
-> Ptr DBusServer
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr DBusServer -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO DBusServer
fromGValue GValue
gv = do
Ptr DBusServer
ptr <- GValue -> IO (Ptr DBusServer)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr DBusServer)
(ManagedPtr DBusServer -> DBusServer)
-> Ptr DBusServer -> IO DBusServer
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr DBusServer -> DBusServer
DBusServer Ptr DBusServer
ptr
class (SP.GObject o, O.IsDescendantOf DBusServer o) => IsDBusServer o
instance (SP.GObject o, O.IsDescendantOf DBusServer o) => IsDBusServer o
instance O.HasParentTypes DBusServer
type instance O.ParentTypes DBusServer = '[GObject.Object.Object, Gio.Initable.Initable]
toDBusServer :: (MonadIO m, IsDBusServer o) => o -> m DBusServer
toDBusServer :: o -> m DBusServer
toDBusServer = IO DBusServer -> m DBusServer
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DBusServer -> m DBusServer)
-> (o -> IO DBusServer) -> o -> m DBusServer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr DBusServer -> DBusServer) -> o -> IO DBusServer
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr DBusServer -> DBusServer
DBusServer
#if defined(ENABLE_OVERLOADING)
type family ResolveDBusServerMethod (t :: Symbol) (o :: *) :: * where
ResolveDBusServerMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveDBusServerMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveDBusServerMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveDBusServerMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveDBusServerMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveDBusServerMethod "init" o = Gio.Initable.InitableInitMethodInfo
ResolveDBusServerMethod "isActive" o = DBusServerIsActiveMethodInfo
ResolveDBusServerMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveDBusServerMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveDBusServerMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveDBusServerMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveDBusServerMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveDBusServerMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveDBusServerMethod "start" o = DBusServerStartMethodInfo
ResolveDBusServerMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveDBusServerMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveDBusServerMethod "stop" o = DBusServerStopMethodInfo
ResolveDBusServerMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveDBusServerMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveDBusServerMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveDBusServerMethod "getClientAddress" o = DBusServerGetClientAddressMethodInfo
ResolveDBusServerMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveDBusServerMethod "getFlags" o = DBusServerGetFlagsMethodInfo
ResolveDBusServerMethod "getGuid" o = DBusServerGetGuidMethodInfo
ResolveDBusServerMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveDBusServerMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveDBusServerMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveDBusServerMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveDBusServerMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveDBusServerMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveDBusServerMethod t DBusServer, O.MethodInfo info DBusServer p) => OL.IsLabel t (DBusServer -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif
type DBusServerNewConnectionCallback =
Gio.DBusConnection.DBusConnection
-> IO Bool
noDBusServerNewConnectionCallback :: Maybe DBusServerNewConnectionCallback
noDBusServerNewConnectionCallback :: Maybe DBusServerNewConnectionCallback
noDBusServerNewConnectionCallback = Maybe DBusServerNewConnectionCallback
forall a. Maybe a
Nothing
type C_DBusServerNewConnectionCallback =
Ptr () ->
Ptr Gio.DBusConnection.DBusConnection ->
Ptr () ->
IO CInt
foreign import ccall "wrapper"
mk_DBusServerNewConnectionCallback :: C_DBusServerNewConnectionCallback -> IO (FunPtr C_DBusServerNewConnectionCallback)
genClosure_DBusServerNewConnection :: MonadIO m => DBusServerNewConnectionCallback -> m (GClosure C_DBusServerNewConnectionCallback)
genClosure_DBusServerNewConnection :: DBusServerNewConnectionCallback
-> m (GClosure C_DBusServerNewConnectionCallback)
genClosure_DBusServerNewConnection DBusServerNewConnectionCallback
cb = IO (GClosure C_DBusServerNewConnectionCallback)
-> m (GClosure C_DBusServerNewConnectionCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_DBusServerNewConnectionCallback)
-> m (GClosure C_DBusServerNewConnectionCallback))
-> IO (GClosure C_DBusServerNewConnectionCallback)
-> m (GClosure C_DBusServerNewConnectionCallback)
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_DBusServerNewConnectionCallback
cb' = DBusServerNewConnectionCallback
-> C_DBusServerNewConnectionCallback
wrap_DBusServerNewConnectionCallback DBusServerNewConnectionCallback
cb
C_DBusServerNewConnectionCallback
-> IO (FunPtr C_DBusServerNewConnectionCallback)
mk_DBusServerNewConnectionCallback C_DBusServerNewConnectionCallback
cb' IO (FunPtr C_DBusServerNewConnectionCallback)
-> (FunPtr C_DBusServerNewConnectionCallback
-> IO (GClosure C_DBusServerNewConnectionCallback))
-> IO (GClosure C_DBusServerNewConnectionCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_DBusServerNewConnectionCallback
-> IO (GClosure C_DBusServerNewConnectionCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_DBusServerNewConnectionCallback ::
DBusServerNewConnectionCallback ->
C_DBusServerNewConnectionCallback
wrap_DBusServerNewConnectionCallback :: DBusServerNewConnectionCallback
-> C_DBusServerNewConnectionCallback
wrap_DBusServerNewConnectionCallback DBusServerNewConnectionCallback
_cb Ptr ()
_ Ptr DBusConnection
connection Ptr ()
_ = do
DBusConnection
connection' <- ((ManagedPtr DBusConnection -> DBusConnection)
-> Ptr DBusConnection -> IO DBusConnection
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr DBusConnection -> DBusConnection
Gio.DBusConnection.DBusConnection) Ptr DBusConnection
connection
Bool
result <- DBusServerNewConnectionCallback
_cb DBusConnection
connection'
let result' :: CInt
result' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
result
CInt -> IO CInt
forall (m :: * -> *) a. Monad m => a -> m a
return CInt
result'
onDBusServerNewConnection :: (IsDBusServer a, MonadIO m) => a -> DBusServerNewConnectionCallback -> m SignalHandlerId
onDBusServerNewConnection :: a -> DBusServerNewConnectionCallback -> m SignalHandlerId
onDBusServerNewConnection a
obj DBusServerNewConnectionCallback
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_DBusServerNewConnectionCallback
cb' = DBusServerNewConnectionCallback
-> C_DBusServerNewConnectionCallback
wrap_DBusServerNewConnectionCallback DBusServerNewConnectionCallback
cb
FunPtr C_DBusServerNewConnectionCallback
cb'' <- C_DBusServerNewConnectionCallback
-> IO (FunPtr C_DBusServerNewConnectionCallback)
mk_DBusServerNewConnectionCallback C_DBusServerNewConnectionCallback
cb'
a
-> Text
-> FunPtr C_DBusServerNewConnectionCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"new-connection" FunPtr C_DBusServerNewConnectionCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterDBusServerNewConnection :: (IsDBusServer a, MonadIO m) => a -> DBusServerNewConnectionCallback -> m SignalHandlerId
afterDBusServerNewConnection :: a -> DBusServerNewConnectionCallback -> m SignalHandlerId
afterDBusServerNewConnection a
obj DBusServerNewConnectionCallback
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_DBusServerNewConnectionCallback
cb' = DBusServerNewConnectionCallback
-> C_DBusServerNewConnectionCallback
wrap_DBusServerNewConnectionCallback DBusServerNewConnectionCallback
cb
FunPtr C_DBusServerNewConnectionCallback
cb'' <- C_DBusServerNewConnectionCallback
-> IO (FunPtr C_DBusServerNewConnectionCallback)
mk_DBusServerNewConnectionCallback C_DBusServerNewConnectionCallback
cb'
a
-> Text
-> FunPtr C_DBusServerNewConnectionCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"new-connection" FunPtr C_DBusServerNewConnectionCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data DBusServerNewConnectionSignalInfo
instance SignalInfo DBusServerNewConnectionSignalInfo where
type HaskellCallbackType DBusServerNewConnectionSignalInfo = DBusServerNewConnectionCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_DBusServerNewConnectionCallback cb
cb'' <- mk_DBusServerNewConnectionCallback cb'
connectSignalFunPtr obj "new-connection" cb'' connectMode detail
#endif
getDBusServerActive :: (MonadIO m, IsDBusServer o) => o -> m Bool
getDBusServerActive :: o -> m Bool
getDBusServerActive o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"active"
#if defined(ENABLE_OVERLOADING)
data DBusServerActivePropertyInfo
instance AttrInfo DBusServerActivePropertyInfo where
type AttrAllowedOps DBusServerActivePropertyInfo = '[ 'AttrGet]
type AttrBaseTypeConstraint DBusServerActivePropertyInfo = IsDBusServer
type AttrSetTypeConstraint DBusServerActivePropertyInfo = (~) ()
type AttrTransferTypeConstraint DBusServerActivePropertyInfo = (~) ()
type AttrTransferType DBusServerActivePropertyInfo = ()
type AttrGetType DBusServerActivePropertyInfo = Bool
type AttrLabel DBusServerActivePropertyInfo = "active"
type AttrOrigin DBusServerActivePropertyInfo = DBusServer
attrGet = getDBusServerActive
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
#endif
getDBusServerAddress :: (MonadIO m, IsDBusServer o) => o -> m (Maybe T.Text)
getDBusServerAddress :: o -> m (Maybe Text)
getDBusServerAddress o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"address"
constructDBusServerAddress :: (IsDBusServer o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructDBusServerAddress :: Text -> m (GValueConstruct o)
constructDBusServerAddress Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"address" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
#if defined(ENABLE_OVERLOADING)
data DBusServerAddressPropertyInfo
instance AttrInfo DBusServerAddressPropertyInfo where
type AttrAllowedOps DBusServerAddressPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint DBusServerAddressPropertyInfo = IsDBusServer
type AttrSetTypeConstraint DBusServerAddressPropertyInfo = (~) T.Text
type AttrTransferTypeConstraint DBusServerAddressPropertyInfo = (~) T.Text
type AttrTransferType DBusServerAddressPropertyInfo = T.Text
type AttrGetType DBusServerAddressPropertyInfo = (Maybe T.Text)
type AttrLabel DBusServerAddressPropertyInfo = "address"
type AttrOrigin DBusServerAddressPropertyInfo = DBusServer
attrGet = getDBusServerAddress
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructDBusServerAddress
attrClear = undefined
#endif
getDBusServerAuthenticationObserver :: (MonadIO m, IsDBusServer o) => o -> m (Maybe Gio.DBusAuthObserver.DBusAuthObserver)
getDBusServerAuthenticationObserver :: o -> m (Maybe DBusAuthObserver)
getDBusServerAuthenticationObserver o
obj = IO (Maybe DBusAuthObserver) -> m (Maybe DBusAuthObserver)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe DBusAuthObserver) -> m (Maybe DBusAuthObserver))
-> IO (Maybe DBusAuthObserver) -> m (Maybe DBusAuthObserver)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr DBusAuthObserver -> DBusAuthObserver)
-> IO (Maybe DBusAuthObserver)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"authentication-observer" ManagedPtr DBusAuthObserver -> DBusAuthObserver
Gio.DBusAuthObserver.DBusAuthObserver
constructDBusServerAuthenticationObserver :: (IsDBusServer o, MIO.MonadIO m, Gio.DBusAuthObserver.IsDBusAuthObserver a) => a -> m (GValueConstruct o)
constructDBusServerAuthenticationObserver :: a -> m (GValueConstruct o)
constructDBusServerAuthenticationObserver a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"authentication-observer" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)
#if defined(ENABLE_OVERLOADING)
data DBusServerAuthenticationObserverPropertyInfo
instance AttrInfo DBusServerAuthenticationObserverPropertyInfo where
type AttrAllowedOps DBusServerAuthenticationObserverPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint DBusServerAuthenticationObserverPropertyInfo = IsDBusServer
type AttrSetTypeConstraint DBusServerAuthenticationObserverPropertyInfo = Gio.DBusAuthObserver.IsDBusAuthObserver
type AttrTransferTypeConstraint DBusServerAuthenticationObserverPropertyInfo = Gio.DBusAuthObserver.IsDBusAuthObserver
type AttrTransferType DBusServerAuthenticationObserverPropertyInfo = Gio.DBusAuthObserver.DBusAuthObserver
type AttrGetType DBusServerAuthenticationObserverPropertyInfo = (Maybe Gio.DBusAuthObserver.DBusAuthObserver)
type AttrLabel DBusServerAuthenticationObserverPropertyInfo = "authentication-observer"
type AttrOrigin DBusServerAuthenticationObserverPropertyInfo = DBusServer
attrGet = getDBusServerAuthenticationObserver
attrSet = undefined
attrTransfer _ v = do
unsafeCastTo Gio.DBusAuthObserver.DBusAuthObserver v
attrConstruct = constructDBusServerAuthenticationObserver
attrClear = undefined
#endif
getDBusServerClientAddress :: (MonadIO m, IsDBusServer o) => o -> m T.Text
getDBusServerClientAddress :: o -> m Text
getDBusServerClientAddress o
obj = 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
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getDBusServerClientAddress" (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
"client-address"
#if defined(ENABLE_OVERLOADING)
data DBusServerClientAddressPropertyInfo
instance AttrInfo DBusServerClientAddressPropertyInfo where
type AttrAllowedOps DBusServerClientAddressPropertyInfo = '[ 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint DBusServerClientAddressPropertyInfo = IsDBusServer
type AttrSetTypeConstraint DBusServerClientAddressPropertyInfo = (~) ()
type AttrTransferTypeConstraint DBusServerClientAddressPropertyInfo = (~) ()
type AttrTransferType DBusServerClientAddressPropertyInfo = ()
type AttrGetType DBusServerClientAddressPropertyInfo = T.Text
type AttrLabel DBusServerClientAddressPropertyInfo = "client-address"
type AttrOrigin DBusServerClientAddressPropertyInfo = DBusServer
attrGet = getDBusServerClientAddress
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
#endif
getDBusServerFlags :: (MonadIO m, IsDBusServer o) => o -> m [Gio.Flags.DBusServerFlags]
getDBusServerFlags :: o -> m [DBusServerFlags]
getDBusServerFlags o
obj = IO [DBusServerFlags] -> m [DBusServerFlags]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [DBusServerFlags] -> m [DBusServerFlags])
-> IO [DBusServerFlags] -> m [DBusServerFlags]
forall a b. (a -> b) -> a -> b
$ o -> String -> IO [DBusServerFlags]
forall a b.
(GObject a, IsGFlag b, BoxedFlags b) =>
a -> String -> IO [b]
B.Properties.getObjectPropertyFlags o
obj String
"flags"
constructDBusServerFlags :: (IsDBusServer o, MIO.MonadIO m) => [Gio.Flags.DBusServerFlags] -> m (GValueConstruct o)
constructDBusServerFlags :: [DBusServerFlags] -> m (GValueConstruct o)
constructDBusServerFlags [DBusServerFlags]
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> [DBusServerFlags] -> IO (GValueConstruct o)
forall a o.
(IsGFlag a, BoxedFlags a) =>
String -> [a] -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyFlags String
"flags" [DBusServerFlags]
val
#if defined(ENABLE_OVERLOADING)
data DBusServerFlagsPropertyInfo
instance AttrInfo DBusServerFlagsPropertyInfo where
type AttrAllowedOps DBusServerFlagsPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint DBusServerFlagsPropertyInfo = IsDBusServer
type AttrSetTypeConstraint DBusServerFlagsPropertyInfo = (~) [Gio.Flags.DBusServerFlags]
type AttrTransferTypeConstraint DBusServerFlagsPropertyInfo = (~) [Gio.Flags.DBusServerFlags]
type AttrTransferType DBusServerFlagsPropertyInfo = [Gio.Flags.DBusServerFlags]
type AttrGetType DBusServerFlagsPropertyInfo = [Gio.Flags.DBusServerFlags]
type AttrLabel DBusServerFlagsPropertyInfo = "flags"
type AttrOrigin DBusServerFlagsPropertyInfo = DBusServer
attrGet = getDBusServerFlags
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructDBusServerFlags
attrClear = undefined
#endif
getDBusServerGuid :: (MonadIO m, IsDBusServer o) => o -> m T.Text
getDBusServerGuid :: o -> m Text
getDBusServerGuid o
obj = 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
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getDBusServerGuid" (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
"guid"
constructDBusServerGuid :: (IsDBusServer o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructDBusServerGuid :: Text -> m (GValueConstruct o)
constructDBusServerGuid Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"guid" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
#if defined(ENABLE_OVERLOADING)
data DBusServerGuidPropertyInfo
instance AttrInfo DBusServerGuidPropertyInfo where
type AttrAllowedOps DBusServerGuidPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint DBusServerGuidPropertyInfo = IsDBusServer
type AttrSetTypeConstraint DBusServerGuidPropertyInfo = (~) T.Text
type AttrTransferTypeConstraint DBusServerGuidPropertyInfo = (~) T.Text
type AttrTransferType DBusServerGuidPropertyInfo = T.Text
type AttrGetType DBusServerGuidPropertyInfo = T.Text
type AttrLabel DBusServerGuidPropertyInfo = "guid"
type AttrOrigin DBusServerGuidPropertyInfo = DBusServer
attrGet = getDBusServerGuid
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructDBusServerGuid
attrClear = undefined
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DBusServer
type instance O.AttributeList DBusServer = DBusServerAttributeList
type DBusServerAttributeList = ('[ '("active", DBusServerActivePropertyInfo), '("address", DBusServerAddressPropertyInfo), '("authenticationObserver", DBusServerAuthenticationObserverPropertyInfo), '("clientAddress", DBusServerClientAddressPropertyInfo), '("flags", DBusServerFlagsPropertyInfo), '("guid", DBusServerGuidPropertyInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
dBusServerActive :: AttrLabelProxy "active"
dBusServerActive = AttrLabelProxy
dBusServerAddress :: AttrLabelProxy "address"
dBusServerAddress = AttrLabelProxy
dBusServerAuthenticationObserver :: AttrLabelProxy "authenticationObserver"
dBusServerAuthenticationObserver = AttrLabelProxy
dBusServerClientAddress :: AttrLabelProxy "clientAddress"
dBusServerClientAddress = AttrLabelProxy
dBusServerFlags :: AttrLabelProxy "flags"
dBusServerFlags = AttrLabelProxy
dBusServerGuid :: AttrLabelProxy "guid"
dBusServerGuid = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList DBusServer = DBusServerSignalList
type DBusServerSignalList = ('[ '("newConnection", DBusServerNewConnectionSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "g_dbus_server_new_sync" g_dbus_server_new_sync ::
CString ->
CUInt ->
CString ->
Ptr Gio.DBusAuthObserver.DBusAuthObserver ->
Ptr Gio.Cancellable.Cancellable ->
Ptr (Ptr GError) ->
IO (Ptr DBusServer)
dBusServerNewSync ::
(B.CallStack.HasCallStack, MonadIO m, Gio.DBusAuthObserver.IsDBusAuthObserver a, Gio.Cancellable.IsCancellable b) =>
T.Text
-> [Gio.Flags.DBusServerFlags]
-> T.Text
-> Maybe (a)
-> Maybe (b)
-> m DBusServer
dBusServerNewSync :: Text
-> [DBusServerFlags] -> Text -> Maybe a -> Maybe b -> m DBusServer
dBusServerNewSync Text
address [DBusServerFlags]
flags Text
guid Maybe a
observer Maybe b
cancellable = IO DBusServer -> m DBusServer
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DBusServer -> m DBusServer) -> IO DBusServer -> m DBusServer
forall a b. (a -> b) -> a -> b
$ do
CString
address' <- Text -> IO CString
textToCString Text
address
let flags' :: CUInt
flags' = [DBusServerFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [DBusServerFlags]
flags
CString
guid' <- Text -> IO CString
textToCString Text
guid
Ptr DBusAuthObserver
maybeObserver <- case Maybe a
observer of
Maybe a
Nothing -> Ptr DBusAuthObserver -> IO (Ptr DBusAuthObserver)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr DBusAuthObserver
forall a. Ptr a
nullPtr
Just a
jObserver -> do
Ptr DBusAuthObserver
jObserver' <- a -> IO (Ptr DBusAuthObserver)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
jObserver
Ptr DBusAuthObserver -> IO (Ptr DBusAuthObserver)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr DBusAuthObserver
jObserver'
Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
Just b
jCancellable -> do
Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
IO DBusServer -> IO () -> IO DBusServer
forall a b. IO a -> IO b -> IO a
onException (do
Ptr DBusServer
result <- (Ptr (Ptr GError) -> IO (Ptr DBusServer)) -> IO (Ptr DBusServer)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr DBusServer)) -> IO (Ptr DBusServer))
-> (Ptr (Ptr GError) -> IO (Ptr DBusServer)) -> IO (Ptr DBusServer)
forall a b. (a -> b) -> a -> b
$ CString
-> CUInt
-> CString
-> Ptr DBusAuthObserver
-> Ptr Cancellable
-> Ptr (Ptr GError)
-> IO (Ptr DBusServer)
g_dbus_server_new_sync CString
address' CUInt
flags' CString
guid' Ptr DBusAuthObserver
maybeObserver Ptr Cancellable
maybeCancellable
Text -> Ptr DBusServer -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"dBusServerNewSync" Ptr DBusServer
result
DBusServer
result' <- ((ManagedPtr DBusServer -> DBusServer)
-> Ptr DBusServer -> IO DBusServer
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr DBusServer -> DBusServer
DBusServer) Ptr DBusServer
result
Maybe a -> (a -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe a
observer a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
address'
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
guid'
DBusServer -> IO DBusServer
forall (m :: * -> *) a. Monad m => a -> m a
return DBusServer
result'
) (do
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
address'
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
guid'
)
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "g_dbus_server_get_client_address" g_dbus_server_get_client_address ::
Ptr DBusServer ->
IO CString
dBusServerGetClientAddress ::
(B.CallStack.HasCallStack, MonadIO m, IsDBusServer a) =>
a
-> m T.Text
dBusServerGetClientAddress :: a -> m Text
dBusServerGetClientAddress a
server = 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 DBusServer
server' <- a -> IO (Ptr DBusServer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
server
CString
result <- Ptr DBusServer -> IO CString
g_dbus_server_get_client_address Ptr DBusServer
server'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"dBusServerGetClientAddress" CString
result
Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
server
Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data DBusServerGetClientAddressMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDBusServer a) => O.MethodInfo DBusServerGetClientAddressMethodInfo a signature where
overloadedMethod = dBusServerGetClientAddress
#endif
foreign import ccall "g_dbus_server_get_flags" g_dbus_server_get_flags ::
Ptr DBusServer ->
IO CUInt
dBusServerGetFlags ::
(B.CallStack.HasCallStack, MonadIO m, IsDBusServer a) =>
a
-> m [Gio.Flags.DBusServerFlags]
dBusServerGetFlags :: a -> m [DBusServerFlags]
dBusServerGetFlags a
server = IO [DBusServerFlags] -> m [DBusServerFlags]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [DBusServerFlags] -> m [DBusServerFlags])
-> IO [DBusServerFlags] -> m [DBusServerFlags]
forall a b. (a -> b) -> a -> b
$ do
Ptr DBusServer
server' <- a -> IO (Ptr DBusServer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
server
CUInt
result <- Ptr DBusServer -> IO CUInt
g_dbus_server_get_flags Ptr DBusServer
server'
let result' :: [DBusServerFlags]
result' = CUInt -> [DBusServerFlags]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
server
[DBusServerFlags] -> IO [DBusServerFlags]
forall (m :: * -> *) a. Monad m => a -> m a
return [DBusServerFlags]
result'
#if defined(ENABLE_OVERLOADING)
data DBusServerGetFlagsMethodInfo
instance (signature ~ (m [Gio.Flags.DBusServerFlags]), MonadIO m, IsDBusServer a) => O.MethodInfo DBusServerGetFlagsMethodInfo a signature where
overloadedMethod = dBusServerGetFlags
#endif
foreign import ccall "g_dbus_server_get_guid" g_dbus_server_get_guid ::
Ptr DBusServer ->
IO CString
dBusServerGetGuid ::
(B.CallStack.HasCallStack, MonadIO m, IsDBusServer a) =>
a
-> m T.Text
dBusServerGetGuid :: a -> m Text
dBusServerGetGuid a
server = 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 DBusServer
server' <- a -> IO (Ptr DBusServer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
server
CString
result <- Ptr DBusServer -> IO CString
g_dbus_server_get_guid Ptr DBusServer
server'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"dBusServerGetGuid" CString
result
Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
server
Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data DBusServerGetGuidMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDBusServer a) => O.MethodInfo DBusServerGetGuidMethodInfo a signature where
overloadedMethod = dBusServerGetGuid
#endif
foreign import ccall "g_dbus_server_is_active" g_dbus_server_is_active ::
Ptr DBusServer ->
IO CInt
dBusServerIsActive ::
(B.CallStack.HasCallStack, MonadIO m, IsDBusServer a) =>
a
-> m Bool
dBusServerIsActive :: a -> m Bool
dBusServerIsActive a
server = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr DBusServer
server' <- a -> IO (Ptr DBusServer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
server
CInt
result <- Ptr DBusServer -> IO CInt
g_dbus_server_is_active Ptr DBusServer
server'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
server
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data DBusServerIsActiveMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDBusServer a) => O.MethodInfo DBusServerIsActiveMethodInfo a signature where
overloadedMethod = dBusServerIsActive
#endif
foreign import ccall "g_dbus_server_start" g_dbus_server_start ::
Ptr DBusServer ->
IO ()
dBusServerStart ::
(B.CallStack.HasCallStack, MonadIO m, IsDBusServer a) =>
a
-> m ()
dBusServerStart :: a -> m ()
dBusServerStart a
server = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr DBusServer
server' <- a -> IO (Ptr DBusServer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
server
Ptr DBusServer -> IO ()
g_dbus_server_start Ptr DBusServer
server'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
server
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data DBusServerStartMethodInfo
instance (signature ~ (m ()), MonadIO m, IsDBusServer a) => O.MethodInfo DBusServerStartMethodInfo a signature where
overloadedMethod = dBusServerStart
#endif
foreign import ccall "g_dbus_server_stop" g_dbus_server_stop ::
Ptr DBusServer ->
IO ()
dBusServerStop ::
(B.CallStack.HasCallStack, MonadIO m, IsDBusServer a) =>
a
-> m ()
dBusServerStop :: a -> m ()
dBusServerStop a
server = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr DBusServer
server' <- a -> IO (Ptr DBusServer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
server
Ptr DBusServer -> IO ()
g_dbus_server_stop Ptr DBusServer
server'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
server
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data DBusServerStopMethodInfo
instance (signature ~ (m ()), MonadIO m, IsDBusServer a) => O.MethodInfo DBusServerStopMethodInfo a signature where
overloadedMethod = dBusServerStop
#endif