{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A helper class for testing code which uses D-Bus without touching the user\'s
-- session bus.
-- 
-- Note that t'GI.Gio.Objects.TestDBus.TestDBus' modifies the user’s environment, calling @/setenv()/@.
-- This is not thread-safe, so all t'GI.Gio.Objects.TestDBus.TestDBus' calls should be completed before
-- threads are spawned, or should have appropriate locking to ensure no access
-- conflicts to environment variables shared between t'GI.Gio.Objects.TestDBus.TestDBus' and other
-- threads.
-- 
-- == Creating unit tests using GTestDBus
-- 
-- Testing of D-Bus services can be tricky because normally we only ever run
-- D-Bus services over an existing instance of the D-Bus daemon thus we
-- usually don\'t activate D-Bus services that are not yet installed into the
-- target system. The t'GI.Gio.Objects.TestDBus.TestDBus' object makes this easier for us by taking care
-- of the lower level tasks such as running a private D-Bus daemon and looking
-- up uninstalled services in customizable locations, typically in your source
-- code tree.
-- 
-- The first thing you will need is a separate service description file for the
-- D-Bus daemon. Typically a @services@ subdirectory of your @tests@ directory
-- is a good place to put this file.
-- 
-- The service file should list your service along with an absolute path to the
-- uninstalled service executable in your source tree. Using autotools we would
-- achieve this by adding a file such as @my-server.service.in@ in the services
-- directory and have it processed by configure.
-- >
-- >    [D-BUS Service]
-- >    Name=org.gtk.GDBus.Examples.ObjectManager
-- >    Exec=@abs_top_builddir@/gio/tests/gdbus-example-objectmanager-server
-- 
-- You will also need to indicate this service directory in your test
-- fixtures, so you will need to pass the path while compiling your
-- test cases. Typically this is done with autotools with an added
-- preprocessor flag specified to compile your tests such as:
-- >
-- >    -DTEST_SERVICES=\""$(abs_top_builddir)/tests/services"\"
-- 
--     Once you have a service definition file which is local to your source tree,
-- you can proceed to set up a GTest fixture using the t'GI.Gio.Objects.TestDBus.TestDBus' scaffolding.
-- 
-- An example of a test fixture for D-Bus services can be found
-- here:
-- <https://git.gnome.org/browse/glib/tree/gio/tests/gdbus-test-fixture.c gdbus-test-fixture.c>
-- 
-- Note that these examples only deal with isolating the D-Bus aspect of your
-- service. To successfully run isolated unit tests on your service you may need
-- some additional modifications to your test case fixture. For example; if your
-- service uses GSettings and installs a schema then it is important that your test service
-- not load the schema in the ordinary installed location (chances are that your service
-- and schema files are not yet installed, or worse; there is an older version of the
-- schema file sitting in the install location).
-- 
-- Most of the time we can work around these obstacles using the
-- environment. Since the environment is inherited by the D-Bus daemon
-- created by t'GI.Gio.Objects.TestDBus.TestDBus' and then in turn inherited by any services the
-- D-Bus daemon activates, using the setup routine for your fixture is
-- a practical place to help sandbox your runtime environment. For the
-- rather typical GSettings case we can work around this by setting
-- @GSETTINGS_SCHEMA_DIR@ to the in tree directory holding your schemas
-- in the above @/fixture_setup()/@ routine.
-- 
-- The GSettings schemas need to be locally pre-compiled for this to work. This can be achieved
-- by compiling the schemas locally as a step before running test cases, an autotools setup might
-- do the following in the directory holding schemas:
-- >
-- >    all-am:
-- >            $(GLIB_COMPILE_SCHEMAS) .
-- >
-- >    CLEANFILES += gschemas.compiled
-- 
-- 
-- /Since: 2.34/

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

module GI.Gio.Objects.TestDBus
    ( 

-- * Exported types
    TestDBus(..)                            ,
    IsTestDBus                              ,
    toTestDBus                              ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [addServiceDir]("GI.Gio.Objects.TestDBus#g:method:addServiceDir"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [down]("GI.Gio.Objects.TestDBus#g:method:down"), [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"), [stop]("GI.Gio.Objects.TestDBus#g:method:stop"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [up]("GI.Gio.Objects.TestDBus#g:method:up"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getBusAddress]("GI.Gio.Objects.TestDBus#g:method:getBusAddress"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getFlags]("GI.Gio.Objects.TestDBus#g:method:getFlags"), [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)
    ResolveTestDBusMethod                   ,
#endif

-- ** addServiceDir #method:addServiceDir#

#if defined(ENABLE_OVERLOADING)
    TestDBusAddServiceDirMethodInfo         ,
#endif
    testDBusAddServiceDir                   ,


-- ** down #method:down#

#if defined(ENABLE_OVERLOADING)
    TestDBusDownMethodInfo                  ,
#endif
    testDBusDown                            ,


-- ** getBusAddress #method:getBusAddress#

#if defined(ENABLE_OVERLOADING)
    TestDBusGetBusAddressMethodInfo         ,
#endif
    testDBusGetBusAddress                   ,


-- ** getFlags #method:getFlags#

#if defined(ENABLE_OVERLOADING)
    TestDBusGetFlagsMethodInfo              ,
#endif
    testDBusGetFlags                        ,


-- ** new #method:new#

    testDBusNew                             ,


-- ** stop #method:stop#

#if defined(ENABLE_OVERLOADING)
    TestDBusStopMethodInfo                  ,
#endif
    testDBusStop                            ,


-- ** unset #method:unset#

    testDBusUnset                           ,


-- ** up #method:up#

#if defined(ENABLE_OVERLOADING)
    TestDBusUpMethodInfo                    ,
#endif
    testDBusUp                              ,




 -- * Properties


-- ** flags #attr:flags#
-- | t'GI.Gio.Flags.TestDBusFlags' specifying the behaviour of the D-Bus session.
-- 
-- /Since: 2.34/

#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.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.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.Flags as Gio.Flags

-- | Memory-managed wrapper type.
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

-- | Type class for types which can be safely cast to `TestDBus`, for instance with `toTestDBus`.
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]

-- | Cast to `TestDBus`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toTestDBus :: (MIO.MonadIO m, IsTestDBus o) => o -> m TestDBus
toTestDBus :: forall (m :: * -> *) o.
(MonadIO m, IsTestDBus o) =>
o -> m TestDBus
toTestDBus = IO TestDBus -> m TestDBus
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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'
B.ManagedPtr.unsafeCastTo ManagedPtr TestDBus -> TestDBus
TestDBus

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

#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.OverloadedMethod 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

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveTestDBusMethod t TestDBus, O.OverloadedMethod info TestDBus p, R.HasField t TestDBus p) => R.HasField t TestDBus p where
    getField = O.overloadedMethod @info

#endif

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

#endif

-- VVV Prop "flags"
   -- Type: TInterface (Name {namespace = "Gio", name = "TestDBusFlags"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@flags@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' testDBus #flags
-- @
getTestDBusFlags :: (MonadIO m, IsTestDBus o) => o -> m [Gio.Flags.TestDBusFlags]
getTestDBusFlags :: forall (m :: * -> *) o.
(MonadIO m, IsTestDBus o) =>
o -> m [TestDBusFlags]
getTestDBusFlags o
obj = IO [TestDBusFlags] -> m [TestDBusFlags]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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"

-- | Construct a `GValueConstruct` with valid value for the “@flags@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructTestDBusFlags :: (IsTestDBus o, MIO.MonadIO m) => [Gio.Flags.TestDBusFlags] -> m (GValueConstruct o)
constructTestDBusFlags :: forall o (m :: * -> *).
(IsTestDBus o, MonadIO m) =>
[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
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (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

-- method TestDBus::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TestDBusFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTestDBusFlags" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "TestDBus" })
-- throws : False
-- Skip return : False

foreign import ccall "g_test_dbus_new" g_test_dbus_new :: 
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gio", name = "TestDBusFlags"})
    IO (Ptr TestDBus)

-- | Create a new t'GI.Gio.Objects.TestDBus.TestDBus' object.
testDBusNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    [Gio.Flags.TestDBusFlags]
    -- ^ /@flags@/: a t'GI.Gio.Flags.TestDBusFlags'
    -> m TestDBus
    -- ^ __Returns:__ a new t'GI.Gio.Objects.TestDBus.TestDBus'.
testDBusNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
[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

-- method TestDBus::add_service_dir
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TestDBus" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTestDBus" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "path"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "path to a directory containing .service files"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_test_dbus_add_service_dir" g_test_dbus_add_service_dir :: 
    Ptr TestDBus ->                         -- self : TInterface (Name {namespace = "Gio", name = "TestDBus"})
    CString ->                              -- path : TBasicType TUTF8
    IO ()

-- | Add a path where dbus-daemon will look up .service files. This can\'t be
-- called after 'GI.Gio.Objects.TestDBus.testDBusUp'.
testDBusAddServiceDir ::
    (B.CallStack.HasCallStack, MonadIO m, IsTestDBus a) =>
    a
    -- ^ /@self@/: a t'GI.Gio.Objects.TestDBus.TestDBus'
    -> T.Text
    -- ^ /@path@/: path to a directory containing .service files
    -> m ()
testDBusAddServiceDir :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTestDBus a) =>
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.OverloadedMethod TestDBusAddServiceDirMethodInfo a signature where
    overloadedMethod = testDBusAddServiceDir

instance O.OverloadedMethodInfo TestDBusAddServiceDirMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Objects.TestDBus.testDBusAddServiceDir",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Objects-TestDBus.html#v:testDBusAddServiceDir"
        }


#endif

-- method TestDBus::down
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TestDBus" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTestDBus" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_test_dbus_down" g_test_dbus_down :: 
    Ptr TestDBus ->                         -- self : TInterface (Name {namespace = "Gio", name = "TestDBus"})
    IO ()

-- | Stop the session bus started by 'GI.Gio.Objects.TestDBus.testDBusUp'.
-- 
-- This will wait for the singleton returned by 'GI.Gio.Functions.busGet' or 'GI.Gio.Functions.busGetSync'
-- to be destroyed. This is done to ensure that the next unit test won\'t get a
-- leaked singleton from this test.
testDBusDown ::
    (B.CallStack.HasCallStack, MonadIO m, IsTestDBus a) =>
    a
    -- ^ /@self@/: a t'GI.Gio.Objects.TestDBus.TestDBus'
    -> m ()
testDBusDown :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTestDBus a) =>
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.OverloadedMethod TestDBusDownMethodInfo a signature where
    overloadedMethod = testDBusDown

instance O.OverloadedMethodInfo TestDBusDownMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Objects.TestDBus.testDBusDown",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Objects-TestDBus.html#v:testDBusDown"
        }


#endif

-- method TestDBus::get_bus_address
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TestDBus" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTestDBus" , 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_test_dbus_get_bus_address" g_test_dbus_get_bus_address :: 
    Ptr TestDBus ->                         -- self : TInterface (Name {namespace = "Gio", name = "TestDBus"})
    IO CString

-- | Get the address on which dbus-daemon is running. If 'GI.Gio.Objects.TestDBus.testDBusUp' has not
-- been called yet, 'P.Nothing' is returned. This can be used with
-- 'GI.Gio.Objects.DBusConnection.dBusConnectionNewForAddress'.
testDBusGetBusAddress ::
    (B.CallStack.HasCallStack, MonadIO m, IsTestDBus a) =>
    a
    -- ^ /@self@/: a t'GI.Gio.Objects.TestDBus.TestDBus'
    -> m (Maybe T.Text)
    -- ^ __Returns:__ the address of the bus, or 'P.Nothing'.
testDBusGetBusAddress :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTestDBus a) =>
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.OverloadedMethod TestDBusGetBusAddressMethodInfo a signature where
    overloadedMethod = testDBusGetBusAddress

instance O.OverloadedMethodInfo TestDBusGetBusAddressMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Objects.TestDBus.testDBusGetBusAddress",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Objects-TestDBus.html#v:testDBusGetBusAddress"
        }


#endif

-- method TestDBus::get_flags
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TestDBus" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTestDBus" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gio" , name = "TestDBusFlags" })
-- throws : False
-- Skip return : False

foreign import ccall "g_test_dbus_get_flags" g_test_dbus_get_flags :: 
    Ptr TestDBus ->                         -- self : TInterface (Name {namespace = "Gio", name = "TestDBus"})
    IO CUInt

-- | Get the flags of the t'GI.Gio.Objects.TestDBus.TestDBus' object.
testDBusGetFlags ::
    (B.CallStack.HasCallStack, MonadIO m, IsTestDBus a) =>
    a
    -- ^ /@self@/: a t'GI.Gio.Objects.TestDBus.TestDBus'
    -> m [Gio.Flags.TestDBusFlags]
    -- ^ __Returns:__ the value of t'GI.Gio.Objects.TestDBus.TestDBus':@/flags/@ property
testDBusGetFlags :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTestDBus a) =>
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.OverloadedMethod TestDBusGetFlagsMethodInfo a signature where
    overloadedMethod = testDBusGetFlags

