{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gio.Objects.TestDBus
(
TestDBus(..) ,
IsTestDBus ,
toTestDBus ,
#if defined(ENABLE_OVERLOADING)
ResolveTestDBusMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
TestDBusAddServiceDirMethodInfo ,
#endif
testDBusAddServiceDir ,
#if defined(ENABLE_OVERLOADING)
TestDBusDownMethodInfo ,
#endif
testDBusDown ,
#if defined(ENABLE_OVERLOADING)
TestDBusGetBusAddressMethodInfo ,
#endif
testDBusGetBusAddress ,
#if defined(ENABLE_OVERLOADING)
TestDBusGetFlagsMethodInfo ,
#endif
testDBusGetFlags ,
testDBusNew ,
#if defined(ENABLE_OVERLOADING)
TestDBusStopMethodInfo ,
#endif
testDBusStop ,
testDBusUnset ,
#if defined(ENABLE_OVERLOADING)
TestDBusUpMethodInfo ,
#endif
testDBusUp ,
#if defined(ENABLE_OVERLOADING)
TestDBusFlagsPropertyInfo ,
#endif
constructTestDBusFlags ,
getTestDBusFlags ,
#if defined(ENABLE_OVERLOADING)
testDBusFlags ,
#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.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
newtype TestDBus = TestDBus (SP.ManagedPtr TestDBus)
deriving (TestDBus -> TestDBus -> Bool
(TestDBus -> TestDBus -> Bool)
-> (TestDBus -> TestDBus -> Bool) -> Eq TestDBus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TestDBus -> TestDBus -> Bool
$c/= :: TestDBus -> TestDBus -> Bool
== :: TestDBus -> TestDBus -> Bool
$c== :: TestDBus -> TestDBus -> Bool
Eq)
instance SP.ManagedPtrNewtype TestDBus where
toManagedPtr :: TestDBus -> ManagedPtr TestDBus
toManagedPtr (TestDBus ManagedPtr TestDBus
p) = ManagedPtr TestDBus
p
foreign import ccall "g_test_dbus_get_type"
c_g_test_dbus_get_type :: IO B.Types.GType
instance B.Types.TypedObject TestDBus where
glibType :: IO GType
glibType = IO GType
c_g_test_dbus_get_type
instance B.Types.GObject TestDBus
instance B.GValue.IsGValue TestDBus where
toGValue :: TestDBus -> IO GValue
toGValue TestDBus
o = do
GType
gtype <- IO GType
c_g_test_dbus_get_type
TestDBus -> (Ptr TestDBus -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr TestDBus
o (GType
-> (GValue -> Ptr TestDBus -> IO ()) -> Ptr TestDBus -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr TestDBus -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO TestDBus
fromGValue GValue
gv = do
Ptr TestDBus
ptr <- GValue -> IO (Ptr TestDBus)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr TestDBus)
(ManagedPtr TestDBus -> TestDBus) -> Ptr TestDBus -> IO TestDBus
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr TestDBus -> TestDBus
TestDBus Ptr TestDBus
ptr
class (SP.GObject o, O.IsDescendantOf TestDBus o) => IsTestDBus o
instance (SP.GObject o, O.IsDescendantOf TestDBus o) => IsTestDBus o
instance O.HasParentTypes TestDBus
type instance O.ParentTypes TestDBus = '[GObject.Object.Object]
toTestDBus :: (MonadIO m, IsTestDBus o) => o -> m TestDBus
toTestDBus :: o -> m TestDBus
toTestDBus = IO TestDBus -> m TestDBus
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TestDBus -> m TestDBus)
-> (o -> IO TestDBus) -> o -> m TestDBus
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr TestDBus -> TestDBus) -> o -> IO TestDBus
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr TestDBus -> TestDBus
TestDBus
#if defined(ENABLE_OVERLOADING)
type family ResolveTestDBusMethod (t :: Symbol) (o :: *) :: * where
ResolveTestDBusMethod "addServiceDir" o = TestDBusAddServiceDirMethodInfo
ResolveTestDBusMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveTestDBusMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveTestDBusMethod "down" o = TestDBusDownMethodInfo
ResolveTestDBusMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveTestDBusMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveTestDBusMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveTestDBusMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveTestDBusMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveTestDBusMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveTestDBusMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveTestDBusMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveTestDBusMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveTestDBusMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveTestDBusMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveTestDBusMethod "stop" o = TestDBusStopMethodInfo
ResolveTestDBusMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveTestDBusMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveTestDBusMethod "up" o = TestDBusUpMethodInfo
ResolveTestDBusMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveTestDBusMethod "getBusAddress" o = TestDBusGetBusAddressMethodInfo
ResolveTestDBusMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveTestDBusMethod "getFlags" o = TestDBusGetFlagsMethodInfo
ResolveTestDBusMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveTestDBusMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveTestDBusMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveTestDBusMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveTestDBusMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveTestDBusMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveTestDBusMethod t TestDBus, O.MethodInfo info TestDBus p) => OL.IsLabel t (TestDBus -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif
getTestDBusFlags :: (MonadIO m, IsTestDBus o) => o -> m [Gio.Flags.TestDBusFlags]
getTestDBusFlags :: o -> m [TestDBusFlags]
getTestDBusFlags o
obj = IO [TestDBusFlags] -> m [TestDBusFlags]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [TestDBusFlags] -> m [TestDBusFlags])
-> IO [TestDBusFlags] -> m [TestDBusFlags]
forall a b. (a -> b) -> a -> b
$ o -> String -> IO [TestDBusFlags]
forall a b.
(GObject a, IsGFlag b, BoxedFlags b) =>
a -> String -> IO [b]
B.Properties.getObjectPropertyFlags o
obj String
"flags"
constructTestDBusFlags :: (IsTestDBus o, MIO.MonadIO m) => [Gio.Flags.TestDBusFlags] -> m (GValueConstruct o)
constructTestDBusFlags :: [TestDBusFlags] -> m (GValueConstruct o)
constructTestDBusFlags [TestDBusFlags]
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 -> [TestDBusFlags] -> IO (GValueConstruct o)
forall a o.
(IsGFlag a, BoxedFlags a) =>
String -> [a] -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyFlags String
"flags" [TestDBusFlags]
val
#if defined(ENABLE_OVERLOADING)
data TestDBusFlagsPropertyInfo
instance AttrInfo TestDBusFlagsPropertyInfo where
type AttrAllowedOps TestDBusFlagsPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint TestDBusFlagsPropertyInfo = IsTestDBus
type AttrSetTypeConstraint TestDBusFlagsPropertyInfo = (~) [Gio.Flags.TestDBusFlags]
type AttrTransferTypeConstraint TestDBusFlagsPropertyInfo = (~) [Gio.Flags.TestDBusFlags]
type AttrTransferType TestDBusFlagsPropertyInfo = [Gio.Flags.TestDBusFlags]
type AttrGetType TestDBusFlagsPropertyInfo = [Gio.Flags.TestDBusFlags]
type AttrLabel TestDBusFlagsPropertyInfo = "flags"
type AttrOrigin TestDBusFlagsPropertyInfo = TestDBus
attrGet = getTestDBusFlags
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructTestDBusFlags
attrClear = undefined
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList TestDBus
type instance O.AttributeList TestDBus = TestDBusAttributeList
type TestDBusAttributeList = ('[ '("flags", TestDBusFlagsPropertyInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
testDBusFlags :: AttrLabelProxy "flags"
testDBusFlags = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList TestDBus = TestDBusSignalList
type TestDBusSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "g_test_dbus_new" g_test_dbus_new ::
CUInt ->
IO (Ptr TestDBus)
testDBusNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
[Gio.Flags.TestDBusFlags]
-> m TestDBus
testDBusNew :: [TestDBusFlags] -> m TestDBus
testDBusNew [TestDBusFlags]
flags = IO TestDBus -> m TestDBus
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TestDBus -> m TestDBus) -> IO TestDBus -> m TestDBus
forall a b. (a -> b) -> a -> b
$ do
let flags' :: CUInt
flags' = [TestDBusFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [TestDBusFlags]
flags
Ptr TestDBus
result <- CUInt -> IO (Ptr TestDBus)
g_test_dbus_new CUInt
flags'
Text -> Ptr TestDBus -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"testDBusNew" Ptr TestDBus
result
TestDBus
result' <- ((ManagedPtr TestDBus -> TestDBus) -> Ptr TestDBus -> IO TestDBus
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr TestDBus -> TestDBus
TestDBus) Ptr TestDBus
result
TestDBus -> IO TestDBus
forall (m :: * -> *) a. Monad m => a -> m a
return TestDBus
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "g_test_dbus_add_service_dir" g_test_dbus_add_service_dir ::
Ptr TestDBus ->
CString ->
IO ()
testDBusAddServiceDir ::
(B.CallStack.HasCallStack, MonadIO m, IsTestDBus a) =>
a
-> T.Text
-> m ()
testDBusAddServiceDir :: a -> Text -> m ()
testDBusAddServiceDir a
self Text
path = 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 TestDBus
self' <- a -> IO (Ptr TestDBus)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CString
path' <- Text -> IO CString
textToCString Text
path
Ptr TestDBus -> CString -> IO ()
g_test_dbus_add_service_dir Ptr TestDBus
self' CString
path'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
path'
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TestDBusAddServiceDirMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsTestDBus a) => O.MethodInfo TestDBusAddServiceDirMethodInfo a signature where
overloadedMethod = testDBusAddServiceDir
#endif
foreign import ccall "g_test_dbus_down" g_test_dbus_down ::
Ptr TestDBus ->
IO ()
testDBusDown ::
(B.CallStack.HasCallStack, MonadIO m, IsTestDBus a) =>
a
-> m ()
testDBusDown :: a -> m ()
testDBusDown a
self = 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 TestDBus
self' <- a -> IO (Ptr TestDBus)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr TestDBus -> IO ()
g_test_dbus_down Ptr TestDBus
self'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TestDBusDownMethodInfo
instance (signature ~ (m ()), MonadIO m, IsTestDBus a) => O.MethodInfo TestDBusDownMethodInfo a signature where
overloadedMethod = testDBusDown
#endif
foreign import ccall "g_test_dbus_get_bus_address" g_test_dbus_get_bus_address ::
Ptr TestDBus ->
IO CString
testDBusGetBusAddress ::
(B.CallStack.HasCallStack, MonadIO m, IsTestDBus a) =>
a
-> m (Maybe T.Text)
testDBusGetBusAddress :: a -> m (Maybe Text)
testDBusGetBusAddress a
self = 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
$ do
Ptr TestDBus
self' <- a -> IO (Ptr TestDBus)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CString
result <- Ptr TestDBus -> IO CString
g_test_dbus_get_bus_address Ptr TestDBus
self'
Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult
#if defined(ENABLE_OVERLOADING)
data TestDBusGetBusAddressMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsTestDBus a) => O.MethodInfo TestDBusGetBusAddressMethodInfo a signature where
overloadedMethod = testDBusGetBusAddress
#endif
foreign import ccall "g_test_dbus_get_flags" g_test_dbus_get_flags ::
Ptr TestDBus ->
IO CUInt
testDBusGetFlags ::
(B.CallStack.HasCallStack, MonadIO m, IsTestDBus a) =>
a
-> m [Gio.Flags.TestDBusFlags]
testDBusGetFlags :: a -> m [TestDBusFlags]
testDBusGetFlags a
self = IO [TestDBusFlags] -> m [TestDBusFlags]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [TestDBusFlags] -> m [TestDBusFlags])
-> IO [TestDBusFlags] -> m [TestDBusFlags]
forall a b. (a -> b) -> a -> b
$ do
Ptr TestDBus
self' <- a -> IO (Ptr TestDBus)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CUInt
result <- Ptr TestDBus -> IO CUInt
g_test_dbus_get_flags Ptr TestDBus
self'
let result' :: [TestDBusFlags]
result' = CUInt -> [TestDBusFlags]
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
self
[TestDBusFlags] -> IO [TestDBusFlags]
forall (m :: * -> *) a. Monad m => a -> m a
return [TestDBusFlags]
result'
#if defined(ENABLE_OVERLOADING)
data TestDBusGetFlagsMethodInfo
instance (signature ~ (m [Gio.Flags.TestDBusFlags]), MonadIO m, IsTestDBus a) => O.MethodInfo TestDBusGetFlagsMethodInfo a signature where
overloadedMethod = testDBusGetFlags
#endif
foreign import ccall "g_test_dbus_stop" g_test_dbus_stop ::
Ptr TestDBus ->
IO ()
testDBusStop ::
(B.CallStack.HasCallStack, MonadIO m, IsTestDBus a) =>
a
-> m ()
testDBusStop :: a -> m ()
testDBusStop a
self = 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 TestDBus
self' <- a -> IO (Ptr TestDBus)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr TestDBus -> IO ()
g_test_dbus_stop Ptr TestDBus
self'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TestDBusStopMethodInfo
instance (signature ~ (m ()), MonadIO m, IsTestDBus a) => O.MethodInfo TestDBusStopMethodInfo a signature where
overloadedMethod = testDBusStop
#endif
foreign import ccall "g_test_dbus_up" g_test_dbus_up ::
Ptr TestDBus ->
IO ()
testDBusUp ::
(B.CallStack.HasCallStack, MonadIO m, IsTestDBus a) =>
a
-> m ()
testDBusUp :: a -> m ()
testDBusUp a
self = 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 TestDBus
self' <- a -> IO (Ptr TestDBus)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr TestDBus -> IO ()
g_test_dbus_up Ptr TestDBus
self'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TestDBusUpMethodInfo
instance (signature ~ (m ()), MonadIO m, IsTestDBus a) => O.MethodInfo TestDBusUpMethodInfo a signature where
overloadedMethod = testDBusUp
#endif
foreign import ccall "g_test_dbus_unset" g_test_dbus_unset ::
IO ()
testDBusUnset ::
(B.CallStack.HasCallStack, MonadIO m) =>
m ()
testDBusUnset :: m ()
testDBusUnset = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
IO ()
g_test_dbus_unset
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
#endif