{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Instances of the t'GI.Gio.Objects.DBusMethodInvocation.DBusMethodInvocation' class are used when
-- handling D-Bus method calls. It provides a way to asynchronously
-- return results and errors.
-- 
-- The normal way to obtain a t'GI.Gio.Objects.DBusMethodInvocation.DBusMethodInvocation' object is to receive
-- it as an argument to the @/handle_method_call()/@ function in a
-- t'GI.Gio.Structs.DBusInterfaceVTable.DBusInterfaceVTable' that was passed to @/g_dbus_connection_register_object()/@.
-- 
-- /Since: 2.26/

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

module GI.Gio.Objects.DBusMethodInvocation
    ( 

-- * Exported types
    DBusMethodInvocation(..)                ,
    IsDBusMethodInvocation                  ,
    toDBusMethodInvocation                  ,
    noDBusMethodInvocation                  ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolveDBusMethodInvocationMethod       ,
#endif


-- ** getConnection #method:getConnection#

#if defined(ENABLE_OVERLOADING)
    DBusMethodInvocationGetConnectionMethodInfo,
#endif
    dBusMethodInvocationGetConnection       ,


-- ** getInterfaceName #method:getInterfaceName#

#if defined(ENABLE_OVERLOADING)
    DBusMethodInvocationGetInterfaceNameMethodInfo,
#endif
    dBusMethodInvocationGetInterfaceName    ,


-- ** getMessage #method:getMessage#

#if defined(ENABLE_OVERLOADING)
    DBusMethodInvocationGetMessageMethodInfo,
#endif
    dBusMethodInvocationGetMessage          ,


-- ** getMethodInfo #method:getMethodInfo#

#if defined(ENABLE_OVERLOADING)
    DBusMethodInvocationGetMethodInfoMethodInfo,
#endif
    dBusMethodInvocationGetMethodInfo       ,


-- ** getMethodName #method:getMethodName#

#if defined(ENABLE_OVERLOADING)
    DBusMethodInvocationGetMethodNameMethodInfo,
#endif
    dBusMethodInvocationGetMethodName       ,


-- ** getObjectPath #method:getObjectPath#

#if defined(ENABLE_OVERLOADING)
    DBusMethodInvocationGetObjectPathMethodInfo,
#endif
    dBusMethodInvocationGetObjectPath       ,


-- ** getParameters #method:getParameters#

#if defined(ENABLE_OVERLOADING)
    DBusMethodInvocationGetParametersMethodInfo,
#endif
    dBusMethodInvocationGetParameters       ,


-- ** getPropertyInfo #method:getPropertyInfo#

#if defined(ENABLE_OVERLOADING)
    DBusMethodInvocationGetPropertyInfoMethodInfo,
#endif
    dBusMethodInvocationGetPropertyInfo     ,


-- ** getSender #method:getSender#

#if defined(ENABLE_OVERLOADING)
    DBusMethodInvocationGetSenderMethodInfo ,
#endif
    dBusMethodInvocationGetSender           ,


-- ** returnDbusError #method:returnDbusError#

#if defined(ENABLE_OVERLOADING)
    DBusMethodInvocationReturnDbusErrorMethodInfo,
#endif
    dBusMethodInvocationReturnDbusError     ,


-- ** returnErrorLiteral #method:returnErrorLiteral#

#if defined(ENABLE_OVERLOADING)
    DBusMethodInvocationReturnErrorLiteralMethodInfo,
#endif
    dBusMethodInvocationReturnErrorLiteral  ,


-- ** returnGerror #method:returnGerror#

#if defined(ENABLE_OVERLOADING)
    DBusMethodInvocationReturnGerrorMethodInfo,
#endif
    dBusMethodInvocationReturnGerror        ,


-- ** returnValue #method:returnValue#

#if defined(ENABLE_OVERLOADING)
    DBusMethodInvocationReturnValueMethodInfo,
#endif
    dBusMethodInvocationReturnValue         ,


-- ** returnValueWithUnixFdList #method:returnValueWithUnixFdList#

#if defined(ENABLE_OVERLOADING)
    DBusMethodInvocationReturnValueWithUnixFdListMethodInfo,
#endif
    dBusMethodInvocationReturnValueWithUnixFdList,




    ) 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.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 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.Objects.DBusConnection as Gio.DBusConnection
import {-# SOURCE #-} qualified GI.Gio.Objects.DBusMessage as Gio.DBusMessage
import {-# SOURCE #-} qualified GI.Gio.Objects.UnixFDList as Gio.UnixFDList
import {-# SOURCE #-} qualified GI.Gio.Structs.DBusMethodInfo as Gio.DBusMethodInfo
import {-# SOURCE #-} qualified GI.Gio.Structs.DBusPropertyInfo as Gio.DBusPropertyInfo

-- | Memory-managed wrapper type.
newtype DBusMethodInvocation = DBusMethodInvocation (ManagedPtr DBusMethodInvocation)
    deriving (DBusMethodInvocation -> DBusMethodInvocation -> Bool
(DBusMethodInvocation -> DBusMethodInvocation -> Bool)
-> (DBusMethodInvocation -> DBusMethodInvocation -> Bool)
-> Eq DBusMethodInvocation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DBusMethodInvocation -> DBusMethodInvocation -> Bool
$c/= :: DBusMethodInvocation -> DBusMethodInvocation -> Bool
== :: DBusMethodInvocation -> DBusMethodInvocation -> Bool
$c== :: DBusMethodInvocation -> DBusMethodInvocation -> Bool
Eq)
foreign import ccall "g_dbus_method_invocation_get_type"
    c_g_dbus_method_invocation_get_type :: IO GType

instance GObject DBusMethodInvocation where
    gobjectType :: IO GType
gobjectType = IO GType
c_g_dbus_method_invocation_get_type
    

-- | Convert 'DBusMethodInvocation' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue DBusMethodInvocation where
    toGValue :: DBusMethodInvocation -> IO GValue
toGValue o :: DBusMethodInvocation
o = do
        GType
gtype <- IO GType
c_g_dbus_method_invocation_get_type
        DBusMethodInvocation
-> (Ptr DBusMethodInvocation -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr DBusMethodInvocation
o (GType
-> (GValue -> Ptr DBusMethodInvocation -> IO ())
-> Ptr DBusMethodInvocation
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr DBusMethodInvocation -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
        
    fromGValue :: GValue -> IO DBusMethodInvocation
fromGValue gv :: GValue
gv = do
        Ptr DBusMethodInvocation
ptr <- GValue -> IO (Ptr DBusMethodInvocation)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr DBusMethodInvocation)
        (ManagedPtr DBusMethodInvocation -> DBusMethodInvocation)
-> Ptr DBusMethodInvocation -> IO DBusMethodInvocation
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr DBusMethodInvocation -> DBusMethodInvocation
DBusMethodInvocation Ptr DBusMethodInvocation
ptr
        
    

-- | Type class for types which can be safely cast to `DBusMethodInvocation`, for instance with `toDBusMethodInvocation`.
class (GObject o, O.IsDescendantOf DBusMethodInvocation o) => IsDBusMethodInvocation o
instance (GObject o, O.IsDescendantOf DBusMethodInvocation o) => IsDBusMethodInvocation o

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

-- | Cast to `DBusMethodInvocation`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toDBusMethodInvocation :: (MonadIO m, IsDBusMethodInvocation o) => o -> m DBusMethodInvocation
toDBusMethodInvocation :: o -> m DBusMethodInvocation
toDBusMethodInvocation = IO DBusMethodInvocation -> m DBusMethodInvocation
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DBusMethodInvocation -> m DBusMethodInvocation)
-> (o -> IO DBusMethodInvocation) -> o -> m DBusMethodInvocation
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr DBusMethodInvocation -> DBusMethodInvocation)
-> o -> IO DBusMethodInvocation
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr DBusMethodInvocation -> DBusMethodInvocation
DBusMethodInvocation

-- | A convenience alias for `Nothing` :: `Maybe` `DBusMethodInvocation`.
noDBusMethodInvocation :: Maybe DBusMethodInvocation
noDBusMethodInvocation :: Maybe DBusMethodInvocation
noDBusMethodInvocation = Maybe DBusMethodInvocation
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolveDBusMethodInvocationMethod (t :: Symbol) (o :: *) :: * where
    ResolveDBusMethodInvocationMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveDBusMethodInvocationMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveDBusMethodInvocationMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveDBusMethodInvocationMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveDBusMethodInvocationMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveDBusMethodInvocationMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveDBusMethodInvocationMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveDBusMethodInvocationMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveDBusMethodInvocationMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveDBusMethodInvocationMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveDBusMethodInvocationMethod "returnDbusError" o = DBusMethodInvocationReturnDbusErrorMethodInfo
    ResolveDBusMethodInvocationMethod "returnErrorLiteral" o = DBusMethodInvocationReturnErrorLiteralMethodInfo
    ResolveDBusMethodInvocationMethod "returnGerror" o = DBusMethodInvocationReturnGerrorMethodInfo
    ResolveDBusMethodInvocationMethod "returnValue" o = DBusMethodInvocationReturnValueMethodInfo
    ResolveDBusMethodInvocationMethod "returnValueWithUnixFdList" o = DBusMethodInvocationReturnValueWithUnixFdListMethodInfo
    ResolveDBusMethodInvocationMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveDBusMethodInvocationMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveDBusMethodInvocationMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveDBusMethodInvocationMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveDBusMethodInvocationMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveDBusMethodInvocationMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveDBusMethodInvocationMethod "getConnection" o = DBusMethodInvocationGetConnectionMethodInfo
    ResolveDBusMethodInvocationMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveDBusMethodInvocationMethod "getInterfaceName" o = DBusMethodInvocationGetInterfaceNameMethodInfo
    ResolveDBusMethodInvocationMethod "getMessage" o = DBusMethodInvocationGetMessageMethodInfo
    ResolveDBusMethodInvocationMethod "getMethodInfo" o = DBusMethodInvocationGetMethodInfoMethodInfo
    ResolveDBusMethodInvocationMethod "getMethodName" o = DBusMethodInvocationGetMethodNameMethodInfo
    ResolveDBusMethodInvocationMethod "getObjectPath" o = DBusMethodInvocationGetObjectPathMethodInfo
    ResolveDBusMethodInvocationMethod "getParameters" o = DBusMethodInvocationGetParametersMethodInfo
    ResolveDBusMethodInvocationMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveDBusMethodInvocationMethod "getPropertyInfo" o = DBusMethodInvocationGetPropertyInfoMethodInfo
    ResolveDBusMethodInvocationMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveDBusMethodInvocationMethod "getSender" o = DBusMethodInvocationGetSenderMethodInfo
    ResolveDBusMethodInvocationMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveDBusMethodInvocationMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveDBusMethodInvocationMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveDBusMethodInvocationMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveDBusMethodInvocationMethod t DBusMethodInvocation, O.MethodInfo info DBusMethodInvocation p) => OL.IsLabel t (DBusMethodInvocation -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DBusMethodInvocation
type instance O.AttributeList DBusMethodInvocation = DBusMethodInvocationAttributeList
type DBusMethodInvocationAttributeList = ('[ ] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList DBusMethodInvocation = DBusMethodInvocationSignalList
type DBusMethodInvocationSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

-- method DBusMethodInvocation::get_connection
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "invocation"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "DBusMethodInvocation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusMethodInvocation."
--                 , 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 "g_dbus_method_invocation_get_connection" g_dbus_method_invocation_get_connection :: 
    Ptr DBusMethodInvocation ->             -- invocation : TInterface (Name {namespace = "Gio", name = "DBusMethodInvocation"})
    IO (Ptr Gio.DBusConnection.DBusConnection)

-- | Gets the t'GI.Gio.Objects.DBusConnection.DBusConnection' the method was invoked on.
-- 
-- /Since: 2.26/
dBusMethodInvocationGetConnection ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMethodInvocation a) =>
    a
    -- ^ /@invocation@/: A t'GI.Gio.Objects.DBusMethodInvocation.DBusMethodInvocation'.
    -> m Gio.DBusConnection.DBusConnection
    -- ^ __Returns:__ A t'GI.Gio.Objects.DBusConnection.DBusConnection'. Do not free, it is owned by /@invocation@/.
dBusMethodInvocationGetConnection :: a -> m DBusConnection
dBusMethodInvocationGetConnection invocation :: a
invocation = IO DBusConnection -> m DBusConnection
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 DBusMethodInvocation
invocation' <- a -> IO (Ptr DBusMethodInvocation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
invocation
    Ptr DBusConnection
result <- Ptr DBusMethodInvocation -> IO (Ptr DBusConnection)
g_dbus_method_invocation_get_connection Ptr DBusMethodInvocation
invocation'
    Text -> Ptr DBusConnection -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusMethodInvocationGetConnection" 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
invocation
    DBusConnection -> IO DBusConnection
forall (m :: * -> *) a. Monad m => a -> m a
return DBusConnection
result'

#if defined(ENABLE_OVERLOADING)
data DBusMethodInvocationGetConnectionMethodInfo
instance (signature ~ (m Gio.DBusConnection.DBusConnection), MonadIO m, IsDBusMethodInvocation a) => O.MethodInfo DBusMethodInvocationGetConnectionMethodInfo a signature where
    overloadedMethod = dBusMethodInvocationGetConnection

#endif

-- method DBusMethodInvocation::get_interface_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "invocation"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "DBusMethodInvocation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusMethodInvocation."
--                 , 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_dbus_method_invocation_get_interface_name" g_dbus_method_invocation_get_interface_name :: 
    Ptr DBusMethodInvocation ->             -- invocation : TInterface (Name {namespace = "Gio", name = "DBusMethodInvocation"})
    IO CString

-- | Gets the name of the D-Bus interface the method was invoked on.
-- 
-- If this method call is a property Get, Set or GetAll call that has
-- been redirected to the method call handler then
-- \"org.freedesktop.DBus.Properties\" will be returned.  See
-- t'GI.Gio.Structs.DBusInterfaceVTable.DBusInterfaceVTable' for more information.
-- 
-- /Since: 2.26/
dBusMethodInvocationGetInterfaceName ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMethodInvocation a) =>
    a
    -- ^ /@invocation@/: A t'GI.Gio.Objects.DBusMethodInvocation.DBusMethodInvocation'.
    -> m T.Text
    -- ^ __Returns:__ A string. Do not free, it is owned by /@invocation@/.
dBusMethodInvocationGetInterfaceName :: a -> m Text
dBusMethodInvocationGetInterfaceName invocation :: a
invocation = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusMethodInvocation
invocation' <- a -> IO (Ptr DBusMethodInvocation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
invocation
    CString
result <- Ptr DBusMethodInvocation -> IO CString
g_dbus_method_invocation_get_interface_name Ptr DBusMethodInvocation
invocation'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusMethodInvocationGetInterfaceName" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
invocation
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data DBusMethodInvocationGetInterfaceNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDBusMethodInvocation a) => O.MethodInfo DBusMethodInvocationGetInterfaceNameMethodInfo a signature where
    overloadedMethod = dBusMethodInvocationGetInterfaceName

#endif

-- method DBusMethodInvocation::get_message
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "invocation"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "DBusMethodInvocation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusMethodInvocation."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "DBusMessage" })
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_method_invocation_get_message" g_dbus_method_invocation_get_message :: 
    Ptr DBusMethodInvocation ->             -- invocation : TInterface (Name {namespace = "Gio", name = "DBusMethodInvocation"})
    IO (Ptr Gio.DBusMessage.DBusMessage)

