{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- An IBusService is a base class for services.

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

module GI.IBus.Objects.Service
    ( 

-- * Exported types
    Service(..)                             ,
    IsService                               ,
    toService                               ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [destroy]("GI.IBus.Objects.Object#g:method:destroy"), [emitSignal]("GI.IBus.Objects.Service#g:method:emitSignal"), [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"), [register]("GI.IBus.Objects.Service#g:method:register"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [unregister]("GI.IBus.Objects.Service#g:method:unregister"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getConnection]("GI.IBus.Objects.Service#g:method:getConnection"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getObjectPath]("GI.IBus.Objects.Service#g:method:getObjectPath"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveServiceMethod                    ,
#endif

-- ** emitSignal #method:emitSignal#

#if defined(ENABLE_OVERLOADING)
    ServiceEmitSignalMethodInfo             ,
#endif
    serviceEmitSignal                       ,


-- ** getConnection #method:getConnection#

#if defined(ENABLE_OVERLOADING)
    ServiceGetConnectionMethodInfo          ,
#endif
    serviceGetConnection                    ,


-- ** getObjectPath #method:getObjectPath#

#if defined(ENABLE_OVERLOADING)
    ServiceGetObjectPathMethodInfo          ,
#endif
    serviceGetObjectPath                    ,


-- ** new #method:new#

    serviceNew                              ,


-- ** register #method:register#

#if defined(ENABLE_OVERLOADING)
    ServiceRegisterMethodInfo               ,
#endif
    serviceRegister                         ,


-- ** unregister #method:unregister#

#if defined(ENABLE_OVERLOADING)
    ServiceUnregisterMethodInfo             ,
#endif
    serviceUnregister                       ,




 -- * Properties


-- ** connection #attr:connection#
-- | The connection of service object.

#if defined(ENABLE_OVERLOADING)
    ServiceConnectionPropertyInfo           ,
#endif
    constructServiceConnection              ,
    getServiceConnection                    ,
#if defined(ENABLE_OVERLOADING)
    serviceConnection                       ,
#endif


-- ** objectPath #attr:objectPath#
-- | The path of service object.

#if defined(ENABLE_OVERLOADING)
    ServiceObjectPathPropertyInfo           ,
#endif
    constructServiceObjectPath              ,
    getServiceObjectPath                    ,
#if defined(ENABLE_OVERLOADING)
    serviceObjectPath                       ,
#endif




    ) where

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

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.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 qualified GI.Gio.Objects.DBusConnection as Gio.DBusConnection
import {-# SOURCE #-} qualified GI.IBus.Objects.Object as IBus.Object

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

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

foreign import ccall "ibus_service_get_type"
    c_ibus_service_get_type :: IO B.Types.GType

instance B.Types.TypedObject Service where
    glibType :: IO GType
glibType = IO GType
c_ibus_service_get_type

instance B.Types.GObject Service

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

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

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveServiceMethod (t :: Symbol) (o :: *) :: * where
    ResolveServiceMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveServiceMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveServiceMethod "destroy" o = IBus.Object.ObjectDestroyMethodInfo
    ResolveServiceMethod "emitSignal" o = ServiceEmitSignalMethodInfo
    ResolveServiceMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveServiceMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveServiceMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveServiceMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveServiceMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveServiceMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveServiceMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveServiceMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveServiceMethod "register" o = ServiceRegisterMethodInfo
    ResolveServiceMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveServiceMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveServiceMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveServiceMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveServiceMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveServiceMethod "unregister" o = ServiceUnregisterMethodInfo
    ResolveServiceMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveServiceMethod "getConnection" o = ServiceGetConnectionMethodInfo
    ResolveServiceMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveServiceMethod "getObjectPath" o = ServiceGetObjectPathMethodInfo
    ResolveServiceMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveServiceMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveServiceMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveServiceMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveServiceMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveServiceMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

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

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

-- | Construct a `GValueConstruct` with valid value for the “@connection@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructServiceConnection :: (IsService o, MIO.MonadIO m, Gio.DBusConnection.IsDBusConnection a) => a -> m (GValueConstruct o)
constructServiceConnection :: forall o (m :: * -> *) a.
(IsService o, MonadIO m, IsDBusConnection a) =>
a -> m (GValueConstruct o)
constructServiceConnection a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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 a. IO a -> IO a
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 -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"connection" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

#if defined(ENABLE_OVERLOADING)
data ServiceConnectionPropertyInfo
instance AttrInfo ServiceConnectionPropertyInfo where
    type AttrAllowedOps ServiceConnectionPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ServiceConnectionPropertyInfo = IsService
    type AttrSetTypeConstraint ServiceConnectionPropertyInfo = Gio.DBusConnection.IsDBusConnection
    type AttrTransferTypeConstraint ServiceConnectionPropertyInfo = Gio.DBusConnection.IsDBusConnection
    type AttrTransferType ServiceConnectionPropertyInfo = Gio.DBusConnection.DBusConnection
    type AttrGetType ServiceConnectionPropertyInfo = Gio.DBusConnection.DBusConnection
    type AttrLabel ServiceConnectionPropertyInfo = "connection"
    type AttrOrigin ServiceConnectionPropertyInfo = Service
    attrGet = getServiceConnection
    attrSet = undefined
    attrTransfer _ v = do
        unsafeCastTo Gio.DBusConnection.DBusConnection v
    attrConstruct = constructServiceConnection
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.IBus.Objects.Service.connection"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ibus-1.5.5/docs/GI-IBus-Objects-Service.html#g:attr:connection"
        })
#endif

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

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

-- | Construct a `GValueConstruct` with valid value for the “@object-path@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructServiceObjectPath :: (IsService o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructServiceObjectPath :: forall o (m :: * -> *).
(IsService o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructServiceObjectPath Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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 a. IO a -> IO a
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 -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"object-path" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

#if defined(ENABLE_OVERLOADING)
data ServiceObjectPathPropertyInfo
instance AttrInfo ServiceObjectPathPropertyInfo where
    type AttrAllowedOps ServiceObjectPathPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ServiceObjectPathPropertyInfo = IsService
    type AttrSetTypeConstraint ServiceObjectPathPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint ServiceObjectPathPropertyInfo = (~) T.Text
    type AttrTransferType ServiceObjectPathPropertyInfo = T.Text
    type AttrGetType ServiceObjectPathPropertyInfo = T.Text
    type AttrLabel ServiceObjectPathPropertyInfo = "object-path"
    type AttrOrigin ServiceObjectPathPropertyInfo = Service
    attrGet = getServiceObjectPath
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructServiceObjectPath
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.IBus.Objects.Service.objectPath"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ibus-1.5.5/docs/GI-IBus-Objects-Service.html#g:attr:objectPath"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Service
type instance O.AttributeList Service = ServiceAttributeList
type ServiceAttributeList = ('[ '("connection", ServiceConnectionPropertyInfo), '("objectPath", ServiceObjectPathPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
serviceConnection :: AttrLabelProxy "connection"
serviceConnection = AttrLabelProxy

serviceObjectPath :: AttrLabelProxy "objectPath"
serviceObjectPath = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Service = ServiceSignalList
type ServiceSignalList = ('[ '("destroy", IBus.Object.ObjectDestroySignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

-- method Service::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "connection"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A GDBusConnection." , 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 "Object path." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "IBus" , name = "Service" })
-- throws : False
-- Skip return : False

foreign import ccall "ibus_service_new" ibus_service_new :: 
    Ptr Gio.DBusConnection.DBusConnection -> -- connection : TInterface (Name {namespace = "Gio", name = "DBusConnection"})
    CString ->                              -- path : TBasicType TUTF8
    IO (Ptr Service)

-- | Creantes a new t'GI.IBus.Objects.Service.Service'.
serviceNew ::
    (B.CallStack.HasCallStack, MonadIO m, Gio.DBusConnection.IsDBusConnection a) =>
    a
    -- ^ /@connection@/: A GDBusConnection.
    -> T.Text
    -- ^ /@path@/: Object path.
    -> m Service
    -- ^ __Returns:__ A newly allocated t'GI.IBus.Objects.Service.Service'
serviceNew :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusConnection a) =>
a -> Text -> m Service
serviceNew a
connection Text
path = IO Service -> m Service
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Service -> m Service) -> IO Service -> m Service
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusConnection
connection' <- a -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
connection
    CString
path' <- Text -> IO CString
textToCString Text
path
    Ptr Service
result <- Ptr DBusConnection -> CString -> IO (Ptr Service)
ibus_service_new Ptr DBusConnection
connection' CString
path'
    Text -> Ptr Service -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"serviceNew" Ptr Service
result
    Service
result' <- ((ManagedPtr Service -> Service) -> Ptr Service -> IO Service
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Service -> Service
Service) Ptr Service
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
connection
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
path'
    Service -> IO Service
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Service
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Service::emit_signal
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "service"
--           , argType =
--               TInterface Name { namespace = "IBus" , name = "Service" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "dest_bus_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "interface_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "signal_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "parameters"
--           , argType = TVariant
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "ibus_service_emit_signal" ibus_service_emit_signal :: 
    Ptr Service ->                          -- service : TInterface (Name {namespace = "IBus", name = "Service"})
    CString ->                              -- dest_bus_name : TBasicType TUTF8
    CString ->                              -- interface_name : TBasicType TUTF8
    CString ->                              -- signal_name : TBasicType TUTF8
    Ptr GVariant ->                         -- parameters : TVariant
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | /No description available in the introspection data./
serviceEmitSignal ::
    (B.CallStack.HasCallStack, MonadIO m, IsService a) =>
    a
    -> T.Text
    -> T.Text
    -> T.Text
    -> GVariant
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
serviceEmitSignal :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsService a) =>
a -> Text -> Text -> Text -> GVariant -> m ()
serviceEmitSignal a
service Text
destBusName Text
interfaceName Text
signalName GVariant
parameters = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Service
service' <- a -> IO (Ptr Service)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
service
    CString
destBusName' <- Text -> IO CString
textToCString Text
destBusName
    CString
interfaceName' <- Text -> IO CString
textToCString Text
interfaceName
    CString
signalName' <- Text -> IO CString
textToCString Text
signalName
    Ptr GVariant
parameters' <- GVariant -> IO (Ptr GVariant)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GVariant
parameters
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr Service
-> CString
-> CString
-> CString
-> Ptr GVariant
-> Ptr (Ptr GError)
-> IO CInt
ibus_service_emit_signal Ptr Service
service' CString
destBusName' CString
interfaceName' CString
signalName' Ptr GVariant
parameters'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
service
        GVariant -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GVariant
parameters
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
destBusName'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
interfaceName'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
signalName'
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
destBusName'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
interfaceName'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
signalName'
     )

#if defined(ENABLE_OVERLOADING)
data ServiceEmitSignalMethodInfo
instance (signature ~ (T.Text -> T.Text -> T.Text -> GVariant -> m ()), MonadIO m, IsService a) => O.OverloadedMethod ServiceEmitSignalMethodInfo a signature where
    overloadedMethod = serviceEmitSignal

instance O.OverloadedMethodInfo ServiceEmitSignalMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.IBus.Objects.Service.serviceEmitSignal",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ibus-1.5.5/docs/GI-IBus-Objects-Service.html#v:serviceEmitSignal"
        })