instance O.OverloadedMethodInfo TestDBusGetFlagsMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Objects.TestDBus.testDBusGetFlags",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Objects-TestDBus.html#v:testDBusGetFlags"
        }


#endif

-- method TestDBus::stop
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TestDBus" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTestDBus" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_test_dbus_stop" g_test_dbus_stop :: 
    Ptr TestDBus ->                         -- self : TInterface (Name {namespace = "Gio", name = "TestDBus"})
    IO ()

-- | Stop the session bus started by 'GI.Gio.Objects.TestDBus.testDBusUp'.
-- 
-- Unlike 'GI.Gio.Objects.TestDBus.testDBusDown', this won\'t verify the t'GI.Gio.Objects.DBusConnection.DBusConnection'
-- singleton returned by 'GI.Gio.Functions.busGet' or 'GI.Gio.Functions.busGetSync' is destroyed. Unit
-- tests wanting to verify behaviour after the session bus has been stopped
-- can use this function but should still call 'GI.Gio.Objects.TestDBus.testDBusDown' when done.
testDBusStop ::
    (B.CallStack.HasCallStack, MonadIO m, IsTestDBus a) =>
    a
    -- ^ /@self@/: a t'GI.Gio.Objects.TestDBus.TestDBus'
    -> m ()
testDBusStop :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTestDBus a) =>
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.OverloadedMethod TestDBusStopMethodInfo a signature where
    overloadedMethod = testDBusStop