-- | Gets the t'GI.Gio.Objects.DBusMessage.DBusMessage' for the method invocation. This is useful if
-- you need to use low-level protocol features, such as UNIX file
-- descriptor passing, that cannot be properly expressed in the
-- t'GVariant' API.
-- 
-- See this [server][gdbus-server] and [client][gdbus-unix-fd-client]
-- for an example of how to use this low-level API to send and receive
-- UNIX file descriptors.
-- 
-- /Since: 2.26/
dBusMethodInvocationGetMessage ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMethodInvocation a) =>
    a
    -- ^ /@invocation@/: A t'GI.Gio.Objects.DBusMethodInvocation.DBusMethodInvocation'.
    -> m Gio.DBusMessage.DBusMessage
    -- ^ __Returns:__ t'GI.Gio.Objects.DBusMessage.DBusMessage'. Do not free, it is owned by /@invocation@/.
dBusMethodInvocationGetMessage :: a -> m DBusMessage
dBusMethodInvocationGetMessage invocation :: a
invocation = IO DBusMessage -> m DBusMessage
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DBusMessage -> m DBusMessage)
-> IO DBusMessage -> m DBusMessage
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusMethodInvocation
invocation' <- a -> IO (Ptr DBusMethodInvocation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
invocation
    Ptr DBusMessage