#endif

-- method Service::get_connection
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "service"
--           , argType =
--               TInterface Name { namespace = "IBus" , name = "Service" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An IBusService." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gio" , name = "DBusConnection" })
-- throws : False
-- Skip return : False

foreign import ccall "ibus_service_get_connection" ibus_service_get_connection :: 
    Ptr Service ->                          -- service : TInterface (Name {namespace = "IBus", name = "Service"})
    IO (Ptr Gio.DBusConnection.DBusConnection)

-- | Gets a connections.
serviceGetConnection ::
    (B.CallStack.HasCallStack, MonadIO m, IsService a) =>
    a
    -- ^ /@service@/: An IBusService.
    -> m Gio.DBusConnection.DBusConnection
    -- ^ __Returns:__ A t'GI.Gio.Objects.DBusConnection.DBusConnection' of an t'GI.IBus.Objects.Service.Service' instance.
serviceGetConnection :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsService a) =>
a -> m DBusConnection
serviceGetConnection a
service = IO DBusConnection -> m DBusConnection
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DBusConnection -> m DBusConnection)
-> IO DBusConnection -> m DBusConnection
forall a b. (a -> b) -> a -> b
$ do
    Ptr Service
service' <- a -> IO (Ptr Service)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
service
    Ptr DBusConnection