instance O.OverloadedMethodInfo TestDBusStopMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Objects.TestDBus.testDBusStop",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Objects-TestDBus.html#v:testDBusStop"
        }


#endif

-- method TestDBus::up
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TestDBus" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTestDBus" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_test_dbus_up" g_test_dbus_up :: 
    Ptr TestDBus ->                         -- self : TInterface (Name {namespace = "Gio", name = "TestDBus"})
    IO ()

-- | Start a dbus-daemon instance and set DBUS_SESSION_BUS_ADDRESS. After this
-- call, it is safe for unit tests to start sending messages on the session bus.
-- 
-- If this function is called from setup callback of @/g_test_add()/@,
-- 'GI.Gio.Objects.TestDBus.testDBusDown' must be called in its teardown callback.
-- 
-- If this function is called from unit test\'s @/main()/@, then 'GI.Gio.Objects.TestDBus.testDBusDown'
-- must be called after 'GI.GLib.Functions.testRun'.
testDBusUp ::
    (B.CallStack.HasCallStack, MonadIO m, IsTestDBus a) =>
    a
    -- ^ /@self@/: a t'GI.Gio.Objects.TestDBus.TestDBus'
    -> m ()
testDBusUp :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTestDBus a) =>
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.OverloadedMethod TestDBusUpMethodInfo a signature where
    overloadedMethod = testDBusUp

instance O.OverloadedMethodInfo TestDBusUpMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Objects.TestDBus.testDBusUp",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Objects-TestDBus.html#v:testDBusUp"
        }


#endif

-- method TestDBus::unset
-- method type : MemberFunction
-- Args: []
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_test_dbus_unset" g_test_dbus_unset :: 
    IO ()

-- | Unset DISPLAY and DBUS_SESSION_BUS_ADDRESS env variables to ensure the test
-- won\'t use user\'s session bus.
-- 
-- This is useful for unit tests that want to verify behaviour when no session
-- bus is running. It is not necessary to call this if unit test already calls
-- 'GI.Gio.Objects.TestDBus.testDBusUp' before acquiring the session bus.
testDBusUnset ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m ()
testDBusUnset :: forall (m :: * -> *). (HasCallStack, MonadIO m) => 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