result <- Ptr DBusMethodInvocation -> IO (Ptr DBusMessage)
g_dbus_method_invocation_get_message Ptr DBusMethodInvocation
invocation'
    Text -> Ptr DBusMessage -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusMethodInvocationGetMessage" Ptr DBusMessage
result
    DBusMessage
result' <- ((ManagedPtr DBusMessage -> DBusMessage)
-> Ptr DBusMessage -> IO DBusMessage
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr DBusMessage -> DBusMessage
Gio.DBusMessage.DBusMessage) Ptr DBusMessage
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
invocation
    DBusMessage -> IO DBusMessage
forall (m :: * -> *) a. Monad m => a -> m a
return DBusMessage
result'

#if defined(ENABLE_OVERLOADING)
data DBusMethodInvocationGetMessageMethodInfo
instance (signature ~ (m Gio.DBusMessage.DBusMessage), MonadIO m, IsDBusMethodInvocation a) => O.MethodInfo DBusMethodInvocationGetMessageMethodInfo a signature where
    overloadedMethod = dBusMethodInvocationGetMessage

#endif

-- method DBusMethodInvocation::get_method_info
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "invocation"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "DBusMethodInvocation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusMethodInvocation."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gio" , name = "DBusMethodInfo" })
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_method_invocation_get_method_info" g_dbus_method_invocation_get_method_info :: 
    Ptr DBusMethodInvocation ->             -- invocation : TInterface (Name {namespace = "Gio", name = "DBusMethodInvocation"})
    IO (Ptr Gio.DBusMethodInfo.DBusMethodInfo)