result <- Ptr Service -> IO (Ptr DBusConnection)
ibus_service_get_connection Ptr Service
service'
    Text -> Ptr DBusConnection -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"serviceGetConnection" Ptr DBusConnection
result
    DBusConnection
result' <- ((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
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
service
    DBusConnection -> IO DBusConnection
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return DBusConnection
result'

#if defined(ENABLE_OVERLOADING)
data ServiceGetConnectionMethodInfo
instance (signature ~ (m Gio.DBusConnection.DBusConnection), MonadIO m, IsService a) => O.OverloadedMethod ServiceGetConnectionMethodInfo a signature where
    overloadedMethod = serviceGetConnection

instance O.OverloadedMethodInfo ServiceGetConnectionMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.IBus.Objects.Service.serviceGetConnection",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ibus-1.5.5/docs/GI-IBus-Objects-Service.html#v:serviceGetConnection"
        })


#endif

-- method Service::get_object_path
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "service"
--           , argType =
--               TInterface Name { namespace = "IBus" , name = "Service" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An IBusService." , 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 "ibus_service_get_object_path" ibus_service_get_object_path :: 
    Ptr Service ->                          -- service : TInterface (Name {namespace = "IBus", name = "Service"})
    IO CString

-- | Gets the object path of an IBusService.
serviceGetObjectPath ::
    (B.CallStack.HasCallStack, MonadIO m, IsService a) =>
    a
    -- ^ /@service@/: An IBusService.
    -> m T.Text
    -- ^ __Returns:__ The object path of /@service@/
serviceGetObjectPath :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsService a) =>
a -> m Text
serviceGetObjectPath a
service = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr Service
service' <- a -> IO (Ptr Service)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
service
    CString