-- | Gets information about the method call, if any.
-- 
-- If this method invocation is a property Get, Set or GetAll call that
-- has been redirected to the method call handler then 'P.Nothing' will be
-- returned.  See 'GI.Gio.Objects.DBusMethodInvocation.dBusMethodInvocationGetPropertyInfo' and
-- t'GI.Gio.Structs.DBusInterfaceVTable.DBusInterfaceVTable' for more information.
-- 
-- /Since: 2.26/
dBusMethodInvocationGetMethodInfo ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMethodInvocation a) =>
    a
    -- ^ /@invocation@/: A t'GI.Gio.Objects.DBusMethodInvocation.DBusMethodInvocation'.
    -> m Gio.DBusMethodInfo.DBusMethodInfo
    -- ^ __Returns:__ A t'GI.Gio.Structs.DBusMethodInfo.DBusMethodInfo' or 'P.Nothing'. Do not free, it is owned by /@invocation@/.
dBusMethodInvocationGetMethodInfo :: a -> m DBusMethodInfo
dBusMethodInvocationGetMethodInfo invocation :: a
invocation = IO DBusMethodInfo -> m DBusMethodInfo
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DBusMethodInfo -> m DBusMethodInfo)
-> IO DBusMethodInfo -> m DBusMethodInfo
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusMethodInvocation
invocation' <- a -> IO (Ptr DBusMethodInvocation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
invocation
    Ptr DBusMethodInfo
result <- Ptr DBusMethodInvocation -> IO (Ptr DBusMethodInfo)
g_dbus_method_invocation_get_method_info Ptr DBusMethodInvocation
invocation'
    Text -> Ptr DBusMethodInfo -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusMethodInvocationGetMethodInfo" Ptr DBusMethodInfo
result
    DBusMethodInfo
result' <- ((ManagedPtr DBusMethodInfo -> DBusMethodInfo)
-> Ptr DBusMethodInfo -> IO DBusMethodInfo
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr DBusMethodInfo -> DBusMethodInfo
Gio.DBusMethodInfo.DBusMethodInfo) Ptr DBusMethodInfo
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
invocation
    DBusMethodInfo -> IO DBusMethodInfo
forall (m :: * -> *) a. Monad m => a -> m a
return DBusMethodInfo
result'

#if defined(ENABLE_OVERLOADING)
data DBusMethodInvocationGetMethodInfoMethodInfo
instance (signature ~ (m Gio.DBusMethodInfo.DBusMethodInfo), MonadIO m, IsDBusMethodInvocation a) => O.MethodInfo DBusMethodInvocationGetMethodInfoMethodInfo a signature where
    overloadedMethod = dBusMethodInvocationGetMethodInfo

#endif

-- method DBusMethodInvocation::get_method_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "invocation"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "DBusMethodInvocation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusMethodInvocation."
--                 , 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_dbus_method_invocation_get_method_name" g_dbus_method_invocation_get_method_name :: 
    Ptr DBusMethodInvocation ->             -- invocation : TInterface (Name {namespace = "Gio", name = "DBusMethodInvocation"})
    IO CString

-- | Gets the name of the method that was invoked.
-- 
-- /Since: 2.26/
dBusMethodInvocationGetMethodName ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMethodInvocation a) =>
    a
    -- ^ /@invocation@/: A t'GI.Gio.Objects.DBusMethodInvocation.DBusMethodInvocation'.
    -> m T.Text
    -- ^ __Returns:__ A string. Do not free, it is owned by /@invocation@/.
dBusMethodInvocationGetMethodName :: a -> m Text
dBusMethodInvocationGetMethodName invocation :: a
invocation = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusMethodInvocation
invocation' <- a -> IO (Ptr DBusMethodInvocation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
invocation
    CString
result <- Ptr DBusMethodInvocation -> IO CString
g_dbus_method_invocation_get_method_name Ptr DBusMethodInvocation
invocation'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusMethodInvocationGetMethodName" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
invocation
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data DBusMethodInvocationGetMethodNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDBusMethodInvocation a) => O.MethodInfo DBusMethodInvocationGetMethodNameMethodInfo a signature where
    overloadedMethod = dBusMethodInvocationGetMethodName

#endif

-- method DBusMethodInvocation::get_object_path
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "invocation"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "DBusMethodInvocation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusMethodInvocation."
--                 , 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_dbus_method_invocation_get_object_path" g_dbus_method_invocation_get_object_path :: 
    Ptr DBusMethodInvocation ->             -- invocation : TInterface (Name {namespace = "Gio", name = "DBusMethodInvocation"})
    IO CString

-- | Gets the object path the method was invoked on.
-- 
-- /Since: 2.26/
dBusMethodInvocationGetObjectPath ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMethodInvocation a) =>
    a
    -- ^ /@invocation@/: A t'GI.Gio.Objects.DBusMethodInvocation.DBusMethodInvocation'.
    -> m T.Text
    -- ^ __Returns:__ A string. Do not free, it is owned by /@invocation@/.
dBusMethodInvocationGetObjectPath :: a -> m Text
dBusMethodInvocationGetObjectPath invocation :: a
invocation = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusMethodInvocation
invocation' <- a -> IO (Ptr DBusMethodInvocation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
invocation
    CString
result <- Ptr DBusMethodInvocation -> IO CString
g_dbus_method_invocation_get_object_path Ptr DBusMethodInvocation
invocation'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusMethodInvocationGetObjectPath" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
invocation
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data DBusMethodInvocationGetObjectPathMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDBusMethodInvocation a) => O.MethodInfo DBusMethodInvocationGetObjectPathMethodInfo a signature where
    overloadedMethod = dBusMethodInvocationGetObjectPath

#endif

-- method DBusMethodInvocation::get_parameters
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "invocation"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "DBusMethodInvocation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusMethodInvocation."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just TVariant
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_method_invocation_get_parameters" g_dbus_method_invocation_get_parameters :: 
    Ptr DBusMethodInvocation ->             -- invocation : TInterface (Name {namespace = "Gio", name = "DBusMethodInvocation"})
    IO (Ptr GVariant)

-- | Gets the parameters of the method invocation. If there are no input
-- parameters then this will return a GVariant with 0 children rather than NULL.
-- 
-- /Since: 2.26/
dBusMethodInvocationGetParameters ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMethodInvocation a) =>
    a
    -- ^ /@invocation@/: A t'GI.Gio.Objects.DBusMethodInvocation.DBusMethodInvocation'.
    -> m GVariant
    -- ^ __Returns:__ A t'GVariant' tuple. Do not unref this because it is owned by /@invocation@/.
dBusMethodInvocationGetParameters :: a -> m GVariant
dBusMethodInvocationGetParameters invocation :: a
invocation = IO GVariant -> m GVariant
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GVariant -> m GVariant) -> IO GVariant -> m GVariant
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusMethodInvocation
invocation' <- a -> IO (Ptr DBusMethodInvocation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
invocation
    Ptr GVariant
result <- Ptr DBusMethodInvocation -> IO (Ptr GVariant)
g_dbus_method_invocation_get_parameters Ptr DBusMethodInvocation
invocation'
    Text -> Ptr GVariant -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusMethodInvocationGetParameters" Ptr GVariant
result
    GVariant
result' <- Ptr GVariant -> IO GVariant
B.GVariant.newGVariantFromPtr Ptr GVariant
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
invocation
    GVariant -> IO GVariant
forall (m :: * -> *) a. Monad m => a -> m a
return GVariant
result'

#if defined(ENABLE_OVERLOADING)
data DBusMethodInvocationGetParametersMethodInfo
instance (signature ~ (m GVariant), MonadIO m, IsDBusMethodInvocation a) => O.MethodInfo DBusMethodInvocationGetParametersMethodInfo a signature where
    overloadedMethod = dBusMethodInvocationGetParameters

#endif

-- method DBusMethodInvocation::get_property_info
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "invocation"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "DBusMethodInvocation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusMethodInvocation"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gio" , name = "DBusPropertyInfo" })
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_method_invocation_get_property_info" g_dbus_method_invocation_get_property_info :: 
    Ptr DBusMethodInvocation ->             -- invocation : TInterface (Name {namespace = "Gio", name = "DBusMethodInvocation"})
    IO (Ptr Gio.DBusPropertyInfo.DBusPropertyInfo)

-- | Gets information about the property that this method call is for, if
-- any.
-- 
-- This will only be set in the case of an invocation in response to a
-- property Get or Set call that has been directed to the method call
-- handler for an object on account of its @/property_get()/@ or
-- @/property_set()/@ vtable pointers being unset.
-- 
-- See t'GI.Gio.Structs.DBusInterfaceVTable.DBusInterfaceVTable' for more information.
-- 
-- If the call was GetAll, 'P.Nothing' will be returned.
-- 
-- /Since: 2.38/
dBusMethodInvocationGetPropertyInfo ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMethodInvocation a) =>
    a
    -- ^ /@invocation@/: A t'GI.Gio.Objects.DBusMethodInvocation.DBusMethodInvocation'
    -> m Gio.DBusPropertyInfo.DBusPropertyInfo
    -- ^ __Returns:__ a t'GI.Gio.Structs.DBusPropertyInfo.DBusPropertyInfo' or 'P.Nothing'
dBusMethodInvocationGetPropertyInfo :: a -> m DBusPropertyInfo
dBusMethodInvocationGetPropertyInfo invocation :: a
invocation = IO DBusPropertyInfo -> m DBusPropertyInfo
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DBusPropertyInfo -> m DBusPropertyInfo)
-> IO DBusPropertyInfo -> m DBusPropertyInfo
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusMethodInvocation
invocation' <- a -> IO (Ptr DBusMethodInvocation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
invocation
    Ptr DBusPropertyInfo
result <- Ptr DBusMethodInvocation -> IO (Ptr DBusPropertyInfo)
g_dbus_method_invocation_get_property_info Ptr DBusMethodInvocation
invocation'
    Text -> Ptr DBusPropertyInfo -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusMethodInvocationGetPropertyInfo" Ptr DBusPropertyInfo
result
    DBusPropertyInfo
result' <- ((ManagedPtr DBusPropertyInfo -> DBusPropertyInfo)
-> Ptr DBusPropertyInfo -> IO DBusPropertyInfo
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr DBusPropertyInfo -> DBusPropertyInfo
Gio.DBusPropertyInfo.DBusPropertyInfo) Ptr DBusPropertyInfo
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
invocation
    DBusPropertyInfo -> IO DBusPropertyInfo
forall (m :: * -> *) a. Monad m => a -> m a
return DBusPropertyInfo
result'