result <- Ptr Service -> IO CString
ibus_service_get_object_path Ptr Service
service'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"serviceGetObjectPath" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
service
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data ServiceGetObjectPathMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsService a) => O.OverloadedMethod ServiceGetObjectPathMethodInfo a signature where
    overloadedMethod = serviceGetObjectPath

instance O.OverloadedMethodInfo ServiceGetObjectPathMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.IBus.Objects.Service.serviceGetObjectPath",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ibus-1.5.5/docs/GI-IBus-Objects-Service.html#v:serviceGetObjectPath"
        })


#endif

-- method Service::register
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "service"
--           , argType =
--               TInterface Name { namespace = "IBus" , name = "Service" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An IBusService." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "connection"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "A GDBusConnection the service will be registered to."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "ibus_service_register" ibus_service_register :: 
    Ptr Service ->                          -- service : TInterface (Name {namespace = "IBus", name = "Service"})
    Ptr Gio.DBusConnection.DBusConnection -> -- connection : TInterface (Name {namespace = "Gio", name = "DBusConnection"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Registers service to a connection.
serviceRegister ::
    (B.CallStack.HasCallStack, MonadIO m, IsService a, Gio.DBusConnection.IsDBusConnection b) =>
    a
    -- ^ /@service@/: An IBusService.
    -> b
    -- ^ /@connection@/: A GDBusConnection the service will be registered to.
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
serviceRegister :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsService a, IsDBusConnection b) =>
a -> b -> m ()
serviceRegister a
service b
connection = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Service
service' <- a -> IO (Ptr Service)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
service
    Ptr DBusConnection
connection' <- b -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
connection
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr Service -> Ptr DBusConnection -> Ptr (Ptr GError) -> IO CInt
ibus_service_register Ptr Service
service' Ptr DBusConnection
connection'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
service
        b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
connection
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data ServiceRegisterMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsService a, Gio.DBusConnection.IsDBusConnection b) => O.OverloadedMethod ServiceRegisterMethodInfo a signature where
    overloadedMethod = serviceRegister

instance O.OverloadedMethodInfo ServiceRegisterMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.IBus.Objects.Service.serviceRegister",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ibus-1.5.5/docs/GI-IBus-Objects-Service.html#v:serviceRegister"
        })


#endif

-- method Service::unregister
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "service"
--           , argType =
--               TInterface Name { namespace = "IBus" , name = "Service" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An IBusService." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "connection"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "A GDBusConnection the service was registered with."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "ibus_service_unregister" ibus_service_unregister :: 
    Ptr Service ->                          -- service : TInterface (Name {namespace = "IBus", name = "Service"})
    Ptr Gio.DBusConnection.DBusConnection -> -- connection : TInterface (Name {namespace = "Gio", name = "DBusConnection"})
    IO ()

-- | Unregisters service from a connection.
serviceUnregister ::
    (B.CallStack.HasCallStack, MonadIO m, IsService a, Gio.DBusConnection.IsDBusConnection b) =>
    a
    -- ^ /@service@/: An IBusService.
    -> b
    -- ^ /@connection@/: A GDBusConnection the service was registered with.
    -> m ()
serviceUnregister :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsService a, IsDBusConnection b) =>
a -> b -> m ()
serviceUnregister a
service b
connection = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Service
service' <- a -> IO (Ptr Service)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
service
    Ptr DBusConnection
connection' <- b -> IO (Ptr DBusConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
connection
    Ptr Service -> Ptr DBusConnection -> IO ()
ibus_service_unregister Ptr Service
service' Ptr DBusConnection
connection'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
service
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
connection
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ServiceUnregisterMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsService a, Gio.DBusConnection.IsDBusConnection b) => O.OverloadedMethod ServiceUnregisterMethodInfo a signature where
    overloadedMethod = serviceUnregister

instance O.OverloadedMethodInfo ServiceUnregisterMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.IBus.Objects.Service.serviceUnregister",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ibus-1.5.5/docs/GI-IBus-Objects-Service.html#v:serviceUnregister"
        })


#endif