#if defined(ENABLE_OVERLOADING)
data DBusMethodInvocationGetPropertyInfoMethodInfo
instance (signature ~ (m Gio.DBusPropertyInfo.DBusPropertyInfo), MonadIO m, IsDBusMethodInvocation a) => O.MethodInfo DBusMethodInvocationGetPropertyInfoMethodInfo a signature where
    overloadedMethod = dBusMethodInvocationGetPropertyInfo

#endif

-- method DBusMethodInvocation::get_sender
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "invocation"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "DBusMethodInvocation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusMethodInvocation."
--                 , 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_dbus_method_invocation_get_sender" g_dbus_method_invocation_get_sender :: 
    Ptr DBusMethodInvocation ->             -- invocation : TInterface (Name {namespace = "Gio", name = "DBusMethodInvocation"})
    IO CString

-- | Gets the bus name that invoked the method.
-- 
-- /Since: 2.26/
dBusMethodInvocationGetSender ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMethodInvocation a) =>
    a
    -- ^ /@invocation@/: A t'GI.Gio.Objects.DBusMethodInvocation.DBusMethodInvocation'.
    -> m T.Text
    -- ^ __Returns:__ A string. Do not free, it is owned by /@invocation@/.
dBusMethodInvocationGetSender :: a -> m Text
dBusMethodInvocationGetSender invocation :: a
invocation = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusMethodInvocation
invocation' <- a -> IO (Ptr DBusMethodInvocation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
invocation
    CString
result <- Ptr DBusMethodInvocation -> IO CString
g_dbus_method_invocation_get_sender Ptr DBusMethodInvocation
invocation'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusMethodInvocationGetSender" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
invocation
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data DBusMethodInvocationGetSenderMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDBusMethodInvocation a) => O.MethodInfo DBusMethodInvocationGetSenderMethodInfo a signature where
    overloadedMethod = dBusMethodInvocationGetSender

#endif

-- method DBusMethodInvocation::return_dbus_error
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "invocation"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "DBusMethodInvocation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusMethodInvocation."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "error_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A valid D-Bus error name."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "error_message"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A valid D-Bus error message."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_method_invocation_return_dbus_error" g_dbus_method_invocation_return_dbus_error :: 
    Ptr DBusMethodInvocation ->             -- invocation : TInterface (Name {namespace = "Gio", name = "DBusMethodInvocation"})
    CString ->                              -- error_name : TBasicType TUTF8
    CString ->                              -- error_message : TBasicType TUTF8
    IO ()

-- | Finishes handling a D-Bus method call by returning an error.
-- 
-- This method will take ownership of /@invocation@/. See
-- t'GI.Gio.Structs.DBusInterfaceVTable.DBusInterfaceVTable' for more information about the ownership of
-- /@invocation@/.
-- 
-- /Since: 2.26/
dBusMethodInvocationReturnDbusError ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMethodInvocation a) =>
    a
    -- ^ /@invocation@/: A t'GI.Gio.Objects.DBusMethodInvocation.DBusMethodInvocation'.
    -> T.Text
    -- ^ /@errorName@/: A valid D-Bus error name.
    -> T.Text
    -- ^ /@errorMessage@/: A valid D-Bus error message.
    -> m ()
dBusMethodInvocationReturnDbusError :: a -> Text -> Text -> m ()
dBusMethodInvocationReturnDbusError invocation :: a
invocation errorName :: Text
errorName errorMessage :: Text
errorMessage = 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 DBusMethodInvocation
invocation' <- a -> IO (Ptr DBusMethodInvocation)
forall a b. (HasCallStack, GObject a) => a -> IO (Ptr b)
B.ManagedPtr.disownObject a
invocation
    CString
errorName' <- Text -> IO CString
textToCString Text
errorName
    CString
errorMessage' <- Text -> IO CString
textToCString Text
errorMessage
    Ptr DBusMethodInvocation -> CString -> CString -> IO ()
g_dbus_method_invocation_return_dbus_error Ptr DBusMethodInvocation
invocation' CString
errorName' CString
errorMessage'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
invocation
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
errorName'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
errorMessage'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DBusMethodInvocationReturnDbusErrorMethodInfo
instance (signature ~ (T.Text -> T.Text -> m ()), MonadIO m, IsDBusMethodInvocation a) => O.MethodInfo DBusMethodInvocationReturnDbusErrorMethodInfo a signature where
    overloadedMethod = dBusMethodInvocationReturnDbusError

#endif

-- method DBusMethodInvocation::return_error_literal
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "invocation"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "DBusMethodInvocation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusMethodInvocation."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "domain"
--           , argType = TBasicType TUInt32
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GQuark for the #GError error domain."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "code"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The error code." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "message"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The error message." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_method_invocation_return_error_literal" g_dbus_method_invocation_return_error_literal :: 
    Ptr DBusMethodInvocation ->             -- invocation : TInterface (Name {namespace = "Gio", name = "DBusMethodInvocation"})
    Word32 ->                               -- domain : TBasicType TUInt32
    Int32 ->                                -- code : TBasicType TInt
    CString ->                              -- message : TBasicType TUTF8
    IO ()

-- | Like @/g_dbus_method_invocation_return_error()/@ but without @/printf()/@-style formatting.
-- 
-- This method will take ownership of /@invocation@/. See
-- t'GI.Gio.Structs.DBusInterfaceVTable.DBusInterfaceVTable' for more information about the ownership of
-- /@invocation@/.
-- 
-- /Since: 2.26/
dBusMethodInvocationReturnErrorLiteral ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMethodInvocation a) =>
    a
    -- ^ /@invocation@/: A t'GI.Gio.Objects.DBusMethodInvocation.DBusMethodInvocation'.
    -> Word32
    -- ^ /@domain@/: A @/GQuark/@ for the t'GError' error domain.
    -> Int32
    -- ^ /@code@/: The error code.
    -> T.Text
    -- ^ /@message@/: The error message.
    -> m ()
dBusMethodInvocationReturnErrorLiteral :: a -> Word32 -> Int32 -> Text -> m ()
dBusMethodInvocationReturnErrorLiteral invocation :: a
invocation domain :: Word32
domain code :: Int32
code message :: Text
message = 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 DBusMethodInvocation
invocation' <- a -> IO (Ptr DBusMethodInvocation)
forall a b. (HasCallStack, GObject a) => a -> IO (Ptr b)
B.ManagedPtr.disownObject a
invocation
    CString
message' <- Text -> IO CString
textToCString Text
message
    Ptr DBusMethodInvocation -> Word32 -> Int32 -> CString -> IO ()
g_dbus_method_invocation_return_error_literal Ptr DBusMethodInvocation
invocation' Word32
domain Int32
code CString
message'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
invocation
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
message'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DBusMethodInvocationReturnErrorLiteralMethodInfo
instance (signature ~ (Word32 -> Int32 -> T.Text -> m ()), MonadIO m, IsDBusMethodInvocation a) => O.MethodInfo DBusMethodInvocationReturnErrorLiteralMethodInfo a signature where
    overloadedMethod = dBusMethodInvocationReturnErrorLiteral

#endif

-- method DBusMethodInvocation::return_gerror
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "invocation"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "DBusMethodInvocation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusMethodInvocation."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "error"
--           , argType = TError
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GError." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_method_invocation_return_gerror" g_dbus_method_invocation_return_gerror :: 
    Ptr DBusMethodInvocation ->             -- invocation : TInterface (Name {namespace = "Gio", name = "DBusMethodInvocation"})
    Ptr GError ->                           -- error : TError
    IO ()

-- | Like @/g_dbus_method_invocation_return_error()/@ but takes a t'GError'
-- instead of the error domain, error code and message.
-- 
-- This method will take ownership of /@invocation@/. See
-- t'GI.Gio.Structs.DBusInterfaceVTable.DBusInterfaceVTable' for more information about the ownership of
-- /@invocation@/.
-- 
-- /Since: 2.26/
dBusMethodInvocationReturnGerror ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMethodInvocation a) =>
    a
    -- ^ /@invocation@/: A t'GI.Gio.Objects.DBusMethodInvocation.DBusMethodInvocation'.
    -> GError
    -- ^ /@error@/: A t'GError'.
    -> m ()
dBusMethodInvocationReturnGerror :: a -> GError -> m ()
dBusMethodInvocationReturnGerror invocation :: a
invocation error_ :: GError
error_ = 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 DBusMethodInvocation
invocation' <- a -> IO (Ptr DBusMethodInvocation)
forall a b. (HasCallStack, GObject a) => a -> IO (Ptr b)
B.ManagedPtr.disownObject a
invocation
    Ptr GError
error_' <- GError -> IO (Ptr GError)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GError
error_
    Ptr DBusMethodInvocation -> Ptr GError -> IO ()
g_dbus_method_invocation_return_gerror Ptr DBusMethodInvocation
invocation' Ptr GError
error_'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
invocation
    GError -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GError
error_
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DBusMethodInvocationReturnGerrorMethodInfo
instance (signature ~ (GError -> m ()), MonadIO m, IsDBusMethodInvocation a) => O.MethodInfo DBusMethodInvocationReturnGerrorMethodInfo a signature where
    overloadedMethod = dBusMethodInvocationReturnGerror

#endif

-- method DBusMethodInvocation::return_value
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "invocation"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "DBusMethodInvocation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusMethodInvocation."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "parameters"
--           , argType = TVariant
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A #GVariant tuple with out parameters for the method or %NULL if not passing any parameters."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_method_invocation_return_value" g_dbus_method_invocation_return_value :: 
    Ptr DBusMethodInvocation ->             -- invocation : TInterface (Name {namespace = "Gio", name = "DBusMethodInvocation"})
    Ptr GVariant ->                         -- parameters : TVariant
    IO ()

-- | Finishes handling a D-Bus method call by returning /@parameters@/.
-- If the /@parameters@/ GVariant is floating, it is consumed.
-- 
-- It is an error if /@parameters@/ is not of the right format: it must be a tuple
-- containing the out-parameters of the D-Bus method. Even if the method has a
-- single out-parameter, it must be contained in a tuple. If the method has no
-- out-parameters, /@parameters@/ may be 'P.Nothing' or an empty tuple.
-- 
-- 
-- === /C code/
-- >
-- >GDBusMethodInvocation *invocation = some_invocation;
-- >g_autofree gchar *result_string = NULL;
-- >g_autoptr (GError) error = NULL;
-- >
-- >result_string = calculate_result (&error);
-- >
-- >if (error != NULL)
-- >  g_dbus_method_invocation_return_gerror (invocation, error);
-- >else
-- >  g_dbus_method_invocation_return_value (invocation,
-- >                                         g_variant_new ("(s)", result_string));
-- >
-- >// Do not free @invocation here; returning a value does that
-- 
-- 
-- This method will take ownership of /@invocation@/. See
-- t'GI.Gio.Structs.DBusInterfaceVTable.DBusInterfaceVTable' for more information about the ownership of
-- /@invocation@/.
-- 
-- Since 2.48, if the method call requested for a reply not to be sent
-- then this call will sink /@parameters@/ and free /@invocation@/, but
-- otherwise do nothing (as per the recommendations of the D-Bus
-- specification).
-- 
-- /Since: 2.26/
dBusMethodInvocationReturnValue ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMethodInvocation a) =>
    a
    -- ^ /@invocation@/: A t'GI.Gio.Objects.DBusMethodInvocation.DBusMethodInvocation'.
    -> Maybe (GVariant)
    -- ^ /@parameters@/: A t'GVariant' tuple with out parameters for the method or 'P.Nothing' if not passing any parameters.
    -> m ()
dBusMethodInvocationReturnValue :: a -> Maybe GVariant -> m ()
dBusMethodInvocationReturnValue invocation :: a
invocation parameters :: Maybe GVariant
parameters = 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 DBusMethodInvocation
invocation' <- a -> IO (Ptr DBusMethodInvocation)
forall a b. (HasCallStack, GObject a) => a -> IO (Ptr b)
B.ManagedPtr.disownObject a
invocation
    Ptr GVariant
maybeParameters <- case Maybe GVariant
parameters of
        Nothing -> Ptr GVariant -> IO (Ptr GVariant)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GVariant
forall a. Ptr a
nullPtr
        Just jParameters :: GVariant
jParameters -> do
            Ptr GVariant
jParameters' <- GVariant -> IO (Ptr GVariant)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GVariant
jParameters
            Ptr GVariant -> IO (Ptr GVariant)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GVariant
jParameters'
    Ptr DBusMethodInvocation -> Ptr GVariant -> IO ()
g_dbus_method_invocation_return_value Ptr DBusMethodInvocation
invocation' Ptr GVariant
maybeParameters
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
invocation
    Maybe GVariant -> (GVariant -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe GVariant
parameters GVariant -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DBusMethodInvocationReturnValueMethodInfo
instance (signature ~ (Maybe (GVariant) -> m ()), MonadIO m, IsDBusMethodInvocation a) => O.MethodInfo DBusMethodInvocationReturnValueMethodInfo a signature where
    overloadedMethod = dBusMethodInvocationReturnValue

#endif

-- method DBusMethodInvocation::return_value_with_unix_fd_list
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "invocation"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "DBusMethodInvocation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusMethodInvocation."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "parameters"
--           , argType = TVariant
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A #GVariant tuple with out parameters for the method or %NULL if not passing any parameters."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "fd_list"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "UnixFDList" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GUnixFDList or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_method_invocation_return_value_with_unix_fd_list" g_dbus_method_invocation_return_value_with_unix_fd_list :: 
    Ptr DBusMethodInvocation ->             -- invocation : TInterface (Name {namespace = "Gio", name = "DBusMethodInvocation"})
    Ptr GVariant ->                         -- parameters : TVariant
    Ptr Gio.UnixFDList.UnixFDList ->        -- fd_list : TInterface (Name {namespace = "Gio", name = "UnixFDList"})
    IO ()

-- | Like 'GI.Gio.Objects.DBusMethodInvocation.dBusMethodInvocationReturnValue' but also takes a t'GI.Gio.Objects.UnixFDList.UnixFDList'.
-- 
-- This method is only available on UNIX.
-- 
-- This method will take ownership of /@invocation@/. See
-- t'GI.Gio.Structs.DBusInterfaceVTable.DBusInterfaceVTable' for more information about the ownership of
-- /@invocation@/.
-- 
-- /Since: 2.30/
dBusMethodInvocationReturnValueWithUnixFdList ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMethodInvocation a, Gio.UnixFDList.IsUnixFDList b) =>
    a
    -- ^ /@invocation@/: A t'GI.Gio.Objects.DBusMethodInvocation.DBusMethodInvocation'.
    -> Maybe (GVariant)
    -- ^ /@parameters@/: A t'GVariant' tuple with out parameters for the method or 'P.Nothing' if not passing any parameters.
    -> Maybe (b)
    -- ^ /@fdList@/: A t'GI.Gio.Objects.UnixFDList.UnixFDList' or 'P.Nothing'.
    -> m ()
dBusMethodInvocationReturnValueWithUnixFdList :: a -> Maybe GVariant -> Maybe b -> m ()
dBusMethodInvocationReturnValueWithUnixFdList invocation :: a
invocation parameters :: Maybe GVariant
parameters fdList :: Maybe b
fdList = 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 DBusMethodInvocation
invocation' <- a -> IO (Ptr DBusMethodInvocation)
forall a b. (HasCallStack, GObject a) => a -> IO (Ptr b)
B.ManagedPtr.disownObject a
invocation
    Ptr GVariant
maybeParameters <- case Maybe GVariant
parameters of
        Nothing -> Ptr GVariant -> IO (Ptr GVariant)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GVariant
forall a. Ptr a
nullPtr
        Just jParameters :: GVariant
jParameters -> do
            Ptr GVariant
jParameters' <- GVariant -> IO (Ptr GVariant)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GVariant
jParameters
            Ptr GVariant -> IO (Ptr GVariant)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GVariant
jParameters'
    Ptr UnixFDList
maybeFdList <- case Maybe b
fdList of
        Nothing -> Ptr UnixFDList -> IO (Ptr UnixFDList)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr UnixFDList
forall a. Ptr a
nullPtr
        Just jFdList :: b
jFdList -> do
            Ptr UnixFDList
jFdList' <- b -> IO (Ptr UnixFDList)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jFdList
            Ptr UnixFDList -> IO (Ptr UnixFDList)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr UnixFDList
jFdList'
    Ptr DBusMethodInvocation -> Ptr GVariant -> Ptr UnixFDList -> IO ()
g_dbus_method_invocation_return_value_with_unix_fd_list Ptr DBusMethodInvocation
invocation' Ptr GVariant
maybeParameters Ptr UnixFDList
maybeFdList
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
invocation
    Maybe GVariant -> (GVariant -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe GVariant
parameters GVariant -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
fdList b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DBusMethodInvocationReturnValueWithUnixFdListMethodInfo
instance (signature ~ (Maybe (GVariant) -> Maybe (b) -> m ()), MonadIO m, IsDBusMethodInvocation a, Gio.UnixFDList.IsUnixFDList b) => O.MethodInfo DBusMethodInvocationReturnValueWithUnixFdListMethodInfo a signature where
    overloadedMethod = dBusMethodInvocationReturnValueWithUnixFdList

#endif